| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Pipes.Attoparsec
Description
pipes utilities for incrementally running attoparsec-based parsers.
This module assumes familiarity with pipes-parse, you can learn about it in
 Pipes.Parse.Tutorial.
Synopsis
- parse :: (Monad m, ParserInput a) => Parser a b -> Parser a m (Maybe (Either ParsingError b))
- parsed :: (Monad m, ParserInput a) => Parser a b -> Producer a m r -> Producer b m (Either (ParsingError, Producer a m r) r)
- parseL :: (Monad m, ParserInput a) => Parser a b -> Parser a m (Maybe (Either ParsingError (Int, b)))
- parsedL :: (Monad m, ParserInput a) => Parser a b -> Producer a m r -> Producer (Int, b) m (Either (ParsingError, Producer a m r) r)
- isEndOfParserInput :: (Monad m, ParserInput a) => Parser a m Bool
- class (Eq a, Monoid a) => ParserInput a
- data ParsingError = ParsingError {- peContexts :: [String]
- peMessage :: String
 
Parsing
Arguments
| :: (Monad m, ParserInput a) | |
| => Parser a b | Attoparsec parser | 
| -> Parser a m (Maybe (Either ParsingError b)) | Pipes parser | 
Convert an attoparsec Parser to a pipes-parse
 Parser.
This Parser is compatible with the tools from Pipes.Parse.
It returns Nothing if the underlying Producer is exhausted, otherwise
 it attempts to run the given attoparsec Parser on the underlying
 Producer, possibly failing with ParsingError.
Arguments
| :: (Monad m, ParserInput a) | |
| => Parser a b | Attoparsec parser | 
| -> Producer a m r | Raw input | 
| -> Producer b m (Either (ParsingError, Producer a m r) r) | 
Convert a producer of ParserInput to a producer of parsed values.
This producer returns Right when end-of-input is reached successfully,
 otherwise it returns a ParsingError and the leftovers including
 the malformed input that couldn't be parsed. You can use errorP
 to promote the Either return value to an ErrorT
 monad transformer.
Including input length
Like the functions above, but these also provide information about the length of input consumed in order to fully parse each value.
Arguments
| :: (Monad m, ParserInput a) | |
| => Parser a b | Attoparsec parser | 
| -> Parser a m (Maybe (Either ParsingError (Int, b))) | Pipes parser | 
Like parse, but also returns the length of input consumed to parse the
 value.
Arguments
| :: (Monad m, ParserInput a) | |
| => Parser a b | Attoparsec parser | 
| -> Producer a m r | Raw input | 
| -> Producer (Int, b) m (Either (ParsingError, Producer a m r) r) | 
Like parsed, except this tags each parsed value with the length of input
 consumed to parse the value.
Utils
isEndOfParserInput :: (Monad m, ParserInput a) => Parser a m Bool Source #
Like isEndOfInput, except that it also consumes and discards
 leading empty chunks.
Types
class (Eq a, Monoid a) => ParserInput a Source #
A class for valid attoparsec input types
Minimal complete definition
_parse, _length
Instances
| ParserInput ByteString Source # | Strict  | 
| Defined in Pipes.Attoparsec Methods _parse :: Parser ByteString b -> ByteString -> IResult ByteString b _length :: ByteString -> Int | |
| ParserInput Text Source # | Strict  | 
data ParsingError Source #
A parsing error report, as provided by Attoparsec's Fail.
Constructors
| ParsingError | |
| Fields 
 | |