Copyright | (c) Edward Kmett 2013 |
---|---|
License | BSD3 |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | experimental |
Portability | type-families |
Safe Haskell | Trustworthy |
Language | Haskell98 |
- class (Integral (Remaining m), Monad m, Applicative m) => MonadGet m where
- type Remaining m :: *
- type Bytes m :: *
- skip :: Int -> m ()
- ensure :: Int -> m ByteString
- lookAhead :: m a -> m a
- lookAheadM :: m (Maybe a) -> m (Maybe a)
- lookAheadE :: m (Either a b) -> m (Either a b)
- getBytes :: Int -> m ByteString
- remaining :: m (Remaining m)
- isEmpty :: m Bool
- getWord8 :: m Word8
- getByteString :: Int -> m ByteString
- getLazyByteString :: Int64 -> m ByteString
- getWord16be :: m Word16
- getWord16le :: m Word16
- getWord16host :: m Word16
- getWord32be :: m Word32
- getWord32le :: m Word32
- getWord32host :: m Word32
- getWord64be :: m Word64
- getWord64le :: m Word64
- getWord64host :: m Word64
- getWordhost :: m Word
- runGetL :: Get a -> ByteString -> a
- runGetS :: Get a -> ByteString -> Either String a
Documentation
class (Integral (Remaining m), Monad m, Applicative m) => MonadGet m where Source
An Integral
number type used for unchecked skips and counting.
The underlying ByteString type used by this instance
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.
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.
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.
Test whether all input has been consumed, i.e. there are no remaining unparsed bytes.
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.
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.
getWord16be :: m Word16 Source
Read a Word16
in big endian format
getWord16le :: 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.
getWord32be :: m Word32 Source
Read a Word32
in big endian format
getWord32le :: 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.
getWord64be :: m Word64 Source
Read a Word64
in big endian format
getWord64le :: 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 endianess.
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.
MonadGet Get | |
MonadGet Get | |
MonadGet m => MonadGet (ReaderT e m) | |
MonadGet m => MonadGet (StateT s m) | |
MonadGet m => MonadGet (StateT s m) | |
MonadGet m => MonadGet (ExceptT e m) | |
(MonadGet m, Monoid w) => MonadGet (WriterT w m) | |
(MonadGet m, Monoid w) => MonadGet (WriterT w m) | |
(MonadGet m, Monoid w) => MonadGet (RWST r w s m) | |
(MonadGet m, Monoid w) => MonadGet (RWST r w s m) |
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
.