Safe Haskell | Safe-Infered |
---|
Basic pipe combinators.
- tryAwait :: Monad m => Pipe a b m (Maybe a)
- forP :: Monad m => (a -> Pipe a b m r) -> Pipe a b m ()
- ($$) :: Monad m => Pipe x a m r' -> Pipe a y m r -> Pipe x y m (Maybe r)
- fromList :: Monad m => [a] -> Pipe x a m ()
- fold :: Monad m => (b -> a -> b) -> b -> Pipe a x m b
- fold1 :: Monad m => (a -> a -> a) -> Pipe a x m a
- consume :: Monad m => Pipe a x m [a]
- consume1 :: Monad m => Pipe a x m [a]
- take :: Monad m => Int -> Pipe a a m ()
- drop :: Monad m => Int -> Pipe a a m r
- takeWhile :: Monad m => (a -> Bool) -> Pipe a a m a
- takeWhile_ :: Monad m => (a -> Bool) -> Pipe a a m ()
- dropWhile :: Monad m => (a -> Bool) -> Pipe a a m r
- intersperse :: Monad m => (a -> Bool) -> Pipe a (Maybe a) m r
- groupBy :: Monad m => (a -> a -> Bool) -> Pipe a [a] m r
- filter :: Monad m => (a -> Bool) -> Pipe a a m r
- pipeList :: Monad m => (a -> [b]) -> Pipe a b m r
- nullP :: Monad m => Pipe a b m ()
- feed :: Monad m => a -> Pipe a b m r -> Pipe a b m r
Control operators
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
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 Consumer
s, 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.
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.
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.