conduit-parse-0.1.1.1: Parsing framework based on conduit.

Safe HaskellNone
LanguageHaskell2010

Data.Conduit.Parser

Contents

Description

This module introduces ConduitParser, a wrapper around Sink that behaves like a parser.

You probably want to import the Text.Parser.Combinators module together with this module.

Synopsis

Conduit parser monad

data ConduitParser i m a Source

Core type of the package. This is basically a Sink with a parsing state.

Instances

MonadError ConduitParserException (ConduitParser i m) Source

Backtracking is supported by pushing back consumed elements (using leftover) whenever an error is catched.

As a consequence, within the scope of a catchError, all streamed items are kept in memory, which means the consumer no longer uses constant memory.

MonadTrans (ConduitParser i) Source 
Monad (ConduitParser i m) Source 
Functor (ConduitParser i m) Source 
Applicative (ConduitParser i m) Source 
Alternative (ConduitParser i m) Source

Parsers can be combined with (<|>), some, many, optional, choice.

The use of guard is not recommended as it generates unhelpful error messages. Please consider using throwError or unexpected instead.

MonadThrow m => MonadThrow (ConduitParser i m) Source 
MonadCatch m => MonadCatch (ConduitParser i m) Source 
MonadIO m => MonadIO (ConduitParser i m) Source 
Monad m => Parsing (ConduitParser i m) Source

Parsing combinators can be used with ConduitParsers.

runConduitParser :: MonadThrow m => ConduitParser i m a -> Sink i m a Source

Run a ConduitParser. Any parsing failure will be thrown as an exception.

named :: Monad m => Text -> ConduitParser i m a -> ConduitParser i m a Source

Flipped version of (<?>).

Primitives

await :: Monad m => ConduitParser i m i Source

await wrapped as a ConduitParser.

If no data is available, UnexpectedEndOfInput is thrown.

leftover :: i -> ConduitParser i m () Source

leftover wrapped as a ConduitParser.

getParserName :: ConduitParser i m Text Source

Return the name of the parser (assigned through (<?>)), or mempty if has none.

Utility

peek :: Monad m => ConduitParser i m (Maybe i) Source

peek wrapped as a ConduitParser.

Exception

data ConduitParserException Source

Instances

Eq ConduitParserException Source 
Show ConduitParserException Source 
Exception ConduitParserException Source 
MonadError ConduitParserException (ConduitParser i m) Source

Backtracking is supported by pushing back consumed elements (using leftover) whenever an error is catched.

As a consequence, within the scope of a catchError, all streamed items are kept in memory, which means the consumer no longer uses constant memory.