binary-ext-2.0.2: An alternate with strong-typed errors for `Data.Binary.Get` monad from `binary` package.

Safe HaskellNone
LanguageHaskell2010

Data.Conduit.Parsers.Binary.Get

Description

At the first look, Data.Binary.Conduit.Get module is very similar with Data.Binary.Get. The main differences between them are the following. While the Get from binary is a very custom monad, the local Get is ConduitT, which leads to easy integration in complicated format parsing. The Data.Binary.Get module does not have a function to create custom Get monad, this module provides getC. Unlike isolate from binary, local isolate does not "cut" bytes counter. While the binary's Get is MonadFail, which leads to very ugly errors handling in complicated cases, local Get is MonadError.

Synopsis

Documentation

class (MonadError e m_e, MonadError e' m_e') => MonadMapError e m_e e' m_e' | m_e -> e, m_e' -> e', m_e e' -> m_e', m_e' e -> m_e where Source #

Minimal complete definition

mapError

Methods

mapError :: (e -> e') -> m_e a -> m_e' a Source #

Instances
MonadMapError e (Either e) e' (Either e') Source # 
Instance details

Defined in Control.Monad.Error.Map

Methods

mapError :: (e -> e') -> Either e a -> Either e' a Source #

Monad m => MonadMapError e (ExceptT e m) e' (ExceptT e' m) Source # 
Instance details

Defined in Control.Monad.Error.Map

Methods

mapError :: (e -> e') -> ExceptT e m a -> ExceptT e' m a Source #

MonadMapError e m_e e' m_e' => MonadMapError e (ConduitT i o m_e) e' (ConduitT i o m_e') Source # 
Instance details

Defined in Control.Monad.Error.Map

Methods

mapError :: (e -> e') -> ConduitT i o m_e a -> ConduitT i o m_e' a Source #

Monad m => MonadMapError e (GetC s i e m) e' (GetC s i e' m) Source # 
Instance details

Defined in Data.Conduit.Parsers.GetC

Methods

mapError :: (e -> e') -> GetC s i e m a -> GetC s i e' m a Source #

(?=>>) :: (MonadMapError e m_e (Either e e') m_Either_e_e', MonadMapError Void m_Void (Either e e') m_Either_e_e', MonadMapError (Either e e') m_Either_e_e' e' m_e') => m_e a -> (e -> m_Void e') -> m_e' a infixl 1 Source #

(?>>) :: (MonadMapError () m_Unit (Maybe e) m_Maybe_e, MonadMapError Void m_Void (Maybe e) m_Maybe_e, MonadMapError (Maybe e) m_Maybe_e e m_e) => m_Unit a -> m_Void e -> m_e a infixl 1 Source #

type GetT s i o e m = ConduitT i o (GetC s i e m) Source #

A ConduitT with internal transformers supposed to a binary deserialization.

type Get e a = forall s o m. (DefaultDecodingState s, Monad m) => GetT s ByteString o e m a Source #

The shortening of GetT for the most common use case of binary deserialization.

runGet :: Monad m => GetT ByteOffset i o e m a -> ConduitT i o m (Either e a) Source #

Run a decoder presented as a Get monad. Returns decoder result and consumed bytes count.

bytesRead :: (DecodingState s, DecodingElemsRead s, Monad m) => GetT s i o e m Word64 Source #

Get the total number of bytes read to this point.

castGet :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => Get a -> GetT s ByteString o String m a Source #

Run the given Get monad from binary package and convert result into Get.

skip :: (DecodingState s, Chunk (DecodingToken s), Monad m) => Word64 -> GetT s (DecodingToken s) o () m () Source #

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

isolate Source #

Arguments

:: (DecodingState s, Chunk (DecodingToken s), DecodingElemsRead s, Monad m) 
=> Word64

The number of bytes that must be consumed.

-> GetT s (DecodingToken s) o e m a

The decoder to isolate.

-> GetT s (DecodingToken s) o (Either (Maybe Word64) e) m a 

Isolate a decoder to operate with a fixed number of bytes, and fail if fewer bytes were consumed, or if fewer bytes are left in the input. Unlike isolate from binary package, offset from bytesRead will NOT be relative to the start of isolate.

getByteString :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => Int -> GetT s ByteString o () m 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 :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => Int64 -> GetT s ByteString o () m ByteString Source #

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

getLazyByteStringNul :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m 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 :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o e m 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.

getWord8 :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Word8 Source #

Read a Word8 from the monad state.

getInt8 :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Int8 Source #

Read an Int8 from the monad state.

getWord16be :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Word16 Source #

Read a Word16 in big endian format.

getWord32be :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Word32 Source #

Read a Word32 in big endian format.

getWord64be :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Word64 Source #

Read a Word64 in big endian format.

getWord16le :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Word16 Source #

Read a Word16 in little endian format.

getWord32le :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Word32 Source #

Read a Word32 in little endian format.

getWord64le :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Word64 Source #

Read a Word64 in little endian format.

getWordhost :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Word Source #

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 :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Word16 Source #

Read a 2 byte Word16 in native host order and host endianness.

getWord32host :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Word32 Source #

Read a 4 byte Word32 in native host order and host endianness.

getWord64host :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Word64 Source #

Read a 8 byte Word64 in native host order and host endianness.

getInt16be :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Int16 Source #

Read an Int16 in big endian format.

getInt32be :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Int32 Source #

Read an Int32 in big endian format.

getInt64be :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Int64 Source #

Read an Int64 in big endian format.

getInt16le :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Int16 Source #

Read an Int16 in little endian format.

getInt32le :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Int32 Source #

Read an Int32 in little endian format.

getInt64le :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Int64 Source #

Read an Int64 in little endian format.

getInthost :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Int Source #

Read a single native machine word. It works in the same way as getWordhost.

getInt16host :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Int16 Source #

Read a 2 byte Int16 in native host order and host endianness.

getInt32host :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Int32 Source #

Read a 4 byte Int32 in native host order and host endianness.

getInt64host :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Int64 Source #

Read a 8 byte Int64 in native host order and host endianness.

getFloatbe :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Float Source #

Read a Float in big endian IEEE-754 format.

getFloatle :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Float Source #

Read a Float in little endian IEEE-754 format.

getFloathost :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Float Source #

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

getDoublebe :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Double Source #

Read a Double in big endian IEEE-754 format.

getDoublele :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Double Source #

Read a Double in little endian IEEE-754 format.

getDoublehost :: (DecodingState s, DecodingToken s ~ ByteString, Monad m) => GetT s ByteString o () m Double Source #

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