pipes-core-0.1.0: Compositional pipelines

Safe HaskellSafe-Infered

Control.Pipe.Combinators

Contents

Description

Basic pipe combinators.

Synopsis

Control operators

tryAwait :: Monad m => Pipe a b m (Maybe a)Source

Like await, but returns Just x when the upstream pipe yields some value x, and Nothing when it terminates.

Further calls to tryAwait after upstream termination will keep returning Nothing, whereas calling await will terminate the current pipe immediately.

forP :: Monad m => (a -> Pipe a b m r) -> Pipe a b m ()Source

Execute the specified pipe for each value in the input stream.

Any action after a call to forP will be executed when upstream terminates.

Composition

($$) :: Monad m => Pipe x a m r' -> Pipe a y m r -> Pipe x y m (Maybe r)Source

Connect producer to consumer, ignoring producer return value.

Producers

fromList :: Monad m => [a] -> Pipe x a m ()Source

Successively yield elements of a list.

Folds

Folds are pipes that consume all their input and return a value. Some of them, like fold1, do not return anything when they don't receive any input at all. That means that the upstream return value will be returned instead.

Folds are normally used as Consumers, but they are actually polymorphic in the output type, to encourage their use in the implementation of higher-level combinators.

fold :: Monad m => (b -> a -> b) -> b -> Pipe a x m bSource

A fold pipe. Apply a binary function to successive input values and an accumulator, and return the final result.

fold1 :: Monad m => (a -> a -> a) -> Pipe a x m aSource

A variation of fold without an initial value for the accumulator. This pipe doesn't return any value if no input values are received.

consume :: Monad m => Pipe a x m [a]Source

Accumulate all input values into a list.

consume1 :: Monad m => Pipe a x m [a]Source

Accumulate all input values into a non-empty list.

List-like pipe combinators

take :: Monad m => Int -> Pipe a a m ()Source

Act as an identity for the first n values, then terminate.

drop :: Monad m => Int -> Pipe a a m rSource

Remove the first n values from the stream, then act as an identity.

takeWhile :: Monad m => (a -> Bool) -> Pipe a a m aSource

Act as an identity until as long as inputs satisfy the given predicate. Return the first element that doesn't satisfy the predicate.

takeWhile_ :: Monad m => (a -> Bool) -> Pipe a a m ()Source

Variation of takeWhile returning ().

dropWhile :: Monad m => (a -> Bool) -> Pipe a a m rSource

Remove inputs as long as they satisfy the given predicate, then act as an identity.

intersperse :: Monad m => (a -> Bool) -> Pipe a (Maybe a) m rSource

Yield Nothing when an input satisfying the predicate is received.

groupBy :: Monad m => (a -> a -> Bool) -> Pipe a [a] m rSource

Group input values by the given predicate.

filter :: Monad m => (a -> Bool) -> Pipe a a m rSource

Remove values from the stream that don't satisfy the given predicate.

Other combinators

pipeList :: Monad m => (a -> [b]) -> Pipe a b m rSource

Apply a function with multiple return values to the stream.

nullP :: Monad m => Pipe a b m ()Source

A pipe that terminates immediately.

feed :: Monad m => a -> Pipe a b m r -> Pipe a b m rSource

Feed an input element to a pipe.