| Copyright | (c) 2022 Tim Emiola |
|---|---|
| License | BSD3 |
| Maintainer | Tim Emiola <adetokunbo@emio.la> |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Data.Attoparsec.Framer
Description
Provides the Framer data type that combines an Attoparsec 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.Parser
A specifies how the processing function Framer should
parse a byte stream.runFramer
Minimally, a Framer specifies
- a
, used to extract frames from the byte streamParser - a
responsible for using the parsed framesFrameHandler - the byte stream source, represented by a
ByteSource
reads chunks from the runFramerByteSource, 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
- type ByteSource m = Word32 -> m ByteString
- data Framer m frame
- type FrameHandler m frame = frame -> m Progression
- data Progression
- mkFramer :: MonadThrow m => Parser frame -> (frame -> m ()) -> ByteSource m -> Framer m frame
- mkFramer' :: MonadThrow m => Parser frame -> FrameHandler m frame -> ByteSource m -> Framer m frame
- setChunkSize :: Word32 -> Framer m a -> Framer m a
- setOnBadParse :: (Text -> m ()) -> Framer m a -> Framer m a
- setOnClosed :: m () -> Framer m a -> Framer m a
- setOnFrame :: FrameHandler m frame -> Framer m frame -> Framer m frame
- chunkSize :: Framer m a -> Word32
- runFramer :: MonadThrow m => Framer m frame -> m ()
- runOneFrame :: MonadThrow m => Maybe ByteString -> Framer m frame -> m (Maybe ByteString, Bool)
- newtype BrokenFrame = BrokenFrame String
- data NoMoreInput = NoMoreInput
Framer
type ByteSource m = Word32 -> m ByteString Source #
A byte stream from which chunks are to be retrieved.
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
| Show Progression Source # | |
Defined in Data.Attoparsec.Framer Methods showsPrec :: Int -> Progression -> ShowS # show :: Progression -> String # showList :: [Progression] -> ShowS # | |
| Eq Progression Source # | |
Defined in Data.Attoparsec.Framer | |
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 that loops continuously.Framer
mkFramer' :: MonadThrow m => Parser frame -> FrameHandler m frame -> ByteSource m -> Framer m frame Source #
Construct a that will handle Framerframes repeatedly until the
FrameHandler returns a that stops it.Progression
query/update a Framer
FramersetOnBadParse :: (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.
Run the Framer
runFramer :: MonadThrow m => Framer m frame -> m () Source #
Repeatedly parse and handle frames until the configured FrameHandler ends handling.
Arguments
| :: MonadThrow m | |
| => Maybe ByteString | the unparsed bytes from an earlier invocation, if any |
| -> Framer m frame | the |
| -> 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, throws runFramer using Exceptions rather
than using an MonadThrowEither 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 |
Instances
| Exception BrokenFrame Source # | |
Defined in Data.Attoparsec.Framer Methods toException :: BrokenFrame -> SomeException # fromException :: SomeException -> Maybe BrokenFrame # displayException :: BrokenFrame -> String # | |
| Show BrokenFrame Source # | |
Defined in Data.Attoparsec.Framer Methods showsPrec :: Int -> BrokenFrame -> ShowS # show :: BrokenFrame -> String # showList :: [BrokenFrame] -> ShowS # | |
| Eq BrokenFrame Source # | |
Defined in Data.Attoparsec.Framer | |
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 |
Instances
| Exception NoMoreInput Source # | |
Defined in Data.Attoparsec.Framer Methods toException :: NoMoreInput -> SomeException # fromException :: SomeException -> Maybe NoMoreInput # displayException :: NoMoreInput -> String # | |
| Show NoMoreInput Source # | |
Defined in Data.Attoparsec.Framer Methods showsPrec :: Int -> NoMoreInput -> ShowS # show :: NoMoreInput -> String # showList :: [NoMoreInput] -> ShowS # | |
| Eq NoMoreInput Source # | |
Defined in Data.Attoparsec.Framer | |