Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
NOTE It is recommended to start using Data.Conduit.Combinators instead of this module.
Higher-level functions to interact with the elements of a stream. Most of these are based on list functions.
For many purposes, it's recommended to use the conduit-combinators library, which provides a more complete set of functions.
Note that these functions all deal with individual elements of a stream as a
sort of "black box", where there is no introspection of the contained
elements. Values such as ByteString
and Text
will likely need to be
treated specially to deal with their contents properly (Word8
and Char
,
respectively). See the Data.Conduit.Binary
and Data.Conduit.Text
modules in the conduit-extra
package.
Synopsis
- sourceList :: Monad m => [a] -> ConduitT i a m ()
- sourceNull :: Monad m => ConduitT i o m ()
- unfold :: Monad m => (b -> Maybe (a, b)) -> b -> ConduitT i a m ()
- unfoldEither :: Monad m => (b -> Either r (a, b)) -> b -> ConduitT i a m r
- unfoldM :: Monad m => (b -> m (Maybe (a, b))) -> b -> ConduitT i a m ()
- unfoldEitherM :: Monad m => (b -> m (Either r (a, b))) -> b -> ConduitT i a m r
- enumFromTo :: (Enum a, Ord a, Monad m) => a -> a -> ConduitT i a m ()
- iterate :: Monad m => (a -> a) -> a -> ConduitT i a m ()
- replicate :: Monad m => Int -> a -> ConduitT i a m ()
- replicateM :: Monad m => Int -> m a -> ConduitT i a m ()
- fold :: Monad m => (b -> a -> b) -> b -> ConduitT a o m b
- foldMap :: (Monad m, Monoid b) => (a -> b) -> ConduitT a o m b
- uncons :: SealedConduitT () o Identity () -> Maybe (o, SealedConduitT () o Identity ())
- unconsEither :: SealedConduitT () o Identity r -> Either r (o, SealedConduitT () o Identity r)
- take :: Monad m => Int -> ConduitT a o m [a]
- drop :: Monad m => Int -> ConduitT a o m ()
- head :: Monad m => ConduitT a o m (Maybe a)
- peek :: Monad m => ConduitT a o m (Maybe a)
- consume :: Monad m => ConduitT a o m [a]
- sinkNull :: Monad m => ConduitT i o m ()
- foldMapM :: (Monad m, Monoid b) => (a -> m b) -> ConduitT a o m b
- foldM :: Monad m => (b -> a -> m b) -> b -> ConduitT a o m b
- unconsM :: Monad m => SealedConduitT () o m () -> m (Maybe (o, SealedConduitT () o m ()))
- unconsEitherM :: Monad m => SealedConduitT () o m r -> m (Either r (o, SealedConduitT () o m r))
- mapM_ :: Monad m => (a -> m ()) -> ConduitT a o m ()
- map :: Monad m => (a -> b) -> ConduitT a b m ()
- mapMaybe :: Monad m => (a -> Maybe b) -> ConduitT a b m ()
- mapFoldable :: (Monad m, Foldable f) => (a -> f b) -> ConduitT a b m ()
- catMaybes :: Monad m => ConduitT (Maybe a) a m ()
- concat :: (Monad m, Foldable f) => ConduitT (f a) a m ()
- concatMap :: Monad m => (a -> [b]) -> ConduitT a b m ()
- concatMapAccum :: Monad m => (a -> accum -> (accum, [b])) -> accum -> ConduitT a b m ()
- scanl :: Monad m => (a -> s -> (s, b)) -> s -> ConduitT a b m ()
- scan :: Monad m => (a -> b -> b) -> b -> ConduitT a b m b
- mapAccum :: Monad m => (a -> s -> (s, b)) -> s -> ConduitT a b m s
- chunksOf :: Monad m => Int -> ConduitT a [a] m ()
- groupBy :: Monad m => (a -> a -> Bool) -> ConduitT a [a] m ()
- groupOn1 :: (Monad m, Eq b) => (a -> b) -> ConduitT a (a, [a]) m ()
- isolate :: Monad m => Int -> ConduitT a a m ()
- filter :: Monad m => (a -> Bool) -> ConduitT a a m ()
- mapM :: Monad m => (a -> m b) -> ConduitT a b m ()
- iterM :: Monad m => (a -> m ()) -> ConduitT a a m ()
- scanlM :: Monad m => (a -> s -> m (s, b)) -> s -> ConduitT a b m ()
- scanM :: Monad m => (a -> b -> m b) -> b -> ConduitT a b m b
- mapAccumM :: Monad m => (a -> s -> m (s, b)) -> s -> ConduitT a b m s
- mapMaybeM :: Monad m => (a -> m (Maybe b)) -> ConduitT a b m ()
- mapFoldableM :: (Monad m, Foldable f) => (a -> m (f b)) -> ConduitT a b m ()
- concatMapM :: Monad m => (a -> m [b]) -> ConduitT a b m ()
- concatMapAccumM :: Monad m => (a -> accum -> m (accum, [b])) -> accum -> ConduitT a b m ()
- sequence :: Monad m => ConduitT i o m o -> ConduitT i o m ()
Sources
sourceList :: Monad m => [a] -> ConduitT i a m () Source #
Yield the values from the list.
Subject to fusion
sourceNull :: Monad m => ConduitT i o m () Source #
A source that outputs no values. Note that this is just a type-restricted
synonym for mempty
.
Subject to fusion
Since 0.3.0
unfold :: Monad m => (b -> Maybe (a, b)) -> b -> ConduitT i a m () Source #
Generate a source from a seed value.
Subject to fusion
Since 0.4.2
unfoldEither :: Monad m => (b -> Either r (a, b)) -> b -> ConduitT i a m r Source #
Generate a source from a seed value with a return value.
Subject to fusion
Since: 1.2.11
unfoldM :: Monad m => (b -> m (Maybe (a, b))) -> b -> ConduitT i a m () Source #
A monadic unfold.
Subject to fusion
Since 1.1.2
unfoldEitherM :: Monad m => (b -> m (Either r (a, b))) -> b -> ConduitT i a m r Source #
A monadic unfoldEither.
Subject to fusion
Since: 1.2.11
enumFromTo :: (Enum a, Ord a, Monad m) => a -> a -> ConduitT i a m () Source #
Enumerate from a value to a final value, inclusive, via succ
.
This is generally more efficient than using Prelude
's enumFromTo
and
combining with sourceList
since this avoids any intermediate data
structures.
Subject to fusion
Since 0.4.2
iterate :: Monad m => (a -> a) -> a -> ConduitT i a m () Source #
Produces an infinite stream of repeated applications of f to x.
Subject to fusion
replicate :: Monad m => Int -> a -> ConduitT i a m () Source #
Replicate a single value the given number of times.
Subject to fusion
Since 1.2.0
replicateM :: Monad m => Int -> m a -> ConduitT i a m () Source #
Replicate a monadic value the given number of times.
Subject to fusion
Since 1.2.0
Sinks
Pure
fold :: Monad m => (b -> a -> b) -> b -> ConduitT a o m b Source #
A strict left fold.
Subject to fusion
Since 0.3.0
foldMap :: (Monad m, Monoid b) => (a -> b) -> ConduitT a o m b Source #
A monoidal strict left fold.
Subject to fusion
Since 0.5.3
uncons :: SealedConduitT () o Identity () -> Maybe (o, SealedConduitT () o Identity ()) Source #
Split a pure conduit into head and tail.
This is equivalent to runIdentity . unconsM
.
Note that you have to sealConduitT
it first.
Since 1.3.3
unconsEither :: SealedConduitT () o Identity r -> Either r (o, SealedConduitT () o Identity r) Source #
Split a pure conduit into head and tail or return its result if it is done.
This is equivalent to runIdentity . unconsEitherM
.
Note that you have to sealConduitT
it first.
Since 1.3.3
take :: Monad m => Int -> ConduitT a o m [a] Source #
Take some values from the stream and return as a list. If you want to
instead create a conduit that pipes data to another sink, see isolate
.
This function is semantically equivalent to:
take i = isolate i =$ consume
Subject to fusion
Since 0.3.0
drop :: Monad m => Int -> ConduitT a o m () Source #
Ignore a certain number of values in the stream. This function is semantically equivalent to:
drop i = take i >> return ()
However, drop
is more efficient as it does not need to hold values in
memory.
Subject to fusion
Since 0.3.0
head :: Monad m => ConduitT a o m (Maybe a) Source #
Take a single value from the stream, if available.
Subject to fusion
Since 0.3.0
peek :: Monad m => ConduitT a o m (Maybe a) Source #
Look at the next value in the stream, if available. This function will not change the state of the stream.
Since 0.3.0
consume :: Monad m => ConduitT a o m [a] Source #
Consume all values from the stream and return as a list. Note that this will pull all values into memory.
Subject to fusion
Since 0.3.0
sinkNull :: Monad m => ConduitT i o m () Source #
Ignore the remainder of values in the source. Particularly useful when
combined with isolate
.
Subject to fusion
Since 0.3.0
Monadic
foldMapM :: (Monad m, Monoid b) => (a -> m b) -> ConduitT a o m b Source #
A monoidal strict left fold in a Monad.
Since 1.0.8
foldM :: Monad m => (b -> a -> m b) -> b -> ConduitT a o m b Source #
A monadic strict left fold.
Subject to fusion
Since 0.3.0
unconsM :: Monad m => SealedConduitT () o m () -> m (Maybe (o, SealedConduitT () o m ())) Source #
unconsEitherM :: Monad m => SealedConduitT () o m r -> m (Either r (o, SealedConduitT () o m r)) Source #
Split a conduit into head and tail or return its result if it is done.
Note that you have to sealConduitT
it first.
Since 1.3.3
mapM_ :: Monad m => (a -> m ()) -> ConduitT a o m () Source #
Apply the action to all values in the stream.
Subject to fusion
Since 0.3.0
Conduits
Pure
map :: Monad m => (a -> b) -> ConduitT a b m () Source #
Apply a transformation to all values in a stream.
Subject to fusion
Since 0.3.0
mapMaybe :: Monad m => (a -> Maybe b) -> ConduitT a b m () Source #
Apply a transformation that may fail to all values in a stream, discarding the failures.
Subject to fusion
Since 0.5.1
catMaybes :: Monad m => ConduitT (Maybe a) a m () Source #
Filter the Just
values from a stream, discarding the Nothing
values.
Subject to fusion
Since 0.5.1
concatMap :: Monad m => (a -> [b]) -> ConduitT a b m () Source #
Apply a transformation to all values in a stream, concatenating the output values.
Subject to fusion
Since 0.3.0
concatMapAccum :: Monad m => (a -> accum -> (accum, [b])) -> accum -> ConduitT a b m () Source #
scanl :: Monad m => (a -> s -> (s, b)) -> s -> ConduitT a b m () Source #
Deprecated: Use mapAccum instead
Deprecated synonym for mapAccum
Since 1.0.6
mapAccum :: Monad m => (a -> s -> (s, b)) -> s -> ConduitT a b m s Source #
Analog of mapAccumL
for lists. Note that in contrast to mapAccumL
, the function argument
takes the accumulator as its second argument, not its first argument, and the accumulated value
is strict.
Subject to fusion
Since 1.1.1
chunksOf :: Monad m => Int -> ConduitT a [a] m () Source #
Group a stream into chunks of a given size. The last chunk may contain fewer than n elements.
Subject to fusion
Since 1.2.9
groupBy :: Monad m => (a -> a -> Bool) -> ConduitT a [a] m () Source #
Grouping input according to an equality function.
Subject to fusion
Since 0.3.0
groupOn1 :: (Monad m, Eq b) => (a -> b) -> ConduitT a (a, [a]) m () Source #
groupOn1
is similar to groupBy id
returns a pair, indicating there are always 1 or more items in the grouping. This is designed to be converted into a NonEmpty structure but it avoids a dependency on another package
import Data.List.NonEmpty groupOn1 :: (Monad m, Eq b) => (a -> b) -> Conduit a m (NonEmpty a) groupOn1 f = CL.groupOn1 f .| CL.map (uncurry (:|))
Subject to fusion
Since 1.1.7
isolate :: Monad m => Int -> ConduitT a a m () Source #
Ensure that the inner sink consumes no more than the given number of
values. Note this this does not ensure that the sink consumes all of those
values. To get the latter behavior, combine with sinkNull
, e.g.:
src $$ do x <- isolate count =$ do x <- someSink sinkNull return x someOtherSink ...
Subject to fusion
Since 0.3.0
filter :: Monad m => (a -> Bool) -> ConduitT a a m () Source #
Keep only values in the stream passing a given predicate.
Subject to fusion
Since 0.3.0
Monadic
mapM :: Monad m => (a -> m b) -> ConduitT a b m () Source #
Apply a monadic transformation to all values in a stream.
If you do not need the transformed values, and instead just want the monadic
side-effects of running the action, see mapM_
.
Subject to fusion
Since 0.3.0
iterM :: Monad m => (a -> m ()) -> ConduitT a a m () Source #
Apply a monadic action on all values in a stream.
This Conduit
can be used to perform a monadic side-effect for every
value, whilst passing the value through the Conduit
as-is.
iterM f = mapM (\a -> f a >>= \() -> return a)
Subject to fusion
Since 0.5.6
scanlM :: Monad m => (a -> s -> m (s, b)) -> s -> ConduitT a b m () Source #
Deprecated: Use mapAccumM instead
Deprecated synonym for mapAccumM
Since 1.0.6
scanM :: Monad m => (a -> b -> m b) -> b -> ConduitT a b m b Source #
Monadic scanl
.
Subject to fusion
Since 1.1.1
mapMaybeM :: Monad m => (a -> m (Maybe b)) -> ConduitT a b m () Source #
Apply a monadic transformation that may fail to all values in a stream, discarding the failures.
Subject to fusion
Since 0.5.1
concatMapM :: Monad m => (a -> m [b]) -> ConduitT a b m () Source #
Apply a monadic transformation to all values in a stream, concatenating the output values.
Subject to fusion
Since 0.3.0
concatMapAccumM :: Monad m => (a -> accum -> m (accum, [b])) -> accum -> ConduitT a b m () Source #