store-streaming-0.2.0.2: Streaming interfaces for `store`

Safe HaskellNone
LanguageHaskell2010

Data.Store.Streaming

Contents

Description

For efficiency reasons, Store does not provide facilities for incrementally consuming input. In order to avoid partial input, this module introduces Messages that wrap values of instances of Store.

In addition to the serialisation of a value, the serialised message also contains the length of the serialisation. This way, instead of consuming input incrementally, more input can be demanded before serialisation is attempted in the first place.

Each message starts with a fixed magic number, in order to detect (randomly) invalid data.

Synopsis

Messages to stream data using Store for serialisation.

newtype Message a Source #

If a is an instance of Store, Message a can be serialised and deserialised in a streaming fashion.

Constructors

Message 

Fields

Instances
Eq a => Eq (Message a) Source # 
Instance details

Defined in Data.Store.Streaming

Methods

(==) :: Message a -> Message a -> Bool #

(/=) :: Message a -> Message a -> Bool #

Show a => Show (Message a) Source # 
Instance details

Defined in Data.Store.Streaming

Methods

showsPrec :: Int -> Message a -> ShowS #

show :: Message a -> String #

showList :: [Message a] -> ShowS #

Encoding Messages

Decoding Messages

type PeekMessage i m a = FT ((->) i) m a Source #

The result of peeking at the next message can either be a successfully deserialised object, or a request for more input.

type FillByteBuffer i m = ByteBuffer -> Int -> i -> m () Source #

Given some sort of input, fills the ByteBuffer with it.

The Int is how many bytes we'd like: this is useful when the filling function is fillFromFd, where we can specify a max size.

peekMessage :: (MonadIO m, Store a) => FillByteBuffer i m -> ByteBuffer -> PeekMessage i m (Message a) Source #

Decode some object from a ByteBuffer, by first reading its header, and then the actual data.

decodeMessage :: (Store a, MonadIO m) => FillByteBuffer i m -> ByteBuffer -> m (Maybe i) -> m (Maybe (Message a)) Source #

Decode a Message from a ByteBuffer and an action that can get additional inputs to refill the buffer when necessary.

The only conditions under which this function will give Nothing, is when the ByteBuffer contains zero bytes, and refilling yields Nothing. If there is some data available, but not enough to decode the whole Message, a PeekException will be thrown.

peekMessageBS :: (MonadIO m, Store a) => ByteBuffer -> PeekMessage ByteString m (Message a) Source #

Decode some Message from a ByteBuffer, by first reading its header, and then the actual Message.

data ReadMoreData Source #

We use this type as a more descriptive unit to signal that more input should be read from the Fd.

This data-type is only available on POSIX systems (essentially, non-windows)

Constructors

ReadMoreData 

peekMessageFd :: (MonadIO m, MonadFail m, Store a) => ByteBuffer -> Fd -> PeekMessage ReadMoreData m (Message a) Source #

Peeks a message from a _non blocking_ Fd.

This function is only available on POSIX systems (essentially, non-windows)

decodeMessageFd :: (MonadIO m, MonadFail m, Store a) => ByteBuffer -> Fd -> m (Message a) Source #

Decodes all the message using registerFd to find out when a Socket is ready for reading.

This function is only available on POSIX systems (essentially, non-windows)

Conduits for encoding and decoding

conduitEncode Source #

Arguments

:: (Monad m, Store a) 
=> Conduit (Message a) m ByteString

NOTE: ignore the conduit deprecation warning. Otherwise incompatible with old conduit versions

Conduit for encoding Messages to ByteStrings.

conduitDecode Source #

Arguments

:: (MonadResource m, Store a) 
=> Maybe Int

Initial length of the ByteBuffer used for buffering the incoming ByteStrings. If Nothing, use the default value of 4MB.

-> Conduit ByteString m (Message a)

NOTE: ignore the conduit deprecation warning. Otherwise incompatible with old conduit versions.

Conduit for decoding Messages from ByteStrings.