Safe Haskell | Safe-Infered |
---|
Data.Conduit
Contents
Description
The main module, exporting types, utility functions, and fuse and connect operators.
There are three main types in this package: Source
(data producer), Sink
(data consumer), and Conduit
(data transformer). All three are in fact
type synonyms for the underlying Pipe
data type.
The typical approach to use of this package is:
- Compose multiple
Sink
s together using itsMonad
instance. - Left-fuse
Source
s andConduit
s into newConduit
s. - Right-fuse
Conduit
s andSink
s into newSink
s. - Middle-fuse two
Conduit
s into a newConduit
. - Connect a
Source
to aSink
to obtain a result.
- data Pipe i o m r
- type Source m a = Pipe Void a m ()
- type Conduit i m o = Pipe i o m ()
- type Sink i m r = Pipe i Void m r
- ($$) :: Monad m => Source m a -> Sink a m b -> m b
- ($$+) :: Monad m => Source m a -> Sink a m b -> m (Source m a, b)
- ($=) :: Monad m => Source m a -> Conduit a m b -> Source m b
- (=$) :: Monad m => Conduit a m b -> Sink b m c -> Sink a m c
- (=$=) :: Monad m => Pipe a b m () -> Pipe b c m r -> Pipe a c m r
- await :: Pipe i o m (Maybe i)
- yield :: Monad m => o -> Pipe i o m ()
- hasInput :: Pipe i o m Bool
- transPipe :: Monad m => (forall a. m a -> n a) -> Pipe i o m r -> Pipe i o n r
- mapOutput :: Monad m => (o1 -> o2) -> Pipe i o1 m r -> Pipe i o2 m r
- sourceState :: Monad m => state -> (state -> m (SourceStateResult state output)) -> Source m output
- sourceStateIO :: MonadResource m => IO state -> (state -> IO ()) -> (state -> m (SourceStateResult state output)) -> Source m output
- data SourceStateResult state output
- = StateOpen state output
- | StateClosed
- sourceIO :: MonadResource m => IO state -> (state -> IO ()) -> (state -> m (SourceIOResult output)) -> Source m output
- data SourceIOResult output
- sinkState :: Monad m => state -> (state -> input -> m (SinkStateResult state input output)) -> (state -> m output) -> Sink input m output
- data SinkStateResult state input output
- = StateDone (Maybe input) output
- | StateProcessing state
- sinkIO :: MonadResource m => IO state -> (state -> IO ()) -> (state -> input -> m (SinkIOResult input output)) -> (state -> m output) -> Sink input m output
- data SinkIOResult input output
- = IODone (Maybe input) output
- | IOProcessing
- haveMore :: Conduit a m b -> m () -> [b] -> Conduit a m b
- conduitState :: Monad m => state -> (state -> input -> m (ConduitStateResult state input output)) -> (state -> m [output]) -> Conduit input m output
- data ConduitStateResult state input output
- = StateFinished (Maybe input) [output]
- | StateProducing state [output]
- conduitIO :: MonadResource m => IO state -> (state -> IO ()) -> (state -> input -> m (ConduitIOResult input output)) -> (state -> m [output]) -> Conduit input m output
- data ConduitIOResult input output
- = IOFinished (Maybe input) [output]
- | IOProducing [output]
- type SequencedSink state input m output = state -> Sink input m (SequencedSinkResponse state input m output)
- sequenceSink :: Monad m => state -> SequencedSink state input m output -> Conduit input m output
- sequence :: Monad m => Sink input m output -> Conduit input m output
- data SequencedSinkResponse state input m output
- = Emit state [output]
- | Stop
- | StartConduit (Conduit input m output)
- data Flush a
- data ResourceT m a
- class (MonadThrow m, MonadUnsafeIO m, MonadIO m, Applicative m) => MonadResource m
- class Monad m => MonadThrow m where
- monadThrow :: Exception e => e -> m a
- class Monad m => MonadUnsafeIO m where
- unsafeLiftIO :: IO a -> m a
- runResourceT :: MonadBaseControl IO m => ResourceT m a -> m a
Types
The underlying datatype for all the types in this package. In has four type parameters:
- i is the type of values for this
Pipe
's input stream. - o is the type of values for this
Pipe
's output stream. - m is the underlying monad.
- r is the result type.
Note that o and r are inherently different. o is the type of the
stream of values this Pipe
will produce and send downstream. r is the
final output of this Pipe
.
Pipe
s can be composed via the pipe
function. To do so, the output type
of the left pipe much match the input type of the left pipe, and the result
type of the left pipe must be unit ()
. This is due to the fact that any
result produced by the left pipe must be discarded in favor of the result of
the right pipe.
Since 0.4.0
Constructors
HaveOutput (Pipe i o m r) (Finalize m r) o | Provide new output to be sent downstream. This constructor has three
fields: the next |
NeedInput (i -> Pipe i o m r) (Pipe i o m r) | Request more input from upstream. The first field takes a new input
value and provides a new |
Done (Maybe i) r | Processing with this |
PipeM (m (Pipe i o m r)) (Finalize m r) | Require running of a monadic action to get the next |
type Source m a = Pipe Void a m ()Source
A Pipe
which provides a stream of output values, without consuming any
input. The input parameter is set to Void
to indicate that this Pipe
takes no input. A Source
is not used to produce a final result, and thus
the result parameter is set to ()
.
Since 0.4.0
type Conduit i m o = Pipe i o m ()Source
A Pipe
which consumes a stream of input values and produces a stream of
output values. It does not produce a result value, and thus the result
parameter is set to ()
.
Since 0.4.0
type Sink i m r = Pipe i Void m rSource
A Pipe
which consumes a stream of input values and produces a final
result. It cannot produce any output values, and thus the output parameter
is set to Void
. In other words, it is impossible to create a HaveOutput
constructor for a Sink
.
Since 0.4.0
Connect/fuse operators
($$) :: Monad m => Source m a -> Sink a m b -> m bSource
The connect operator, which pulls data from a source and pushes to a sink. There are two ways this process can terminate:
- If the
Sink
is aDone
constructor, theSource
is closed. - If the
Source
is aDone
constructor, theSink
is closed.
In other words, both the Source
and Sink
will always be closed. If you
would like to keep the Source
open to be used for another operations, use
the connect-and-resume operators $$+
.
Since 0.4.0
($$+) :: Monad m => Source m a -> Sink a m b -> m (Source m a, b)Source
The connect-and-resume operator. Does not close the Source
, but instead
returns it to be used again. This allows a Source
to be used incrementally
in a large program, without forcing the entire program to live in the Sink
monad.
Mnemonic: connect + do more.
Since 0.4.0
($=) :: Monad m => Source m a -> Conduit a m b -> Source m bSource
Left fuse, combining a source and a conduit together into a new source.
Both the Source
and Conduit
will be closed when the newly-created
Source
is closed.
Leftover data from the Conduit
will be discarded.
Since 0.4.0
(=$) :: Monad m => Conduit a m b -> Sink b m c -> Sink a m cSource
Right fuse, combining a conduit and a sink together into a new sink.
Both the Conduit
and Sink
will be closed when the newly-created Sink
is closed.
Leftover data returned from the Sink
will be discarded.
Since 0.4.0
(=$=) :: Monad m => Pipe a b m () -> Pipe b c m r -> Pipe a c m rSource
Fusion operator, combining two Pipe
s together into a new Pipe
.
Both Pipe
s will be closed when the newly-created Pipe
is closed.
Leftover data returned from the right Pipe
will be discarded.
Note: in previous versions, this operator would only fuse together two
Conduit
s (known as middle fusion). This operator is generalized to work on
all Pipe
s, including Source
s and Sink
s.
Since 0.4.0
Utility functions
General
await :: Pipe i o m (Maybe i)Source
Wait for a single input value from upstream, and remove it from the
stream. Returns Nothing
if no more data is available.
Since 0.4.0
hasInput :: Pipe i o m BoolSource
Check if input is available from upstream. Will not remove the data from the stream.
Since 0.4.0
transPipe :: Monad m => (forall a. m a -> n a) -> Pipe i o m r -> Pipe i o n rSource
Transform the monad that a Pipe
lives in.
Since 0.4.0
Source
Arguments
:: Monad m | |
=> state | Initial state |
-> (state -> m (SourceStateResult state output)) | Pull function |
-> Source m output |
Construct a Source
with some stateful functions. This function addresses
threading the state value for you.
Since 0.3.0
Arguments
:: MonadResource m | |
=> IO state | resource and/or state allocation |
-> (state -> IO ()) | resource and/or state cleanup |
-> (state -> m (SourceStateResult state output)) | Pull function. Note that this need not explicitly perform any cleanup. |
-> Source m output |
A combination of sourceIO
and sourceState
.
Since 0.3.0
data SourceStateResult state output Source
The return value when pulling in the sourceState
function. Either
indicates no more data, or the next value and an updated state.
Since 0.3.0
Constructors
StateOpen state output | |
StateClosed |
Arguments
:: MonadResource m | |
=> IO state | resource and/or state allocation |
-> (state -> IO ()) | resource and/or state cleanup |
-> (state -> m (SourceIOResult output)) | Pull function. Note that this should not perform any cleanup. |
-> Source m output |
Construct a Source
based on some IO actions for alloc/release.
Since 0.3.0
data SourceIOResult output Source
The return value when pulling in the sourceIO
function. Either indicates
no more data, or the next value.
Since 0.3.0
Sink
Arguments
:: Monad m | |
=> state | initial state |
-> (state -> input -> m (SinkStateResult state input output)) | push |
-> (state -> m output) | Close. Note that the state is not returned, as it is not needed. |
-> Sink input m output |
Construct a Sink
with some stateful functions. This function addresses
threading the state value for you.
Since 0.3.0
data SinkStateResult state input output Source
A helper type for sinkState
, indicating the result of being pushed to.
It can either indicate that processing is done, or to continue with the
updated state.
Since 0.3.0
Constructors
StateDone (Maybe input) output | |
StateProcessing state |
Arguments
:: MonadResource m | |
=> IO state | resource and/or state allocation |
-> (state -> IO ()) | resource and/or state cleanup |
-> (state -> input -> m (SinkIOResult input output)) | push |
-> (state -> m output) | close |
-> Sink input m output |
Construct a Sink
. Note that your push and close functions need not
explicitly perform any cleanup.
Since 0.3.0
data SinkIOResult input output Source
A helper type for sinkIO
, indicating the result of being pushed to. It
can either indicate that processing is done, or to continue.
Since 0.3.0
Constructors
IODone (Maybe input) output | |
IOProcessing |
Conduit
Arguments
:: Conduit a m b | The next |
-> m () | A close action for early termination. |
-> [b] | The values to send down the stream. |
-> Conduit a m b |
A helper function for returning a list of values from a Conduit
.
Since 0.3.0
Arguments
:: Monad m | |
=> state | initial state |
-> (state -> input -> m (ConduitStateResult state input output)) | Push function. |
-> (state -> m [output]) | Close function. The state need not be returned, since it will not be used again. |
-> Conduit input m output |
Construct a Conduit
with some stateful functions. This function addresses
threading the state value for you.
Since 0.3.0
data ConduitStateResult state input output Source
A helper type for conduitState
, indicating the result of being pushed
to. It can either indicate that processing is done, or to continue with the
updated state.
Since 0.3.0
Constructors
StateFinished (Maybe input) [output] | |
StateProducing state [output] |
Instances
Functor (ConduitStateResult state input) |
Arguments
:: MonadResource m | |
=> IO state | resource and/or state allocation |
-> (state -> IO ()) | resource and/or state cleanup |
-> (state -> input -> m (ConduitIOResult input output)) | Push function. Note that this need not explicitly perform any cleanup. |
-> (state -> m [output]) | Close function. Note that this need not explicitly perform any cleanup. |
-> Conduit input m output |
Construct a Conduit
.
Since 0.3.0
data ConduitIOResult input output Source
A helper type for conduitIO
, indicating the result of being pushed to.
It can either indicate that processing is done, or to continue.
Since 0.3.0
Constructors
IOFinished (Maybe input) [output] | |
IOProducing [output] |
Instances
Functor (ConduitIOResult input) |
Sequencing
type SequencedSink state input m output = state -> Sink input m (SequencedSinkResponse state input m output)Source
Helper type for constructing a Conduit
based on Sink
s. This allows you
to write higher-level code that takes advantage of existing conduits and
sinks, and leverages a sink's monadic interface.
Since 0.3.0
Arguments
:: Monad m | |
=> state | initial state |
-> SequencedSink state input m output | |
-> Conduit input m output |
Convert a SequencedSink
into a Conduit
.
Since 0.3.0
sequence :: Monad m => Sink input m output -> Conduit input m outputSource
Specialised version of sequenceSink
Note that this function will return an infinite stream if provided a
Sink
which does not consume data. In other words, you probably don't want to do
sequence . return
.
Since 0.3.0
data SequencedSinkResponse state input m output Source
Return value from a SequencedSink
.
Since 0.3.0
Constructors
Emit state [output] | Set a new state, and emit some new output. |
Stop | End the conduit. |
StartConduit (Conduit input m output) | Pass control to a new conduit. |
Flushing
Provide for a stream of data that can be flushed.
A number of Conduit
s (e.g., zlib compression) need the ability to flush
the stream at some point. This provides a single wrapper datatype to be used
in all such circumstances.
Since 0.3.0
Convenience re-exports
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
Instances
MonadTrans ResourceT | |
MonadTransControl ResourceT | |
MonadBase b m => MonadBase b (ResourceT m) | |
MonadBaseControl b m => MonadBaseControl b (ResourceT m) | |
Monad m => Monad (ResourceT m) | |
Functor m => Functor (ResourceT m) | |
Typeable1 m => Typeable1 (ResourceT m) | |
Applicative m => Applicative (ResourceT m) | |
(MonadThrow m, MonadUnsafeIO m, MonadIO m, Applicative m) => MonadResource (ResourceT m) | |
MonadThrow m => MonadThrow (ResourceT m) | |
(MonadIO m, MonadActive m) => MonadActive (ResourceT m) | |
MonadIO m => MonadIO (ResourceT m) |
class (MonadThrow m, MonadUnsafeIO m, MonadIO m, Applicative 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
Instances
(MonadThrow m, MonadUnsafeIO m, MonadIO m, Applicative m) => MonadResource (ResourceT m) | |
MonadResource m => MonadResource (MaybeT m) | |
MonadResource m => MonadResource (ListT m) | |
MonadResource m => MonadResource (IdentityT m) | |
MonadResource m => MonadResource (Finalize 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) | |
(Monoid w, MonadResource m) => MonadResource (RWST r w s m) | |
(Monoid w, MonadResource m) => MonadResource (RWST r w s m) |
class Monad m => MonadThrow m where
A Monad
which can throw exceptions. Note that this does not work in a
vanilla ST
or Identity
monad. Instead, you should use the ExceptionT
transformer in your stack if you are dealing with a non-IO
base monad.
Since 0.3.0
Methods
monadThrow :: Exception e => e -> m a
Instances
MonadThrow IO | |
MonadThrow m => MonadThrow (ResourceT m) | |
Monad m => MonadThrow (ExceptionT m) | |
MonadThrow m => MonadThrow (MaybeT m) | |
MonadThrow m => MonadThrow (ListT m) | |
MonadThrow m => MonadThrow (IdentityT m) | |
MonadThrow m => MonadThrow (Finalize m) | |
(Monoid w, MonadThrow m) => MonadThrow (WriterT w m) | |
(Monoid w, MonadThrow m) => 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) | |
MonadThrow m => MonadThrow (ContT r m) | |
(Monoid w, MonadThrow m) => MonadThrow (RWST r w s m) | |
(Monoid w, MonadThrow m) => MonadThrow (RWST r w s m) |
class Monad m => MonadUnsafeIO m where
A Monad
based on some monad which allows running of some IO
actions,
via unsafe calls. This applies to IO
and ST
, for instance.
Since 0.3.0
Methods
unsafeLiftIO :: IO a -> m a
Instances
MonadUnsafeIO IO | |
(MonadTrans t, MonadUnsafeIO m, Monad (t m)) => MonadUnsafeIO (t m) | |
MonadUnsafeIO (ST s) | |
MonadUnsafeIO (ST s) |
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