| Safe Haskell | None | 
|---|
Data.Conduit.List
Description
Higher-level functions to interact with the elements of a stream. Most of these are based on list 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.
- sourceList :: Monad m => [a] -> Pipe l i a u m ()
 - sourceNull :: Monad m => GSource m a
 - unfold :: Monad m => (b -> Maybe (a, b)) -> b -> GSource m a
 - enumFromTo :: (Enum a, Eq a, Monad m) => a -> a -> GSource m a
 - iterate :: Monad m => (a -> a) -> a -> GSource m a
 - fold :: Monad m => (b -> a -> b) -> b -> GSink a m b
 - foldMap :: (Monad m, Monoid b) => (a -> b) -> GSink a m b
 - take :: Monad m => Int -> GSink a m [a]
 - drop :: Monad m => Int -> GSink a m ()
 - head :: Monad m => GSink a m (Maybe a)
 - peek :: Monad m => GLSink a m (Maybe a)
 - consume :: Monad m => GSink a m [a]
 - sinkNull :: Monad m => GInfSink a m
 - foldM :: Monad m => (b -> a -> m b) -> b -> GSink a m b
 - mapM_ :: Monad m => (a -> m ()) -> GInfSink a m
 - map :: Monad m => (a -> b) -> GInfConduit a m b
 - mapMaybe :: Monad m => (a -> Maybe b) -> GInfConduit a m b
 - catMaybes :: Monad m => GInfConduit (Maybe a) m a
 - concatMap :: Monad m => (a -> [b]) -> GInfConduit a m b
 - concatMapAccum :: Monad m => (a -> accum -> (accum, [b])) -> accum -> GInfConduit a m b
 - groupBy :: Monad m => (a -> a -> Bool) -> GInfConduit a m [a]
 - isolate :: Monad m => Int -> GConduit a m a
 - filter :: Monad m => (a -> Bool) -> GInfConduit a m a
 - mapM :: Monad m => (a -> m b) -> GInfConduit a m b
 - mapMaybeM :: Monad m => (a -> m (Maybe b)) -> GInfConduit a m b
 - concatMapM :: Monad m => (a -> m [b]) -> GInfConduit a m b
 - concatMapAccumM :: Monad m => (a -> accum -> m (accum, [b])) -> accum -> GInfConduit a m b
 - sequence :: Monad m => GLSink i m o -> GLInfConduit i m o
 
Sources
sourceList :: Monad m => [a] -> Pipe l i a u m ()Source
Convert a list into a source.
Since 0.3.0
sourceNull :: Monad m => GSource m aSource
A source that outputs no values. Note that this is just a type-restricted
 synonym for mempty.
Since 0.3.0
unfold :: Monad m => (b -> Maybe (a, b)) -> b -> GSource m aSource
Generate a source from a seed value.
Since 0.4.2
enumFromTo :: (Enum a, Eq a, Monad m) => a -> a -> GSource m aSource
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.
Since 0.4.2
iterate :: Monad m => (a -> a) -> a -> GSource m aSource
Produces an infinite stream of repeated applications of f to x.
Sinks
Pure
foldMap :: (Monad m, Monoid b) => (a -> b) -> GSink a m bSource
A monoidal strict left fold.
Since 0.5.3
take :: Monad m => Int -> GSink a 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
Since 0.3.0
drop :: Monad m => Int -> GSink a 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.
Since 0.3.0
head :: Monad m => GSink a m (Maybe a)Source
Take a single value from the stream, if available.
Since 0.3.0
peek :: Monad m => GLSink a 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 => GSink a m [a]Source
Consume all values from the stream and return as a list. Note that this will pull all values into memory. For a lazy variant, see Data.Conduit.Lazy.
Since 0.3.0
sinkNull :: Monad m => GInfSink a mSource
Ignore the remainder of values in the source. Particularly useful when
 combined with isolate.
Since 0.3.0
Monadic
foldM :: Monad m => (b -> a -> m b) -> b -> GSink a m bSource
A monadic strict left fold.
Since 0.3.0
mapM_ :: Monad m => (a -> m ()) -> GInfSink a mSource
Apply the action to all values in the stream.
Since 0.3.0
Conduits
Pure
map :: Monad m => (a -> b) -> GInfConduit a m bSource
Apply a transformation to all values in a stream.
Since 0.3.0
mapMaybe :: Monad m => (a -> Maybe b) -> GInfConduit a m bSource
Apply a transformation that may fail to all values in a stream, discarding the failures.
Since 0.5.1
catMaybes :: Monad m => GInfConduit (Maybe a) m aSource
Filter the Just values from a stream, discarding the Nothing  values.
Since 0.5.1
concatMap :: Monad m => (a -> [b]) -> GInfConduit a m bSource
Apply a transformation to all values in a stream, concatenating the output values.
Since 0.3.0
concatMapAccum :: Monad m => (a -> accum -> (accum, [b])) -> accum -> GInfConduit a m bSource
concatMap with an accumulator.
Since 0.3.0
groupBy :: Monad m => (a -> a -> Bool) -> GInfConduit a m [a]Source
Grouping input according to an equality function.
Since 0.3.0
isolate :: Monad m => Int -> GConduit a m aSource
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
     ...
Since 0.3.0
filter :: Monad m => (a -> Bool) -> GInfConduit a m aSource
Keep only values in the stream passing a given predicate.
Since 0.3.0
Monadic
mapM :: Monad m => (a -> m b) -> GInfConduit a m bSource
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_.
Since 0.3.0
mapMaybeM :: Monad m => (a -> m (Maybe b)) -> GInfConduit a m bSource
Apply a monadic transformation that may fail to all values in a stream, discarding the failures.
Since 0.5.1
concatMapM :: Monad m => (a -> m [b]) -> GInfConduit a m bSource
Apply a monadic transformation to all values in a stream, concatenating the output values.
Since 0.3.0
concatMapAccumM :: Monad m => (a -> accum -> m (accum, [b])) -> accum -> GInfConduit a m bSource
concatMapM with an accumulator.
Since 0.3.0
Misc
Arguments
| :: Monad m | |
| => GLSink i m o | 
  | 
| -> GLInfConduit i m o | 
Run a Pipe repeatedly, and output its result value downstream. Stops
 when no more input is available from upstream.
Since 0.5.0