tickle-0.0.1: A port of @Data.Binary@

Safe HaskellTrustworthy
LanguageHaskell2010

Data.Tickle.Get

Contents

Synopsis

Get data type

data Get e a Source

Instances

Bifunctor Get

Map on the error and result of a Get decoder.

>>> runGet (bimap (const True) (\x -> x + x) getWord8) (BLC.pack "")
RunGetFail 0 True
>>> runGet (bimap (const True) (\x -> x + x) getWord8) (BLC.pack "abc")
RunGet 194
Monad (Get e)

Sequence an action through the Get decoder.

>>> runGet (return 7 :: Get () Int) (BLC.pack "abc")
RunGet 7
runGet (return x :: Get () Int) (BLC.pack "abc") == _RunGet # x
>>> runGet (getWord8 >>= \c1 -> getWord8 >>= \c2 -> return (c1 + c2)) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (getWord8 >>= \c1 -> getWord8 >>= \c2 -> return (c1 + c2)) (BLC.pack "a")
RunGetFail 1 ()
>>> runGet (getWord8 >>= \c1 -> getWord8 >>= \c2 -> return (c1 + c2)) (BLC.pack "ab")
RunGet 195
>>> runGet (getWord8 >>= \c1 -> getWord8 >>= \c2 -> return (c1 + c2)) (BLC.pack "abc")
RunGet 195
Functor (Get e)

Map on the result of a Get decoder.

>>> runGet (fmap (\x -> x + x) getWord8) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (fmap (\x -> x + x) getWord8) (BLC.pack "abc")
RunGet 194
Applicative (Get e)

Apply a function on the Get decoder result.

>>> runGet (fmap (+) getWord8 <*> getWord8) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (fmap (+) getWord8 <*> getWord8) (BLC.pack "a")
RunGetFail 1 ()
>>> runGet (fmap (+) getWord8 <*> getWord8) (BLC.pack "ab")
RunGet 195
>>> runGet (fmap (+) getWord8 <*> getWord8) (BLC.pack "abc")
RunGet 195
>>> runGet (pure 7 :: Get () Int) (BLC.pack "abc")
RunGet 7
runGet (pure x :: Get () Int) (BLC.pack "abc") == _RunGet # x
Alt (Get e)

Pick between two Get decoders, finding the first to not fail.

>>> runGet ((+1) <$> getWord8 <!> subtract 1 <$> getWord8) (BLC.pack "")
RunGetFail 0 ()
>>> runGet ((+1) <$> getWord8 <!> subtract 1 <$> getWord8) (BLC.pack "abc")
RunGet 98
>>> runGet (getWord8 <!> failGet ()) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (getWord8 <!> failGet ()) (BLC.pack "abc")
RunGet 97
>>> runGet (Al.some getWord8) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (Al.some getWord8) (BLC.pack "a")
RunGet [97]
>>> runGet (Al.some getWord8) (BLC.pack "abc")
RunGet [97,98,99]
>>> runGet (Al.many getWord8) (BLC.pack "")
RunGet []
>>> runGet (Al.many getWord8) (BLC.pack "a")
RunGet [97]
>>> runGet (Al.many getWord8) (BLC.pack "abc")
RunGet [97,98,99]
Apply (Get e)

Apply a function on the Get decoder result.

>>> runGet (fmap (+) getWord8 <.> getWord8) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (fmap (+) getWord8 <.> getWord8) (BLC.pack "a")
RunGetFail 1 ()
>>> runGet (fmap (+) getWord8 <.> getWord8) (BLC.pack "ab")
RunGet 195
>>> runGet (fmap (+) getWord8 <.> getWord8) (BLC.pack "abc")
RunGet 195
Bind (Get e)

Sequence an action through the Get decoder.

>>> runGet (getWord8 >>- \c1 -> fmap (\c2 -> c1 + c2) getWord8) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (getWord8 >>- \c1 -> fmap (\c2 -> c1 + c2) getWord8) (BLC.pack "a")
RunGetFail 1 ()
>>> runGet (getWord8 >>- \c1 -> fmap (\c2 -> c1 + c2) getWord8) (BLC.pack "ab")
RunGet 195
>>> runGet (getWord8 >>- \c1 -> fmap (\c2 -> c1 + c2) getWord8) (BLC.pack "abc")
RunGet 195
Semigroup (Get e a)

Pick between two Get decoders, finding the first to not fail.

>>> runGet (((+1) <$> getWord8) <> (subtract 1 <$> getWord8)) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (((+1) <$> getWord8) <> (subtract 1 <$> getWord8)) (BLC.pack "abc")
RunGet 98
>>> runGet (getWord8 <> failGet ()) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (getWord8 <> failGet ()) (BLC.pack "abc")
RunGet 97

Primitive parsers

getLazyByteString :: Int64 -> Get () ByteString Source

>>> runGet (getLazyByteString 5) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (getLazyByteString 5) (BLC.pack "abc")
RunGetFail 3 ()
>>> runGet (getLazyByteString 5) (BLC.pack "abcdefg")
RunGet "abcde"

getLazyByteStringNul :: Get () ByteString Source

>>> runGet getLazyByteStringNul (BLC.pack "")
RunGetFail 0 ()
>>> runGet getLazyByteStringNul (BLC.pack "abc")
RunGetFail 3 ()
>>> runGet getLazyByteStringNul (BLC.pack "abc\0")
RunGet "abc"
>>> runGet getLazyByteStringNul (BLC.pack "abc\0def")
RunGet "abc"

getRemainingLazyByteString :: Get e ByteString Source

>>> runGet getRemainingLazyByteString  (BLC.pack "")
RunGet ""
>>> runGet getRemainingLazyByteString  (BLC.pack "abc")
RunGet "abc"

getPtr :: Storable a => Int -> Get () a Source

getWord8 :: Get () Word8 Source

>>> runGet getWord8 (BLC.pack "abc")
RunGet 97
>>> runGet getWord8 (BLC.pack "123")
RunGet 49

getWord16be :: Get () Word16 Source

>>> runGet getWord16be (BLC.pack "abc")
RunGet 24930
>>> runGet getWord16be (BLC.pack "123")
RunGet 12594

getWord16le :: Get () Word16 Source

>>> runGet getWord16le (BLC.pack "abc")
RunGet 25185
>>> runGet getWord16le (BLC.pack "123")
RunGet 12849

getWord32be :: Get () Word32 Source

>>> runGet getWord32be (BLC.pack "abcdef")
RunGet 1633837924
>>> runGet getWord32be (BLC.pack "123456")
RunGet 825373492

getWord32le :: Get () Word32 Source

  • - >>> runGet getWord32le (BLC.pack "abcdef") RunGet 1684234849
>>> runGet getWord32le (BLC.pack "123456")
RunGet 875770417

getWord64be :: Get () Word64 Source

>>> runGet getWord64be (BLC.pack "abcdefghi")
RunGet 7017280452245743464
>>> runGet getWord64be (BLC.pack "123456789")
RunGet 3544952156018063160

getWord64le :: Get () Word64 Source

>>> runGet getWord64le (BLC.pack "abcdefghi")
RunGet 7523094288207667809
>>> runGet getWord64le (BLC.pack "123456789")
RunGet 4050765991979987505

getWordhost :: Get () Word Source

>>> runGet getWordhost (BLC.pack "abcdefghi")
RunGet 7523094288207667809
>>> runGet getWordhost (BLC.pack "123456789")
RunGet 4050765991979987505

getWord16host :: Get () Word16 Source

>>> runGet getWord16host (BLC.pack "abcde")
RunGet 25185
>>> runGet getWord16host (BLC.pack "12345")
RunGet 12849

getWord32host :: Get () Word32 Source

>>> runGet getWord32host (BLC.pack "abcde")
RunGet 1684234849
>>> runGet getWord32host (BLC.pack "12345")
RunGet 875770417

getWord64host :: Get () Word64 Source

>>> runGet getWord64host (BLC.pack "abcdeghi")
RunGet 7595434456733934177
>>> runGet getWord64host (BLC.pack "123456789")
RunGet 4050765991979987505

failGet :: e -> Get e a Source

A Get decoder that always fails with the given value.

runGet (failGet x :: Get Int ()) (BLC.pack s) == _RunGetFail # (0, x)
>>> runGet (failGet "abc" :: Get String ()) (BLC.pack "def")
RunGetFail 0 "abc"

constant :: (forall r. XDecoder e r) -> Get e a Source

bytesRead :: Get e Int64 Source

>>> runGet (bytesRead :: Get () Int64) (BLC.pack "")
RunGet 0
>>> runGet (bytesRead :: Get () Int64) (BLC.pack "abc")
RunGet 0
>>> runGet (getWord8 >> getWord16be >> getWord32le >> bytesRead) (BLC.pack "abcdefghijk")
RunGet 7

demandInput :: Get () () Source

>>> runGet demandInput (BLC.pack "")
RunGetFail 0 ()
>>> runGet demandInput (BLC.pack "a")
RunGet ()
>>> runGet demandInput (BLC.pack "abc")
RunGet ()

skip :: Int -> Get () () Source

>>> runGet (getWord8 >>= \c -> skip 2 >> getWord8 >>= \d -> return (c,d)) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (getWord8 >>= \c -> skip 2 >> getWord8 >>= \d -> return (c,d)) (BLC.pack "abcdefghi")
RunGet (97,100)
>>> runGet (getWord8 >>= \c -> skip 2 >> getWord8 >>= \d -> return (c,d)) (BLC.pack "abc")
RunGetFail 3 ()

isNotEmpty :: Get e Bool Source

>>> runGet isNotEmpty (BLC.pack "")
RunGet False
>>> runGet isNotEmpty (BLC.pack "abc")
RunGet True
>>> runGet (isNotEmpty >>= \p -> getWord8 >>= \w -> return (w, p)) (BLC.pack "abc")
RunGet (97,True)
>>> runGet (isNotEmpty >>= \p -> getWord8 >>= \w -> return (w, p)) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (isNotEmpty >>= \p -> getWord8 >>= \w -> return (w, p)) (BLC.pack "a")
RunGet (97,True)

isEmpty :: Get e Bool Source

>>> runGet isEmpty (BLC.pack "")
RunGet True
>>> runGet isEmpty (BLC.pack "abc")
RunGet False
>>> runGet (isEmpty >>= \p -> getWord8 >>= \w -> return (w, p)) (BLC.pack "abc")
RunGet (97,False)
>>> runGet (isEmpty >>= \p -> getWord8 >>= \w -> return (w, p)) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (isEmpty >>= \p -> getWord8 >>= \w -> return (w, p)) (BLC.pack "a")
RunGet (97,False)

getByteString :: Int -> Get () ByteString Source

>>> runGet (getByteString (-3)) (BLC.pack "")
RunGet ""
>>> runGet (getByteString 3) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (getByteString 3) (BLC.pack "abc")
RunGet "abc"
>>> runGet (getByteString 3) (BLC.pack "abcdef")
RunGet "abc"

readN :: Int -> (ByteString -> a) -> Get () a Source

>>> runGet (readN 3 id) (BLC.pack "abc")
RunGet "abc"
>>> runGet (readN 3 id) (BLC.pack "ab")
RunGetFail 0 ()
>>> runGet (readN 3 id) (BLC.pack "abcdef")
RunGet "abcdef"
>>> runGet (readN (-3) id) (BLC.pack "abcdef")
RunGet ""

ensureN :: Int -> Get () () Source

>>> runGet (ensureN 3) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (ensureN 3) (BLC.pack "abc")
RunGet ()
>>> runGet (ensureN 3) (BLC.pack "abcdef")
RunGet ()

Higher-level combinators

runAndKeepTrack :: Get e a -> Get x (CompletedXDecoder e a, [ByteString]) Source

Run a Get decoder, but keep a track of the input that ran it to completion.

>>> runGet (runAndKeepTrack getWord8 :: Get () (CompletedXDecoder () Word8, [BC.ByteString])) (BLC.pack "")
RunGet (CompletedFail "" (),[])
>>> runGet (runAndKeepTrack getWord8 :: Get () (CompletedXDecoder () Word8, [BC.ByteString])) (BLC.pack "abc")
RunGet (CompletedDone "bc" 97,["abc"])

pushBack :: [ByteString] -> Get e () Source

>>> runGet (pushBack [] :: Get () ()) (BLC.pack "")
RunGet ()
>>> runGet (pushBack [] :: Get () ()) (BLC.pack "abc")
RunGet ()
>>> runGet (pushBack [BC.pack "def"] :: Get () ()) (BLC.pack "")
RunGet ()
>>> runGet (pushBack [BC.pack "def"] :: Get () ()) (BLC.pack "abc")
RunGet ()

pushFront :: ByteString -> Get e () Source

>>> runGet (pushFront (BC.pack "def") :: Get () ()) (BLC.pack "")
RunGet ()
>>> runGet (pushFront (BC.pack "def") :: Get () ()) (BLC.pack "abc")
RunGet ()

isolate :: Int -> Get e a -> Get (IsolateError e) a Source

>>> runGet (isolate 1 getWord8) (BLC.pack "ab")
RunGet 97
>>> runGet (isolate 1 getWord8) (BLC.pack "abcde")
RunGet 97
>>> runGet (isolate 2 getWord16le) (BLC.pack "abcde")
RunGet 25185
>>> runGet (isolate 1 getWord16le) (BLC.pack "abcde")
RunGetFail 0 (IsolateXFail ())
>>> runGet (isolate (-3) getWord16le) (BLC.pack "abcde")
RunGetFail 0 NegativeSize
>>> runGet (isolate 3 getWord16le) (BLC.pack "abcde")
RunGetFail 2 (UnexpectedConsumed 2 3)

lookAhead :: Get e a -> Get e a Source

>>> runGet (lookAhead getWord8) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (lookAhead getWord8) (BLC.pack "abc")
RunGet 97
>>> runGet (lookAhead getWord8) (BLC.pack "a")
RunGet 97

lookAheadM :: Get e (Maybe a) -> Get e (Maybe a) Source

>>> runGet (lookAheadM (getWord8 >>= \w -> return (if even w then Just (w + 5) else Nothing))) (BLC.pack "abc")
RunGet Nothing
>>> runGet (lookAheadM (getWord8 >>= \w -> return (if even w then Just (w + 5) else Nothing))) (BLC.pack "bc")
RunGet (Just 103)
>>> runGet (lookAheadM (getWord8 >>= \w -> return (if even w then Just (w + 5) else Nothing))) (BLC.pack "")
RunGetFail 0 ()

lookAheadE :: Get e (Either a b) -> Get e (Either a b) Source

>>> runGet (lookAheadE (getWord8 >>= \w -> return (if even w then Left (w + 5) else Right (w - 4)))) (BLC.pack "abc")
RunGet (Right 93)
>>> runGet (lookAheadE (getWord8 >>= \w -> return (if even w then Left (w + 5) else Right (w - 4)))) (BLC.pack "bc")
RunGet (Left 103)
>>> runGet (lookAheadE (getWord8 >>= \w -> return (if even w then Left (w + 5) else Right (w - 4)))) (BLC.pack "")
RunGetFail 0 ()

readNWith :: Int -> (Ptr a -> IO a) -> Get () a Source

Error label

(!+) :: Semigroup e => e -> Get e a -> Get e a infixl 3 Source

>>> runGet ([(), ()] !+ (setLabel [] getWord8)) (BLC.pack "")
RunGetFail 0 [(),()]
>>> runGet ([(), ()] !+ (setLabel [] getWord8)) (BLC.pack "abc")
RunGet 97

addLabel :: Semigroup e => e -> Get e a -> Get e a Source

>>> runGet ([(), ()] `addLabel` (setLabel [] getWord8)) (BLC.pack "")
RunGetFail 0 [(),()]
>>> runGet ([(), ()] `addLabel` (setLabel [] getWord8)) (BLC.pack "abc")
RunGet 97

(!-) :: e -> Get d a -> Get e a infixl 3 Source

>>> runGet ("error" !- getWord8) (BLC.pack "")
RunGetFail 0 "error"
>>> runGet ("error" !- getWord8) (BLC.pack "abc")
RunGet 97

setLabel :: e -> Get d a -> Get e a Source

>>> runGet ("error" `setLabel` getWord8) (BLC.pack "")
RunGetFail 0 "error"
>>> runGet ("error" `setLabel` getWord8) (BLC.pack "abc")
RunGet 97

(!!-) :: (d -> e) -> Get d a -> Get e a infixl 3 Source

>>> runGet (reverse !!- setLabel "error" getWord8) (BLC.pack "")
RunGetFail 0 "rorre"
>>> runGet (reverse !!- setLabel "error" getWord8) (BLC.pack "abc")
RunGet 97

modifyLabel :: (d -> e) -> Get d a -> Get e a Source

>>> runGet (reverse `modifyLabel` setLabel "error" getWord8) (BLC.pack "")
RunGetFail 0 "rorre"
>>> runGet (reverse `modifyLabel` setLabel "error" getWord8) (BLC.pack "abc")
RunGet 97

Decoder

data Decoder e a Source

Instances

Bifunctor Decoder
>>> (bimap (+10) (*20) (_Fail # (BC.pack "abc", 19, 31))) ^? _Fail
Just ("abc",19,41)
>>> (bimap (+10) (*20) (_Done # (BC.pack "abc", 19, 31))) ^? _Done
Just ("abc",19,620)
Functor (Decoder e)
>>> (fmap (+10) (_Fail # (BC.pack "abc", 19, 31))) ^? _Fail
Just ("abc",19,31)
>>> (fmap (+10) (_Done # (BC.pack "abc", 19, 31))) ^? _Done
Just ("abc",19,41)

decoder :: (ByteString -> Int64 -> e -> x) -> ((Maybe ByteString -> Decoder e a) -> x) -> (ByteString -> Int64 -> a -> x) -> Decoder e a -> x Source

>>> decoder (\b i n -> B.length b + fromIntegral i + n) (\_ -> 99) (\b n a -> B.length b + fromIntegral n + a) (_Fail # (BC.pack "abc", 12, 19))
34
>>> decoder (\b i n -> B.length b + fromIntegral i + n) (\_ -> 99) (\b n a -> B.length b + fromIntegral n + a) (_Partial # (\b -> _Fail # (fromMaybe (BC.pack "abc") b, 12, 19)))
99
>>> decoder (\b i n -> B.length b + fromIntegral i + n) (\_ -> 99) (\b n a -> B.length b + fromIntegral n + a) (_Done # (BC.pack "abc", 12, 19))
34

_Fail :: Prism' (Decoder e a) (ByteString, Int64, e) Source

>>> (_Fail # (BC.pack "abc", 19, 31)) ^? _Fail
Just ("abc",19,31)
>>> isNothing ((_Fail # (BC.pack "abc", 19, 31)) ^? _Partial)
True
>>> (_Fail # (BC.pack "abc", 19, 31)) ^? _Done
Nothing

_Partial :: Prism' (Decoder e a) (Maybe ByteString -> Decoder e a) Source

>>> (_Partial # (\b -> _Fail # (fromMaybe (BC.pack "abc") b, 12, 19))) ^? _Fail
Nothing
>>> isJust ((_Partial # (\b -> _Fail # (fromMaybe (BC.pack "abc") b, 12, 19))) ^? _Partial)
True
>>> (_Partial # (\b -> _Fail # (fromMaybe (BC.pack "abc") b, 12, 19))) ^? _Done
Nothing

_Done :: Prism' (Decoder e a) (ByteString, Int64, a) Source

>>> (_Done # (BC.pack "abc", 19, 31)) ^? _Fail
Nothing
>>> isNothing ((_Done # (BC.pack "abc", 19, 31)) ^? _Partial)
True
>>> (_Done # (BC.pack "abc", 19, 31)) ^? _Done
Just ("abc",19,31)

Run Get parser

XDecoder data type

Reduction

xdecoder :: (ByteString -> e -> x) -> ((Maybe ByteString -> XDecoder e a) -> x) -> (ByteString -> a -> x) -> (Int64 -> (Int64 -> XDecoder e a) -> x) -> XDecoder e a -> x Source

Prisms

CompletedXDecoder data type

Reduction

completedXDecoder :: (ByteString -> e -> x) -> (ByteString -> a -> x) -> CompletedXDecoder e a -> x Source

Prism

Isomorphism

Lens

Prism

Traversal