pipes-4.0.0: Compositional pipelines

Safe HaskellNone

Pipes.Prelude

Contents

Description

General purpose utilities

The names in this module clash heavily with the Haskell Prelude, so I recommend the following import scheme:

 import Pipes
 import qualified Pipes.Prelude as P  -- or use any other qualifier you prefer

Note that String-based IO.IO is inefficient. The String-based utilities in this module exist only for simple demonstrations without incurring a dependency on the text package.

Also, stdinLn and stdoutLn remove and add newlines, respectively. This behavior is intended to simplify examples. The upcoming ByteString and Text utilities for pipes will preserve newlines.

Synopsis

Producers

Use for loops to iterate over Producers whenever you want to perform the same action for every element:

 -- Echo all lines from standard input to standard output
 runEffect $ for P.stdinLn $ \str -> do
     lift $ putStrLn str

... or more concisely:

>>> runEffect $ for P.stdinLn (lift . putStrLn)
Test<Enter>
Test
ABC<Enter>
ABC
...

stdinLn :: MonadIO m => Producer' String m ()Source

Read Strings from stdin using IO.getLine

Terminates on end of input

readLn :: MonadIO m => Read a => Producer' a m ()Source

read values from stdin, ignoring failed parses

fromHandle :: MonadIO m => Handle -> Producer' String m ()Source

Read Strings from a Handle using hGetLine

Terminates on end of input

replicateM :: Monad m => Int -> m a -> Producer a m ()Source

Repeat a monadic action a fixed number of times, yielding each result

Consumers

Feed a Consumer the same value repeatedly using (>~):

>>> runEffect $ lift getLine >~ P.stdoutLn
Test<Enter>
Test
ABC<Enter>
ABC
...

stdoutLn :: MonadIO m => Consumer' String m ()Source

Write Strings to stdout using IO.putStrLn

Unlike toHandle, stdoutLn gracefully terminates on a broken output pipe

print :: MonadIO m => Show a => Consumer' a m rSource

print values to stdout

Pipes

Use (>->) to connect Producers, Pipes, and Consumers:

>>> runEffect $ P.stdinLn >-> P.takeWhile (/= "quit") >-> P.stdoutLn
Test<Enter>
Test
ABC<Enter>
ABC
quit<Enter>
>>> 

map :: Monad m => (a -> b) -> Pipe a b m rSource

Apply a function to all values flowing downstream

mapM :: Monad m => (a -> m b) -> Pipe a b m rSource

Apply a monadic function to all values flowing downstream

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

(filter predicate) only forwards values that satisfy the predicate.

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

(filterM predicate) only forwards values that satisfy the monadic predicate

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

(take n) only allows n values to pass through

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

(takeWhile p) allows values to pass downstream so long as they satisfy the predicate p.

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

(drop n) discards n values going downstream

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

(dropWhile p) discards values going downstream until one violates the predicate p.

concat :: (Monad m, Foldable f) => Pipe (f a) a m rSource

Flatten all Foldable elements flowing downstream

elemIndices :: (Monad m, Eq a) => a -> Pipe a Int m rSource

Outputs the indices of all elements that match the given element

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

Outputs the indices of all elements that satisfied the predicate

scan :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Pipe a b m rSource

Strict left scan

scanM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Pipe a b m rSource

Strict, monadic left scan

chain :: Monad m => (a -> m ()) -> Pipe a a m rSource

Apply an action to all values flowing downstream

read :: (Monad m, Read a) => Pipe String a m rSource

Parse Readable values, only forwarding the value if the parse succeeds

show :: (Monad m, Show a) => Pipe a String m rSource

Convert Showable values to Strings

Folds

Use these to fold the output of a Producer. Many of these folds will stop drawing elements if they can compute their result early, like any:

>>> P.any null P.stdinLn
Test<Enter>
ABC<Enter>
<Enter>
True
>>> 

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

Strict fold of the elements of a Producer

foldM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Producer a m () -> m bSource

Strict, monadic fold of the elements of a Producer

all :: Monad m => (a -> Bool) -> Producer a m () -> m BoolSource

(all predicate p) determines whether all the elements of p satisfy the predicate.

any :: Monad m => (a -> Bool) -> Producer a m () -> m BoolSource

(any predicate p) determines whether any element of p satisfies the predicate.

and :: Monad m => Producer Bool m () -> m BoolSource

Determines whether all elements are True

or :: Monad m => Producer Bool m () -> m BoolSource

Determines whether any element is True

elem :: (Monad m, Eq a) => a -> Producer a m () -> m BoolSource

(elem a p) returns True if p has an element equal to a, False otherwise

notElem :: (Monad m, Eq a) => a -> Producer a m () -> m BoolSource

(notElem a) returns False if p has an element equal to a, True otherwise

find :: Monad m => (a -> Bool) -> Producer a m () -> m (Maybe a)Source

Find the first element of a Producer that satisfies the predicate

findIndex :: Monad m => (a -> Bool) -> Producer a m () -> m (Maybe Int)Source

Find the index of the first element of a Producer that satisfies the predicate

head :: Monad m => Producer a m () -> m (Maybe a)Source

Retrieve the first element from a Producer

index :: Monad m => Int -> Producer a m () -> m (Maybe a)Source

Index into a Producer

last :: Monad m => Producer a m () -> m (Maybe a)Source

Retrieve the last element from a Producer

length :: Monad m => Producer a m () -> m IntSource

Count the number of elements in a Producer

maximum :: (Monad m, Ord a) => Producer a m () -> m (Maybe a)Source

Find the maximum element of a Producer

minimum :: (Monad m, Ord a) => Producer a m () -> m (Maybe a)Source

Find the minimum element of a Producer

null :: Monad m => Producer a m () -> m BoolSource

Determine if a Producer is empty

sum :: (Monad m, Num a) => Producer a m () -> m aSource

Compute the sum of the elements of a Producer

product :: (Monad m, Num a) => Producer a m () -> m aSource

Compute the product of the elements of a Producer

toList :: Producer a Identity () -> [a]Source

Convert a pure Producer into a list

toListM :: Monad m => Producer a m () -> m [a]Source

Convert an effectful Producer into a list

Note: toListM is not an idiomatic use of pipes, but I provide it for simple testing purposes. Idiomatic pipes style consumes the elements immediately as they are generated instead of loading all elements into memory.

Zips

zip :: Monad m => Producer a m r -> Producer b m r -> Producer' (a, b) m rSource

Zip two Producers

zipWith :: Monad m => (a -> b -> c) -> Producer a m r -> Producer b m r -> Producer' c m rSource

Zip two Producers using the provided combining function

Utilities

tee :: Monad m => Consumer a m r -> Pipe a a m rSource

Transform a Consumer to a Pipe that reforwards all values further downstream

generalize :: Monad m => Pipe a b m r -> x -> Proxy x a x b m rSource

Transform a unidirectional Pipe to a bidirectional Proxy

 generalize (f >-> g) = generalize f >+> generalize g

 generalize cat = pull