module Ptr.Poking
where
import Ptr.Prelude hiding (length)
import qualified Ptr.IO as A
import qualified Ptr.Poke as C
import qualified Ptr.PokeAndPeek as D
import qualified Ptr.PokeIO as E
import qualified Data.ByteString.Internal as B
data Poking =
Poking !Int !(Ptr Word8 -> IO ())
instance Semigroup Poking where
(<>) (Poking space1 action1) (Poking space2 action2) =
Poking (space1 + space2) action
where
action =
if space1 < 2048 || space2 < 2048
then E.sequentially space1 action1 action2
else E.concurrently space1 action1 action2
instance Monoid Poking where
mempty =
Poking 0 (const (pure ()))
mappend =
(<>)
null :: Poking -> Bool
null =
(== 0) . length
length :: Poking -> Int
length (Poking size _) =
size
word8 :: Word8 -> Poking
word8 x =
Poking 1 (flip A.pokeWord8 x)
beWord32 :: Word32 -> Poking
beWord32 x =
Poking 4 (flip A.pokeBEWord32 x)
beWord64 :: Word64 -> Poking
beWord64 x =
Poking 8 (flip A.pokeBEWord64 x)
bytes :: ByteString -> Poking
bytes (B.PS bytesFPtr offset length) =
Poking length (\ptr -> withForeignPtr bytesFPtr (\bytesPtr -> B.memcpy ptr (plusPtr bytesPtr offset) length))
poke :: C.Poke input -> input -> Poking
poke (C.Poke space poke) input =
Poking space (\ptr -> poke ptr input)
pokeAndPeek :: D.PokeAndPeek input output -> input -> Poking
pokeAndPeek (D.PokeAndPeek space poke _) input =
Poking space (\ptr -> poke ptr input)
asciiIntegral :: Integral a => a -> Poking
asciiIntegral =
\case
0 ->
word8 48
x ->
bool ((<>) (word8 45)) id (x >= 0) $
loop mempty $
abs x
where
loop builder remainder =
case remainder of
0 ->
builder
_ ->
case quotRem remainder 10 of
(quot, rem) ->
loop (word8 (48 + fromIntegral rem) <> builder) quot
asciiChar :: Char -> Poking
asciiChar =
word8 . fromIntegral . ord
asciiPaddedAndTrimmedIntegral :: Integral a => Int -> a -> Poking
asciiPaddedAndTrimmedIntegral !length !integral =
if length > 0
then
if integral >= 0
then case quotRem integral 10 of
(quot, rem) ->
asciiPaddedAndTrimmedIntegral (pred length) quot <>
word8 (48 + fromIntegral rem)
else stimes length (word8 48)
else mempty
asciiUtcTimeInIso8601 :: UTCTime -> Poking
asciiUtcTimeInIso8601 utcTime =
asciiPaddedAndTrimmedIntegral 4 year <> word8 45 <>
asciiPaddedAndTrimmedIntegral 2 month <> word8 45 <>
asciiPaddedAndTrimmedIntegral 2 day <>
word8 84 <>
asciiPaddedAndTrimmedIntegral 2 hour <> word8 58 <>
asciiPaddedAndTrimmedIntegral 2 minute <> word8 58 <>
asciiPaddedAndTrimmedIntegral 2 (round second) <>
word8 90
where
LocalTime date (TimeOfDay hour minute second) = utcToLocalTime utc utcTime
(year, month, day) = toGregorian date
list :: (element -> Poking) -> [element] -> Poking
list element =
loop mempty
where
loop state =
\ case
head : tail -> loop (state <> word8 1 <> element head) tail
_ -> state <> word8 0