simple-conduit-0.4.0: A simple streaming library based on composing monadic folds.

Safe HaskellNone
LanguageHaskell98

Conduit.Simple

Description

Synopsis

Documentation

newtype Source m a Source

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. And if it weren't for conduits like takeC, we wouldn't even need that most of the time.

Sources form a Monad that behaves a lot like ListT; for example:

do line <- sourceFile "foo.txt"
   liftIO $ putStrLn $ "line: " ++ show line
   x <- yieldMany [1..10]
   return (x, line)

The above Source yields a series of pairs, proving ten copies of each line from the file plus an index number.

To skip to the next value in a Source, use the function skip or mempty; to abort the whole pipeline, use abort or mzero. For example:

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

This outputs the list [2].

One difference from conduit is that monadic chaining of sources with >> results in the values from the first source being used to determine how many values are generated by the next source, just like ListT:

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

To achieve the same behavior as conduit, use the Monoid instance for Sources:

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

Constructors

Source 

Fields

runSource :: forall r. r -> (r -> a -> EitherT r m r) -> EitherT r m r
 

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

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

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]]

newtype ZipSink a m r Source

Constructors

ZipSink 

Fields

getZipSink :: Source m a -> m r
 

Instances

Monad m => Functor (ZipSink a m) 
Monad m => Applicative (ZipSink a m) 

sequenceSinks :: (Traversable f, Monad m) => f (Sink a m r) -> Sink a m (f r) 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.

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

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

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 b Source

Most of the time conduit will pass through the fold variable unmolested, but sometimes you need to ignore that variable and use your own within that 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 r Source

($=) :: a -> (a -> b) -> b infixl 1 Source

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 -> c infixr 2 Source

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) -> b infixr 0 Source

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.

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

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.

abort :: Monad m => Source m a Source

skip :: Monad m => Source m a Source

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

sinkList :: Monad m => Sink 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 builder Source

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

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 len Source

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

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

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

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 a Source

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

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

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 a Source

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

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

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

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 Source

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 mono Source

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 w Source

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

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

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

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 Source

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

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

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

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

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

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

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

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

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

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

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

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 mono Source

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Zip sinks together. This function may be used multiple times:

>>> let mySink s = sink () $ \() x -> liftIO $ print $ s <> show x
>>> zipSinks sinkList (zipSinks (mySink "foo") (mySink "bar")) $ yieldMany [1,2,3]
"foo: 1"
"bar: 1"
"foo: 2"
"bar: 2"
"foo: 3"
"bar: 3"
([1,2,3],((),()))

Note that the two sinks are run concurrently, so watch out for possible race conditions if they try to interact with the same resources.

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

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

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

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

fromFoldM :: Monad m => FoldM m a b -> Source m a -> m b Source

Convert a FoldM fold abstraction into a Sink.

NOTE: This requires ImpredicativeTypes in the code that uses it.

>>> fromFoldM (FoldM ((return .) . (+)) (return 0) return) $ yieldMany [1..10]
55

toFoldM :: Monad m => Sink a m r -> (forall s. FoldM (EitherT s m) a s -> EitherT s m s) -> m r Source

Convert a Sink into a FoldM, passing it into a continuation.

>>> toFoldM sumC (\f -> Control.Foldl.foldM f [1..10])
55

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

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

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

sourceTBQueue :: forall a. TBQueue a -> Source STM a Source

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

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