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

Safe HaskellNone

Conduit.Simple

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.

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.

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

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.

skip :: Monad m => Source m aSource

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

yieldMany :: (Monad m, MonoFoldable mono) => mono -> Source m (Element mono)Source

sourceList :: Monad m => [a] -> Source m aSource

unfoldC :: forall m a b. Monad m => (b -> Maybe (a, b)) -> b -> Source m aSource

enumFromToC :: forall m a. (Monad m, Enum a, Eq a) => a -> a -> Source m aSource

iterateC :: forall m a. Monad m => (a -> a) -> a -> Source m aSource

repeatC :: forall m a. Monad m => a -> Source m aSource

replicateC :: forall m a. Monad m => Int -> a -> Source m aSource

sourceLazy :: (Monad m, LazySequence lazy strict) => lazy -> Source m strictSource

repeatMC :: forall m a. Monad m => m a -> Source m aSource

repeatWhileMC :: forall m a. Monad m => m a -> (a -> Bool) -> Source m aSource

replicateMC :: forall m a. Monad m => Int -> m a -> Source m aSource

sourceHandle :: forall m a. (MonadIO m, IOData a) => Handle -> Source m aSource

initRepeat :: Monad m => m seed -> (seed -> m a) -> Source m aSource

initReplicate :: Monad m => m seed -> (seed -> m a) -> Int -> Source m aSource

sourceRandomGen :: (Variate a, MonadBase base m, PrimMonad base) => Gen (PrimState base) -> Source m aSource

sourceRandomNGen :: (Variate a, MonadBase base m, PrimMonad base) => Gen (PrimState base) -> Int -> Source m aSource

dropC :: Monad m => Int -> Conduit a m aSource

dropCE :: (Monad m, IsSequence seq) => Index seq -> Conduit seq m seqSource

dropWhileC :: Monad m => (a -> Bool) -> Conduit a m aSource

dropWhileCE :: (Monad m, IsSequence seq) => (Element seq -> Bool) -> Conduit seq m seqSource

foldC :: (Monad m, Monoid a) => Sink a m aSource

foldCE :: (Monad m, MonoFoldable mono, Monoid (Element mono)) => Sink mono m (Element mono)Source

foldlC :: Monad m => (a -> b -> a) -> a -> Sink b m aSource

foldlCE :: (Monad m, MonoFoldable mono) => (a -> Element mono -> a) -> a -> Sink mono m aSource

foldMapC :: (Monad m, Monoid b) => (a -> b) -> Sink a m bSource

foldMapCE :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> w) -> Sink mono m wSource

allC :: Monad m => (a -> Bool) -> Sink a m BoolSource

allCE :: (Monad m, MonoFoldable mono) => (Element mono -> Bool) -> Sink mono m BoolSource

anyC :: Monad m => (a -> Bool) -> Sink a m BoolSource

anyCE :: (Monad m, MonoFoldable mono) => (Element mono -> Bool) -> Sink mono m BoolSource

andCE :: (Monad m, MonoFoldable mono, Element mono ~ Bool) => Sink mono m BoolSource

orCE :: (Monad m, MonoFoldable mono, Element mono ~ Bool) => Sink mono m BoolSource

elemC :: (Monad m, Eq a) => a -> Sink a m BoolSource

elemCE :: (Monad m, EqSequence seq) => Element seq -> Sink seq m BoolSource

notElemC :: (Monad m, Eq a) => a -> Sink a m BoolSource

notElemCE :: (Monad m, EqSequence seq) => Element seq -> Sink seq m BoolSource

sinkLazy :: (Monad m, LazySequence lazy strict) => Sink strict m lazySource

sinkList :: Monad m => Sink a m [a]Source

sinkVector :: (MonadBase base m, Vector v a, PrimMonad base) => Sink a m (v a)Source

sinkBuilder :: (Monad m, Monoid builder, ToBuilder a builder) => Sink a m builderSource

sinkLazyBuilder :: (Monad m, Monoid builder, ToBuilder a builder, Builder builder lazy) => Sink a m lazySource

sinkNull :: Monad m => Sink a m ()Source

headCE :: (Monad m, IsSequence seq) => Sink seq m (Maybe (Element seq))Source

lastC :: Monad m => Sink a m (Maybe a)Source

lastCE :: (Monad m, IsSequence seq) => Sink seq m (Maybe (Element seq))Source

lengthC :: (Monad m, Num len) => Sink a m lenSource

lengthCE :: (Monad m, Num len, MonoFoldable mono) => Sink mono m lenSource

lengthIfC :: (Monad m, Num len) => (a -> Bool) -> Sink a m lenSource

lengthIfCE :: (Monad m, Num len, MonoFoldable mono) => (Element mono -> Bool) -> Sink mono m lenSource

maximumC :: (Monad m, Ord a) => Sink a m (Maybe a)Source

maximumCE :: (Monad m, OrdSequence seq) => Sink seq m (Maybe (Element seq))Source

minimumC :: (Monad m, Ord a) => Sink a m (Maybe a)Source

minimumCE :: (Monad m, OrdSequence seq) => Sink seq m (Maybe (Element seq))Source

sumC :: (Monad m, Num a) => Sink a m aSource

sumCE :: (Monad m, MonoFoldable mono, Num (Element mono)) => Sink mono m (Element mono)Source

productC :: (Monad m, Num a) => Sink a m aSource

productCE :: (Monad m, MonoFoldable mono, Num (Element mono)) => Sink mono m (Element mono)Source

findC :: Monad m => (a -> Bool) -> Sink a m (Maybe a)Source

mapM_C :: Monad m => (a -> m ()) -> Sink a m ()Source

mapM_CE :: (Monad m, MonoFoldable mono) => (Element mono -> m ()) -> Sink mono m ()Source

foldMC :: Monad m => (a -> b -> m a) -> a -> Sink b m aSource

foldMCE :: (Monad m, MonoFoldable mono) => (a -> Element mono -> m a) -> a -> Sink mono m aSource

foldMapMC :: (Monad m, Monoid w) => (a -> m w) -> Sink a m wSource

foldMapMCE :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> m w) -> Sink mono m wSource

sinkHandle :: (MonadIO m, IOData a) => Handle -> Sink a m ()Source

printC :: (Show a, MonadIO m) => Sink a m ()Source

stdoutC :: (MonadIO m, IOData a) => Sink a m ()Source

stderrC :: (MonadIO m, IOData a) => Sink a m ()Source

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

mapCE :: (Monad m, Functor f) => (a -> b) -> Conduit (f a) m (f b)Source

omapCE :: (Monad m, MonoFunctor mono) => (Element mono -> Element mono) -> Conduit mono m monoSource

concatMapC :: (Monad m, MonoFoldable mono) => (a -> mono) -> Conduit a m (Element mono)Source

concatMapCE :: (Monad m, MonoFoldable mono, Monoid w) => (Element mono -> w) -> Conduit mono m wSource

takeC :: Monad m => Int -> Conduit a m aSource

takeCE :: (Monad m, IsSequence seq) => Index seq -> Conduit seq m seqSource

takeWhileC :: Monad m => (a -> Bool) -> Conduit a m aSource

This function reads one more element than it yields, which would be a problem if Sinks were monadic, as they are in conduit or pipes. There is no such concept as resuming where the last conduit left off in this library.

takeWhileCE :: (Monad m, IsSequence seq) => (Element seq -> Bool) -> Conduit seq m seqSource

takeExactlyC :: Monad m => Int -> Conduit a m b -> Conduit a m bSource

takeExactlyCE :: (Monad m, IsSequence a) => Index a -> Conduit a m b -> Conduit a m bSource

concatC :: (Monad m, MonoFoldable mono) => Conduit mono m (Element mono)Source

filterC :: Monad m => (a -> Bool) -> Conduit a m aSource

filterCE :: (IsSequence seq, Monad m) => (Element seq -> Bool) -> Conduit seq m seqSource

mapWhileC :: Monad m => (a -> Maybe b) -> Conduit a m bSource

conduitVector :: (MonadBase base m, Vector v a, PrimMonad base) => Int -> Conduit a m (v a)Source

Collect elements into a vector until the size maxSize is reached, then yield that vector downstream.

scanlC :: Monad m => (a -> b -> a) -> a -> Conduit b m aSource

concatMapAccumC :: Monad m => (a -> accum -> (accum, [b])) -> accum -> Conduit a m bSource

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

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

mapMCE :: (Monad m, Traversable f) => (a -> m b) -> Conduit (f a) m (f b)Source

omapMCE :: (Monad m, MonoTraversable mono) => (Element mono -> m (Element mono)) -> Conduit mono m monoSource

concatMapMC :: (Monad m, MonoFoldable mono) => (a -> m mono) -> Conduit a m (Element mono)Source

filterMC :: Monad m => (a -> m Bool) -> Conduit a m aSource

filterMCE :: (Monad m, IsSequence seq) => (Element seq -> m Bool) -> Conduit seq m seqSource

iterMC :: Monad m => (a -> m ()) -> Conduit a m aSource

scanlMC :: Monad m => (a -> b -> m a) -> a -> Conduit b m aSource

concatMapAccumMC :: Monad m => (a -> accum -> m (accum, [b])) -> accum -> Conduit a m bSource

encodeUtf8C :: (Monad m, Utf8 text binary) => Conduit text m binarySource

lineC :: (Monad m, IsSequence seq, Element seq ~ Char) => Conduit seq m o -> Conduit seq m oSource

lineAsciiC :: (Monad m, IsSequence seq, Element seq ~ Word8) => Conduit seq m o -> Conduit seq m oSource

unlinesC :: (Monad m, IsSequence seq, Element seq ~ Char) => Conduit seq m seqSource

unlinesAsciiC :: (Monad m, IsSequence seq, Element seq ~ Word8) => Conduit seq m seqSource

linesUnboundedC_ :: forall m seq. (Monad m, IsSequence seq, Eq (Element seq)) => Element seq -> Conduit seq m seqSource

linesUnboundedC :: (Monad m, IsSequence seq, Element seq ~ Char) => Conduit seq m seqSource

linesC :: (Monad m, IsSequence seq, Element seq ~ Char) => Conduit seq m seqSource

linesAsciiC :: (Monad m, IsSequence seq, Element seq ~ Word8) => Conduit seq m seqSource

sourceMaybeMVar :: forall m a. MonadIO m => MVar (Maybe a) -> Source m aSource

Keep taking from an MVar (Maybe a) until it yields Nothing.

sourceMaybeTMVar :: forall a. TMVar (Maybe a) -> Source STM aSource

Keep taking from an TMVar (Maybe a) until it yields Nothing.

asyncC :: (MonadBaseControl IO m, Monad m) => (a -> m b) -> Conduit a m (Async (StM m b))Source

sourceTChan :: forall a. TChan a -> Source STM aSource

A Source for exhausting a TChan, but blocks if it is initially empty.

sourceTQueue :: forall a. TQueue a -> Source STM aSource

untilMC :: forall m a. Monad m => m a -> m Bool -> Source m aSource

whileMC :: forall m a. Monad m => m Bool -> m a -> Source m aSource

zipSinks :: forall a m r r'. (MonadBaseControl IO m, MonadIO m) => Sink a m r -> Sink a m r' -> Sink a m (r, r')Source

($=) :: a -> (a -> b) -> bSource

Compose a Source and a Conduit into a new Source. Note that this is just flipped function application, so ($) can be used to achieve the same thing.

(=$) :: (a -> b) -> (b -> c) -> a -> cSource

Compose a Conduit and a Sink into a new Sink. Note that this is just function composition, so (.) can be used to achieve the same thing.

(=$=) :: (a -> b) -> (b -> c) -> a -> cSource

Compose two Conduit. This is also just function composition.

($$) :: a -> (a -> b) -> bSource

Compose a Source and a Sink and compute the result. Note that this is just flipped function application, so ($) can be used to achieve the same thing.

sequenceSources :: (Traversable f, Monad m) => f (Source m a) -> Source m (f a)Source

Sequence a collection of sources.

>>> sinkList $ sequenceSources [yieldOne 1, yieldOne 2, yieldOne 3]
[[1,2,3]]