simple-conduit-0.5.1: A simple streaming I/O library based on monadic folds

Safe HaskellNone

Conduit.Simple.Core

Description

Please see the project README for more details:

https:github.comjwiegleysimple-conduitblobmaster/README.md

Also see this blog article:

https:www.newartisans.com201406/simpler-conduit-library

Synopsis

Documentation

newtype Source m a Source

A Source is a short-circuiting monadic fold.

Source forms a Monad that behaves as ListT; for example:

 do x <- yieldMany [1..3]
    line <- sourceFile foo.txt
    return (x, line)

This yields the cross-product of [3] and the lines in the files, but only reading chunks from the file as needed by the sink.

To skip to the next value in a Source, use the function skip or mempty; to close the source, use close. For example:

 do x <- yieldMany [1..10]
    if x == 2 || x == 9
    then return x
    else if x < 5
         then skip
         else close

This outputs the list [2].

A key difference from the conduit library is that monadic chaining of sources with >> follows ListT, and not concatenation as in conduit. To achieve conduit-style behavior, use the Monoid instance:

>>> sinkList $ yieldMany [1..3] <> yieldMany [4..6]
[1,2,3,4,5,6]

Constructors

Source 

Fields

getSource :: forall r. Cont (r -> EitherT r m r) a
 

type Conduit a m b = Source m a -> Source m bSource

A Conduit is a Source homomorphism, or simple a mapping between sources. There is no need for it to be a type synonym, except to save repetition across type signatures.

type Sink a m r = Source m a -> m rSource

A Sink folds a Source down to its result value. It is simply a convenient type synonym for functions mapping a Source to some result type.

returnC :: Monad m => m a -> Source m aSource

Promote any sink to a source. This can be used as if it were a source transformer (aka, a conduit):

>>> sinkList $ returnC $ sumC $ mapC (+1) $ yieldMany [1..10]
[65]

Note that returnC is a synonym for lift.

prod :: Source m (Cont (r -> EitherT r m r) (Source m a)) -> Cont (r -> EitherT r m r) (Source m a)Source

skip :: Monad m => Source m aSource

runSource :: Source m a -> r -> (r -> a -> EitherT r m r) -> EitherT r m rSource

lowerSource :: (Monad m, Monoid a) => Source m a -> m aSource

source :: (forall r. r -> (r -> a -> EitherT r m r) -> EitherT r m r) -> Source m aSource

conduit :: (forall r. r -> (r -> b -> EitherT r m r) -> a -> EitherT r m r) -> Conduit a m bSource

conduitWith :: Monad m => s -> (forall r. (r, s) -> (r -> b -> EitherT (r, s) m (r, s)) -> a -> EitherT (r, s) m (r, s)) -> Conduit a m bSource

Most of the time conduits pass the fold variable through unmolested, but sometimes you need to ignore that variable and use your own within a stage of the pipeline. This is done by wrapping the fold variable in a tuple and then unwrapping it when the conduit is done. conduitWith makes this transparent.

unwrap :: Monad m => EitherT a m a -> m aSource

rewrap :: Monad m => (a -> b) -> EitherT a m a -> EitherT b m bSource

sink :: forall m a r. Monad m => r -> (r -> a -> EitherT r m r) -> Sink a m rSource

awaitForever :: (a -> Source m b) -> Conduit a m bSource