Safe Haskell | Trustworthy |
---|
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.
- stdinLn :: MonadIO m => Producer' String m ()
- readLn :: MonadIO m => Read a => Producer' a m ()
- fromHandle :: MonadIO m => Handle -> Producer' String m ()
- replicateM :: Monad m => Int -> m a -> Producer a m ()
- stdoutLn :: MonadIO m => Consumer' String m ()
- print :: (MonadIO m, Show a) => Consumer' a m r
- toHandle :: MonadIO m => Handle -> Consumer' String m r
- map :: Monad m => (a -> b) -> Pipe a b m r
- mapM :: Monad m => (a -> m b) -> Pipe a b m r
- mapFoldable :: (Monad m, Foldable t) => (a -> t b) -> Pipe a b m r
- filter :: Monad m => (a -> Bool) -> Pipe a a m r
- filterM :: Monad m => (a -> m Bool) -> Pipe a a m r
- take :: Monad m => Int -> Pipe a a m ()
- takeWhile :: Monad m => (a -> Bool) -> Pipe a a m ()
- drop :: Monad m => Int -> Pipe a a m r
- dropWhile :: Monad m => (a -> Bool) -> Pipe a a m r
- concat :: (Monad m, Foldable f) => Pipe (f a) a m r
- elemIndices :: (Monad m, Eq a) => a -> Pipe a Int m r
- findIndices :: Monad m => (a -> Bool) -> Pipe a Int m r
- scan :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Pipe a b m r
- scanM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Pipe a b m r
- chain :: Monad m => (a -> m ()) -> Pipe a a m r
- read :: (Monad m, Read a) => Pipe String a m r
- show :: (Monad m, Show a) => Pipe a String m r
- fold :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Producer a m () -> m b
- foldM :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Producer a m () -> m b
- all :: Monad m => (a -> Bool) -> Producer a m () -> m Bool
- any :: Monad m => (a -> Bool) -> Producer a m () -> m Bool
- and :: Monad m => Producer Bool m () -> m Bool
- or :: Monad m => Producer Bool m () -> m Bool
- elem :: (Monad m, Eq a) => a -> Producer a m () -> m Bool
- notElem :: (Monad m, Eq a) => a -> Producer a m () -> m Bool
- find :: Monad m => (a -> Bool) -> Producer a m () -> m (Maybe a)
- findIndex :: Monad m => (a -> Bool) -> Producer a m () -> m (Maybe Int)
- head :: Monad m => Producer a m () -> m (Maybe a)
- index :: Monad m => Int -> Producer a m () -> m (Maybe a)
- last :: Monad m => Producer a m () -> m (Maybe a)
- length :: Monad m => Producer a m () -> m Int
- maximum :: (Monad m, Ord a) => Producer a m () -> m (Maybe a)
- minimum :: (Monad m, Ord a) => Producer a m () -> m (Maybe a)
- null :: Monad m => Producer a m () -> m Bool
- sum :: (Monad m, Num a) => Producer a m () -> m a
- product :: (Monad m, Num a) => Producer a m () -> m a
- toList :: Producer a Identity () -> [a]
- toListM :: Monad m => Producer a m () -> m [a]
- zip :: Monad m => Producer a m r -> Producer b m r -> Producer' (a, b) m r
- zipWith :: Monad m => (a -> b -> c) -> Producer a m r -> Producer b m r -> Producer' c m r
- tee :: Monad m => Consumer a m r -> Pipe a a m r
- generalize :: Monad m => Pipe a b m r -> x -> Proxy x a x b m r
Producers
Use for
loops to iterate over Producer
s 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 ...
replicateM :: Monad m => Int -> m a -> Producer a m ()Source
Repeat a monadic action a fixed number of times, yield
ing each result
Consumers
Feed a Consumer
the same value repeatedly using (>~
):
>>>
runEffect $ lift getLine >~ P.stdoutLn
Test<Enter> Test ABC<Enter> ABC ...
Pipes
Use (>->
) to connect Producer
s, Pipe
s, and Consumer
s:
>>>
runEffect $ P.stdinLn >-> P.takeWhile (/= "quit") >-> P.stdoutLn
Test<Enter> Test ABC<Enter> ABC quit<Enter>>>>
mapM :: Monad m => (a -> m b) -> Pipe a b m rSource
Apply a monadic function to all values flowing downstream
mapFoldable :: (Monad m, Foldable t) => (a -> t b) -> Pipe a b m rSource
Apply a function to all values flowing downstream, and forward each element of the result.
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
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
.
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
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 Read
able values, only forwarding the value if the parse succeeds
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.
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
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
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
Zips
zipWith :: Monad m => (a -> b -> c) -> Producer a m r -> Producer b m r -> Producer' c m rSource
Zip two Producer
s using the provided combining function