binary-strict-0.4.8.6: Binary deserialisation using strict ByteStrings

CopyrightLennart Kolmodin
LicenseBSD3-style (see LICENSE)
MaintainerAdam Langley <agl@imperialviolet.org>
Stabilityexperimental
Portabilityportable to Hugs and GHC.
Safe HaskellNone
LanguageHaskell2010

Data.Binary.Strict.IncrementalGet

Contents

Description

This is a version of the Get monad for incremental parsing. The parser is written as if a single, huge, strict ByteString was to be parsed. It produces results as it parses by calling yield.

However, if the parser runs out of data, rather than failing the caller sees a Partial result, which includes the list of yielded values so far and a continuation. By calling the continuation with more data, the parser continues, none the wiser.

Take the following example

testParse = do
  a <- getWord16be
  b <- getWord16be
  return $ a + b

test = runGet testParse $ B.pack [1,0,0]

Here testParse needs to read 4 bytes in order to complete, so test is a Partial, which includes the continuation function, so which you can pass more data until it completes

The lookahead functions have been removed from this parser because of their incompatibility with the incremental monad at the moment.

Synopsis

The Get type

data Get r a Source #

Instances
Monad (Get r) Source # 
Instance details

Defined in Data.Binary.Strict.IncrementalGet

Methods

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

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

return :: a -> Get r a #

fail :: String -> Get r a #

Functor (Get r) Source # 
Instance details

Defined in Data.Binary.Strict.IncrementalGet

Methods

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

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

Applicative (Get r) Source # 
Instance details

Defined in Data.Binary.Strict.IncrementalGet

Methods

pure :: a -> Get r a #

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

liftA2 :: (a -> b -> c) -> Get r a -> Get r b -> Get r c #

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

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

Alternative (Get r) Source # 
Instance details

Defined in Data.Binary.Strict.IncrementalGet

Methods

empty :: Get r a #

(<|>) :: Get r a -> Get r a -> Get r a #

some :: Get r a -> Get r [a] #

many :: Get r a -> Get r [a] #

MonadPlus (Get r) Source # 
Instance details

Defined in Data.Binary.Strict.IncrementalGet

Methods

mzero :: Get r a #

mplus :: Get r a -> Get r a -> Get r a #

BinaryParser (Get r) Source # 
Instance details

Defined in Data.Binary.Strict.IncrementalGet

data Result a Source #

The result of a partial parse

Constructors

Failed String

the parse failed with the given error message

Finished ByteString a

the parse finished and produced the given list of results doing so. Any unparsed data is returned.

Partial (ByteString -> Result a)

the parse ran out of data before finishing, but produced the given list of results before doing so. To continue the parse pass more data to the given continuation

Instances
Show a => Show (Result a) Source # 
Instance details

Defined in Data.Binary.Strict.IncrementalGet

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

runGet :: Get r r -> ByteString -> Result r Source #

Start a parser and return the first Result.

Utility

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

Skip ahead n bytes. Fails if fewer than n bytes are available.

bytesRead :: Get r Int Source #

Get the total number of bytes read to this point.

remaining :: Get r Int Source #

Get the number of remaining unparsed bytes. Useful for checking whether all input has been consumed.

isEmpty :: Get r Bool Source #

Test whether all input has been consumed, i.e. there are no remaining unparsed bytes.

plus :: Get r a -> Get r a -> Get r a Source #

This is the choice operator. If the first option fails, the second is tried. The failure of the first option must happen within this function otherwise rollback is not attempted.

zero :: Get r a Source #

suspend :: Get r () Source #

Yield a partial and get more data

Parsing particular types

ByteStrings

getByteString :: Int -> Get r ByteString Source #

An efficient get method for strict ByteStrings. Fails if fewer than n bytes are left in the input.

Big-endian reads

Little-endian reads

Host-endian, unaligned reads