{-# lANGUAGE LambdaCase #-}
module Haskus.Binary.Get
( Get
, runGet
, runGetOrFail
, isEmpty
, remaining
, skip
, uncheckedSkip
, skipAlign
, uncheckedSkipAlign
, countBytes
, alignAfter
, consumeExactly
, consumeAtMost
, lookAhead
, lookAheadM
, lookAheadE
, getRemaining
, getBuffer
, getBufferNul
, getWord8
, getWord16le
, getWord16be
, getWord32le
, getWord32be
, getWord64le
, getWord64be
, getWhile
, getWhole
, getBitGet
, getManyAtMost
, getManyBounded
)
where
import qualified Data.Serialize.Get as BG
import Data.Serialize.Get (Get)
import Haskus.Binary.Buffer
import Haskus.Number.Word
import Haskus.Binary.Bits.Order
import Haskus.Binary.Bits.Get (BitGet, runBitGetPartial, skipBitsToAlignOnWord8M, bitGetStateInput)
import Haskus.Utils.Maybe
isEmpty :: Get Bool
isEmpty = BG.isEmpty
remaining :: Get Word
remaining = fromIntegral <$> BG.remaining
skip :: Word -> Get ()
skip = BG.skip . fromIntegral
uncheckedSkip :: Word -> Get ()
uncheckedSkip = BG.uncheckedSkip . fromIntegral
skipAlign :: Word -> Word -> Get ()
skipAlign n al = skip n'
where
n' = case n `mod` al of
0 -> 0
x -> al - fromIntegral x
uncheckedSkipAlign :: Word -> Word -> Get ()
uncheckedSkipAlign n al = uncheckedSkip n'
where
n' = case n `mod` al of
0 -> 0
x -> al - fromIntegral x
lookAhead :: Get a -> Get a
lookAhead = BG.lookAhead
lookAheadM :: Get (Maybe a) -> Get (Maybe a)
lookAheadM = BG.lookAheadM
lookAheadE :: Get (Either a b) -> Get (Either a b)
lookAheadE = BG.lookAheadE
consumeExactly :: Word -> Get a -> Get a
consumeExactly sz = BG.isolate (fromIntegral sz)
consumeAtMost :: Word -> Get a -> Get a
consumeAtMost sz f = do
sz' <- remaining
(r,res) <- BG.lookAhead $ BG.isolate (fromIntegral (min sz sz')) $ do
res <- f
r <- remaining
skip r
return (r,res)
skip (min sz' sz - r)
return res
getBuffer :: Word -> Get Buffer
getBuffer sz = Buffer <$> BG.getBytes (fromIntegral sz)
getWord8 :: Get Word8
getWord8 = BG.getWord8
getWord16le :: Get Word16
getWord16le = BG.getWord16le
getWord16be :: Get Word16
getWord16be = BG.getWord16be
getWord32le :: Get Word32
getWord32le = BG.getWord32le
getWord32be :: Get Word32
getWord32be = BG.getWord32be
getWord64le :: Get Word64
getWord64le = BG.getWord64le
getWord64be :: Get Word64
getWord64be = BG.getWord64be
getWhile :: (a -> Bool) -> Get a -> Get [a]
getWhile cond getter = rec []
where
rec xs = do
x <- getter
if cond x
then rec (x:xs)
else return (reverse xs)
getWhole :: Get a -> Get [a]
getWhole getter = rec []
where
rec xs = do
cond <- isEmpty
if cond
then return (reverse xs)
else do
x <- getter
rec (x:xs)
getRemaining :: Get Buffer
getRemaining = do
r <- remaining
getBuffer r
countBytes :: Get a -> Get (Word, a)
countBytes g = do
cnt0 <- remaining
r <- g
cnt1 <- remaining
return (cnt0 - cnt1, r)
alignAfter :: Word -> Get a -> Get a
alignAfter alignment getter = do
(cnt,r) <- countBytes getter
uncheckedSkipAlign cnt alignment
return r
getBufferNul :: Get Buffer
getBufferNul = do
bs <- lookAhead getRemaining
let v = bufferTakeWhile (/= 0) bs
uncheckedSkip (bufferSize v + 1)
return v
runGet :: Get a -> Buffer -> Either String a
runGet g (Buffer bs) = BG.runGet g bs
runGetOrFail :: Get a -> Buffer -> a
runGetOrFail g bs = case runGet g bs of
Left err -> error err
Right x -> x
getBitGet :: BitOrder -> BitGet a -> (a -> Get b) -> Get b
getBitGet bo bg cont = do
bs <- getRemaining
let (v,s) = runBitGetPartial bo (bg <* skipBitsToAlignOnWord8M) bs
return $ runGetOrFail (cont v) (bitGetStateInput s)
getManyAtMost :: Word -> Get (Maybe a) -> Get [a]
getManyAtMost mx f = fromMaybe [] <$> getManyBounded Nothing (Just mx) f
getManyBounded :: Maybe Word -> Maybe Word -> Get (Maybe a) -> Get (Maybe [a])
getManyBounded _ (Just 0) _ = return (Just [])
getManyBounded (Just 0) mx f = getManyBounded Nothing mx f
getManyBounded mn mx f = lookAheadM $ f >>= \case
Nothing -> case mn of
Just n | n > 0 -> return Nothing
_ -> return (Just [])
Just x -> fmap (x:) <$> getManyBounded (minus1 mn) (minus1 mx) f
where
minus1 = fmap (\k -> k - 1)