Copyright | 2011 Michael Snoyman 2010 John Millikin |
---|---|
License | MIT |
Safe Haskell | None |
Language | Haskell2010 |
Consume attoparsec parsers via conduit.
This code was taken from attoparsec-enumerator and adapted for conduits.
Synopsis
- sinkParser :: (AttoparsecInput a, MonadThrow m) => Parser a b -> ConduitT a o m b
- sinkParserEither :: (AttoparsecInput a, Monad m) => Parser a b -> ConduitT a o m (Either ParseError b)
- conduitParser :: (AttoparsecInput a, MonadThrow m) => Parser a b -> ConduitT a (PositionRange, b) m ()
- conduitParserEither :: (Monad m, AttoparsecInput a) => Parser a b -> ConduitT a (Either ParseError (PositionRange, b)) m ()
- 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 -> ConduitT a o m b Source #
sinkParserEither :: (AttoparsecInput a, Monad m) => Parser a b -> ConduitT a o 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 -> ConduitT a (PositionRange, b) m () 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 -> ConduitT a (Either ParseError (PositionRange, b)) m () 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.
ParseError | |
| |
DivergentParser |
Instances
Show ParseError Source # | |
Defined in Data.Conduit.Attoparsec showsPrec :: Int -> ParseError -> ShowS # show :: ParseError -> String # showList :: [ParseError] -> ShowS # | |
Exception ParseError Source # | |
Defined in Data.Conduit.Attoparsec toException :: ParseError -> SomeException # fromException :: SomeException -> Maybe ParseError # displayException :: ParseError -> String # |
data PositionRange Source #
Instances
Eq PositionRange Source # | |
Defined in Data.Conduit.Attoparsec (==) :: PositionRange -> PositionRange -> Bool # (/=) :: PositionRange -> PositionRange -> Bool # | |
Ord PositionRange Source # | |
Defined in Data.Conduit.Attoparsec compare :: PositionRange -> PositionRange -> Ordering # (<) :: PositionRange -> PositionRange -> Bool # (<=) :: PositionRange -> PositionRange -> Bool # (>) :: PositionRange -> PositionRange -> Bool # (>=) :: PositionRange -> PositionRange -> Bool # max :: PositionRange -> PositionRange -> PositionRange # min :: PositionRange -> PositionRange -> PositionRange # | |
Show PositionRange Source # | |
Defined in Data.Conduit.Attoparsec showsPrec :: Int -> PositionRange -> ShowS # show :: PositionRange -> String # showList :: [PositionRange] -> ShowS # |
Classes
class AttoparsecInput a Source #
A class of types which may be consumed by an Attoparsec parser.
parseA, feedA, empty, isNull, getLinesCols, stripFromEnd
Instances
AttoparsecInput ByteString Source # | |
Defined in Data.Conduit.Attoparsec parseA :: Parser ByteString b -> ByteString -> IResult ByteString b feedA :: IResult ByteString b -> ByteString -> IResult ByteString b empty :: ByteString isNull :: ByteString -> Bool getLinesCols :: ByteString -> Position stripFromEnd :: ByteString -> ByteString -> ByteString | |
AttoparsecInput Text Source # | |