Copyright | 2011 Michael Snoyman 2010 John Millikin |
---|---|
License | MIT |
Safe Haskell | None |
Language | Haskell98 |
Consume attoparsec parsers via conduit.
This code was taken from attoparsec-enumerator and adapted for conduits.
- sinkParser :: (AttoparsecInput a, MonadThrow m) => Parser a b -> Consumer a m b
- sinkParserEither :: (AttoparsecInput a, Monad m) => Parser a b -> Consumer a m (Either ParseError b)
- conduitParser :: (AttoparsecInput a, MonadThrow m) => Parser a b -> Conduit a m (PositionRange, b)
- conduitParserEither :: (Monad m, AttoparsecInput a) => Parser a b -> Conduit a m (Either ParseError (PositionRange, b))
- data ParseError
- = ParseError { }
- | DivergentParser
- data Position = Position {}
- data PositionRange = PositionRange {
- posRangeStart :: !Position
- posRangeEnd :: !Position
- class AttoparsecInput a
Sink
sinkParser :: (AttoparsecInput a, MonadThrow m) => Parser a b -> Consumer a m b Source #
Convert an Attoparsec Parser
into a Sink
. The parser will
be streamed bytes until it returns Done
or Fail
.
If parsing fails, a ParseError
will be thrown with monadThrow
.
Since 0.5.0
sinkParserEither :: (AttoparsecInput a, Monad m) => Parser a b -> Consumer a m (Either ParseError b) Source #
Same as sinkParser
, but we return an Either
type instead
of raising an exception.
Since 1.1.5
Conduit
conduitParser :: (AttoparsecInput a, MonadThrow m) => Parser a b -> Conduit a m (PositionRange, b) Source #
Consume a stream of parsed tokens, returning both the token and
the position it appears at. This function will raise a ParseError
on bad input.
Since 0.5.0
conduitParserEither :: (Monad m, AttoparsecInput a) => Parser a b -> Conduit a m (Either ParseError (PositionRange, b)) Source #
Same as conduitParser
, but we return an Either
type instead
of raising an exception.
Types
data ParseError Source #
The context and message from a Fail
value.
data PositionRange Source #
Classes
class AttoparsecInput a Source #
A class of types which may be consumed by an Attoparsec parser.
parseA, feedA, empty, isNull, notEmpty, getLinesCols, stripFromEnd