pipes-parse-3.0.7: Parsing infrastructure for the pipes ecosystem

Safe HaskellSafe-Inferred

Pipes.Parse

Contents

Description

Element-agnostic parsing utilities for pipes

See Pipes.Parse.Tutorial for an extended tutorial

Synopsis

Parsing

pipes-parse handles end-of-input and pushback by storing a Producer in a StateT layer.

Connect Parsers to Producers using either runStateT, evalStateT, or execStateT:

 runStateT  :: Parser a m r -> Producer a m x -> m (r, Producer a m x)
 evalStateT :: Parser a m r -> Producer a m x -> m  r
 execStateT :: Parser a m r -> Producer a m x -> m    (Producer a m x)
                                                       ^^^^^^^^^^^^^^
                                                          Leftovers

type Parser a m r = forall x. StateT (Producer a m x) m rSource

A Parser is an action that reads from and writes to a stored Producer

draw :: Monad m => Parser a m (Maybe a)Source

Draw one element from the underlying Producer, returning Nothing if the Producer is empty

skip :: Monad m => Parser a m BoolSource

Skip one element from the underlying Producer, returning True if successful or False if the Producer is empty

 skip = fmap isJust draw

drawAll :: Monad m => Parser a m [a]Source

Draw all elements from the underlying Producer

Note that drawAll is not an idiomatic use of pipes-parse, but I provide it for simple testing purposes. Idiomatic pipes-parse style consumes the elements immediately as they are generated instead of loading all elements into memory. For example, you can use foldAll or foldAllM for this purpose.

skipAll :: Monad m => Parser a m ()Source

Drain all elements from the underlying Producer

unDraw :: Monad m => a -> Parser a m ()Source

Push back an element onto the underlying Producer

peek :: Monad m => Parser a m (Maybe a)Source

peek checks the first element of the stream, but uses unDraw to push the element back so that it is available for the next draw command.

 peek = do
     x <- draw
     case x of
         Nothing -> return ()
         Just a  -> unDraw a
     return x

isEndOfInput :: Monad m => Parser a m BoolSource

Check if the underlying Producer is empty

 isEndOfInput = fmap isNothing peek

foldAllSource

Arguments

:: Monad m 
=> (x -> a -> x)

Step function

-> x

Initial accumulator

-> (x -> b)

Extraction function

-> Parser a m b 

Fold all input values

 Control.Foldl.purely foldAll :: Monad m => Fold a b -> Parser a m b

foldAllMSource

Arguments

:: Monad m 
=> (x -> a -> m x)

Step function

-> m x

Initial accumulator

-> (x -> m b)

Extraction function

-> Parser a m b 

Fold all input values monadically

 Control.Foldl.impurely foldAllM :: Monad m => FoldM a m b -> Parser a m b

Parsing Lenses

Connect lenses to Producers using (^.) or view:

 (^.) :: Producer a m x
      -> Lens' (Producer a m x) (Producer b m y)
      -> Producer b m y

Connect lenses to Parsers using zoom:

 zoom :: Lens' (Producer a m x) (Producer b m y)
      -> Parser b m r
      -> Parser a m r

Connect lenses to each other using (.) (i.e. function composition):

 (.) :: Lens' (Producer a m x) (Producer b m y)
     -> Lens' (Producer b m y) (Producer c m z)
     -> Lens' (Producer a m y) (Producer c m z)

span :: Monad m => (a -> Bool) -> Lens' (Producer a m x) (Producer a m (Producer a m x))Source

span is an improper lens that splits the Producer into two Producers, where the outer Producer is the longest consecutive group of elements that satisfy the predicate

splitAt :: Monad m => Int -> Lens' (Producer a m x) (Producer a m (Producer a m x))Source

splitAt is an improper lens that splits a Producer into two Producers after a fixed number of elements

groupBy :: Monad m => (a -> a -> Bool) -> Lens' (Producer a m x) (Producer a m (Producer a m x))Source

groupBy splits a Producer into two Producers after the first group of elements that are equal according to the equality predicate

group :: (Monad m, Eq a) => Lens' (Producer a m x) (Producer a m (Producer a m x))Source

Like groupBy, where the equality predicate is (==)

Utilities

toParser :: Monad m => Consumer (Maybe a) m r -> Parser a m rSource

Convert a Consumer to a Parser

Nothing signifies end of input

toParser_ :: Monad m => Consumer a m X -> Parser a m ()Source

Convert a never-ending Consumer to a Parser

parsed :: Monad m => Parser a m (Either e b) -> Producer a m r -> Producer b m (e, Producer a m r)Source

Run a Parser repeatedly on a Producer, yielding each `Right result

Returns the remainder of the Producer when the Parser returns Left

parsed_ :: Monad m => Parser a m (Maybe b) -> Producer a m r -> Producer b m (Producer a m r)Source

Run a Parser repeatedly on a Producer, yielding each Just result

Returns the remainder of the Producer when the Parser returns Nothing

parseForever :: Monad m => (forall n. Monad n => Parser a n (Either r b)) -> Pipe a b m rSource

Deprecated: Use parsed instead

Convert a Parser to a Pipe by running it repeatedly on the input

parseForever_ :: Monad m => (forall n. Monad n => Parser a n (Maybe b)) -> Pipe a b m ()Source

Deprecated: Use parsed_ instead

Variant of parseForever for parsers which return a Maybe instead of an Either

Re-exports

module Pipes