haskus-binary-1.4: Haskus binary format manipulation

Safe HaskellNone
LanguageHaskell2010

Haskus.Format.Binary.Get

Contents

Description

Get utilities

Synopsis

Documentation

data Get a #

The Get monad is an Exception and State monad.

Instances
Monad Get 
Instance details

Defined in Data.Serialize.Get

Methods

(>>=) :: Get a -> (a -> Get b) -> Get b #

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

return :: a -> Get a #

fail :: String -> Get a #

Functor Get 
Instance details

Defined in Data.Serialize.Get

Methods

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

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

MonadFail Get 
Instance details

Defined in Data.Serialize.Get

Methods

fail :: String -> Get a #

Applicative Get 
Instance details

Defined in Data.Serialize.Get

Methods

pure :: a -> Get a #

(<*>) :: Get (a -> b) -> Get a -> Get b #

liftA2 :: (a -> b -> c) -> Get a -> Get b -> Get c #

(*>) :: Get a -> Get b -> Get b #

(<*) :: Get a -> Get b -> Get a #

Alternative Get 
Instance details

Defined in Data.Serialize.Get

Methods

empty :: Get a #

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

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

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

MonadPlus Get 
Instance details

Defined in Data.Serialize.Get

Methods

mzero :: Get a #

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

runGet :: Get a -> Buffer -> Either String a Source #

Run the Get monad

runGetOrFail :: Get a -> Buffer -> a Source #

Run a getter and throw an exception on error

Size & alignment

isEmpty :: Get Bool Source #

Test whether all input *in the current chunk* has been consumed

remaining :: Get Word Source #

Get the number of remaining unparsed bytes *in the current chunk*

skip :: Word -> Get () Source #

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

uncheckedSkip :: Word -> Get () Source #

Skip ahead n bytes. No error if there isn't enough bytes.

skipAlign :: Word -> Word -> Get () Source #

Skip to align n to al. Fails if fewer than n bytes are available.

uncheckedSkipAlign :: Word -> Word -> Get () Source #

Skip to align n to al. Fails if fewer than n bytes are available.

countBytes :: Get a -> Get (Word, a) Source #

Count the number of bytes consumed by a getter

alignAfter :: Word -> Get a -> Get a Source #

Execute the getter and align on the given number of Word8

Isolation

consumeExactly :: Word -> Get a -> Get a Source #

Require an action to consume exactly the given number of bytes, fail otherwise

consumeAtMost :: Word -> Get a -> Get a Source #

Require an action to consume at most the given number of bytes, fail otherwise

Look-ahead

lookAhead :: Get a -> Get a Source #

Run the getter without consuming its input. Fails if it fails

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

Run the getter. Consume its input if Just _ returned. Fails if it fails

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

Run the getter. Consume its input if Right _ returned. Fails if it fails

Read

getRemaining :: Get Buffer Source #

Get remaining bytes

getBuffer :: Word -> Get Buffer Source #

Pull n bytes from the input, as a Buffer

getBufferNul :: Get Buffer Source #

Get Buffer terminated with 0 (consume 0)

getWord8 :: Get Word8 Source #

Get Word8

getWord16le :: Get Word16 Source #

Get Word16 little-endian

getWord16be :: Get Word16 Source #

Get Word16 big-endian

getWord32le :: Get Word32 Source #

Get Word32 little-endian

getWord32be :: Get Word32 Source #

Get Word32 big-endian

getWord64le :: Get Word64 Source #

Get Word64 little-endian

getWord64be :: Get Word64 Source #

Get Word64 big-endian

Utilities

getWhile :: (a -> Bool) -> Get a -> Get [a] Source #

Get while True (read and discard the ending element)

getWhole :: Get a -> Get [a] Source #

Repeat the getter to read the whole bytestring

getBitGet :: BitOrder -> BitGet a -> (a -> Get b) -> Get b Source #

Get bits from a BitGet.

Discard last bits to align on a Word8 boundary

FIXME: we use a continuation because Data.Serialize.Get doesn't export "put"

getManyAtMost :: Word -> Get (Maybe a) -> Get [a] Source #

Apply the getter at most max times

getManyBounded :: Maybe Word -> Maybe Word -> Get (Maybe a) -> Get (Maybe [a]) Source #

Apply the getter at least min times and at most max times