binary-ext-1.0: An alternate with typed errors for Data.Binary.Get monad from 'binary' library.

Safe HaskellTrustworthy
LanguageHaskell98

Data.Binary.Get.Ext

Contents

Synopsis

The Get monad

data Get e a Source #

Instances

Monad (Get e) Source # 

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 # 

Methods

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

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

MonadFail (Get e) Source # 

Methods

fail :: String -> Get e a #

Applicative (Get e) Source # 

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 #

Alternative (Get e) Source # 

Methods

empty :: Get e a #

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

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

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

MonadPlus (Get e) Source # 

Methods

mzero :: Get e a #

mplus :: Get e a -> Get e a -> Get e a #

The lazy input interface

The lazy interface consumes a single lazy ByteString. It's the easiest interface to get started with, but it doesn't support interleaving I/O and parsing, unless lazy I/O is used.

There is no way to provide more input other than the initial data. To be able to incrementally give more data, see the incremental input interface.

runGetOrFail :: ByteOffset -> Get e a -> ByteString -> Either (ByteString, ByteOffset, Either String e) (ByteString, ByteOffset, a) Source #

Run a Get monad and return Left on failure and Right on success. In both cases any unconsumed input and the number of bytes consumed is returned. In the case of failure, a human-readable error message is included as well.

type ByteOffset = Int64 Source #

An offset, counted in bytes.

The incremental input interface

The incremental interface gives you more control over how input is provided during parsing. This lets you e.g. interleave parsing and I/O.

The incremental interface consumes a strict ByteString at a time, each being part of the total amount of input. If your decoder needs more input to finish it will return a Partial with a continuation. If there is no more input, provide it Nothing.

Fail will be returned if it runs into an error, together with a message, the position and the remaining input. If it succeeds it will return Done with the resulting value, the position and the remaining input.

data Decoder e a Source #

A decoder procuced by running a Get monad.

Constructors

Fail !ByteString !ByteOffset (Either String e)

The decoder ran into an error. The decoder either used fail or was not provided enough input. Contains any unconsumed input and the number of bytes consumed.

Partial (Maybe ByteString -> Decoder e a)

The decoder has consumed the available input and needs more to continue. Provide Just if more input is available and Nothing otherwise, and you will get a new Decoder.

Done !ByteString !ByteOffset a

The decoder has successfully finished. Except for the output value you also get any unused input as well as the number of bytes consumed.

runGetIncremental :: ByteOffset -> Get e a -> Decoder e a Source #

Run a Get monad. See Decoder for what to do next, like providing input, handling decoder errors and to get the output value. Hint: Use the helper functions pushChunk, pushChunks and pushEndOfInput.

Providing input

pushChunk :: Decoder e a -> ByteString -> Decoder e a Source #

Feed a Decoder with more input. If the Decoder is Done or Fail it will add the input to ByteString of unconsumed input.

   runGetIncremental myParser `pushChunk` myInput1 `pushChunk` myInput2

pushChunks :: Decoder e a -> ByteString -> Decoder e a Source #

Feed a Decoder with more input. If the Decoder is Done or Fail it will add the input to ByteString of unconsumed input.

   runGetIncremental myParser `pushChunks` myLazyByteString

pushEndOfInput :: Decoder e a -> Decoder e a Source #

Tell a Decoder that there is no more input. This passes Nothing to a Partial decoder, otherwise returns the decoder unchanged.

Decoding

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

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

isEmpty :: Get e Bool Source #

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

bytesRead :: Get e Int64 Source #

Get e the total number of bytes read to this point.

totalBytesRead :: Get e Int64 Source #

Get e the total number of bytes read to this point.

isolate Source #

Arguments

:: Int

The number of bytes that must be consumed

-> Get e a

The decoder to isolate

-> (Int -> e)

The error if fewer bytes were consumed

-> Get e a 

Isolate a decoder to operate with a fixed number of bytes, and fail if fewer bytes were consumed, or more bytes were attempted to be consumed. If the given decoder fails, isolate will also fail. Offset from bytesRead will be relative to the start of isolate, not the absolute of the input.

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

Run the given decoder, but without consuming its input. If the given decoder fails, then so will this function.

Since: 0.7.0.0

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

Run the given decoder, and only consume its input if it returns Just. If Nothing is returned, the input will be unconsumed. If the given decoder fails, then so will this function.

Since: 0.7.0.0

lookAheadE :: Get e (Either a b) -> Get e (Either a b) Source #

Run the given decoder, and only consume its input if it returns Right. If Left is returned, the input will be unconsumed. If the given decoder fails, then so will this function.

onError :: (e -> e') -> Get e a -> Get e' a Source #

Convert decoder error. If the decoder fails, the given function will be applied to the error message.

withError :: Get () a -> e -> Get e a Source #

Set decoder error. If the decoder fails, the given error will be used as the error message.

failG :: e -> Get e a Source #

ByteStrings

getByteString :: Int -> Get () ByteString Source #

An efficient get method for strict ByteStrings. Fails if fewer than n bytes are left in the input. If n <= 0 then the empty string is returned.

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

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

getLazyByteStringNul :: Get () ByteString Source #

Get a lazy ByteString that is terminated with a NUL byte. The returned string does not contain the NUL byte. Fails if it reaches the end of input without finding a NUL.

getRemainingLazyByteString :: Get e ByteString Source #

Get the remaining bytes as a lazy ByteString. Note that this can be an expensive function to use as it forces reading all input and keeping the string in-memory.

Decoding Words

getWord8 :: Get () Word8 Source #

Read a Word8 from the monad state

Big-endian decoding

getWord16be :: Get () Word16 Source #

Read a Word16 in big endian format

getWord32be :: Get () Word32 Source #

Read a Word32 in big endian format

getWord64be :: Get () Word64 Source #

Read a Word64 in big endian format

Little-endian decoding

getWord16le :: Get () Word16 Source #

Read a Word16 in little endian format

getWord32le :: Get () Word32 Source #

Read a Word32 in little endian format

getWord64le :: Get () Word64 Source #

Read a Word64 in little endian format

Host-endian, unaligned decoding

getWordhost :: Get () Word Source #

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

O(1). Read a 2 byte Word16 in native host order and host endianness.

getWord32host :: Get () Word32 Source #

O(1). Read a Word32 in native host order and host endianness.

getWord64host :: Get () Word64 Source #

O(1). Read a Word64 in native host order and host endianess.

Decoding Ints

getInt8 :: Get () Int8 Source #

Read an Int8 from the monad state

Big-endian decoding

getInt16be :: Get () Int16 Source #

Read an Int16 in big endian format.

getInt32be :: Get () Int32 Source #

Read an Int32 in big endian format.

getInt64be :: Get () Int64 Source #

Read an Int64 in big endian format.

Little-endian decoding

getInt16le :: Get () Int16 Source #

Read an Int16 in little endian format.

getInt32le :: Get () Int32 Source #

Read an Int32 in little endian format.

getInt64le :: Get () Int64 Source #

Read an Int64 in little endian format.

Host-endian, unaligned decoding

getInthost :: Get () Int Source #

O(1). Read a single native machine word in native host order. It works in the same way as getWordhost.

getInt16host :: Get () Int16 Source #

O(1). Read a 2 byte Int16 in native host order and host endianness.

getInt32host :: Get () Int32 Source #

O(1). Read an Int32 in native host order and host endianness.

getInt64host :: Get () Int64 Source #

O(1). Read an Int64 in native host order and host endianess.

Decoding Floats/Doubles

getFloatbe :: Get () Float Source #

Read a Float in big endian IEEE-754 format.

getFloatle :: Get () Float Source #

Read a Float in little endian IEEE-754 format.

getFloathost :: Get () Float Source #

Read a Float in IEEE-754 format and host endian.

getDoublebe :: Get () Double Source #

Read a Double in big endian IEEE-754 format.

getDoublele :: Get () Double Source #

Read a Double in little endian IEEE-754 format.

getDoublehost :: Get () Double Source #

Read a Double in IEEE-754 format and host endian.