hw-succinct-0.0.0.1: Conduits for tokenizing streams.

Copyright2016 John Ky, 2011 Michael Snoyman, 2010 John Millikin
LicenseMIT
Safe HaskellNone
LanguageHaskell2010

HaskellWorks.Data.Conduit.Tokenize.Attoparsec.Internal

Contents

Description

Consume attoparsec parsers via conduit.

This code was taken from attoparsec-enumerator and adapted for conduits.

Synopsis

Sink

sinkParser :: (AttoparsecInput a, AttoparsecState a s, MonadThrow m, Exception (ParseError s)) => s -> 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, AttoparsecState a s, Monad m) => s -> Parser a b -> Consumer a m (Either (ParseError s) b) Source

Same as sinkParser, but we return an Either type instead of raising an exception.

Since 1.1.5

Conduit

conduitParser :: (AttoparsecInput a, AttoparsecState a s, MonadThrow m, Exception (ParseError s)) => s -> Parser a b -> Conduit a m (ParseDelta s, 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, AttoparsecState a s) => s -> Parser a b -> Conduit a m (Either (ParseError s) (ParseDelta s, b)) Source

Same as conduitParser, but we return an Either type instead of raising an exception.

Types

data ParseError s Source

The context and message from a Fail value.

data ParseDelta s Source

The before and after state of a single parse in a conduit stream.

Constructors

ParseDelta 

Fields

before :: !s
 
after :: !s
 

Classes

class AttoparsecInput a where Source

A class of types which may be consumed by an Attoparsec parser.

Methods

parseA :: Parser a b -> a -> IResult a b Source

feedA :: IResult a b -> a -> IResult a b Source

empty :: a Source

isNull :: a -> Bool Source

notEmpty :: [a] -> [a] Source

stripFromEnd :: a -> a -> a Source

Return the beginning of the first input with the length of the second input removed. Assumes the second string is shorter than the first.

class AttoparsecState a s where Source

A class of types and states which may be consumed by an Attoparsec parser.

Methods

getState :: a -> s Source

modState :: AttoparsecInput a => a -> s -> s Source