| Copyright | Lennart Kolmodin | 
|---|---|
| License | BSD3-style (see LICENSE) | 
| Maintainer | Adam Langley <agl@imperialviolet.org> | 
| Stability | experimental | 
| Portability | portable to Hugs and GHC. | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Data.Binary.Strict.Get
Contents
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
- data Get a
- runGet :: Get a -> ByteString -> (Either String a, ByteString)
- lookAhead :: Get a -> Get a
- lookAheadM :: Get (Maybe a) -> Get (Maybe a)
- lookAheadE :: Get (Either a b) -> Get (Either a b)
- zero :: Get a
- plus :: Get a -> Get a -> Get a
- spanOf :: (Word8 -> Bool) -> Get ByteString
- skip :: Int -> Get ()
- bytesRead :: Get Int
- remaining :: Get Int
- isEmpty :: Get Bool
- getWord8 :: Get Word8
- getByteString :: Int -> Get ByteString
- getWord16be :: Get Word16
- getWord32be :: Get Word32
- getWord64be :: Get Word64
- getWord16le :: Get Word16
- getWord32le :: Get Word32
- getWord64le :: Get Word64
- getWordhost :: Get Word
- getWord16host :: Get Word16
- getWord32host :: Get Word32
- getWord64host :: Get Word64
- getFloat32host :: Get Float
- getFloat64host :: Get Double
The Get type
Instances
| Monad Get Source # | |
| Functor Get Source # | |
| Applicative Get Source # | |
| Alternative Get Source # | |
| MonadPlus Get Source # | |
| BinaryParser Get Source # | |
| Defined in Data.Binary.Strict.Get Methods skip :: Int -> Get () Source # spanOf :: (Word8 -> Bool) -> Get ByteString Source # spanOf1 :: (Word8 -> Bool) -> Get ByteString Source # string :: ByteString -> Get () Source # word8 :: Word8 -> Get () Source # oneOf :: (Word8 -> Bool) -> Get Word8 Source # many :: Get a -> Get [a] Source # many1 :: Get a -> Get [a] Source # optional :: Get a -> Get (Maybe a) Source # getWord8 :: Get Word8 Source # getByteString :: Int -> Get ByteString Source # getWord16be :: Get Word16 Source # getWord32be :: Get Word32 Source # getWord64be :: Get Word64 Source # getWord16le :: Get Word16 Source # getWord32le :: Get Word32 Source # getWord64le :: Get Word64 Source # getWordhost :: Get Word Source # getWord16host :: Get Word16 Source # | |
runGet :: Get a -> ByteString -> (Either String a, ByteString) Source #
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 Source #
Run ga, but return without consuming its input.
 Fails if ga fails.
lookAheadM :: Get (Maybe a) -> Get (Maybe a) Source #
Like lookAhead, but consume the input if gma returns 'Just _'.
 Fails if gma fails.
lookAheadE :: Get (Either a b) -> Get (Either a b) Source #
Like lookAhead, but consume the input if gea returns 'Right _'.
 Fails if gea fails.
Utility
Get the number of remaining unparsed bytes. Useful for checking whether all input has been consumed.
Test whether all input has been consumed, i.e. there are no remaining unparsed bytes.
Parsing particular types
ByteStrings
getByteString :: Int -> Get ByteString Source #
An efficient get method for strict ByteStrings. Fails if fewer
 than n bytes are left in the input.
Big-endian reads
getWord16be :: Get Word16 Source #
getWord32be :: Get Word32 Source #
getWord64be :: Get Word64 Source #
Little-endian reads
getWord16le :: Get Word16 Source #
getWord32le :: Get Word32 Source #
getWord64le :: Get Word64 Source #
Host-endian, unaligned reads
getWordhost :: Get Word Source #