Safe Haskell | None |
---|---|
Language | Haskell98 |
This module is meant as a replacement for Data.Conduit.List. That module follows a naming scheme which was originally inspired by its enumerator roots. This module is meant to introduce a naming scheme which encourages conduit best practices.
There are two versions of functions in this module. Those with a trailing E work in the individual elements of a chunk of data, e.g., the bytes of a ByteString, the Chars of a Text, or the Ints of a Vector Int. Those without a trailing E work on unchunked streams.
FIXME: discuss overall naming, usage of mono-traversable, etc
Mention take (Conduit) vs drop (Consumer)
- yieldMany :: (Monad m, MonoFoldable mono) => mono -> Producer m (Element mono)
- unfold :: Monad m => (b -> Maybe (a, b)) -> b -> Producer m a
- enumFromTo :: (Monad m, Enum a, Ord a) => a -> a -> Producer m a
- iterate :: Monad m => (a -> a) -> a -> Producer m a
- repeat :: Monad m => a -> Producer m a
- replicate :: Monad m => Int -> a -> Producer m a
- sourceLazy :: (Monad m, LazySequence lazy strict) => lazy -> Producer m strict
- repeatM :: Monad m => m a -> Producer m a
- repeatWhileM :: Monad m => m a -> (a -> Bool) -> Producer m a
- replicateM :: Monad m => Int -> m a -> Producer m a
- sourceFile :: MonadResource m => FilePath -> Producer m ByteString
- sourceFileBS :: MonadResource m => FilePath -> Producer m ByteString
- sourceHandle :: MonadIO m => Handle -> Producer m ByteString
- sourceIOHandle :: MonadResource m => IO Handle -> Producer m ByteString
- stdin :: MonadIO m => Producer m ByteString
- sourceRandom :: (Variate a, MonadIO m) => Producer m a
- sourceRandomN :: (Variate a, MonadIO m) => Int -> Producer m a
- sourceRandomGen :: (Variate a, MonadBase base m, PrimMonad base) => Gen (PrimState base) -> Producer m a
- sourceRandomNGen :: (Variate a, MonadBase base m, PrimMonad base) => Gen (PrimState base) -> Int -> Producer m a
- sourceRandomWith :: (Variate a, MonadIO m) => (GenIO -> IO a) -> Producer m a
- sourceRandomNWith :: (Variate a, MonadIO m) => Int -> (GenIO -> IO a) -> Producer m a
- sourceRandomGenWith :: (Variate a, MonadBase base m, PrimMonad base) => Gen (PrimState base) -> (Gen (PrimState base) -> base a) -> Producer m a
- sourceRandomNGenWith :: (Variate a, MonadBase base m, PrimMonad base) => Gen (PrimState base) -> Int -> (Gen (PrimState base) -> base a) -> Producer m a
- sourceDirectory :: MonadResource m => FilePath -> Producer m FilePath
- sourceDirectoryDeep :: MonadResource m => Bool -> FilePath -> Producer m FilePath
- drop :: Monad m => Int -> Consumer a m ()
- dropE :: (Monad m, IsSequence seq) => Index seq -> Consumer seq m ()
- dropWhile :: Monad m => (a -> Bool) -> Consumer a m ()
- dropWhileE :: (Monad m, IsSequence seq) => (Element seq -> Bool) -> Consumer seq m ()
- fold :: (Monad m, Monoid a) => Consumer a m a
- foldE :: (Monad m, MonoFoldable mono, Monoid (Element mono)) => Consumer mono m (Element mono)
- foldl :: Monad m => (a -> b -> a) -> a -> Consumer b m a
- foldl1 :: Monad m => (a -> a -> a) -> Consumer a m (Maybe a)
- foldlE :: (Monad m, MonoFoldable mono) => (a -> Element mono -> a) -> a -> Consumer mono m a
- foldMap :: (Monad m, Monoid b) => (a -> b) -> Consumer a m b
- foldMapE :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> w) -> Consumer mono m w
- all :: Monad m => (a -> Bool) -> Consumer a m Bool
- allE :: (Monad m, MonoFoldable mono) => (Element mono -> Bool) -> Consumer mono m Bool
- any :: Monad m => (a -> Bool) -> Consumer a m Bool
- anyE :: (Monad m, MonoFoldable mono) => (Element mono -> Bool) -> Consumer mono m Bool
- and :: Monad m => Consumer Bool m Bool
- andE :: (Monad m, MonoFoldable mono, Element mono ~ Bool) => Consumer mono m Bool
- or :: Monad m => Consumer Bool m Bool
- orE :: (Monad m, MonoFoldable mono, Element mono ~ Bool) => Consumer mono m Bool
- elem :: (Monad m, Eq a) => a -> Consumer a m Bool
- elemE :: (Monad m, IsSequence seq, Eq (Element seq)) => Element seq -> Consumer seq m Bool
- notElem :: (Monad m, Eq a) => a -> Consumer a m Bool
- notElemE :: (Monad m, IsSequence seq, Eq (Element seq)) => Element seq -> Consumer seq m Bool
- sinkLazy :: (Monad m, LazySequence lazy strict) => Consumer strict m lazy
- sinkList :: Monad m => Consumer a m [a]
- sinkVector :: (MonadBase base m, Vector v a, PrimMonad base) => Consumer a m (v a)
- sinkVectorN :: (MonadBase base m, Vector v a, PrimMonad base) => Int -> Consumer a m (v a)
- sinkBuilder :: (Monad m, Monoid builder, ToBuilder a builder) => Consumer a m builder
- sinkLazyBuilder :: (Monad m, Monoid builder, ToBuilder a builder, Builder builder lazy) => Consumer a m lazy
- sinkNull :: Monad m => Consumer a m ()
- awaitNonNull :: (Monad m, MonoFoldable a) => Consumer a m (Maybe (NonNull a))
- head :: Monad m => Consumer a m (Maybe a)
- headDef :: Monad m => a -> Consumer a m a
- headE :: (Monad m, IsSequence seq) => Consumer seq m (Maybe (Element seq))
- peek :: Monad m => Consumer a m (Maybe a)
- peekE :: (Monad m, MonoFoldable mono) => Consumer mono m (Maybe (Element mono))
- last :: Monad m => Consumer a m (Maybe a)
- lastDef :: Monad m => a -> Consumer a m a
- lastE :: (Monad m, IsSequence seq) => Consumer seq m (Maybe (Element seq))
- length :: (Monad m, Num len) => Consumer a m len
- lengthE :: (Monad m, Num len, MonoFoldable mono) => Consumer mono m len
- lengthIf :: (Monad m, Num len) => (a -> Bool) -> Consumer a m len
- lengthIfE :: (Monad m, Num len, MonoFoldable mono) => (Element mono -> Bool) -> Consumer mono m len
- maximum :: (Monad m, Ord a) => Consumer a m (Maybe a)
- maximumE :: (Monad m, IsSequence seq, Ord (Element seq)) => Consumer seq m (Maybe (Element seq))
- minimum :: (Monad m, Ord a) => Consumer a m (Maybe a)
- minimumE :: (Monad m, IsSequence seq, Ord (Element seq)) => Consumer seq m (Maybe (Element seq))
- null :: Monad m => Consumer a m Bool
- nullE :: (Monad m, MonoFoldable mono) => Consumer mono m Bool
- sum :: (Monad m, Num a) => Consumer a m a
- sumE :: (Monad m, MonoFoldable mono, Num (Element mono)) => Consumer mono m (Element mono)
- product :: (Monad m, Num a) => Consumer a m a
- productE :: (Monad m, MonoFoldable mono, Num (Element mono)) => Consumer mono m (Element mono)
- find :: Monad m => (a -> Bool) -> Consumer a m (Maybe a)
- mapM_ :: Monad m => (a -> m ()) -> Consumer a m ()
- mapM_E :: (Monad m, MonoFoldable mono) => (Element mono -> m ()) -> Consumer mono m ()
- foldM :: Monad m => (a -> b -> m a) -> a -> Consumer b m a
- foldME :: (Monad m, MonoFoldable mono) => (a -> Element mono -> m a) -> a -> Consumer mono m a
- foldMapM :: (Monad m, Monoid w) => (a -> m w) -> Consumer a m w
- foldMapME :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> m w) -> Consumer mono m w
- sinkFile :: MonadResource m => FilePath -> Consumer ByteString m ()
- sinkFileBS :: MonadResource m => FilePath -> Consumer ByteString m ()
- sinkHandle :: MonadIO m => Handle -> Consumer ByteString m ()
- sinkIOHandle :: MonadResource m => IO Handle -> Consumer ByteString m ()
- print :: (Show a, MonadIO m) => Consumer a m ()
- stdout :: MonadIO m => Consumer ByteString m ()
- stderr :: MonadIO m => Consumer ByteString m ()
- map :: Monad m => (a -> b) -> Conduit a m b
- mapE :: (Monad m, Functor f) => (a -> b) -> Conduit (f a) m (f b)
- omapE :: (Monad m, MonoFunctor mono) => (Element mono -> Element mono) -> Conduit mono m mono
- concatMap :: (Monad m, MonoFoldable mono) => (a -> mono) -> Conduit a m (Element mono)
- concatMapE :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> w) -> Conduit mono m w
- take :: Monad m => Int -> Conduit a m a
- takeE :: (Monad m, IsSequence seq) => Index seq -> Conduit seq m seq
- takeWhile :: Monad m => (a -> Bool) -> Conduit a m a
- takeWhileE :: (Monad m, IsSequence seq) => (Element seq -> Bool) -> Conduit seq m seq
- takeExactly :: Monad m => Int -> ConduitM a b m r -> ConduitM a b m r
- takeExactlyE :: (Monad m, IsSequence a) => Index a -> ConduitM a b m r -> ConduitM a b m r
- concat :: (Monad m, MonoFoldable mono) => Conduit mono m (Element mono)
- filter :: Monad m => (a -> Bool) -> Conduit a m a
- filterE :: (IsSequence seq, Monad m) => (Element seq -> Bool) -> Conduit seq m seq
- mapWhile :: Monad m => (a -> Maybe b) -> Conduit a m b
- conduitVector :: (MonadBase base m, Vector v a, PrimMonad base) => Int -> Conduit a m (v a)
- scanl :: Monad m => (a -> b -> a) -> a -> Conduit b m a
- mapAccumWhile :: Monad m => (a -> s -> Either s (s, b)) -> s -> ConduitM a b m s
- concatMapAccum :: Monad m => (a -> accum -> (accum, [b])) -> accum -> Conduit a m b
- intersperse :: Monad m => a -> Conduit a m a
- slidingWindow :: (Monad m, IsSequence seq, Element seq ~ a) => Int -> Conduit a m seq
- encodeBase64 :: Monad m => Conduit ByteString m ByteString
- decodeBase64 :: Monad m => Conduit ByteString m ByteString
- encodeBase64URL :: Monad m => Conduit ByteString m ByteString
- decodeBase64URL :: Monad m => Conduit ByteString m ByteString
- encodeBase16 :: Monad m => Conduit ByteString m ByteString
- decodeBase16 :: Monad m => Conduit ByteString m ByteString
- mapM :: Monad m => (a -> m b) -> Conduit a m b
- mapME :: (Monad m, Traversable f) => (a -> m b) -> Conduit (f a) m (f b)
- omapME :: (Monad m, MonoTraversable mono) => (Element mono -> m (Element mono)) -> Conduit mono m mono
- concatMapM :: (Monad m, MonoFoldable mono) => (a -> m mono) -> Conduit a m (Element mono)
- filterM :: Monad m => (a -> m Bool) -> Conduit a m a
- filterME :: (Monad m, IsSequence seq) => (Element seq -> m Bool) -> Conduit seq m seq
- iterM :: Monad m => (a -> m ()) -> Conduit a m a
- scanlM :: Monad m => (a -> b -> m a) -> a -> Conduit b m a
- mapAccumWhileM :: Monad m => (a -> s -> m (Either s (s, b))) -> s -> ConduitM a b m s
- concatMapAccumM :: Monad m => (a -> accum -> m (accum, [b])) -> accum -> Conduit a m b
- encodeUtf8 :: (Monad m, Utf8 text binary) => Conduit text m binary
- decodeUtf8 :: MonadThrow m => Conduit ByteString m Text
- decodeUtf8Lenient :: MonadThrow m => Conduit ByteString m Text
- line :: (Monad m, IsSequence seq, Element seq ~ Char) => ConduitM seq o m r -> ConduitM seq o m r
- lineAscii :: (Monad m, IsSequence seq, Element seq ~ Word8) => ConduitM seq o m r -> ConduitM seq o m r
- unlines :: (Monad m, IsSequence seq, Element seq ~ Char) => Conduit seq m seq
- unlinesAscii :: (Monad m, IsSequence seq, Element seq ~ Word8) => Conduit seq m seq
- takeExactlyUntilE :: (Monad m, IsSequence seq) => (Element seq -> Bool) -> ConduitM seq o m r -> ConduitM seq o m r
- linesUnbounded :: (Monad m, IsSequence seq, Element seq ~ Char) => Conduit seq m seq
- linesUnboundedAscii :: (Monad m, IsSequence seq, Element seq ~ Word8) => Conduit seq m seq
- splitOnUnboundedE :: (Monad m, IsSequence seq) => (Element seq -> Bool) -> Conduit seq m seq
- vectorBuilder :: (PrimMonad base, MonadBase base m, Vector v e, MonadBase base n) => Int -> ((e -> n ()) -> Sink i m r) -> ConduitM i (v e) m r
- mapAccumS :: Monad m => (a -> s -> Sink b m s) -> s -> Source m b -> Sink a m s
- peekForever :: Monad m => ConduitM i o m () -> ConduitM i o m ()
- peekForeverE :: (Monad m, MonoFoldable i) => ConduitM i o m () -> ConduitM i o m ()
Producers
Pure
yieldMany :: (Monad m, MonoFoldable mono) => mono -> Producer m (Element mono) Source #
Yield each of the values contained by the given MonoFoldable
.
This will work on many data structures, including lists, ByteString
s, and Vector
s.
Subject to fusion
Since 1.0.0
unfold :: Monad m => (b -> Maybe (a, b)) -> b -> Producer m a Source #
Generate a producer from a seed value.
Subject to fusion
Since 1.0.0
enumFromTo :: (Monad m, Enum a, Ord a) => 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.
Subject to fusion
Since 1.0.0
iterate :: Monad m => (a -> a) -> a -> Producer m a Source #
Produces an infinite stream of repeated applications of f to x.
Subject to fusion
Since 1.0.0
repeat :: Monad m => a -> Producer m a Source #
Produce an infinite stream consisting entirely of the given value.
Subject to fusion
Since 1.0.0
replicate :: Monad m => Int -> a -> Producer m a Source #
Produce a finite stream consisting of n copies of the given value.
Subject to fusion
Since 1.0.0
sourceLazy :: (Monad m, LazySequence lazy strict) => lazy -> Producer m strict Source #
Generate a producer by yielding each of the strict chunks in a LazySequence
.
For more information, see toChunks
.
Subject to fusion
Since 1.0.0
Monadic
repeatM :: Monad m => m a -> Producer m a Source #
Repeatedly run the given action and yield all values it produces.
Subject to fusion
Since 1.0.0
repeatWhileM :: Monad m => m a -> (a -> Bool) -> Producer m a Source #
Repeatedly run the given action and yield all values it produces, until
the provided predicate returns False
.
Subject to fusion
Since 1.0.0
replicateM :: Monad m => Int -> m a -> Producer m a Source #
Perform the given action n times, yielding each result.
Subject to fusion
Since 1.0.0
I/O
sourceFile :: MonadResource m => FilePath -> Producer m ByteString #
Stream the contents of a file as binary data.
Since 0.3.0
sourceFileBS :: MonadResource m => FilePath -> Producer m ByteString Source #
sourceFile
specialized to ByteString
to help with type
inference.
Since: 1.0.7
sourceHandle :: MonadIO m => Handle -> Producer m ByteString #
Stream the contents of a Handle
as binary data. Note that this
function will not automatically close the Handle
when processing
completes, since it did not acquire the Handle
in the first place.
Since 0.3.0
sourceIOHandle :: MonadResource m => IO Handle -> Producer m ByteString #
An alternative to sourceHandle
.
Instead of taking a pre-opened Handle
, it takes an action that opens
a Handle
(in read mode), so that it can open it only when needed
and close it as soon as possible.
Since 0.3.0
stdin :: MonadIO m => Producer m ByteString Source #
sourceHandle
applied to stdin
.
Subject to fusion
Since 1.0.0
Random numbers
sourceRandom :: (Variate a, MonadIO m) => Producer m a Source #
Create an infinite stream of random values, seeding from the system random number.
Subject to fusion
Since 1.0.0
Create a stream of random values of length n, seeding from the system random number.
Subject to fusion
Since 1.0.0
sourceRandomGen :: (Variate a, MonadBase base m, PrimMonad base) => Gen (PrimState base) -> Producer m a Source #
Create an infinite stream of random values, using the given random number generator.
Subject to fusion
Since 1.0.0
Create a stream of random values of length n, seeding from the system random number.
Subject to fusion
Since 1.0.0
sourceRandomWith :: (Variate a, MonadIO m) => (GenIO -> IO a) -> Producer m a Source #
Create an infinite stream of random values from an arbitrary distribution, seeding from the system random number.
Subject to fusion
Since 1.0.3
Create a stream of random values of length n from an arbitrary distribution, seeding from the system random number.
Subject to fusion
Since 1.0.3
sourceRandomGenWith :: (Variate a, MonadBase base m, PrimMonad base) => Gen (PrimState base) -> (Gen (PrimState base) -> base a) -> Producer m a Source #
Create an infinite stream of random values from an arbitrary distribution, using the given random number generator.
Subject to fusion
Since 1.0.3
:: (Variate a, MonadBase base m, PrimMonad base) | |
=> Gen (PrimState base) | |
-> Int | count |
-> (Gen (PrimState base) -> base a) | |
-> Producer m a |
Create a stream of random values of length n from an arbitrary distribution, seeding from the system random number.
Subject to fusion
Since 1.0.3
Filesystem
sourceDirectory :: MonadResource m => FilePath -> Producer m FilePath Source #
Stream the contents of the given directory, without traversing deeply.
This function will return all of the contents of the directory, whether they be files, directories, etc.
Note that the generated filepaths will be the complete path, not just the
filename. In other words, if you have a directory foo
containing files
bar
and baz
, and you use sourceDirectory
on foo
, the results will be
foo/bar
and foo/baz
.
Since 1.0.0
:: MonadResource m | |
=> Bool | Follow directory symlinks |
-> FilePath | Root directory |
-> Producer m FilePath |
Deeply stream the contents of the given directory.
This works the same as sourceDirectory
, but will not return directories at
all. This function also takes an extra parameter to indicate whether
symlinks will be followed.
Since 1.0.0
Consumers
Pure
drop :: Monad m => Int -> Consumer a m () Source #
Ignore a certain number of values in the stream.
Since 1.0.0
dropE :: (Monad m, IsSequence seq) => Index seq -> Consumer seq m () Source #
Drop a certain number of elements from a chunked stream.
Since 1.0.0
dropWhile :: Monad m => (a -> Bool) -> Consumer a m () Source #
Drop all values which match the given predicate.
Since 1.0.0
dropWhileE :: (Monad m, IsSequence seq) => (Element seq -> Bool) -> Consumer seq m () Source #
Drop all elements in the chunked stream which match the given predicate.
Since 1.0.0
fold :: (Monad m, Monoid a) => Consumer a m a Source #
Monoidally combine all values in the stream.
Subject to fusion
Since 1.0.0
foldE :: (Monad m, MonoFoldable mono, Monoid (Element mono)) => Consumer mono m (Element mono) Source #
Monoidally combine all elements in the chunked stream.
Subject to fusion
Since 1.0.0
foldl :: Monad m => (a -> b -> a) -> a -> Consumer b m a Source #
A strict left fold.
Subject to fusion
Since 1.0.0
foldl1 :: Monad m => (a -> a -> a) -> Consumer a m (Maybe a) Source #
A strict left fold with no starting value. Returns Nothing
when the stream is empty.
Subject to fusion
foldlE :: (Monad m, MonoFoldable mono) => (a -> Element mono -> a) -> a -> Consumer mono m a Source #
A strict left fold on a chunked stream.
Subject to fusion
Since 1.0.0
foldMap :: (Monad m, Monoid b) => (a -> b) -> Consumer a m b Source #
Apply the provided mapping function and monoidal combine all values.
Subject to fusion
Since 1.0.0
foldMapE :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> w) -> Consumer mono m w Source #
Apply the provided mapping function and monoidal combine all elements of the chunked stream.
Subject to fusion
Since 1.0.0
all :: Monad m => (a -> Bool) -> Consumer a m Bool Source #
Check that all values in the stream return True.
Subject to shortcut logic: at the first False, consumption of the stream will stop.
Subject to fusion
Since 1.0.0
allE :: (Monad m, MonoFoldable mono) => (Element mono -> Bool) -> Consumer mono m Bool Source #
Check that all elements in the chunked stream return True.
Subject to shortcut logic: at the first False, consumption of the stream will stop.
Subject to fusion
Since 1.0.0
any :: Monad m => (a -> Bool) -> Consumer a m Bool Source #
Check that at least one value in the stream returns True.
Subject to shortcut logic: at the first True, consumption of the stream will stop.
Subject to fusion
Since 1.0.0
anyE :: (Monad m, MonoFoldable mono) => (Element mono -> Bool) -> Consumer mono m Bool Source #
Check that at least one element in the chunked stream returns True.
Subject to shortcut logic: at the first True, consumption of the stream will stop.
Subject to fusion
Since 1.0.0
and :: Monad m => Consumer Bool m Bool Source #
Are all values in the stream True?
Consumption stops once the first False is encountered.
Subject to fusion
Since 1.0.0
andE :: (Monad m, MonoFoldable mono, Element mono ~ Bool) => Consumer mono m Bool Source #
Are all elements in the chunked stream True?
Consumption stops once the first False is encountered.
Subject to fusion
Since 1.0.0
or :: Monad m => Consumer Bool m Bool Source #
Are any values in the stream True?
Consumption stops once the first True is encountered.
Subject to fusion
Since 1.0.0
orE :: (Monad m, MonoFoldable mono, Element mono ~ Bool) => Consumer mono m Bool Source #
Are any elements in the chunked stream True?
Consumption stops once the first True is encountered.
Subject to fusion
Since 1.0.0
elem :: (Monad m, Eq a) => a -> Consumer a m Bool Source #
Are any values in the stream equal to the given value?
Stops consuming as soon as a match is found.
Subject to fusion
Since 1.0.0
elemE :: (Monad m, IsSequence seq, Eq (Element seq)) => Element seq -> Consumer seq m Bool Source #
Are any elements in the chunked stream equal to the given element?
Stops consuming as soon as a match is found.
Subject to fusion
Since 1.0.0
notElem :: (Monad m, Eq a) => a -> Consumer a m Bool Source #
Are no values in the stream equal to the given value?
Stops consuming as soon as a match is found.
Subject to fusion
Since 1.0.0
notElemE :: (Monad m, IsSequence seq, Eq (Element seq)) => Element seq -> Consumer seq m Bool Source #
Are no elements in the chunked stream equal to the given element?
Stops consuming as soon as a match is found.
Subject to fusion
Since 1.0.0
sinkLazy :: (Monad m, LazySequence lazy strict) => Consumer strict m lazy Source #
Consume all incoming strict chunks into a lazy sequence. Note that the entirety of the sequence will be resident at memory.
This can be used to consume a stream of strict ByteStrings into a lazy ByteString, for example.
Subject to fusion
Since 1.0.0
sinkList :: 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.
Subject to fusion
Since 1.0.0
sinkVector :: (MonadBase base m, Vector v a, PrimMonad base) => Consumer a m (v a) Source #
Sink incoming values into a vector, growing the vector as necessary to fit more elements.
Note that using this function is more memory efficient than sinkList
and
then converting to a Vector
, as it avoids intermediate list constructors.
Subject to fusion
Since 1.0.0
Sink incoming values into a vector, up until size maxSize
. Subsequent
values will be left in the stream. If there are less than maxSize
values
present, returns a Vector
of smaller size.
Note that using this function is more memory efficient than sinkList
and
then converting to a Vector
, as it avoids intermediate list constructors.
Subject to fusion
Since 1.0.0
sinkBuilder :: (Monad m, Monoid builder, ToBuilder a builder) => Consumer a m builder Source #
Convert incoming values to a builder and fold together all builder values.
Defined as: foldMap toBuilder
.
Subject to fusion
Since 1.0.0
sinkLazyBuilder :: (Monad m, Monoid builder, ToBuilder a builder, Builder builder lazy) => Consumer a m lazy Source #
Same as sinkBuilder
, but afterwards convert the builder to its lazy
representation.
Alternatively, this could be considered an alternative to sinkLazy
, with
the following differences:
- This function will allow multiple input types, not just the strict version of the lazy structure.
- Some buffer copying may occur in this version.
Subject to fusion
Since 1.0.0
sinkNull :: Monad m => Consumer a m () Source #
Consume and discard all remaining values in the stream.
Subject to fusion
Since 1.0.0
awaitNonNull :: (Monad m, MonoFoldable a) => Consumer a m (Maybe (NonNull a)) Source #
Same as await
, but discards any leading onull
values.
Since 1.0.0
head :: Monad m => Consumer a m (Maybe a) Source #
Take a single value from the stream, if available.
Since 1.0.5
headDef :: Monad m => a -> Consumer a m a Source #
Same as head
, but returns a default value if none are available from the stream.
Since 1.0.5
headE :: (Monad m, IsSequence seq) => Consumer seq m (Maybe (Element seq)) Source #
Get the next element in the chunked stream.
Since 1.0.0
peek :: Monad m => Consumer a m (Maybe a) Source #
View the next value in the stream without consuming it.
Since 1.0.0
peekE :: (Monad m, MonoFoldable mono) => Consumer mono m (Maybe (Element mono)) Source #
View the next element in the chunked stream without consuming it.
Since 1.0.0
last :: Monad m => Consumer a m (Maybe a) Source #
Retrieve the last value in the stream, if present.
Subject to fusion
Since 1.0.0
lastDef :: Monad m => a -> Consumer a m a Source #
Same as last
, but returns a default value if none are available from the stream.
Since 1.0.5
lastE :: (Monad m, IsSequence seq) => Consumer seq m (Maybe (Element seq)) Source #
Retrieve the last element in the chunked stream, if present.
Subject to fusion
Since 1.0.0
length :: (Monad m, Num len) => Consumer a m len Source #
Count how many values are in the stream.
Subject to fusion
Since 1.0.0
lengthE :: (Monad m, Num len, MonoFoldable mono) => Consumer mono m len Source #
Count how many elements are in the chunked stream.
Subject to fusion
Since 1.0.0
lengthIf :: (Monad m, Num len) => (a -> Bool) -> Consumer a m len Source #
Count how many values in the stream pass the given predicate.
Subject to fusion
Since 1.0.0
lengthIfE :: (Monad m, Num len, MonoFoldable mono) => (Element mono -> Bool) -> Consumer mono m len Source #
Count how many elements in the chunked stream pass the given predicate.
Subject to fusion
Since 1.0.0
maximum :: (Monad m, Ord a) => Consumer a m (Maybe a) Source #
Get the largest value in the stream, if present.
Subject to fusion
Since 1.0.0
maximumE :: (Monad m, IsSequence seq, Ord (Element seq)) => Consumer seq m (Maybe (Element seq)) Source #
Get the largest element in the chunked stream, if present.
Subject to fusion
Since 1.0.0
minimum :: (Monad m, Ord a) => Consumer a m (Maybe a) Source #
Get the smallest value in the stream, if present.
Subject to fusion
Since 1.0.0
minimumE :: (Monad m, IsSequence seq, Ord (Element seq)) => Consumer seq m (Maybe (Element seq)) Source #
Get the smallest element in the chunked stream, if present.
Subject to fusion
Since 1.0.0
null :: Monad m => Consumer a m Bool Source #
True if there are no values in the stream.
This function does not modify the stream.
Since 1.0.0
nullE :: (Monad m, MonoFoldable mono) => Consumer mono m Bool Source #
True if there are no elements in the chunked stream.
This function may remove empty leading chunks from the stream, but otherwise will not modify it.
Since 1.0.0
sum :: (Monad m, Num a) => Consumer a m a Source #
Get the sum of all values in the stream.
Subject to fusion
Since 1.0.0
sumE :: (Monad m, MonoFoldable mono, Num (Element mono)) => Consumer mono m (Element mono) Source #
Get the sum of all elements in the chunked stream.
Subject to fusion
Since 1.0.0
product :: (Monad m, Num a) => Consumer a m a Source #
Get the product of all values in the stream.
Subject to fusion
Since 1.0.0
productE :: (Monad m, MonoFoldable mono, Num (Element mono)) => Consumer mono m (Element mono) Source #
Get the product of all elements in the chunked stream.
Subject to fusion
Since 1.0.0
find :: Monad m => (a -> Bool) -> Consumer a m (Maybe a) Source #
Find the first matching value.
Subject to fusion
Since 1.0.0
Monadic
mapM_ :: Monad m => (a -> m ()) -> Consumer a m () Source #
Apply the action to all values in the stream.
Subject to fusion
Since 1.0.0
mapM_E :: (Monad m, MonoFoldable mono) => (Element mono -> m ()) -> Consumer mono m () Source #
Apply the action to all elements in the chunked stream.
Subject to fusion
Since 1.0.0
foldM :: Monad m => (a -> b -> m a) -> a -> Consumer b m a Source #
A monadic strict left fold.
Subject to fusion
Since 1.0.0
foldME :: (Monad m, MonoFoldable mono) => (a -> Element mono -> m a) -> a -> Consumer mono m a Source #
A monadic strict left fold on a chunked stream.
Subject to fusion
Since 1.0.0
foldMapM :: (Monad m, Monoid w) => (a -> m w) -> Consumer a m w Source #
Apply the provided monadic mapping function and monoidal combine all values.
Subject to fusion
Since 1.0.0
foldMapME :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> m w) -> Consumer mono m w Source #
Apply the provided monadic mapping function and monoidal combine all elements in the chunked stream.
Subject to fusion
Since 1.0.0
I/O
sinkFile :: MonadResource m => FilePath -> Consumer ByteString m () #
Stream all incoming data to the given file.
Since 0.3.0
sinkFileBS :: MonadResource m => FilePath -> Consumer ByteString m () Source #
sinkFile
specialized to ByteString
to help with type
inference.
Since: 1.0.7
sinkHandle :: MonadIO m => Handle -> Consumer ByteString m () #
Stream all incoming data to the given Handle
. Note that this function
will not automatically close the Handle
when processing completes.
Since 0.3.0
sinkIOHandle :: MonadResource m => IO Handle -> Consumer ByteString m () #
An alternative to sinkHandle
.
Instead of taking a pre-opened Handle
, it takes an action that opens
a Handle
(in write mode), so that it can open it only when needed
and close it as soon as possible.
Since 0.3.0
print :: (Show a, MonadIO m) => Consumer a m () Source #
Print all incoming values to stdout.
Subject to fusion
Since 1.0.0
stdout :: MonadIO m => Consumer ByteString m () Source #
sinkHandle
applied to stdout
.
Subject to fusion
Since 1.0.0
stderr :: MonadIO m => Consumer ByteString m () Source #
sinkHandle
applied to stderr
.
Subject to fusion
Since 1.0.0
Transformers
Pure
map :: Monad m => (a -> b) -> Conduit a m b Source #
Apply a transformation to all values in a stream.
Subject to fusion
Since 1.0.0
mapE :: (Monad m, Functor f) => (a -> b) -> Conduit (f a) m (f b) Source #
Apply a transformation to all elements in a chunked stream.
Subject to fusion
Since 1.0.0
omapE :: (Monad m, MonoFunctor mono) => (Element mono -> Element mono) -> Conduit mono m mono Source #
Apply a monomorphic transformation to all elements in a chunked stream.
Unlike mapE
, this will work on types like ByteString
and Text
which
are MonoFunctor
but not Functor
.
Subject to fusion
Since 1.0.0
concatMap :: (Monad m, MonoFoldable mono) => (a -> mono) -> Conduit a m (Element mono) Source #
Apply the function to each value in the stream, resulting in a foldable value (e.g., a list). Then yield each of the individual values in that foldable value separately.
Generalizes concatMap, mapMaybe, and mapFoldable.
Subject to fusion
Since 1.0.0
concatMapE :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> w) -> Conduit mono m w Source #
Apply the function to each element in the chunked stream, resulting in a foldable value (e.g., a list). Then yield each of the individual values in that foldable value separately.
Generalizes concatMap, mapMaybe, and mapFoldable.
Subject to fusion
Since 1.0.0
take :: Monad m => Int -> Conduit a m a Source #
Stream up to n number of values downstream.
Note that, if downstream terminates early, not all values will be consumed.
If you want to force exactly the given number of values to be consumed,
see takeExactly
.
Subject to fusion
Since 1.0.0
takeE :: (Monad m, IsSequence seq) => Index seq -> Conduit seq m seq Source #
Stream up to n number of elements downstream in a chunked stream.
Note that, if downstream terminates early, not all values will be consumed.
If you want to force exactly the given number of values to be consumed,
see takeExactlyE
.
Since 1.0.0
takeWhile :: Monad m => (a -> Bool) -> Conduit a m a Source #
Stream all values downstream that match the given predicate.
Same caveats regarding downstream termination apply as with take
.
Since 1.0.0
takeWhileE :: (Monad m, IsSequence seq) => (Element seq -> Bool) -> Conduit seq m seq Source #
Stream all elements downstream that match the given predicate in a chunked stream.
Same caveats regarding downstream termination apply as with takeE
.
Since 1.0.0
takeExactly :: Monad m => Int -> ConduitM a b m r -> ConduitM a b m r Source #
Consume precisely the given number of values and feed them downstream.
This function is in contrast to take
, which will only consume up to the
given number of values, and will terminate early if downstream terminates
early. This function will discard any additional values in the stream if
they are unconsumed.
Note that this function takes a downstream ConduitM
as a parameter, as
opposed to working with normal fusion. For more information, see
http://www.yesodweb.com/blog/2013/10/core-flaw-pipes-conduit, the section
titled "pipes and conduit: isolate".
Since 1.0.0
takeExactlyE :: (Monad m, IsSequence a) => Index a -> ConduitM a b m r -> ConduitM a b m r Source #
Same as takeExactly
, but for chunked streams.
Since 1.0.0
concat :: (Monad m, MonoFoldable mono) => Conduit mono m (Element mono) Source #
Flatten out a stream by yielding the values contained in an incoming
MonoFoldable
as individually yielded values.
Subject to fusion
Since 1.0.0
filter :: Monad m => (a -> Bool) -> Conduit a m a Source #
Keep only values in the stream passing a given predicate.
Subject to fusion
Since 1.0.0
filterE :: (IsSequence seq, Monad m) => (Element seq -> Bool) -> Conduit seq m seq Source #
Keep only elements in the chunked stream passing a given predicate.
Subject to fusion
Since 1.0.0
mapWhile :: Monad m => (a -> Maybe b) -> Conduit a m b Source #
Map values as long as the result is Just
.
Since 1.0.0
Break up a stream of values into vectors of size n. The final vector may be smaller than n if the total number of values is not a strict multiple of n. No empty vectors will be yielded.
Since 1.0.0
concatMapAccum :: Monad m => (a -> accum -> (accum, [b])) -> accum -> Conduit a m b Source #
intersperse :: Monad m => a -> Conduit a m a Source #
Insert the given value between each two values in the stream.
Subject to fusion
Since 1.0.0
slidingWindow :: (Monad m, IsSequence seq, Element seq ~ a) => Int -> Conduit a m seq Source #
Sliding window of values 1,2,3,4,5 with window size 2 gives [1,2],[2,3],[3,4],[4,5]
Best used with structures that support O(1) snoc.
Subject to fusion
Since 1.0.0
Binary base encoding
encodeBase64 :: Monad m => Conduit ByteString m ByteString Source #
Apply base64-encoding to the stream.
Since 1.0.0
decodeBase64 :: Monad m => Conduit ByteString m ByteString Source #
Apply base64-decoding to the stream. Will stop decoding on the first invalid chunk.
Since 1.0.0
encodeBase64URL :: Monad m => Conduit ByteString m ByteString Source #
Apply URL-encoding to the stream.
Since 1.0.0
decodeBase64URL :: Monad m => Conduit ByteString m ByteString Source #
Apply lenient base64URL-decoding to the stream. Will stop decoding on the first invalid chunk.
Since 1.0.0
encodeBase16 :: Monad m => Conduit ByteString m ByteString Source #
Apply base16-encoding to the stream.
Subject to fusion
Since 1.0.0
decodeBase16 :: Monad m => Conduit ByteString m ByteString Source #
Apply base16-decoding to the stream. Will stop decoding on the first invalid chunk.
Since 1.0.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_
.
Subject to fusion
Since 1.0.0
mapME :: (Monad m, Traversable f) => (a -> m b) -> Conduit (f a) m (f b) Source #
Apply a monadic transformation to all elements in a chunked stream.
Subject to fusion
Since 1.0.0
omapME :: (Monad m, MonoTraversable mono) => (Element mono -> m (Element mono)) -> Conduit mono m mono Source #
Apply a monadic monomorphic transformation to all elements in a chunked stream.
Unlike mapME
, this will work on types like ByteString
and Text
which
are MonoFunctor
but not Functor
.
Subject to fusion
Since 1.0.0
concatMapM :: (Monad m, MonoFoldable mono) => (a -> m mono) -> Conduit a m (Element mono) Source #
Apply the monadic function to each value in the stream, resulting in a foldable value (e.g., a list). Then yield each of the individual values in that foldable value separately.
Generalizes concatMapM, mapMaybeM, and mapFoldableM.
Subject to fusion
Since 1.0.0
filterM :: Monad m => (a -> m Bool) -> Conduit a m a Source #
Keep only values in the stream passing a given monadic predicate.
Subject to fusion
Since 1.0.0
filterME :: (Monad m, IsSequence seq) => (Element seq -> m Bool) -> Conduit seq m seq Source #
Keep only elements in the chunked stream passing a given monadic predicate.
Subject to fusion
Since 1.0.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)
Subject to fusion
Since 1.0.0
mapAccumWhileM :: Monad m => (a -> s -> m (Either s (s, b))) -> s -> ConduitM a b m s Source #
Monadic mapAccumWhile
.
Subject to fusion
concatMapAccumM :: Monad m => (a -> accum -> m (accum, [b])) -> accum -> Conduit a m b Source #
Textual
encodeUtf8 :: (Monad m, Utf8 text binary) => Conduit text m binary Source #
Encode a stream of text as UTF8.
Subject to fusion
Since 1.0.0
decodeUtf8 :: MonadThrow m => Conduit ByteString m Text Source #
Decode a stream of binary data as UTF8.
Since 1.0.0
decodeUtf8Lenient :: MonadThrow m => Conduit ByteString m Text Source #
Decode a stream of binary data as UTF8, replacing any invalid bytes with the Unicode replacement character.
Since 1.0.0
line :: (Monad m, IsSequence seq, Element seq ~ Char) => ConduitM seq o m r -> ConduitM seq o m r Source #
Stream in the entirety of a single line.
Like takeExactly
, this will consume the entirety of the line regardless of
the behavior of the inner Conduit.
Since 1.0.0
lineAscii :: (Monad m, IsSequence seq, Element seq ~ Word8) => ConduitM seq o m r -> ConduitM seq o m r Source #
Same as line
, but operates on ASCII/binary data.
Since 1.0.0
unlines :: (Monad m, IsSequence seq, Element seq ~ Char) => Conduit seq m seq Source #
Insert a newline character after each incoming chunk of data.
Subject to fusion
Since 1.0.0
unlinesAscii :: (Monad m, IsSequence seq, Element seq ~ Word8) => Conduit seq m seq Source #
takeExactlyUntilE :: (Monad m, IsSequence seq) => (Element seq -> Bool) -> ConduitM seq o m r -> ConduitM seq o m r Source #
Stream in the chunked input until an element matches a predicate.
Like takeExactly
, this will consume the entirety of the prefix
regardless of the behavior of the inner Conduit.
linesUnbounded :: (Monad m, IsSequence seq, Element seq ~ Char) => Conduit seq m seq Source #
Convert a stream of arbitrarily-chunked textual data into a stream of data where each chunk represents a single line. Note that, if you have unknown or untrusted input, this function is unsafe, since it would allow an attacker to form lines of massive length and exhaust memory.
Subject to fusion
Since 1.0.0
linesUnboundedAscii :: (Monad m, IsSequence seq, Element seq ~ Word8) => Conduit seq m seq Source #
splitOnUnboundedE :: (Monad m, IsSequence seq) => (Element seq -> Bool) -> Conduit seq m seq Source #
Split a stream of arbitrarily-chunked data, based on a predicate on elements. Elements that satisfy the predicate will cause chunks to be split, and aren't included in these output chunks. Note that, if you have unknown or untrusted input, this function is unsafe, since it would allow an attacker to form chunks of massive length and exhaust memory.
Special
:: (PrimMonad base, MonadBase base m, Vector v e, MonadBase base n) | |
=> Int | size |
-> ((e -> n ()) -> Sink i m r) | |
-> ConduitM i (v e) m r |
Generally speaking, yielding values from inside a Conduit requires some allocation for constructors. This can introduce an overhead, similar to the overhead needed to represent a list of values instead of a vector. This overhead is even more severe when talking about unboxed values.
This combinator allows you to overcome this overhead, and efficiently fill up vectors. It takes two parameters. The first is the size of each mutable vector to be allocated. The second is a function. The function takes an argument which will yield the next value into a mutable vector.
Under the surface, this function uses a number of tricks to get high performance. For more information on both usage and implementation, please see: https://www.fpcomplete.com/user/snoyberg/library-documentation/vectorbuilder
Since 1.0.0
mapAccumS :: Monad m => (a -> s -> Sink b m s) -> s -> Source m b -> Sink a m s Source #
Consume a source with a strict accumulator, in a way piecewise defined by a controlling stream. The latter will be evaluated until it terminates.
>>>
let f a s = liftM (:s) $ mapC (*a) =$ CL.take a
>>>
reverse $ runIdentity $ yieldMany [0..3] $$ mapAccumS f [] (yieldMany [1..])
[[],[1],[4,6],[12,15,18]] :: [[Int]]
peekForever :: Monad m => ConduitM i o m () -> ConduitM i o m () Source #
Run a consuming conduit repeatedly, only stopping when there is no more data available from upstream.
Since 1.0.0
peekForeverE :: (Monad m, MonoFoldable i) => ConduitM i o m () -> ConduitM i o m () Source #
Run a consuming conduit repeatedly, only stopping when there is no more data available from upstream.
In contrast to peekForever
, this function will ignore empty
chunks of data. So for example, if a stream of data contains an
empty ByteString
, it is still treated as empty, and the consuming
function is not called.
Since: 1.0.6