attoparsec-framer-0.1.0.3: Use Attoparsec to parse framed protocol byte streams
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 of 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

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

runFramer reads chunks from the ByteSource, parses these into frames and invokes the FrameHandler. Each invocation returns a Progression, which indicates if processing should continue. This allows the FrameHandler to trigger termination of runFramer.

Synopsis

Framer

type ByteSource m = Word32 -> m ByteString Source #

A byte stream from which chunks are to be retrieved.

data Framer m frame Source #

Uses a Parser to parse a stream of frames from a byte stream

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 Source #

Arguments

:: MonadThrow m 
=> Parser frame

parses frames from the byte stream

-> (frame -> m ())

handles parsed frames

-> ByteSource m

obtains the next chunk from the byte stream

-> Framer m frame 

Construct a Framer that loops continuously.

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

Construct a Framer that will handle frames repeatedly until the FrameHandler returns a Progression that 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 frame -> m () Source #

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

runOneFrame Source #

Arguments

:: MonadThrow m 
=> Maybe ByteString

the unparsed bytes from an earlier invocation, if any

-> Framer m frame

the Framer used to parse the frame

-> m (Maybe ByteString, Bool) 

Parse and handle a single frame.

The result is a tuple: (Maybe unparsed, terminated)

where

unparsed are outstanding bytes fetched from the ByteSource and terminated is True if the ByteSource has no further input.

Exception handling

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

This is because its intended use is for parsing framed protocol byte streams; where parsing or connection errors 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