Copyright | (c) 2022 Tim Emiola |
---|---|
License | BSD3 |
Maintainer | Tim Emiola <adetokunbo@emio.la> |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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
from 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
- An
, used to extract frames from the byte streamParser
- a
responsible using the parsed framesFrameHandler
- the bytestream source, represented a
ByteSource
the runFramer
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
- type ByteSource m = Word32 -> m ByteString
- data Framer m frame
- type FrameHandler m frame = frame -> m Progression
- data Progression
- mkFramer :: MonadThrow m => Parser a -> (a -> m ()) -> (Word32 -> m ByteString) -> Framer m a
- 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 a -> m ()
- runOneFrame :: MonadThrow m => Maybe ByteString -> Framer m a -> 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 repeatedly 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.
Instances
Show Progression Source # | |
Defined in Data.Attoparsec.Framer showsPrec :: Int -> Progression -> ShowS # show :: Progression -> String # showList :: [Progression] -> ShowS # | |
Eq Progression Source # | |
Defined in Data.Attoparsec.Framer (==) :: Progression -> Progression -> Bool # (/=) :: Progression -> Progression -> Bool # |
mkFramer :: MonadThrow m => Parser a -> (a -> m ()) -> (Word32 -> m ByteString) -> Framer m a Source #
Construct
that loops continuously.Framer
mkFramer' :: MonadThrow m => Parser frame -> FrameHandler m frame -> ByteSource m -> Framer m frame Source #
Construct
that will handle Framer
frames
repeatedly until a returned
stops it.Progression
query/update a Framer
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
.
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,
throws runFramer
using Exception
s
rather
than using an MonadThrow
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.
Instances
Exception BrokenFrame Source # | |
Defined in Data.Attoparsec.Framer | |
Show BrokenFrame Source # | |
Defined in Data.Attoparsec.Framer showsPrec :: Int -> BrokenFrame -> ShowS # show :: BrokenFrame -> String # showList :: [BrokenFrame] -> ShowS # | |
Eq BrokenFrame Source # | |
Defined in Data.Attoparsec.Framer (==) :: BrokenFrame -> BrokenFrame -> Bool # (/=) :: BrokenFrame -> BrokenFrame -> Bool # |
data NoMoreInput Source #
Thrown by runFramer
or runOneFrame
when no further input is available and
no end of input handler is set using setOnClosed
.
Instances
Exception NoMoreInput Source # | |
Defined in Data.Attoparsec.Framer | |
Show NoMoreInput Source # | |
Defined in Data.Attoparsec.Framer showsPrec :: Int -> NoMoreInput -> ShowS # show :: NoMoreInput -> String # showList :: [NoMoreInput] -> ShowS # | |
Eq NoMoreInput Source # | |
Defined in Data.Attoparsec.Framer (==) :: NoMoreInput -> NoMoreInput -> Bool # (/=) :: NoMoreInput -> NoMoreInput -> Bool # |