pipes-4.3.16: Compositional pipelines
Safe HaskellTrustworthy
LanguageHaskell2010

Pipes.Prelude

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 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 corresponding stdin and stdout utilities from pipes-bytestring and pipes-text 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 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 -> Proxy x' x () String m () Source #

Read Strings from a Handle using hGetLine

Terminates on end of input

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

repeatM :: Monad m => m a -> Proxy x' x () a m r Source #

Repeat a monadic action indefinitely, yielding each result

repeatM :: Monad m => m a -> Producer a m r

replicateM :: Monad m => Int -> m a -> Proxy x' x () a m () Source #

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

replicateM  0      x = return ()

replicateM (m + n) x = replicateM m x >> replicateM n x  -- 0 <= {m,n}
replicateM :: Monad m => Int -> m a -> Producer a m ()

unfoldr :: Monad m => (s -> m (Either r (a, s))) -> s -> Producer a m r Source #

The natural unfold into a Producer with a step function and a seed

unfoldr next = id

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 putStrLn

Unlike toHandle, stdoutLn gracefully terminates on a broken output pipe

stdoutLn' :: MonadIO m => Consumer' String m r Source #

Write Strings to stdout using putStrLn

This does not handle a broken output pipe, but has a polymorphic return value

mapM_ :: Monad m => (a -> m ()) -> Consumer' a m r Source #

Consume all values using a monadic function

print :: (MonadIO m, Show a) => Consumer' a m r Source #

print values to stdout

drain :: Functor m => Consumer' a m r Source #

discard all incoming values

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 :: Functor m => (a -> b) -> Pipe a b m r Source #

Apply a function to all values flowing downstream

map id = cat

map (g . f) = map f >-> map g

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

Apply a monadic function to all values flowing downstream

mapM return = cat

mapM (f >=> g) = mapM f >-> mapM g

sequence :: Monad m => Pipe (m a) a m r Source #

Convert a stream of actions to a stream of values

mapFoldable :: (Functor m, Foldable t) => (a -> t b) -> Pipe a b m r Source #

Apply a function to all values flowing downstream, and forward each element of the result.

filter :: Functor m => (a -> Bool) -> Pipe a a m r Source #

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

filter (pure True) = cat

filter (liftA2 (&&) p1 p2) = filter p1 >-> filter p2

filter f = mapMaybe (\a -> a <$ guard (f a))

mapMaybe :: Functor m => (a -> Maybe b) -> Pipe a b m r Source #

(mapMaybe f) yields Just results of f.

Basic laws:

mapMaybe (f >=> g) = mapMaybe f >-> mapMaybe g

mapMaybe (pure @Maybe . f) = mapMaybe (Just . f) = map f

mapMaybe (const Nothing) = drain

As a result of the second law,

mapMaybe return = mapMaybe Just = cat

filterM :: Monad m => (a -> m Bool) -> Pipe a a m r Source #

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

filterM (pure (pure True)) = cat

filterM (liftA2 (liftA2 (&&)) p1 p2) = filterM p1 >-> filterM p2

filterM f = wither (\a -> (\b -> a <$ guard b) <$> f a)

wither :: Monad m => (a -> m (Maybe b)) -> Pipe a b m r Source #

(wither f) forwards Just values produced by the monadic action.

Basic laws:

wither (runMaybeT . (MaybeT . f >=> MaybeT . g)) = wither f >-> wither g

wither (runMaybeT . lift . f) = wither (fmap Just . f) = mapM f

wither (pure . f) = mapMaybe f

As a result of the second law,

wither (runMaybeT . return) = cat

As a result of the third law,

wither (pure . const Nothing) = wither (const (pure Nothing)) = drain

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

(take n) only allows n values to pass through

take 0 = return ()

take (m + n) = take m >> take n
take <infinity> = cat

take (min m n) = take m >-> take n

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

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

takeWhile (pure True) = cat

takeWhile (liftA2 (&&) p1 p2) = takeWhile p1 >-> takeWhile p2

takeWhile' :: Functor m => (a -> Bool) -> Pipe a a m a Source #

(takeWhile' p) is a version of takeWhile that returns the value failing the predicate.

takeWhile' (pure True) = cat

takeWhile' (liftA2 (&&) p1 p2) = takeWhile' p1 >-> takeWhile' p2

drop :: Functor m => Int -> Pipe a a m r Source #

(drop n) discards n values going downstream

drop 0 = cat

drop (m + n) = drop m >-> drop n

dropWhile :: Functor m => (a -> Bool) -> Pipe a a m r Source #

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

dropWhile (pure False) = cat

dropWhile (liftA2 (||) p1 p2) = dropWhile p1 >-> dropWhile p2

concat :: (Functor m, Foldable f) => Pipe (f a) a m r Source #

Flatten all Foldable elements flowing downstream

elemIndices :: (Functor m, Eq a) => a -> Pipe a Int m r Source #

Outputs the indices of all elements that match the given element

findIndices :: Functor m => (a -> Bool) -> Pipe a Int m r Source #

Outputs the indices of all elements that satisfied the predicate

scan :: Functor m => (x -> a -> x) -> x -> (x -> b) -> Pipe a b m r Source #

Strict left scan

Control.Foldl.purely scan :: Monad m => Fold a b -> Pipe a b m r

scanM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Pipe a b m r Source #

Strict, monadic left scan

Control.Foldl.impurely scanM :: Monad m => FoldM m a b -> Pipe a b m r

chain :: Monad m => (a -> m ()) -> Pipe a a m r Source #

Apply an action to all values flowing downstream

chain (pure (return ())) = cat

chain (liftA2 (>>) m1 m2) = chain m1 >-> chain m2

read :: (Functor m, Read a) => Pipe String a m r Source #

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

show :: (Functor m, Show a) => Pipe a String m r Source #

Convert Showable values to Strings

seq :: Functor m => Pipe a a m r Source #

Evaluate all values flowing downstream to WHNF

ListT

loop :: Monad m => (a -> ListT m b) -> Pipe a b m r Source #

Create a Pipe from a ListT transformation

loop (k1 >=> k2) = loop k1 >-> loop k2

loop return = cat

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 Prelude.null P.stdinLn
Test<Enter>
ABC<Enter>
<Enter>
True
>>> 

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

Strict fold of the elements of a Producer

Control.Foldl.purely fold :: Monad m => Fold a b -> Producer a m () -> m b

fold' :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Producer a m r -> m (b, r) Source #

Strict fold of the elements of a Producer that preserves the return value

Control.Foldl.purely fold' :: Monad m => Fold a b -> Producer a m r -> m (b, r)

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

Strict, monadic fold of the elements of a Producer

Control.Foldl.impurely foldM :: Monad m => FoldM a b -> Producer a m () -> m b

foldM' :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Producer a m r -> m (b, r) Source #

Strict, monadic fold of the elements of a Producer

Control.Foldl.impurely foldM' :: Monad m => FoldM a b -> Producer a m r -> m (b, r)

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

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

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

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

and :: Monad m => Producer Bool m () -> m Bool Source #

Determines whether all elements are True

or :: Monad m => Producer Bool m () -> m Bool Source #

Determines whether any element is True

elem :: (Monad m, Eq a) => a -> Producer a m () -> m Bool Source #

(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 Bool Source #

(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 Int Source #

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 Bool Source #

Determine if a Producer is empty

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

Compute the sum of the elements of a Producer

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

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.

toListM' :: Monad m => Producer a m r -> m ([a], r) Source #

Convert an effectful Producer into a list alongside the return value

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 -> Proxy x' x () (a, b) m r Source #

Zip two Producers

zipWith :: Monad m => (a -> b -> c) -> Producer a m r -> Producer b m r -> Proxy x' x () c m r Source #

Zip two Producers using the provided combining function

Utilities

tee :: Monad m => Consumer a m r -> Pipe a a m r Source #

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 r Source #

Transform a unidirectional Pipe to a bidirectional Proxy

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

generalize cat = pull