 | binary-strict-0.3.0: Binary deserialisation using strict ByteStrings | Contents | Index |
|
| Data.Binary.Strict.Get | | Portability | portable to Hugs and GHC. | | Stability | experimental | | Maintainer | Adam Langley <agl@imperialviolet.org> |
|
|
|
|
|
| Description |
This is a strict version of the Get monad from the binary package. It's
pretty much just a copy and paste job from the original source code.
The binary team are currently unsure about their future plans w.r.t.
strictness, so this is a stop gap measure.
To use, write a function in the Get monad:
import Data.Binary.Strict.Get as BinStrict
import Data.ByteString as BS
parse :: BinStrict.Get
parse = getWord16be
main = print $ runGet parse $ BS.pack [1, 1]
This results in a tuple of (Right 257, "") (where the second element is
just the remaining data after the parser has run)
|
|
| Synopsis |
|
|
|
|
| The Get type
|
|
| data Get a |
| The parse state
| Instances | |
|
|
| runGet :: Get a -> ByteString -> (Either String a, ByteString) |
| Run a parser on the given input and return the result (either an error
string from a call to fail, or the parsing result) and the remainder of
of the input.
|
|
| Parsing
|
|
| lookAhead :: Get a -> Get a |
| Run ga, but return without consuming its input.
Fails if ga fails.
|
|
| lookAheadM :: Get (Maybe a) -> Get (Maybe a) |
| Like lookAhead, but consume the input if gma returns 'Just _'.
Fails if gma fails.
|
|
| lookAheadE :: Get (Either a b) -> Get (Either a b) |
| Like lookAhead, but consume the input if gea returns 'Right _'.
Fails if gea fails.
|
|
| zero :: Get a |
|
| plus :: Get a -> Get a -> Get a |
|
| spanOf :: (Word8 -> Bool) -> Get ByteString |
|
| Utility
|
|
| skip :: Int -> Get () |
| Skip ahead n bytes. Fails if fewer than n bytes are available.
|
|
| bytesRead :: Get Int |
| Get the total number of bytes read to this point.
|
|
| remaining :: Get Int |
| Get the number of remaining unparsed bytes.
Useful for checking whether all input has been consumed.
|
|
| isEmpty :: Get Bool |
| Test whether all input has been consumed,
i.e. there are no remaining unparsed bytes.
|
|
| Parsing particular types
|
|
| getWord8 :: Get Word8 |
|
| ByteStrings
|
|
| getByteString :: Int -> Get ByteString |
| An efficient get method for strict ByteStrings. Fails if fewer
than n bytes are left in the input.
|
|
| Big-endian reads
|
|
| getWord16be :: Get Word16 |
|
| getWord32be :: Get Word32 |
|
| getWord64be :: Get Word64 |
|
| Little-endian reads
|
|
| getWord16le :: Get Word16 |
|
| getWord32le :: Get Word32 |
|
| getWord64le :: Get Word64 |
|
| Host-endian, unaligned reads
|
|
| getWordhost :: Get Word |
|
| getWord16host :: Get Word16 |
|
| getWord32host :: Get Word32 |
|
| getWord64host :: Get Word64 |
|
| Floating point
|
|
| getFloat32host :: Get Float |
|
| getFloat64host :: Get Double |
|
| Produced by Haddock version 0.8 |