binary-ext-0.8.4.1: Binary serialisation for Haskell values using lazy ByteStrings

Safe HaskellNone
LanguageHaskell98

Data.Binary.Get.Ext.Internal

Contents

Synopsis

The Get e type

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 #

runCont :: Get e a -> forall r. Int64 -> ByteString -> Success e a r -> Decoder e r Source #

data Decoder e a Source #

A decoder produced by running a Get monad.

Constructors

Fail !ByteString (Either String e)

The decoder ran into an error. The decoder either used fail or was not provided enough input.

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 a

The decoder has successfully finished. Except for the output value you also get the unused input.

BytesRead !Int64 (Int64 -> Decoder e a)

The decoder needs to know the current position in the input. Given the number of bytes remaning in the decoder, the outer decoder runner needs to calculate the position and resume the decoding.

Instances

Functor (Decoder e) Source # 

Methods

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

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

(Show e, Show a) => Show (Decoder e a) Source # 

Methods

showsPrec :: Int -> Decoder e a -> ShowS #

show :: Decoder e a -> String #

showList :: [Decoder e a] -> ShowS #

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

Run a Get monad. See Decoder for what to do next, like providing input, handling decoding errors and to get the output value.

readN :: Int -> (ByteString -> a) -> Get () a Source #

Return at least n bytes, maybe more. If not enough data is available the computation will escape with Partial.

readNWith :: Int -> (Ptr a -> IO a) -> Get () a Source #

readNWith n f where f must be deterministic and not have side effects.

Parsing

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.

With input chunks

withInputChunks :: s -> Consume s -> ([ByteString] -> b) -> ([ByteString] -> Get e b) -> Get e b Source #

get :: Get e ByteString Source #

Get e the current chunk.

put :: ByteString -> Get e () Source #

Replace the current chunk.

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

Ensure that there are at least n bytes available. If not, the computation will escape with Partial.

Utility

isEmpty :: Get e Bool Source #

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

failG :: e -> Get e a Source #

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.

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.