simple-conduit-0.0.2: A simple streaming library based on composing 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

type Source m a r = r -> (r -> a -> EitherT r m r) -> EitherT r m rSource

In the type variable below, r stands for result, with much the same meaning as you find in ContT. a is the type of each element in the stream. The type of Source should recall foldM:

 Monad m => (a -> b -> m a) -> a -> [b] -> m a

EitherT is used to signal short-circuiting of the pipeline.

type Conduit a m b r = Source m a r -> Source m b rSource

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

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

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) $ sourceList [1..10]
[65]

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

(<+>) :: Monad m => Source m a r -> Conduit a m a rSource

Since Sources are not Monads in this library (as they are in the full conduit library), they can be sequentially chained using this append operator. If Source were a newtype, we could make it an instance of Monoid.

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

This is just like bimapEitherT, but it only requires a Monad constraint rather than Functor.

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

resolve :: Monad m => (r -> a -> EitherT r m r) -> r -> a -> m rSource

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

yieldOne :: Monad m => a -> Source m a rSource

unfoldC :: Monad m => (b -> Maybe (a, b)) -> b -> Source m a rSource

enumFromToC :: (Monad m, Enum a, Eq a) => a -> a -> Source m a rSource

iterateC :: Monad m => (a -> a) -> a -> Source m a rSource

repeatC :: Monad m => a -> Source m a rSource

replicateC :: Monad m => Int -> a -> Source m a rSource

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

repeatMC :: Monad m => m a -> Source m a rSource

repeatWhileMC :: Monad m => m a -> (a -> Bool) -> Source m a rSource

replicateMC :: Monad m => Int -> m a -> Source m a rSource

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

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

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

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

dropC :: Monad m => Int -> Source m a (Int, r) -> Source m a rSource

dropCE :: (Monad m, IsSequence seq) => Index seq -> Source m seq (Index seq, r) -> Source m seq rSource

dropWhileC :: Monad m => (a -> Bool) -> Source m a (a -> Bool, r) -> Source m a rSource

dropWhileCE :: (Monad m, IsSequence seq) => (Element seq -> Bool) -> Source m seq (Element seq -> Bool, r) -> Source m seq rSource

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) -> Source m a All -> m BoolSource

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

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

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

andCE :: (Monad m, MonoFoldable mono, Element mono ~ Bool) => Source m mono All -> m BoolSource

orCE :: (Monad m, MonoFoldable mono, Element mono ~ Bool) => Source m mono Any -> m BoolSource

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

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

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

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

produceList :: Monad m => ([a] -> b) -> Source m a ([a] -> [a]) -> m bSource

sinkLazy :: (Monad m, LazySequence lazy strict) => Source m strict ([strict] -> [strict]) -> m lazySource

sinkList :: Monad m => Source m a ([a] -> [a]) -> m [a]Source

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

sinkVectorN :: (MonadBase base m, Vector v a, PrimMonad base) => Int -> 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) => Source m a builder -> 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 b rSource

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

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

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

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

takeC :: Monad m => Int -> Source m a (Int, r) -> Source m a rSource

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

takeWhileC :: Monad m => (a -> Bool) -> Source m a (a -> Bool, r) -> Source m a rSource

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 seq rSource

takeExactlyC :: Monad m => Int -> Conduit a m b r -> Conduit a m b rSource

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

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

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

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

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

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

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

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

intersperseC :: Monad m => a -> Source m a (Maybe a, r) -> Source m a rSource

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

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

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

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

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

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

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

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

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

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

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

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

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

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

linesUnboundedC_ :: (Monad m, IsSequence seq, Eq (Element seq)) => Element seq -> Source m seq (r, seq) -> Source m seq rSource

linesUnboundedC :: (Monad m, IsSequence seq, Element seq ~ Char) => Source m seq (r, seq) -> Source m seq rSource

linesUnboundedAsciiC :: (Monad m, IsSequence seq, Element seq ~ Word8) => Source m seq (r, seq) -> Source m seq rSource

awaitForever :: Monad m => (a -> (b -> EitherT r m r) -> EitherT r m r -> EitherT r m r) -> Conduit a m b rSource

The use of awaitForever in this library is just a bit different from conduit:

>>> awaitForever $ \x yield skip -> if even x then yield x else skip

zipSourceApp :: Monad m => Source m (x -> y) r -> Source m x r -> Source m y rSource

newtype ZipSource m r a Source

Constructors

ZipSource 

Fields

getZipSource :: Source m a r
 

Instances

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

Sequence a collection of sources, feeding them all the same input and yielding a collection of their results.

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

zipSinks :: Monad m => (Source m i rs -> m r) -> (Source m i rs' -> m r') -> (forall s. Source m i s) -> m (r, r')Source

newtype ZipSink i m r s Source

Constructors

ZipSink 

Fields

getZipSink :: Source m i r -> m s
 

Instances

Monad m => Functor (ZipSink i m r) 
Monad m => Applicative (ZipSink i m r) 

sequenceSinks :: (Traversable f, Monad m) => f (Source m i r -> m s) -> Source m i r -> m (f s)Source

Send incoming values to all of the Sink providing, and ultimately coalesce together all return values.

Implemented on top of ZipSink, see that data type for more details.

Since 1.0.13

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