Stability | Portability : |
---|---|
Maintainer | Trevor Elliott <trevor@galois.com> |
Safe Haskell | None |
The Get monad. A monad for efficiently building structures from strict ByteStrings
- data Get a
- runGet :: Get a -> ByteString -> Either String a
- runGetLazy :: Get a -> ByteString -> Either String a
- runGetState :: Get a -> ByteString -> Int -> Either String (a, ByteString)
- runGetLazyState :: Get a -> ByteString -> Either String (a, ByteString)
- data Result r
- = Fail String ByteString
- | Partial (ByteString -> Result r)
- | Done r ByteString
- runGetPartial :: Get a -> ByteString -> Result a
- ensure :: Int -> Get ByteString
- isolate :: Int -> Get a -> Get a
- label :: String -> Get a -> Get a
- skip :: Int -> Get ()
- uncheckedSkip :: Int -> Get ()
- lookAhead :: Get a -> Get a
- lookAheadM :: Get (Maybe a) -> Get (Maybe a)
- lookAheadE :: Get (Either a b) -> Get (Either a b)
- uncheckedLookAhead :: Int -> Get ByteString
- getBytes :: Int -> Get ByteString
- remaining :: Get Int
- isEmpty :: Get Bool
- getWord8 :: Get Word8
- getByteString :: Int -> Get ByteString
- getLazyByteString :: Int64 -> 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
- getTwoOf :: Get a -> Get b -> Get (a, b)
- getListOf :: Get a -> Get [a]
- getIArrayOf :: (Ix i, IArray a e) => Get i -> Get e -> Get (a i e)
- getTreeOf :: Get a -> Get (Tree a)
- getSeqOf :: Get a -> Get (Seq a)
- getMapOf :: Ord k => Get k -> Get a -> Get (Map k a)
- getIntMapOf :: Get Int -> Get a -> Get (IntMap a)
- getSetOf :: Ord a => Get a -> Get (Set a)
- getIntSetOf :: Get Int -> Get IntSet
- getMaybeOf :: Get a -> Get (Maybe a)
- getEitherOf :: Get a -> Get b -> Get (Either a b)
The Get type
The Get monad is an Exception and State monad.
runGet :: Get a -> ByteString -> Either String aSource
Run the Get monad applies a get
-based parser on the input ByteString
runGetLazy :: Get a -> ByteString -> Either String aSource
Run the Get monad over a Lazy ByteString. Note that this will not run the Get parser lazily, but will operate on lazy ByteStrings.
runGetState :: Get a -> ByteString -> Int -> Either String (a, ByteString)Source
Run the Get monad applies a get
-based parser on the input
ByteString. Additional to the result of get it returns the number of
consumed bytes and the rest of the input.
runGetLazyState :: Get a -> ByteString -> Either String (a, ByteString)Source
Run the Get monad over a Lazy ByteString. Note that this does not run the Get parser lazily, but will operate on lazy ByteStrings.
The result of a parse.
Fail String ByteString | The parse failed. The |
Partial (ByteString -> Result r) | Supply this continuation with more input so that
the parser can resume. To indicate that no more
input is available, use an |
Done r ByteString | The parse succeeded. The |
runGetPartial :: Get a -> ByteString -> Result aSource
Run the Get monad applies a get
-based parser on the input ByteString
Parsing
ensure :: Int -> Get ByteStringSource
If at least n
bytes of input are available, return the current
input, otherwise fail.
isolate :: Int -> Get a -> Get aSource
Isolate an action to operating within a fixed block of bytes. The action is required to consume all the bytes that it is isolated to.
uncheckedSkip :: Int -> Get ()Source
Skip ahead n
bytes. No error if there isn't enough bytes.
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.
uncheckedLookAhead :: Int -> Get ByteStringSource
Get the next up to n
bytes as a ByteString, without consuming them.
Utility
getBytes :: Int -> Get ByteStringSource
Pull n
bytes from the input, as a strict ByteString.
Get the number of remaining unparsed bytes. Useful for checking whether all input has been consumed.
WARNING: when run with runGetPartial
, remaining will only return the number
of bytes that are remaining in the current input.
Test whether all input has been consumed.
WARNING: when run with runGetPartial
, isEmpty will only tell you if you're
at the end of the current chunk.
Parsing particular types
ByteStrings
getByteString :: Int -> Get ByteStringSource
An efficient get
method for strict ByteStrings. Fails if fewer
than n
bytes are left in the input. This function creates a fresh
copy of the underlying bytes.
Big-endian reads
getWord16be :: Get Word16Source
Read a Word16 in big endian format
getWord32be :: Get Word32Source
Read a Word32 in big endian format
getWord64be :: Get Word64Source
Read a Word64 in big endian format
Little-endian reads
getWord16le :: Get Word16Source
Read a Word16 in little endian format
getWord32le :: Get Word32Source
Read a Word32 in little endian format
getWord64le :: Get Word64Source
Read a Word64 in little endian format
Host-endian, unaligned reads
O(1). Read a single native machine word. The word is read in host order, host endian form, for the machine you're on. On a 64 bit machine the Word is an 8 byte value, on a 32 bit machine, 4 bytes.
getWord16host :: Get Word16Source
O(1). Read a 2 byte Word16 in native host order and host endianness.
getWord32host :: Get Word32Source
O(1). Read a Word32 in native host order and host endianness.
getWord64host :: Get Word64Source
O(1). Read a Word64 in native host order and host endianess.
Containers
getListOf :: Get a -> Get [a]Source
Get a list in the following format: Word64 (big endian format) element 1 ... element n
getIArrayOf :: (Ix i, IArray a e) => Get i -> Get e -> Get (a i e)Source
Get an IArray in the following format: index (lower bound) index (upper bound) Word64 (big endian format) element 1 ... element n
getSeqOf :: Get a -> Get (Seq a)Source
Get a sequence in the following format: Word64 (big endian format) element 1 ... element n
getMapOf :: Ord k => Get k -> Get a -> Get (Map k a)Source
Read as a list of pairs of key and element.
getMaybeOf :: Get a -> Get (Maybe a)Source
Read in a Maybe in the following format: Word8 (0 for Nothing, anything else for Just) element (when Just)