Safe Haskell | None |
---|---|
Language | Haskell98 |
Your intended one-stop-shop for conduit functionality. This re-exports functions from many commonly used modules. When there is a conflict with standard functions, functions in this module are disambiguated by adding a trailing C (or for chunked functions, replacing a trailing E with CE). This means that the Conduit module can be imported unqualified without causing naming conflicts.
For more information on the naming scheme and intended usages of the combinators, please see the Data.Conduit.Combinators documentation.
- module Data.Conduit
- module Data.Conduit.Lift
- yieldMany :: (Monad m, MonoFoldable mono) => mono -> Producer m (Element mono)
- unfoldC :: Monad m => (b -> Maybe (a, b)) -> b -> Producer m a
- enumFromToC :: (Monad m, Enum a, Ord a) => a -> a -> Producer m a
- iterateC :: Monad m => (a -> a) -> a -> Producer m a
- repeatC :: Monad m => a -> Producer m a
- replicateC :: Monad m => Int -> a -> Producer m a
- sourceLazy :: (Monad m, LazySequence lazy strict) => lazy -> Producer m strict
- repeatMC :: Monad m => m a -> Producer m a
- repeatWhileMC :: Monad m => m a -> (a -> Bool) -> Producer m a
- replicateMC :: Monad m => Int -> m a -> Producer m a
- sourceFile :: (MonadResource m, IOData a) => FilePath -> Producer m a
- sourceHandle :: (MonadIO m, IOData a) => Handle -> Producer m a
- sourceIOHandle :: (MonadResource m, IOData a) => IO Handle -> Producer m a
- stdinC :: (MonadIO m, IOData a) => Producer m a
- 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
- sourceDirectory :: MonadResource m => FilePath -> Producer m FilePath
- sourceDirectoryDeep :: MonadResource m => Bool -> FilePath -> Producer m FilePath
- dropC :: Monad m => Int -> Consumer a m ()
- dropCE :: (Monad m, IsSequence seq) => Index seq -> Consumer seq m ()
- dropWhileC :: Monad m => (a -> Bool) -> Consumer a m ()
- dropWhileCE :: (Monad m, IsSequence seq) => (Element seq -> Bool) -> Consumer seq m ()
- foldC :: (Monad m, Monoid a) => Consumer a m a
- foldCE :: (Monad m, MonoFoldable mono, Monoid (Element mono)) => Consumer mono m (Element mono)
- foldlC :: Monad m => (a -> b -> a) -> a -> Consumer b m a
- foldlCE :: (Monad m, MonoFoldable mono) => (a -> Element mono -> a) -> a -> Consumer mono m a
- foldMapC :: (Monad m, Monoid b) => (a -> b) -> Consumer a m b
- foldMapCE :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> w) -> Consumer mono m w
- allC :: Monad m => (a -> Bool) -> Consumer a m Bool
- allCE :: (Monad m, MonoFoldable mono) => (Element mono -> Bool) -> Consumer mono m Bool
- anyC :: Monad m => (a -> Bool) -> Consumer a m Bool
- anyCE :: (Monad m, MonoFoldable mono) => (Element mono -> Bool) -> Consumer mono m Bool
- andC :: Monad m => Consumer Bool m Bool
- andCE :: (Monad m, MonoFoldable mono, Element mono ~ Bool) => Consumer mono m Bool
- orC :: Monad m => Consumer Bool m Bool
- orCE :: (Monad m, MonoFoldable mono, Element mono ~ Bool) => Consumer mono m Bool
- elemC :: (Monad m, Eq a) => a -> Consumer a m Bool
- elemCE :: (Monad m, EqSequence seq) => Element seq -> Consumer seq m Bool
- notElemC :: (Monad m, Eq a) => a -> Consumer a m Bool
- notElemCE :: (Monad m, EqSequence 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))
- headCE :: (Monad m, IsSequence seq) => Consumer seq m (Maybe (Element seq))
- peekC :: Monad m => Consumer a m (Maybe a)
- peekCE :: (Monad m, MonoFoldable mono) => Consumer mono m (Maybe (Element mono))
- lastC :: Monad m => Consumer a m (Maybe a)
- lastCE :: (Monad m, IsSequence seq) => Consumer seq m (Maybe (Element seq))
- lengthC :: (Monad m, Num len) => Consumer a m len
- lengthCE :: (Monad m, Num len, MonoFoldable mono) => Consumer mono m len
- lengthIfC :: (Monad m, Num len) => (a -> Bool) -> Consumer a m len
- lengthIfCE :: (Monad m, Num len, MonoFoldable mono) => (Element mono -> Bool) -> Consumer mono m len
- maximumC :: (Monad m, Ord a) => Consumer a m (Maybe a)
- maximumCE :: (Monad m, OrdSequence seq) => Consumer seq m (Maybe (Element seq))
- minimumC :: (Monad m, Ord a) => Consumer a m (Maybe a)
- minimumCE :: (Monad m, OrdSequence seq) => Consumer seq m (Maybe (Element seq))
- nullC :: Monad m => Consumer a m Bool
- nullCE :: (Monad m, MonoFoldable mono) => Consumer mono m Bool
- sumC :: (Monad m, Num a) => Consumer a m a
- sumCE :: (Monad m, MonoFoldable mono, Num (Element mono)) => Consumer mono m (Element mono)
- productC :: (Monad m, Num a) => Consumer a m a
- productCE :: (Monad m, MonoFoldable mono, Num (Element mono)) => Consumer mono m (Element mono)
- findC :: Monad m => (a -> Bool) -> Consumer a m (Maybe a)
- mapM_C :: Monad m => (a -> m ()) -> Consumer a m ()
- mapM_CE :: (Monad m, MonoFoldable mono) => (Element mono -> m ()) -> Consumer mono m ()
- foldMC :: Monad m => (a -> b -> m a) -> a -> Consumer b m a
- foldMCE :: (Monad m, MonoFoldable mono) => (a -> Element mono -> m a) -> a -> Consumer mono m a
- foldMapMC :: (Monad m, Monoid w) => (a -> m w) -> Consumer a m w
- foldMapMCE :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> m w) -> Consumer mono m w
- sinkFile :: (MonadResource m, IOData a) => FilePath -> Consumer a m ()
- sinkHandle :: (MonadIO m, IOData a) => Handle -> Consumer a m ()
- sinkIOHandle :: (MonadResource m, IOData a) => IO Handle -> Consumer a m ()
- printC :: (Show a, MonadIO m) => Consumer a m ()
- stdoutC :: (MonadIO m, IOData a) => Consumer a m ()
- stderrC :: (MonadIO m, IOData a) => Consumer a m ()
- mapC :: Monad m => (a -> b) -> Conduit a m b
- mapCE :: (Monad m, Functor f) => (a -> b) -> Conduit (f a) m (f b)
- omapCE :: (Monad m, MonoFunctor mono) => (Element mono -> Element mono) -> Conduit mono m mono
- concatMapC :: (Monad m, MonoFoldable mono) => (a -> mono) -> Conduit a m (Element mono)
- concatMapCE :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> w) -> Conduit mono m w
- takeC :: Monad m => Int -> Conduit a m a
- takeCE :: (Monad m, IsSequence seq) => Index seq -> Conduit seq m seq
- takeWhileC :: Monad m => (a -> Bool) -> Conduit a m a
- takeWhileCE :: (Monad m, IsSequence seq) => (Element seq -> Bool) -> Conduit seq m seq
- takeExactlyC :: Monad m => Int -> ConduitM a b m r -> ConduitM a b m r
- takeExactlyCE :: (Monad m, IsSequence a) => Index a -> ConduitM a b m r -> ConduitM a b m r
- concatC :: (Monad m, MonoFoldable mono) => Conduit mono m (Element mono)
- filterC :: Monad m => (a -> Bool) -> Conduit a m a
- filterCE :: (IsSequence seq, Monad m) => (Element seq -> Bool) -> Conduit seq m seq
- mapWhileC :: Monad m => (a -> Maybe b) -> Conduit a m b
- conduitVector :: (MonadBase base m, Vector v a, PrimMonad base) => Int -> Conduit a m (v a)
- scanlC :: Monad m => (a -> b -> a) -> a -> Conduit b m a
- concatMapAccumC :: Monad m => (a -> accum -> (accum, [b])) -> accum -> Conduit a m b
- intersperseC :: Monad m => a -> Conduit a m a
- slidingWindowC :: (Monad m, IsSequence seq, Element seq ~ a) => Int -> Conduit a m seq
- encodeBase64C :: Monad m => Conduit ByteString m ByteString
- decodeBase64C :: Monad m => Conduit ByteString m ByteString
- encodeBase64URLC :: Monad m => Conduit ByteString m ByteString
- decodeBase64URLC :: Monad m => Conduit ByteString m ByteString
- encodeBase16C :: Monad m => Conduit ByteString m ByteString
- decodeBase16C :: Monad m => Conduit ByteString m ByteString
- mapMC :: Monad m => (a -> m b) -> Conduit a m b
- mapMCE :: (Monad m, Traversable f) => (a -> m b) -> Conduit (f a) m (f b)
- omapMCE :: (Monad m, MonoTraversable mono) => (Element mono -> m (Element mono)) -> Conduit mono m mono
- concatMapMC :: (Monad m, MonoFoldable mono) => (a -> m mono) -> Conduit a m (Element mono)
- filterMC :: Monad m => (a -> m Bool) -> Conduit a m a
- filterMCE :: (Monad m, IsSequence seq) => (Element seq -> m Bool) -> Conduit seq m seq
- iterMC :: Monad m => (a -> m ()) -> Conduit a m a
- scanlMC :: Monad m => (a -> b -> m a) -> a -> Conduit b m a
- concatMapAccumMC :: Monad m => (a -> accum -> m (accum, [b])) -> accum -> Conduit a m b
- encodeUtf8C :: (Monad m, Utf8 text binary) => Conduit text m binary
- decodeUtf8C :: MonadThrow m => Conduit ByteString m Text
- decodeUtf8LenientC :: MonadThrow m => Conduit ByteString m Text
- lineC :: (Monad m, IsSequence seq, Element seq ~ Char) => ConduitM seq o m r -> ConduitM seq o m r
- lineAsciiC :: (Monad m, IsSequence seq, Element seq ~ Word8) => ConduitM seq o m r -> ConduitM seq o m r
- unlinesC :: (Monad m, IsSequence seq, Element seq ~ Char) => Conduit seq m seq
- unlinesAsciiC :: (Monad m, IsSequence seq, Element seq ~ Word8) => Conduit seq m seq
- linesUnboundedC :: (Monad m, IsSequence seq, Element seq ~ Char) => Conduit seq m seq
- linesUnboundedAsciiC :: (Monad m, IsSequence seq, Element seq ~ Word8) => Conduit seq m seq
- vectorBuilderC :: (PrimMonad base, MonadBase base m, Vector v e, MonadBase base n) => Int -> ((e -> n ()) -> Sink i m r) -> ConduitM i (v e) m r
- class Monad m => MonadIO m where
- class MonadTrans t where
- class (Applicative b, Applicative m, Monad b, Monad m) => MonadBase b m | m -> b where
- liftBase :: b α -> m α
- class Monad m => MonadThrow m where
- class MonadBase b m => MonadBaseControl b m | m -> b
- class (MonadThrow m, MonadIO m, Applicative m, MonadBase IO m) => MonadResource m
- data ResourceT m a :: (* -> *) -> * -> *
- runResourceT :: MonadBaseControl IO m => ResourceT m a -> m a
- module Data.Acquire
- withAcquire :: MonadBaseControl IO m => Acquire a -> (a -> m b) -> m b
- newtype Identity a :: * -> * = Identity {
- runIdentity :: a
Core conduit library
module Data.Conduit
module Data.Conduit.Lift
Commonly used combinators
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.
Since 1.0.0
unfoldC :: Monad m => (b -> Maybe (a, b)) -> b -> Producer m a Source
Generate a producer from a seed value.
Since 1.0.0
enumFromToC :: (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.
Since 1.0.0
iterateC :: Monad m => (a -> a) -> a -> Producer m a Source
Produces an infinite stream of repeated applications of f to x.
Since 1.0.0
repeatC :: Monad m => a -> Producer m a Source
Produce an infinite stream consisting entirely of the given value.
Since 1.0.0
replicateC :: Monad m => Int -> a -> Producer m a Source
Produce a finite stream consisting of n copies of the given value.
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
.
Since 1.0.0
Monadic
repeatMC :: Monad m => m a -> Producer m a Source
Repeatedly run the given action and yield all values it produces.
Since 1.0.0
repeatWhileMC :: 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
.
Since 1.0.0
replicateMC :: Monad m => Int -> m a -> Producer m a Source
Perform the given action n times, yielding each result.
Since 1.0.0
I/O
sourceFile :: (MonadResource m, IOData a) => FilePath -> Producer m a Source
Read all data from the given file.
This function automatically opens and closes the file handle, and ensures
exception safety via MonadResource. It works for all instances of
IOData,
including
ByteString and
Text@.
Since 1.0.0
sourceHandle :: (MonadIO m, IOData a) => Handle -> Producer m a Source
Read all data from the given Handle
.
Does not close the Handle
at any point.
Since 1.0.0
sourceIOHandle :: (MonadResource m, IOData a) => IO Handle -> Producer m a Source
Open a Handle
using the given function and stream data from it.
Automatically closes the file at completion.
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.
Since 1.0.0
Create a stream of random values of length n, seeding from the system random number.
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.
Since 1.0.0
Create a stream of random values of length n, seeding from the system random number.
Since 1.0.0
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
dropC :: Monad m => Int -> Consumer a m () Source
Ignore a certain number of values in the stream.
Since 1.0.0
dropCE :: (Monad m, IsSequence seq) => Index seq -> Consumer seq m () Source
Drop a certain number of elements from a chunked stream.
Since 1.0.0
dropWhileC :: Monad m => (a -> Bool) -> Consumer a m () Source
Drop all values which match the given predicate.
Since 1.0.0
dropWhileCE :: (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
foldC :: (Monad m, Monoid a) => Consumer a m a Source
Monoidally combine all values in the stream.
Since 1.0.0
foldCE :: (Monad m, MonoFoldable mono, Monoid (Element mono)) => Consumer mono m (Element mono) Source
Monoidally combine all elements in the chunked stream.
Since 1.0.0
foldlCE :: (Monad m, MonoFoldable mono) => (a -> Element mono -> a) -> a -> Consumer mono m a Source
A strict left fold on a chunked stream.
Since 1.0.0
foldMapC :: (Monad m, Monoid b) => (a -> b) -> Consumer a m b Source
Apply the provided mapping function and monoidal combine all values.
Since 1.0.0
foldMapCE :: (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.
Since 1.0.0
allC :: 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.
Since 1.0.0
allCE :: (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.
Since 1.0.0
anyC :: 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.
Since 1.0.0
anyCE :: (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.
Since 1.0.0
andC :: Monad m => Consumer Bool m Bool Source
Are all values in the stream True?
Consumption stops once the first False is encountered.
Since 1.0.0
andCE :: (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.
Since 1.0.0
orC :: Monad m => Consumer Bool m Bool Source
Are any values in the stream True?
Consumption stops once the first True is encountered.
Since 1.0.0
orCE :: (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.
Since 1.0.0
elemC :: (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.
Since 1.0.0
elemCE :: (Monad m, EqSequence 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.
Since 1.0.0
notElemC :: (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.
Since 1.0.0
notElemCE :: (Monad m, EqSequence 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.
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.
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.
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.
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.
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
.
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.
Since 1.0.0
sinkNull :: Monad m => Consumer a m () Source
Consume and discard all remaining values in the stream.
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
headCE :: (Monad m, IsSequence seq) => Consumer seq m (Maybe (Element seq)) Source
Get the next element in the chunked stream.
Since 1.0.0
peekC :: Monad m => Consumer a m (Maybe a) Source
View the next value in the stream without consuming it.
Since 1.0.0
peekCE :: (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
lastC :: Monad m => Consumer a m (Maybe a) Source
Retrieve the last value in the stream, if present.
Since 1.0.0
lastCE :: (Monad m, IsSequence seq) => Consumer seq m (Maybe (Element seq)) Source
Retrieve the last element in the chunked stream, if present.
Since 1.0.0
lengthC :: (Monad m, Num len) => Consumer a m len Source
Count how many values are in the stream.
Since 1.0.0
lengthCE :: (Monad m, Num len, MonoFoldable mono) => Consumer mono m len Source
Count how many elements are in the chunked stream.
Since 1.0.0
lengthIfC :: (Monad m, Num len) => (a -> Bool) -> Consumer a m len Source
Count how many values in the stream pass the given predicate.
Since 1.0.0
lengthIfCE :: (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.
Since 1.0.0
maximumC :: (Monad m, Ord a) => Consumer a m (Maybe a) Source
Get the largest value in the stream, if present.
Since 1.0.0
maximumCE :: (Monad m, OrdSequence seq) => Consumer seq m (Maybe (Element seq)) Source
Get the largest element in the chunked stream, if present.
Since 1.0.0
minimumC :: (Monad m, Ord a) => Consumer a m (Maybe a) Source
Get the smallest value in the stream, if present.
Since 1.0.0
minimumCE :: (Monad m, OrdSequence seq) => Consumer seq m (Maybe (Element seq)) Source
Get the smallest element in the chunked stream, if present.
Since 1.0.0
nullC :: 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
nullCE :: (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
sumC :: (Monad m, Num a) => Consumer a m a Source
Get the sum of all values in the stream.
Since 1.0.0
sumCE :: (Monad m, MonoFoldable mono, Num (Element mono)) => Consumer mono m (Element mono) Source
Get the sum of all elements in the chunked stream.
Since 1.0.0
productC :: (Monad m, Num a) => Consumer a m a Source
Get the product of all values in the stream.
Since 1.0.0
productCE :: (Monad m, MonoFoldable mono, Num (Element mono)) => Consumer mono m (Element mono) Source
Get the product of all elements in the chunked stream.
Since 1.0.0
findC :: Monad m => (a -> Bool) -> Consumer a m (Maybe a) Source
Find the first matching value.
Since 1.0.0
Monadic
mapM_C :: Monad m => (a -> m ()) -> Consumer a m () Source
Apply the action to all values in the stream.
Since 1.0.0
mapM_CE :: (Monad m, MonoFoldable mono) => (Element mono -> m ()) -> Consumer mono m () Source
Apply the action to all elements in the chunked stream.
Since 1.0.0
foldMC :: Monad m => (a -> b -> m a) -> a -> Consumer b m a Source
A monadic strict left fold.
Since 1.0.0
foldMCE :: (Monad m, MonoFoldable mono) => (a -> Element mono -> m a) -> a -> Consumer mono m a Source
A monadic strict left fold on a chunked stream.
Since 1.0.0
foldMapMC :: (Monad m, Monoid w) => (a -> m w) -> Consumer a m w Source
Apply the provided monadic mapping function and monoidal combine all values.
Since 1.0.0
foldMapMCE :: (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.
Since 1.0.0
I/O
sinkFile :: (MonadResource m, IOData a) => FilePath -> Consumer a m () Source
Write all data to the given file.
This function automatically opens and closes the file handle, and ensures
exception safety via MonadResource. It works for all instances of
IOData,
including
ByteString and
Text@.
Since 1.0.0
sinkHandle :: (MonadIO m, IOData a) => Handle -> Consumer a m () Source
Write all data to the given Handle
.
Does not close the Handle
at any point.
Since 1.0.0
sinkIOHandle :: (MonadResource m, IOData a) => IO Handle -> Consumer a m () Source
Open a Handle
using the given function and stream data to it.
Automatically closes the file at completion.
Since 1.0.0
printC :: (Show a, MonadIO m) => Consumer a m () Source
Print all incoming values to stdout.
Since 1.0.0
Transformers
Pure
mapC :: Monad m => (a -> b) -> Conduit a m b Source
Apply a transformation to all values in a stream.
Since 1.0.0
mapCE :: (Monad m, Functor f) => (a -> b) -> Conduit (f a) m (f b) Source
Apply a transformation to all elements in a chunked stream.
Since 1.0.0
omapCE :: (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
.
Since 1.0.0
concatMapC :: (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.
Since 1.0.0
concatMapCE :: (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.
Since 1.0.0
takeC :: 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
.
Since 1.0.0
takeCE :: (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
takeWhileC :: 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
takeWhileCE :: (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
takeExactlyC :: 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
takeExactlyCE :: (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
concatC :: (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.
Since 1.0.0
filterC :: Monad m => (a -> Bool) -> Conduit a m a Source
Keep only values in the stream passing a given predicate.
Since 1.0.0
filterCE :: (IsSequence seq, Monad m) => (Element seq -> Bool) -> Conduit seq m seq Source
Keep only elements in the chunked stream passing a given predicate.
Since 1.0.0
mapWhileC :: 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
scanlC :: Monad m => (a -> b -> a) -> a -> Conduit b m a Source
Analog of scanl
for lists.
Since 1.0.6
concatMapAccumC :: Monad m => (a -> accum -> (accum, [b])) -> accum -> Conduit a m b Source
concatMap
with an accumulator.
Since 1.0.0
intersperseC :: Monad m => a -> Conduit a m a Source
Insert the given value between each two values in the stream.
Since 1.0.0
slidingWindowC :: (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.
Since 1.0.0
Binary base encoding
encodeBase64C :: Monad m => Conduit ByteString m ByteString Source
Apply base64-encoding to the stream.
Since 1.0.0
decodeBase64C :: 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
encodeBase64URLC :: Monad m => Conduit ByteString m ByteString Source
Apply URL-encoding to the stream.
Since 1.0.0
decodeBase64URLC :: 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
encodeBase16C :: Monad m => Conduit ByteString m ByteString Source
Apply base16-encoding to the stream.
Since 1.0.0
decodeBase16C :: 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
mapMC :: 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 1.0.0
mapMCE :: (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.
Since 1.0.0
omapMCE :: (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
.
Since 1.0.0
concatMapMC :: (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.
Since 1.0.0
filterMC :: Monad m => (a -> m Bool) -> Conduit a m a Source
Keep only values in the stream passing a given monadic predicate.
Since 1.0.0
filterMCE :: (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.
Since 1.0.0
iterMC :: 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 1.0.0
scanlMC :: Monad m => (a -> b -> m a) -> a -> Conduit b m a Source
Analog of scanl
for lists, monadic.
Since 1.0.6
concatMapAccumMC :: Monad m => (a -> accum -> m (accum, [b])) -> accum -> Conduit a m b Source
concatMapM
with an accumulator.
Since 1.0.0
Textual
encodeUtf8C :: (Monad m, Utf8 text binary) => Conduit text m binary Source
Encode a stream of text as UTF8.
Since 1.0.0
decodeUtf8C :: MonadThrow m => Conduit ByteString m Text Source
Decode a stream of binary data as UTF8.
Since 1.0.0
decodeUtf8LenientC :: 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
lineC :: (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
lineAsciiC :: (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
unlinesC :: (Monad m, IsSequence seq, Element seq ~ Char) => Conduit seq m seq Source
Insert a newline character after each incoming chunk of data.
Since 1.0.0
unlinesAsciiC :: (Monad m, IsSequence seq, Element seq ~ Word8) => Conduit seq m seq Source
Same as unlines
, but operates on ASCII/binary data.
Since 1.0.0
linesUnboundedC :: (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 unknownuntrusted input, this function is unsafe/, since it would allow an attacker to form lines of massive length and exhaust memory.
Since 1.0.0
linesUnboundedAsciiC :: (Monad m, IsSequence seq, Element seq ~ Word8) => Conduit seq m seq Source
Same as linesUnbounded
, but for ASCII/binary data.
Since 1.0.0
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
Monadic lifting
class Monad m => MonadIO m where
Monads in which IO
computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO
monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
is a transformer of monads:
MonadIO IO | |
MonadIO Acquire | |
MonadIO m => MonadIO (IdentityT m) | |
MonadIO m => MonadIO (MaybeT m) | |
MonadIO m => MonadIO (ListT m) | |
MonadIO m => MonadIO (ResourceT m) | |
(Monoid w, MonadIO m) => MonadIO (WriterT w m) | |
(Monoid w, MonadIO m) => MonadIO (WriterT w m) | |
MonadIO m => MonadIO (StateT s m) | |
MonadIO m => MonadIO (StateT s m) | |
MonadIO m => MonadIO (ReaderT r m) | |
(Error e, MonadIO m) => MonadIO (ErrorT e m) | |
MonadIO m => MonadIO (ContT r m) | |
MonadIO m => MonadIO (ExceptT e m) | |
MonadIO m => MonadIO (ConduitM i o m) | |
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) | |
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) | |
MonadIO m => MonadIO (Pipe l i o u m) |
class MonadTrans t where
The class of monad transformers. Instances should satisfy the
following laws, which state that lift
is a monad transformation:
MonadTrans IdentityT | |
MonadTrans MaybeT | |
MonadTrans ListT | |
MonadTrans ResourceT | |
Monoid w => MonadTrans (WriterT w) | |
Monoid w => MonadTrans (WriterT w) | |
MonadTrans (StateT s) | |
MonadTrans (StateT s) | |
MonadTrans (ReaderT r) | |
Error e => MonadTrans (ErrorT e) | |
MonadTrans (ContT r) | |
MonadTrans (ExceptT e) | |
MonadTrans (ConduitM i o) | |
Monoid w => MonadTrans (RWST r w s) | |
Monoid w => MonadTrans (RWST r w s) | |
MonadTrans (Pipe l i o u) |
class (Applicative b, Applicative m, Monad b, Monad m) => MonadBase b m | m -> b where
liftBase :: b α -> m α
Lift a computation from the base monad
MonadBase [] [] | |
MonadBase IO IO | |
MonadBase IO Acquire | |
MonadBase Maybe Maybe | |
MonadBase STM STM | |
MonadBase Identity Identity | |
MonadBase b m => MonadBase b (ResourceT m) | |
MonadBase b m => MonadBase b (MaybeT m) | |
MonadBase b m => MonadBase b (ListT m) | |
MonadBase b m => MonadBase b (IdentityT m) | |
(Monoid w, MonadBase b m) => MonadBase b (WriterT w m) | |
(Monoid w, MonadBase b m) => MonadBase b (WriterT w m) | |
MonadBase b m => MonadBase b (StateT s m) | |
MonadBase b m => MonadBase b (StateT s m) | |
MonadBase b m => MonadBase b (ReaderT r m) | |
MonadBase b m => MonadBase b (ExceptT e m) | |
(Error e, MonadBase b m) => MonadBase b (ErrorT e m) | |
MonadBase b m => MonadBase b (ContT r m) | |
MonadBase base m => MonadBase base (ConduitM i o m) | |
(Monoid w, MonadBase b m) => MonadBase b (RWST r w s m) | |
(Monoid w, MonadBase b m) => MonadBase b (RWST r w s m) | |
MonadBase base m => MonadBase base (Pipe l i o u m) | |
MonadBase ((->) r) ((->) r) | |
MonadBase (Either e) (Either e) | |
MonadBase (ST s) (ST s) | |
MonadBase (ST s) (ST s) |
class Monad m => MonadThrow m where
A class for monads in which exceptions may be thrown.
Instances should obey the following law:
throwM e >> x = throwM e
In other words, throwing an exception short-circuits the rest of the monadic computation.
throwM :: Exception e => e -> m a
Throw an exception. Note that this throws when this action is run in
the monad m
, not when it is applied. It is a generalization of
Control.Exception's throwIO
.
Should satisfy the law:
throwM e >> f = throwM e
MonadThrow [] | |
MonadThrow IO | |
MonadThrow Maybe | |
(~) * e SomeException => MonadThrow (Either e) | |
MonadThrow m => MonadThrow (IdentityT m) | |
MonadThrow m => MonadThrow (MaybeT m) | Throws exceptions into the base monad. |
MonadThrow m => MonadThrow (ListT m) | |
MonadThrow m => MonadThrow (ResourceT m) | |
(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) | |
(MonadThrow m, Monoid w) => MonadThrow (WriterT w m) | |
MonadThrow m => MonadThrow (StateT s m) | |
MonadThrow m => MonadThrow (StateT s m) | |
MonadThrow m => MonadThrow (ReaderT r m) | |
(Error e, MonadThrow m) => MonadThrow (ErrorT e m) | Throws exceptions into the base monad. |
MonadThrow m => MonadThrow (ContT r m) | |
MonadThrow m => MonadThrow (ExceptT e m) | Throws exceptions into the base monad. |
MonadThrow m => MonadThrow (ConduitM i o m) | |
(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) | |
(MonadThrow m, Monoid w) => MonadThrow (RWST r w s m) | |
MonadThrow m => MonadThrow (Pipe l i o u m) |
class MonadBase b m => MonadBaseControl b m | m -> b
ResourceT
class (MonadThrow m, MonadIO m, Applicative m, MonadBase IO m) => MonadResource m
A Monad
which allows for safe resource allocation. In theory, any monad
transformer stack included a ResourceT
can be an instance of
MonadResource
.
Note: runResourceT
has a requirement for a MonadBaseControl IO m
monad,
which allows control operations to be lifted. A MonadResource
does not
have this requirement. This means that transformers such as ContT
can be
an instance of MonadResource
. However, the ContT
wrapper will need to be
unwrapped before calling runResourceT
.
Since 0.3.0
MonadResource m => MonadResource (IdentityT m) | |
MonadResource m => MonadResource (MaybeT m) | |
MonadResource m => MonadResource (ListT m) | |
(MonadThrow m, MonadBase IO m, MonadIO m, Applicative m) => MonadResource (ResourceT m) | |
(Monoid w, MonadResource m) => MonadResource (WriterT w m) | |
(Monoid w, MonadResource m) => MonadResource (WriterT w m) | |
MonadResource m => MonadResource (StateT s m) | |
MonadResource m => MonadResource (StateT s m) | |
MonadResource m => MonadResource (ReaderT r m) | |
(Error e, MonadResource m) => MonadResource (ErrorT e m) | |
MonadResource m => MonadResource (ContT r m) | |
MonadResource m => MonadResource (ConduitM i o m) | |
(Monoid w, MonadResource m) => MonadResource (RWST r w s m) | |
(Monoid w, MonadResource m) => MonadResource (RWST r w s m) | |
MonadResource m => MonadResource (Pipe l i o u m) |
data ResourceT m a :: (* -> *) -> * -> *
The Resource transformer. This transformer keeps track of all registered
actions, and calls them upon exit (via runResourceT
). Actions may be
registered via register
, or resources may be allocated atomically via
allocate
. allocate
corresponds closely to bracket
.
Releasing may be performed before exit via the release
function. This is a
highly recommended optimization, as it will ensure that scarce resources are
freed early. Note that calling release
will deregister the action, so that
a release action will only ever be called once.
Since 0.3.0
MFunctor ResourceT | Since 0.4.7 |
MMonad ResourceT | Since 0.4.7 |
MonadTrans ResourceT | |
MonadTransControl ResourceT | |
MonadRWS r w s m => MonadRWS r w s (ResourceT m) | |
MonadBaseControl b m => MonadBaseControl b (ResourceT m) | |
MonadBase b m => MonadBase b (ResourceT m) | |
MonadError e m => MonadError e (ResourceT m) | |
MonadReader r m => MonadReader r (ResourceT m) | |
MonadState s m => MonadState s (ResourceT m) | |
MonadWriter w m => MonadWriter w (ResourceT m) | |
Monad m => Monad (ResourceT m) | |
Functor m => Functor (ResourceT m) | |
Applicative m => Applicative (ResourceT m) | |
MonadThrow m => MonadThrow (ResourceT m) | |
MonadCatch m => MonadCatch (ResourceT m) | |
MonadMask m => MonadMask (ResourceT m) | |
MonadIO m => MonadIO (ResourceT m) | |
MonadCont m => MonadCont (ResourceT m) | |
(MonadThrow m, MonadBase IO m, MonadIO m, Applicative m) => MonadResource (ResourceT m) | |
Typeable ((* -> *) -> * -> *) ResourceT | |
data StT ResourceT = StReader {
| |
data StM (ResourceT m) = StMT (StM m a) |
runResourceT :: MonadBaseControl IO m => ResourceT m a -> m a
Unwrap a ResourceT
transformer, and call all registered release actions.
Note that there is some reference counting involved due to resourceForkIO
.
If multiple threads are sharing the same collection of resources, only the
last call to runResourceT
will deallocate the resources.
Since 0.3.0
Acquire
module Data.Acquire
withAcquire :: MonadBaseControl IO m => Acquire a -> (a -> m b) -> m b Source
Pure pipelines
newtype Identity a :: * -> *
Identity functor and monad. (a non-strict monad)
Identity | |
|
Monad Identity | |
Functor Identity | |
MonadFix Identity | |
Applicative Identity | |
Foldable Identity | |
Traversable Identity | |
Comonad Identity | |
ComonadApply Identity | |
Keyed Identity | |
Zip Identity | |
ZipWithKey Identity | |
Indexable Identity | |
Lookup Identity | |
Adjustable Identity | |
FoldableWithKey Identity | |
FoldableWithKey1 Identity | |
TraversableWithKey Identity | |
TraversableWithKey1 Identity | |
Apply Identity | |
Bind Identity | |
Eq1 Identity | |
Ord1 Identity | |
Read1 Identity | |
Show1 Identity | |
MonadBaseControl Identity Identity | |
MonadBase Identity Identity | |
Eq a => Eq (Identity a) | |
Ord a => Ord (Identity a) | |
Read a => Read (Identity a) | |
Show a => Show (Identity a) | |
MonoFunctor (Identity a) | |
MonoFoldable (Identity a) | |
Ord a => MonoFoldableOrd (Identity a) | |
MonoTraversable (Identity a) | |
MonoPointed (Identity a) | |
type Key Identity = () | |
data StM Identity = StI a | |
type Element (Identity a) = a |