classy-prelude-conduit-0.4.4: conduit instances for classy-prelude

Safe HaskellNone

Data.Conduit.Classy

Description

Note: This module is experimental, and might be modified at any time. Caveat emptor!

Synopsis

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

newtype SourceM o m r Source

Constructors

SourceM 

Fields

unSourceM :: Pipe () () o () m r
 

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

unConduitM :: Pipe i i o () m r
 

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 ()) 

newtype Sink i m r Source

Consumes a stream of input values and produces a final result, without producing any output.

Since 0.6.0

Constructors

Sink 

Fields

unSink :: Pipe i i Void () m r
 

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 PipeInput m Source

type PipeTerm m Source

type PipeOutput m Source

type PipeMonad 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

addCleanupSource

Arguments

:: (Bool -> PipeMonad m ())

True if Pipe ran to completion, False for early termination.

-> m r 
-> m r 

Add some code to be run when the given Pipe cleans up.

Since 0.4.1

Instances

(Monad (ResourceT m), Monad (PipeMonad (ResourceT m)), IsPipe m) => IsPipe (ResourceT m) 
(Monad (ListT m), Monad (PipeMonad (ListT m)), IsPipe m) => IsPipe (ListT m) 
(Monad (MaybeT m), Monad (PipeMonad (MaybeT m)), IsPipe m) => IsPipe (MaybeT m) 
(Monad (IdentityT m), Monad (PipeMonad (IdentityT m)), IsPipe m) => IsPipe (IdentityT m) 
(Monad (ErrorT e m), Monad (PipeMonad (ErrorT e m)), IsPipe m, Error e) => IsPipe (ErrorT e m) 
(Monad (ReaderT r m), Monad (PipeMonad (ReaderT r m)), IsPipe m) => IsPipe (ReaderT r m) 
(Monad (StateT s m), Monad (PipeMonad (StateT s m)), IsPipe m) => IsPipe (StateT s m) 
(Monad (StateT s m), Monad (PipeMonad (StateT s m)), IsPipe m) => IsPipe (StateT s m) 
(Monad (WriterT w m), Monad (PipeMonad (WriterT w m)), IsPipe m, Monoid w) => IsPipe (WriterT w m) 
(Monad (WriterT w m), Monad (PipeMonad (WriterT w m)), IsPipe m, Monoid w) => IsPipe (WriterT w m) 
(Monad (Sink i m), Monad (PipeMonad (Sink i m)), Monad m) => IsPipe (Sink i m) 
(Monad (SourceM o m), Monad (PipeMonad (SourceM o m)), Monad m) => IsPipe (SourceM o m) 
(Monad (ConduitM i o m), Monad (PipeMonad (ConduitM i o m)), Monad m) => IsPipe (ConduitM i o m) 
(Monad (RWST r w s m), Monad (PipeMonad (RWST r w s m)), IsPipe m, Monoid w) => IsPipe (RWST r w s m) 
(Monad (RWST r w s m), Monad (PipeMonad (RWST r w s m)), IsPipe m, Monoid w) => IsPipe (RWST r w s m) 
(Monad (Pipe l i o u m), Monad (PipeMonad (Pipe l i o u m)), Monad m, ~ * l i) => IsPipe (Pipe l i o u m) 

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:

  1. It will be prompt. The finalization will be run as early as possible.
  2. 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

(IsPipe (ResourceT m), MonadResource (PipeMonad (ResourceT m)), MonadIO (ResourceT m), ResourcePipe m) => ResourcePipe (ResourceT m) 
(IsPipe (ListT m), MonadResource (PipeMonad (ListT m)), MonadIO (ListT m), ResourcePipe m) => ResourcePipe (ListT m) 
(IsPipe (MaybeT m), MonadResource (PipeMonad (MaybeT m)), MonadIO (MaybeT m), ResourcePipe m) => ResourcePipe (MaybeT m) 
(IsPipe (IdentityT m), MonadResource (PipeMonad (IdentityT m)), MonadIO (IdentityT m), ResourcePipe m) => ResourcePipe (IdentityT m) 
(IsPipe (ErrorT e m), MonadResource (PipeMonad (ErrorT e m)), MonadIO (ErrorT e m), ResourcePipe m, Error e) => ResourcePipe (ErrorT e m) 
(IsPipe (ReaderT r m), MonadResource (PipeMonad (ReaderT r m)), MonadIO (ReaderT r m), ResourcePipe m) => ResourcePipe (ReaderT r m) 
(IsPipe (StateT s m), MonadResource (PipeMonad (StateT s m)), MonadIO (StateT s m), ResourcePipe m) => ResourcePipe (StateT s m) 
(IsPipe (StateT s m), MonadResource (PipeMonad (StateT s m)), MonadIO (StateT s m), ResourcePipe m) => ResourcePipe (StateT s m) 
(IsPipe (WriterT w m), MonadResource (PipeMonad (WriterT w m)), MonadIO (WriterT w m), ResourcePipe m, Monoid w) => ResourcePipe (WriterT w m) 
(IsPipe (WriterT w m), MonadResource (PipeMonad (WriterT w m)), MonadIO (WriterT w m), ResourcePipe m, Monoid w) => ResourcePipe (WriterT w m) 
(IsPipe (Sink i m), MonadResource (PipeMonad (Sink i m)), MonadIO (Sink i m), MonadResource m) => ResourcePipe (Sink i m) 
(IsPipe (SourceM o m), MonadResource (PipeMonad (SourceM o m)), MonadIO (SourceM o m), MonadResource m) => ResourcePipe (SourceM 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) 
(IsPipe (RWST r w s m), MonadResource (PipeMonad (RWST r w s m)), MonadIO (RWST r w s m), ResourcePipe m, Monoid w) => ResourcePipe (RWST r w s m) 
(IsPipe (RWST r w s m), MonadResource (PipeMonad (RWST r w s m)), MonadIO (RWST r w s m), ResourcePipe m, Monoid w) => ResourcePipe (RWST r w s m) 
(IsPipe (Pipe l i o u m), MonadResource (PipeMonad (Pipe l i o u m)), MonadIO (Pipe l i o u m), ~ * l i, MonadResource m) => ResourcePipe (Pipe l i o u m) 

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 => Source m a -> Sink a m b -> m bSource

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

(=$=) :: Monad m => Conduit a m b -> Conduit b m c -> Conduit a m cSource

(=$) :: Monad m => Conduit a m b -> Sink b m c -> Sink a m cSource

($$+) :: Monad m => Source m a -> Sink a m b -> m (ResumableSource m a, b)Source

($$++) :: 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

Constructors

Chunk a 
Flush 

Instances

Functor Flush 
Eq a => Eq (Flush a) 
(Eq (Flush a), Ord a) => Ord (Flush a) 
Show a => Show (Flush a) 

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 
(Monoid w, MonadReader r (ResourceT m), MonadWriter w (ResourceT m), MonadState s (ResourceT m), MonadRWS r w s m) => MonadRWS r w s (ResourceT m) 
(MonadBase b (ResourceT m), MonadBaseControl b m) => MonadBaseControl b (ResourceT m) 
(Applicative b, Applicative (ResourceT m), Monad b, Monad (ResourceT m), MonadBase b m) => MonadBase b (ResourceT m) 
(Monad (ResourceT m), MonadError e m) => MonadError e (ResourceT m) 
(Monad (ResourceT m), MonadReader r m) => MonadReader r (ResourceT m) 
(Monad (ResourceT m), MonadState s m) => MonadState s (ResourceT m) 
(Monoid w, Monad (ResourceT m), MonadWriter w m) => MonadWriter w (ResourceT m) 
Monad m => Monad (ResourceT m) 
Functor m => Functor (ResourceT m) 
Typeable1 m => Typeable1 (ResourceT m) 
(Functor (ResourceT m), Applicative m) => Applicative (ResourceT m) 
(Monad (ResourceT m), MonadIO m) => MonadIO (ResourceT m) 
(Monad (ResourceT m), MonadThrow m) => MonadThrow (ResourceT m) 
(MonadThrow (ResourceT m), MonadUnsafeIO (ResourceT m), MonadIO (ResourceT m), Applicative (ResourceT m), MonadThrow m, MonadUnsafeIO m, MonadIO m, Applicative m) => MonadResource (ResourceT m) 
(Monad (ResourceT m), MonadCont m) => MonadCont (ResourceT m) 
(Monad (ResourceT m), MonadIO m, MonadActive m) => MonadActive (ResourceT m) 
(IsPipe (ResourceT m), MonadResource (PipeMonad (ResourceT m)), MonadIO (ResourceT m), ResourcePipe m) => ResourcePipe (ResourceT m) 
(Monad (ResourceT m), Monad (PipeMonad (ResourceT m)), IsPipe m) => IsPipe (ResourceT m) 

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