conduit-1.1.0: Streaming data processing library.

Safe HaskellNone
LanguageHaskell98

Data.Conduit.List

Contents

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.

Synopsis

Sources

sourceList :: Monad m => [a] -> Producer m a Source

sourceNull :: Monad m => Producer m a Source

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 -> Producer m a Source

Generate a source from a seed value.

Since 0.4.2

enumFromTo :: (Enum a, Eq a, Monad m) => a -> a -> Producer m a 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.

Since 0.4.2

iterate :: Monad m => (a -> a) -> a -> Producer m a Source

Produces an infinite stream of repeated applications of f to x.

Sinks

Pure

fold :: Monad m => (b -> a -> b) -> b -> Consumer a m b Source

A strict left fold.

Since 0.3.0

foldMap :: (Monad m, Monoid b) => (a -> b) -> Consumer a m b Source

A monoidal strict left fold.

Since 0.5.3

take :: Monad m => Int -> Consumer 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 -> Consumer 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 => Consumer a m (Maybe a) Source

Take a single value from the stream, if available.

Since 0.3.0

peek :: Monad m => Consumer 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 => Consumer 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 => Consumer a m () Source

Ignore the remainder of values in the source. Particularly useful when combined with isolate.

Since 0.3.0

Monadic

foldMapM :: (Monad m, Monoid b) => (a -> m b) -> Consumer a m b Source

A monoidal strict left fold in a Monad.

Since 1.0.8

foldM :: Monad m => (b -> a -> m b) -> b -> Consumer a m b Source

A monadic strict left fold.

Since 0.3.0

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

Apply the action to all values in the stream.

Since 0.3.0

Conduits

Pure

map :: Monad m => (a -> b) -> Conduit a m b Source

Apply a transformation to all values in a stream.

Since 0.3.0

mapMaybe :: Monad m => (a -> Maybe b) -> Conduit a m b Source

Apply a transformation that may fail to all values in a stream, discarding the failures.

Since 0.5.1

mapFoldable :: (Monad m, Foldable f) => (a -> f b) -> Conduit a m b Source

Generalization of mapMaybe and concatMap. It applies function to all values in a stream and send values inside resulting Foldable downstream.

Since 1.0.6

catMaybes :: Monad m => Conduit (Maybe a) m a Source

Filter the Just values from a stream, discarding the Nothing values.

Since 0.5.1

concat :: (Monad m, Foldable f) => Conduit (f a) m a Source

Generalization of catMaybes. It puts all values from Foldable into stream.

Since 1.0.6

concatMap :: Monad m => (a -> [b]) -> Conduit a m b Source

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 -> Conduit a m b Source

concatMap with an accumulator.

Since 0.3.0

scanl :: Monad m => (a -> s -> (s, b)) -> s -> Conduit a m b Source

Analog of scanl for lists.

Since 1.0.6

groupBy :: Monad m => (a -> a -> Bool) -> Conduit a m [a] Source

Grouping input according to an equality function.

Since 0.3.0

isolate :: Monad m => Int -> Conduit a m a 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
    ...

Since 0.3.0

filter :: Monad m => (a -> Bool) -> Conduit a m a Source

Keep only values in the stream passing a given predicate.

Since 0.3.0

Monadic

mapM :: Monad m => (a -> m b) -> Conduit a m b 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_.

Since 0.3.0

iterM :: Monad m => (a -> m ()) -> Conduit a m a 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)

Since 0.5.6

scanlM :: Monad m => (a -> s -> m (s, b)) -> s -> Conduit a m b Source

Monadic scanl.

Since 1.0.6

mapMaybeM :: Monad m => (a -> m (Maybe b)) -> Conduit a m b Source

Apply a monadic transformation that may fail to all values in a stream, discarding the failures.

Since 0.5.1

mapFoldableM :: (Monad m, Foldable f) => (a -> m (f b)) -> Conduit a m b Source

Monadic variant of mapFoldable.

Since 1.0.6

concatMapM :: Monad m => (a -> m [b]) -> Conduit a m b Source

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 -> Conduit a m b Source

concatMapM with an accumulator.

Since 0.3.0

Misc

sequence Source

Arguments

:: Monad m 
=> Consumer i m o

Pipe to run repeatedly

-> Conduit 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