attoparsec-framer-0.1.0.0: Use Attoparsec to parse framed protocol bytestreams
Copyright(c) 2022 Tim Emiola
LicenseBSD3
MaintainerTim Emiola <adetokunbo@emio.la>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Attoparsec.Framer

Description

Provides the Framer data type that combines an Attoparsec Parser with a a few additional combinators that allow the parser to be used to process frames from the framed byte streams commonly used in network protocol implementations.

A Framer specifies how the processing function runFramer should parse a byte stream.

Minimally, a Framer specifies

  • An Parser, used to extract frames from the byte stream
  • a FrameHandler responsible using the parsed frames
  • the bytestream source, represented a ByteSource

runFramer the FrameHandler is invoked repeatedly; on each invocation it returns a Progression, which indicates if processing should continue. This makes it possible to terminate for the FrameHandler to signal that frame processing should terminate.

Synopsis

Framer

type ByteSource m = Word32 -> m ByteString Source #

A byte stream from which chunks are to be repeatedly retrieved.

data Framer m frame Source #

Use Parser to parse a stream of frames from a bytestream

type FrameHandler m frame = frame -> m Progression Source #

Handles a parsed frame, returning a Progression that indicates if further frames should be parsed.

data Progression Source #

Used by FrameHandler to indicate if additional frames should be parsed.

Constructors

Stop 
StopUnlessExtra 
Continue 

Instances

Instances details
Show Progression Source # 
Instance details

Defined in Data.Attoparsec.Framer

Eq Progression Source # 
Instance details

Defined in Data.Attoparsec.Framer

mkFramer :: MonadThrow m => Parser a -> (a -> m ()) -> (Word32 -> m ByteString) -> Framer m a Source #

Construct Framer that loops continuously.

mkFramer' :: MonadThrow m => Parser frame -> FrameHandler m frame -> ByteSource m -> Framer m frame Source #

Construct Framer that will handle frames repeatedly until a returned Progression stops it.

query/update a Framer

setChunkSize :: Word32 -> Framer m a -> Framer m a Source #

Update the chunk size of a Framer.

setOnBadParse :: (Text -> m ()) -> Framer m a -> Framer m a Source #

Update the parse error handler of a Framer.

setOnClosed :: m () -> Framer m a -> Framer m a Source #

Update the end-of-input handler of a Framer.

setOnFrame :: FrameHandler m frame -> Framer m frame -> Framer m frame Source #

Update the FrameHandler of a Framer.

chunkSize :: Framer m a -> Word32 Source #

The chunk size of a Framer.

Run the Framer

runFramer :: MonadThrow m => Framer m a -> m () Source #

Repeatedly parse and handle frames until the configured FrameHandler ends handling.

runOneFrame :: MonadThrow m => Maybe ByteString -> Framer m a -> m (Maybe ByteString, Bool) Source #

Parse and handle a single frame.

The result is tuple of the outstanding unparsed bytes from the bytestream if any, and a value indicating if the bytestream has terminated.

Exception handling

On failures, runFramer throws Exceptions using MonadThrow rather than using an Either or MonadError

This is because it is intended to be used to parse framed protocol byte streams; where parsing or connection errors here are typically not recoverable. In haskell non-recoverable failures are better modelled using Exceptions.

Although it throws NoMoreInput or BrokenFrame when appropriate, it provides hooks to override these when constructing a Framer.

By use of setOnClosed and setOnBadParse, the caller of runFramer can completely override the exception type that is raised when runFramer encounters any failure.

exceptions

newtype BrokenFrame Source #

Thrown by runFramer or runOneFrame if parsing fails and there is no handler installed using setOnBadParse, or it does not throw an exception.

Constructors

BrokenFrame String 

data NoMoreInput Source #

Thrown by runFramer or runOneFrame when no further input is available and no end of input handler is set using setOnClosed.

Constructors

NoMoreInput