| Safe Haskell | None |
|---|
Data.Conduit.Classy
Description
Note: This module is experimental, and might be modified at any time. Caveat emptor!
- type Source m o = SourceM o m ()
- newtype SourceM o m r = SourceM {}
- type Conduit i m o = ConduitM i o m ()
- newtype ConduitM i o m r = ConduitM {
- unConduitM :: Pipe i i o () m r
- newtype Sink i m r = Sink {}
- class (Monad m, Monad (PipeMonad m)) => IsPipe m where
- type PipeInput m
- type PipeTerm m
- type PipeOutput m
- type PipeMonad m :: * -> *
- await :: m (Maybe (PipeInput m))
- awaitE :: m (Either (PipeTerm m) (PipeInput m))
- leftover :: PipeInput m -> m ()
- yield :: PipeOutput m -> m ()
- yieldOr :: PipeOutput m -> PipeMonad m () -> m ()
- liftPipeMonad :: PipeMonad m a -> m a
- addCleanup :: (Bool -> PipeMonad m ()) -> m r -> m r
- class (IsPipe m, MonadResource (PipeMonad m), MonadIO m) => ResourcePipe m where
- controlBracketP :: (ResourcePipe m, Monad (t m), MonadTransControl t) => IO a -> (a -> IO ()) -> (a -> t m r) -> t m r
- awaitForever :: IsPipe m => (PipeInput m -> m r') -> m (PipeTerm m)
- ($$) :: Monad m => Source m a -> Sink a m b -> m b
- ($=) :: Monad m => Source m a -> Conduit a m b -> Source m b
- (=$=) :: Monad m => Conduit a m b -> Conduit b m c -> Conduit a m c
- (=$) :: Monad m => Conduit a m b -> Sink b m c -> Sink a m c
- ($$+) :: Monad m => Source m a -> Sink a m b -> m (ResumableSource m a, b)
- ($$++) :: Monad m => ResumableSource m a -> Sink a m b -> m (ResumableSource m a, b)
- ($$+-) :: Monad m => ResumableSource m a -> Sink a m b -> m b
- data ResumableSource m o
- runResourceT :: MonadBaseControl IO m => ResourceT m a -> m a
- data Flush a
- data ResourceT m a
- unwrapResumable :: MonadIO m => ResumableSource m o -> m (Source m o, m ())
Documentation
type Source m o = SourceM o m ()Source
Provides a stream of output values, without consuming any input or producing a final result.
Since 0.6.0
Instances
| MonadTrans (SourceM o) | |
| Monad m => Monad (SourceM o m) | |
| Monad m => Functor (SourceM o m) | |
| (Functor (SourceM o m), Monad m) => Applicative (SourceM o m) | |
| (Monad (SourceM o m), MonadIO m) => MonadIO (SourceM o m) | |
| (Monad (SourceM o m), MonadThrow m) => MonadThrow (SourceM o m) | |
| (IsPipe (SourceM o m), MonadResource (PipeMonad (SourceM o m)), MonadIO (SourceM o m), MonadResource m) => ResourcePipe (SourceM o m) | |
| (Monad (SourceM o m), Monad (PipeMonad (SourceM o m)), Monad m) => IsPipe (SourceM o m) | |
| Monad m => Monoid (SourceM o m ()) |
type Conduit i m o = ConduitM i o m ()Source
Consumes a stream of input values and produces a stream of output values, without producing a final result.
Since 0.6.0
newtype ConduitM i o m r Source
Constructors
| ConduitM | |
Fields
| |
Instances
| MonadTrans (ConduitM i o) | |
| Monad m => Monad (ConduitM i o m) | |
| Monad m => Functor (ConduitM i o m) | |
| (Functor (ConduitM i o m), Monad m) => Applicative (ConduitM i o m) | |
| (Monad (ConduitM i o m), MonadIO m) => MonadIO (ConduitM i o m) | |
| (Monad (ConduitM i o m), MonadThrow m) => MonadThrow (ConduitM i o m) | |
| (IsPipe (ConduitM i o m), MonadResource (PipeMonad (ConduitM i o m)), MonadIO (ConduitM i o m), MonadResource m) => ResourcePipe (ConduitM i o m) | |
| (Monad (ConduitM i o m), Monad (PipeMonad (ConduitM i o m)), Monad m) => IsPipe (ConduitM i o m) | |
| Monad m => Monoid (ConduitM i o m ()) |
Consumes a stream of input values and produces a final result, without producing any output.
Since 0.6.0
Instances
| MonadTrans (Sink i) | |
| Monad m => Monad (Sink i m) | |
| Monad m => Functor (Sink i m) | |
| (Functor (Sink i m), Monad m) => Applicative (Sink i m) | |
| (Monad (Sink i m), MonadIO m) => MonadIO (Sink i m) | |
| (Monad (Sink i m), MonadThrow m) => MonadThrow (Sink i m) | |
| (IsPipe (Sink i m), MonadResource (PipeMonad (Sink i m)), MonadIO (Sink i m), MonadResource m) => ResourcePipe (Sink i m) | |
| (Monad (Sink i m), Monad (PipeMonad (Sink i m)), Monad m) => IsPipe (Sink i m) | |
| Monad m => Monoid (Sink i m ()) |
class (Monad m, Monad (PipeMonad m)) => IsPipe m whereSource
Associated Types
type PipeOutput m Source
Methods
await :: m (Maybe (PipeInput m))Source
Wait for a single input value from upstream, terminating immediately if no data is available.
Since 0.5.0
awaitE :: m (Either (PipeTerm m) (PipeInput m))Source
This is similar to await, but will return the upstream result value as
Left if available.
Since 0.5.0
leftover :: PipeInput m -> m ()Source
Provide a single piece of leftover input to be consumed by the next pipe in the current monadic binding.
Note: it is highly encouraged to only return leftover values from input already consumed from upstream.
Since 0.5.0
yield :: PipeOutput m -> m ()Source
Send a single output value downstream. If the downstream Pipe
terminates, this Pipe will terminate as well.
Since 0.5.0
yieldOr :: PipeOutput m -> PipeMonad m () -> m ()Source
Similar to yield, but additionally takes a finalizer to be run if the
downstream Pipe terminates.
Since 0.5.0
liftPipeMonad :: PipeMonad m a -> m aSource
Arguments
| :: (Bool -> PipeMonad m ()) |
|
| -> m r | |
| -> m r |
Add some code to be run when the given Pipe cleans up.
Since 0.4.1
Instances
class (IsPipe m, MonadResource (PipeMonad m), MonadIO m) => ResourcePipe m whereSource
Methods
bracketP :: IO a -> (a -> IO ()) -> (a -> m r) -> m rSource
Perform some allocation and run an inner Pipe. Two guarantees are given
about resource finalization:
- It will be prompt. The finalization will be run as early as possible.
- It is exception safe. Due to usage of
resourcet, the finalization will be run in the event of any exceptions.
Since 0.5.0
Instances
controlBracketP :: (ResourcePipe m, Monad (t m), MonadTransControl t) => IO a -> (a -> IO ()) -> (a -> t m r) -> t m rSource
awaitForever :: IsPipe m => (PipeInput m -> m r') -> m (PipeTerm m)Source
Wait for input forever, calling the given inner Pipe for each piece of
new input. Returns the upstream result type.
Since 0.5.0
($$++) :: Monad m => ResumableSource m a -> Sink a m b -> m (ResumableSource m a, b)Source
($$+-) :: Monad m => ResumableSource m a -> Sink a m b -> m bSource
data ResumableSource m o
A Source which has been started, but has not yet completed.
This type contains both the current state of the Source, and the finalizer
to be run to close it.
Since 0.5.0
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
data Flush a
Provide for a stream of data that can be flushed.
A number of Conduits (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
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
unwrapResumable :: MonadIO m => ResumableSource m o -> m (Source m o, m ())
Unwraps a ResumableSource into a Source and a finalizer.
A ResumableSource represents a Source which has already been run, and
therefore has a finalizer registered. As a result, if we want to turn it
into a regular Source, we need to ensure that the finalizer will be run
appropriately. By appropriately, I mean:
- If a new finalizer is registered, the old one should not be called. * If the old one is called, it should not be called again.
This function returns both a Source and a finalizer which ensures that the
above two conditions hold. Once you call that finalizer, the Source is
invalidated and cannot be used.
Since 0.5.2