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

Safe HaskellSafe-Inferred

Control.Proxy.Parse

Contents

Description

Parsing utilities for pipes

Synopsis

Pushback and Leftovers

unDraw stores all leftovers in a StateP buffer and draw retrieves leftovers from this buffer before drawing new input from upstream.

draw :: (Monad m, Proxy p) => StateP [a] p () (Maybe a) y' y m (Maybe a)Source

Like request (), except try to use the leftovers buffer first

A Nothing return value indicates end of input.

unDraw :: (Monad m, Proxy p) => a -> StateP [a] p x' x y' y m ()Source

Push an element back onto the leftovers buffer

Utilities

peek :: (Monad m, Proxy p) => StateP [a] p () (Maybe a) y' y m (Maybe a)Source

Peek at the next element without consuming it

isEndOfInput :: (Monad m, Proxy p) => StateP [a] p () (Maybe a) y' y m BoolSource

Check if at end of input stream.

drawAll :: (Monad m, Proxy p) => () -> StateP [a] p () (Maybe a) y' y m [a]Source

Fold all input into a list

Note: drawAll is usually an anti-pattern.

skipAll :: (Monad m, Proxy p) => () -> StateP [a] p () (Maybe a) y' y m ()Source

Consume the input completely, discarding all values

passUpTo :: (Monad m, Proxy p) => Int -> () -> Pipe (StateP [a] p) (Maybe a) (Maybe a) m rSource

Forward up to the specified number of elements downstream

passWhile :: (Monad m, Proxy p) => (a -> Bool) -> () -> Pipe (StateP [a] p) (Maybe a) (Maybe a) m rSource

Forward downstream as many consecutive elements satisfying a predicate as possible

Adapters

Use wrap and unwrap to convert between guarded and unguarded pipes.

fmapPull, returnPull, and bindPull promote compatibility with existing utilities that are not Maybe-aware.

wrap :: (Monad m, Proxy p) => p a' a b' b m r -> p a' a b' (Maybe b) m sSource

Guard a pipe from terminating by wrapping every output in Just and ending with a never-ending stream of Nothings.

unwrap :: (Monad m, Proxy p) => x -> p x (Maybe a) x a m ()Source

Compose unwrap downstream of a guarded pipe to unwrap all Justs and terminate on the first Nothing.

fmapPull :: (Monad m, Proxy p) => (x -> p x a x b m r) -> x -> p x (Maybe a) x (Maybe b) m rSource

Lift a Maybe-oblivious pipe to a Maybe-aware pipe by auto-forwarding all Nothings.

 fmapPull f >-> fmapPull g = fmapPull (f >-> g)

 fmapPull pull = pull

returnPull :: (Monad m, Proxy p) => x -> p x a x (Maybe a) m rSource

Wrap all values flowing downstream in Just.

bindPull :: (Monad m, Proxy p) => (x -> p x a x (Maybe b) m r) -> x -> p x (Maybe a) x (Maybe b) m rSource

Lift a Maybe-generating pipe to a Maybe-transforming pipe by auto-forwarding all Nothings

 -- Using: f >>> g = f >-> bindPull g

 returnPull >>> f = f

 f >>> returnPull = f

 (f >>> g) >>> h = f >>> (g >>> h)

Or equivalently:

 returnPull >-> bindPull f = f

 bindPull returnPull = pull

 bindPull (f >-> bindPull g) = bindPull f >-> bindPull g

Lenses

Use zoom, _fst, and _snd to mix pipes that have different leftover buffers or to isolate leftover buffers of different parsing stages.

zoomSource

Arguments

:: (Monad m, Proxy p) 
=> ((s2 -> (s2, s2)) -> s1 -> (s2, s1))

Lens' s1 s2

-> StateP s2 p a' a b' b m r

Local state

-> StateP s1 p a' a b' b m r

Global state

zoom in on a sub-state using a Lens'.

 zoom :: Lens' s1 s2 -> StateP s2 p a' a b' b m r -> StateP s1 p a' a b' b m r
 zoom (f . g) = zoom f . zoom g

 zoom id = id

_fst :: Functor f => (a -> f b) -> (a, x) -> f (b, x)Source

A Lens' to the first element of a pair.

Like _1, but more monomorphic

 _fst :: Lens' (a, b) a

_snd :: Functor f => (a -> f b) -> (x, a) -> f (x, b)Source

A Lens' to the second element of a pair.

Like _2, but more monomorphic

 _snd :: Lens' (a, b) b

Re-exports

Control.Proxy.Trans.State re-exports all functions.

Data.Monoid re-exports the Monoid class.