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

Safe HaskellTrustworthy
LanguageHaskell2010

Data.Tickle.Get

Contents

Synopsis

Get data type

data Get e a Source #

Instances

Bifunctor Get Source #

Map on the error and result of a Get decoder.

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

Methods

bimap :: (a -> b) -> (c -> d) -> Get a c -> Get b d #

first :: (a -> b) -> Get a c -> Get b c #

second :: (b -> c) -> Get a b -> Get a c #

Monad (Get e) Source #

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 (word8 >>= \c1 -> word8 >>= \c2 -> return (c1 + c2)) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (word8 >>= \c1 -> word8 >>= \c2 -> return (c1 + c2)) (BLC.pack "a")
RunGetFail 1 ()
>>> runGet (word8 >>= \c1 -> word8 >>= \c2 -> return (c1 + c2)) (BLC.pack "ab")
RunGet 195
>>> runGet (word8 >>= \c1 -> word8 >>= \c2 -> return (c1 + c2)) (BLC.pack "abc")
RunGet 195

Methods

(>>=) :: Get e a -> (a -> Get e b) -> Get e b #

(>>) :: Get e a -> Get e b -> Get e b #

return :: a -> Get e a #

fail :: String -> Get e a #

Functor (Get e) Source #

Map on the result of a Get decoder.

>>> runGet (fmap (\x -> x + x) word8) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (fmap (\x -> x + x) word8) (BLC.pack "abc")
RunGet 194

Methods

fmap :: (a -> b) -> Get e a -> Get e b #

(<$) :: a -> Get e b -> Get e a #

Applicative (Get e) Source #

Apply a function on the Get decoder result.

>>> runGet (fmap (+) word8 <*> word8) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (fmap (+) word8 <*> word8) (BLC.pack "a")
RunGetFail 1 ()
>>> runGet (fmap (+) word8 <*> word8) (BLC.pack "ab")
RunGet 195
>>> runGet (fmap (+) word8 <*> word8) (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

Methods

pure :: a -> Get e a #

(<*>) :: Get e (a -> b) -> Get e a -> Get e b #

(*>) :: Get e a -> Get e b -> Get e b #

(<*) :: Get e a -> Get e b -> Get e a #

Alt (Get e) Source #

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

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

Methods

(<!>) :: Get e a -> Get e a -> Get e a #

some :: Applicative (Get e) => Get e a -> Get e [a] #

many :: Applicative (Get e) => Get e a -> Get e [a] #

Apply (Get e) Source #

Apply a function on the Get decoder result.

>>> runGet (fmap (+) word8 <.> word8) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (fmap (+) word8 <.> word8) (BLC.pack "a")
RunGetFail 1 ()
>>> runGet (fmap (+) word8 <.> word8) (BLC.pack "ab")
RunGet 195
>>> runGet (fmap (+) word8 <.> word8) (BLC.pack "abc")
RunGet 195

Methods

(<.>) :: Get e (a -> b) -> Get e a -> Get e b #

(.>) :: Get e a -> Get e b -> Get e b #

(<.) :: Get e a -> Get e b -> Get e a #

Bind (Get e) Source #

Sequence an action through the Get decoder.

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

Methods

(>>-) :: Get e a -> (a -> Get e b) -> Get e b #

join :: Get e (Get e a) -> Get e a #

Semigroup (Get e a) Source #

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

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

Methods

(<>) :: Get e a -> Get e a -> Get e a #

sconcat :: NonEmpty (Get e a) -> Get e a #

stimes :: Integral b => b -> Get e a -> Get e a #

Primitive parsers

lazyByteString :: Int64 -> Get () ByteString Source #

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

lazyByteStringNul :: Get () ByteString Source #

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

remainingLazyByteString :: Get e ByteString Source #

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

ptr :: Storable a => Int -> Get () a Source #

word8 :: Get () Word8 Source #

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

word16be :: Get () Word16 Source #

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

word16le :: Get () Word16 Source #

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

word32be :: Get () Word32 Source #

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

word32le :: Get () Word32 Source #

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

word64be :: Get () Word64 Source #

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

word64le :: Get () Word64 Source #

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

wordhost :: Get () Word Source #

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

word16host :: Get () Word16 Source #

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

word32host :: Get () Word32 Source #

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

word64host :: Get () Word64 Source #

>>> runGet word64host (BLC.pack "abcdeghi")
RunGet 7595434456733934177
>>> runGet word64host (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 (word8 >> word16be >> word32le >> 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 (word8 >>= \c -> skip 2 >> word8 >>= \d -> return (c,d)) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (word8 >>= \c -> skip 2 >> word8 >>= \d -> return (c,d)) (BLC.pack "abcdefghi")
RunGet (97,100)
>>> runGet (word8 >>= \c -> skip 2 >> word8 >>= \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 -> word8 >>= \w -> return (w, p)) (BLC.pack "abc")
RunGet (97,True)
>>> runGet (isNotEmpty >>= \p -> word8 >>= \w -> return (w, p)) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (isNotEmpty >>= \p -> word8 >>= \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 -> word8 >>= \w -> return (w, p)) (BLC.pack "abc")
RunGet (97,False)
>>> runGet (isEmpty >>= \p -> word8 >>= \w -> return (w, p)) (BLC.pack "")
RunGetFail 0 ()
>>> runGet (isEmpty >>= \p -> word8 >>= \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 parsers

IEEE754 parsers

toFloat :: (Storable w, Storable f) => w -> f Source #

Integer parsers

integerError :: a -> (Word8 -> a) -> a -> (ListError -> a) -> IntegerError -> a Source #

List parsers

listError :: a -> a -> ListError -> a Source #

list :: Get e a -> Get ListError [a] Source #

many :: Get e a -> Int64 -> Get e [a] Source #

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 word8 :: Get () (CompletedXDecoder () Word8, [BC.ByteString])) (BLC.pack "")
RunGet (CompletedFail "" (),[])
>>> runGet (runAndKeepTrack word8 :: 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 word8) (BLC.pack "ab")
RunGet 97
>>> runGet (isolate 1 word8) (BLC.pack "abcde")
RunGet 97
>>> runGet (isolate 2 word16le) (BLC.pack "abcde")
RunGet 25185
>>> runGet (isolate 1 word16le) (BLC.pack "abcde")
RunGetFail 0 (IsolateXFail ())
>>> runGet (isolate (-3) word16le) (BLC.pack "abcde")
RunGetFail 0 NegativeSize
>>> runGet (isolate 3 word16le) (BLC.pack "abcde")
RunGetFail 2 (UnexpectedConsumed 2 3)

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

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

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

>>> runGet (lookAheadM (word8 >>= \w -> return (if even w then Just (w + 5) else Nothing))) (BLC.pack "abc")
RunGet Nothing
>>> runGet (lookAheadM (word8 >>= \w -> return (if even w then Just (w + 5) else Nothing))) (BLC.pack "bc")
RunGet (Just 103)
>>> runGet (lookAheadM (word8 >>= \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 (word8 >>= \w -> return (if even w then Left (w + 5) else Right (w - 4)))) (BLC.pack "abc")
RunGet (Right 93)
>>> runGet (lookAheadE (word8 >>= \w -> return (if even w then Left (w + 5) else Right (w - 4)))) (BLC.pack "bc")
RunGet (Left 103)
>>> runGet (lookAheadE (word8 >>= \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 [] word8)) (BLC.pack "")
RunGetFail 0 [(),()]
>>> runGet ([(), ()] !+ (setLabel [] word8)) (BLC.pack "abc")
RunGet 97

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

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

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

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

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

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

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

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

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

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

Decoder

data Decoder e a Source #

Instances

Bifunctor Decoder Source #
>>> (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)

Methods

bimap :: (a -> b) -> (c -> d) -> Decoder a c -> Decoder b d #

first :: (a -> b) -> Decoder a c -> Decoder b c #

second :: (b -> c) -> Decoder a b -> Decoder a c #

Functor (Decoder e) Source #
>>> (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)

Methods

fmap :: (a -> b) -> Decoder e a -> Decoder e b #

(<$) :: a -> Decoder e b -> Decoder e a #

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

(.>>) :: Get e a -> ByteString -> RunGetResult e a infixl 2 Source #

An alias for runGet.

>>> (word8 >>= \c1 -> word8 >>= \c2 -> return (c1 + c2)) .>> BLC.pack "abc"
RunGet 195

(<<.) :: ByteString -> Get e a -> RunGetResult e a infixl 2 Source #

An alias for runGet with the arguments flipped.

>>> BLC.pack "abc" <<. (word8 >>= \c1 -> word8 >>= \c2 -> return (c1 + c2))
RunGet 195

XDecoder data type

data XDecoder e a Source #

Instances

Bifunctor XDecoder Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> XDecoder a c -> XDecoder b d #

first :: (a -> b) -> XDecoder a c -> XDecoder b c #

second :: (b -> c) -> XDecoder a b -> XDecoder a c #

Bifoldable XDecoder Source # 

Methods

bifold :: Monoid m => XDecoder m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> XDecoder a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> XDecoder a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> XDecoder a b -> c #

Functor (XDecoder e) Source # 

Methods

fmap :: (a -> b) -> XDecoder e a -> XDecoder e b #

(<$) :: a -> XDecoder e b -> XDecoder e a #

Foldable (XDecoder e) Source # 

Methods

fold :: Monoid m => XDecoder e m -> m #

foldMap :: Monoid m => (a -> m) -> XDecoder e a -> m #

foldr :: (a -> b -> b) -> b -> XDecoder e a -> b #

foldr' :: (a -> b -> b) -> b -> XDecoder e a -> b #

foldl :: (b -> a -> b) -> b -> XDecoder e a -> b #

foldl' :: (b -> a -> b) -> b -> XDecoder e a -> b #

foldr1 :: (a -> a -> a) -> XDecoder e a -> a #

foldl1 :: (a -> a -> a) -> XDecoder e a -> a #

toList :: XDecoder e a -> [a] #

null :: XDecoder e a -> Bool #

length :: XDecoder e a -> Int #

elem :: Eq a => a -> XDecoder e a -> Bool #

maximum :: Ord a => XDecoder e a -> a #

minimum :: Ord a => XDecoder e a -> a #

sum :: Num a => XDecoder e a -> a #

product :: Num a => XDecoder e a -> a #

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

data CompletedXDecoder e a Source #

Instances

Bifunctor CompletedXDecoder Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> CompletedXDecoder a c -> CompletedXDecoder b d #

first :: (a -> b) -> CompletedXDecoder a c -> CompletedXDecoder b c #

second :: (b -> c) -> CompletedXDecoder a b -> CompletedXDecoder a c #

Bitraversable CompletedXDecoder Source # 

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> CompletedXDecoder a b -> f (CompletedXDecoder c d) #

Bifoldable CompletedXDecoder Source # 

Methods

bifold :: Monoid m => CompletedXDecoder m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> CompletedXDecoder a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> CompletedXDecoder a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> CompletedXDecoder a b -> c #

Functor (CompletedXDecoder e) Source # 

Methods

fmap :: (a -> b) -> CompletedXDecoder e a -> CompletedXDecoder e b #

(<$) :: a -> CompletedXDecoder e b -> CompletedXDecoder e a #

Foldable (CompletedXDecoder e) Source # 

Methods

fold :: Monoid m => CompletedXDecoder e m -> m #

foldMap :: Monoid m => (a -> m) -> CompletedXDecoder e a -> m #

foldr :: (a -> b -> b) -> b -> CompletedXDecoder e a -> b #

foldr' :: (a -> b -> b) -> b -> CompletedXDecoder e a -> b #

foldl :: (b -> a -> b) -> b -> CompletedXDecoder e a -> b #

foldl' :: (b -> a -> b) -> b -> CompletedXDecoder e a -> b #

foldr1 :: (a -> a -> a) -> CompletedXDecoder e a -> a #

foldl1 :: (a -> a -> a) -> CompletedXDecoder e a -> a #

toList :: CompletedXDecoder e a -> [a] #

null :: CompletedXDecoder e a -> Bool #

length :: CompletedXDecoder e a -> Int #

elem :: Eq a => a -> CompletedXDecoder e a -> Bool #

maximum :: Ord a => CompletedXDecoder e a -> a #

minimum :: Ord a => CompletedXDecoder e a -> a #

sum :: Num a => CompletedXDecoder e a -> a #

product :: Num a => CompletedXDecoder e a -> a #

Traversable (CompletedXDecoder e) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> CompletedXDecoder e a -> f (CompletedXDecoder e b) #

sequenceA :: Applicative f => CompletedXDecoder e (f a) -> f (CompletedXDecoder e a) #

mapM :: Monad m => (a -> m b) -> CompletedXDecoder e a -> m (CompletedXDecoder e b) #

sequence :: Monad m => CompletedXDecoder e (m a) -> m (CompletedXDecoder e a) #

(Eq a, Eq e) => Eq (CompletedXDecoder e a) Source # 
(Ord a, Ord e) => Ord (CompletedXDecoder e a) Source # 
(Show a, Show e) => Show (CompletedXDecoder e a) Source # 

Reduction

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

Prism

Isomorphism

Lens

Prism

Traversal