bytes-0.15.4: Sharing code for serialization between binary and cereal

Copyright(c) Edward Kmett 2013-2015
LicenseBSD3
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilitytype-families
Safe HaskellTrustworthy
LanguageHaskell98

Data.Bytes.Get

Description

This module generalizes the binary Get and cereal Get monads in an ad hoc fashion to permit code to be written that is compatible across them.

Moreover, this class permits code to be written to be portable over various monad transformers applied to these as base monads.

Synopsis

Documentation

class (Integral (Remaining m), Monad m, Applicative m) => MonadGet m where Source #

Minimal complete definition

lookAhead, lookAheadM, lookAheadE

Associated Types

type Remaining m :: * Source #

An Integral number type used for unchecked skips and counting.

type Bytes m :: * Source #

The underlying ByteString type used by this instance

Methods

skip :: Int -> m () Source #

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

skip :: (MonadTrans t, MonadGet n, m ~ t n) => Int -> m () Source #

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

ensure :: Int -> m ByteString Source #

If at least n bytes are available return at least that much of the current input. Otherwise fail.

ensure :: (MonadTrans t, MonadGet n, m ~ t n) => Int -> m ByteString Source #

If at least n bytes are available return at least that much of the current input. Otherwise fail.

lookAhead :: m a -> m a Source #

Run ga, but return without consuming its input. Fails if ga fails.

lookAheadM :: m (Maybe a) -> m (Maybe a) Source #

Like lookAhead, but consume the input if gma returns 'Just _'. Fails if gma fails.

lookAheadE :: m (Either a b) -> m (Either a b) Source #

Like lookAhead, but consume the input if gea returns 'Right _'. Fails if gea fails.

getBytes :: Int -> m ByteString Source #

Pull n bytes from the input, as a strict ByteString.

getBytes :: (MonadTrans t, MonadGet n, m ~ t n) => Int -> m ByteString Source #

Pull n bytes from the input, as a strict ByteString.

remaining :: m (Remaining m) Source #

Get the number of remaining unparsed bytes. Useful for checking whether all input has been consumed. Note that this forces the rest of the input.

remaining :: (MonadTrans t, MonadGet n, m ~ t n, Remaining m ~ Remaining n) => m (Remaining m) Source #

Get the number of remaining unparsed bytes. Useful for checking whether all input has been consumed. Note that this forces the rest of the input.

isEmpty :: m Bool Source #

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

isEmpty :: (MonadTrans t, MonadGet n, m ~ t n) => m Bool Source #

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

getWord8 :: m Word8 Source #

Read a Word8 from the monad state

getWord8 :: (MonadTrans t, MonadGet n, m ~ t n) => m Word8 Source #

Read a Word8 from the monad state

getByteString :: Int -> m ByteString Source #

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

getByteString :: (MonadTrans t, MonadGet n, m ~ t n) => Int -> m ByteString Source #

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

getLazyByteString :: Int64 -> m ByteString Source #

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

getLazyByteString :: (MonadTrans t, MonadGet n, m ~ t n) => Int64 -> m ByteString Source #

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

getWord16be :: m Word16 Source #

Read a Word16 in big endian format

getWord16be :: (MonadTrans t, MonadGet n, m ~ t n) => m Word16 Source #

Read a Word16 in big endian format

getWord16le :: m Word16 Source #

Read a Word16 in little endian format

getWord16le :: (MonadTrans t, MonadGet n, m ~ t n) => m Word16 Source #

Read a Word16 in little endian format

getWord16host :: m Word16 Source #

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

getWord16host :: (MonadTrans t, MonadGet n, m ~ t n) => m Word16 Source #

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

getWord32be :: m Word32 Source #

Read a Word32 in big endian format

getWord32be :: (MonadTrans t, MonadGet n, m ~ t n) => m Word32 Source #

Read a Word32 in big endian format

getWord32le :: m Word32 Source #

Read a Word32 in little endian format

getWord32le :: (MonadTrans t, MonadGet n, m ~ t n) => m Word32 Source #

Read a Word32 in little endian format

getWord32host :: m Word32 Source #

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

getWord32host :: (MonadTrans t, MonadGet n, m ~ t n) => m Word32 Source #

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

getWord64be :: m Word64 Source #

Read a Word64 in big endian format

getWord64be :: (MonadTrans t, MonadGet n, m ~ t n) => m Word64 Source #

Read a Word64 in big endian format

getWord64le :: m Word64 Source #

Read a Word64 in little endian format

getWord64le :: (MonadTrans t, MonadGet n, m ~ t n) => m Word64 Source #

Read a Word64 in little endian format

getWord64host :: m Word64 Source #

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

getWord64host :: (MonadTrans t, MonadGet n, m ~ t n) => m Word64 Source #

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

getWordhost :: m 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.

getWordhost :: (MonadTrans t, MonadGet n, m ~ t n) => m 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.

Instances

MonadGet Get Source # 
MonadGet Get Source # 
MonadGet m => MonadGet (ExceptT e m) Source # 
MonadGet m => MonadGet (StateT s m) Source # 
MonadGet m => MonadGet (StateT s m) Source # 
(MonadGet m, Monoid w) => MonadGet (WriterT w m) Source # 
(MonadGet m, Monoid w) => MonadGet (WriterT w m) Source # 
MonadGet m => MonadGet (ReaderT * e m) Source # 
(MonadGet m, Monoid w) => MonadGet (RWST r w s m) Source # 

Associated Types

type Remaining (RWST r w s m :: * -> *) :: * Source #

type Bytes (RWST r w s m :: * -> *) :: * Source #

Methods

skip :: Int -> RWST r w s m () Source #

ensure :: Int -> RWST r w s m ByteString Source #

lookAhead :: RWST r w s m a -> RWST r w s m a Source #

lookAheadM :: RWST r w s m (Maybe a) -> RWST r w s m (Maybe a) Source #

lookAheadE :: RWST r w s m (Either a b) -> RWST r w s m (Either a b) Source #

getBytes :: Int -> RWST r w s m ByteString Source #

remaining :: RWST r w s m (Remaining (RWST r w s m)) Source #

isEmpty :: RWST r w s m Bool Source #

getWord8 :: RWST r w s m Word8 Source #

getByteString :: Int -> RWST r w s m ByteString Source #

getLazyByteString :: Int64 -> RWST r w s m ByteString Source #

getWord16be :: RWST r w s m Word16 Source #

getWord16le :: RWST r w s m Word16 Source #

getWord16host :: RWST r w s m Word16 Source #

getWord32be :: RWST r w s m Word32 Source #

getWord32le :: RWST r w s m Word32 Source #

getWord32host :: RWST r w s m Word32 Source #

getWord64be :: RWST r w s m Word64 Source #

getWord64le :: RWST r w s m Word64 Source #

getWord64host :: RWST r w s m Word64 Source #

getWordhost :: RWST r w s m Word Source #

(MonadGet m, Monoid w) => MonadGet (RWST r w s m) Source # 

Associated Types

type Remaining (RWST r w s m :: * -> *) :: * Source #

type Bytes (RWST r w s m :: * -> *) :: * Source #

Methods

skip :: Int -> RWST r w s m () Source #

ensure :: Int -> RWST r w s m ByteString Source #

lookAhead :: RWST r w s m a -> RWST r w s m a Source #

lookAheadM :: RWST r w s m (Maybe a) -> RWST r w s m (Maybe a) Source #

lookAheadE :: RWST r w s m (Either a b) -> RWST r w s m (Either a b) Source #

getBytes :: Int -> RWST r w s m ByteString Source #

remaining :: RWST r w s m (Remaining (RWST r w s m)) Source #

isEmpty :: RWST r w s m Bool Source #

getWord8 :: RWST r w s m Word8 Source #

getByteString :: Int -> RWST r w s m ByteString Source #

getLazyByteString :: Int64 -> RWST r w s m ByteString Source #

getWord16be :: RWST r w s m Word16 Source #

getWord16le :: RWST r w s m Word16 Source #

getWord16host :: RWST r w s m Word16 Source #

getWord32be :: RWST r w s m Word32 Source #

getWord32le :: RWST r w s m Word32 Source #

getWord32host :: RWST r w s m Word32 Source #

getWord64be :: RWST r w s m Word64 Source #

getWord64le :: RWST r w s m Word64 Source #

getWord64host :: RWST r w s m Word64 Source #

getWordhost :: RWST r w s m Word Source #

runGetL :: Get a -> ByteString -> a Source #

Get something from a lazy ByteString using runGet.

runGetS :: Get a -> ByteString -> Either String a Source #

Get something from a strict ByteString using runGet.