| Safe Haskell | Safe |
|---|---|
| Language | Haskell98 |
Conduit.Simple.Core
Description
Please see the project README for more details:
https://github.com/jwiegley/simple-conduit/blob/master/README.md
Also see this blog article:
- newtype Source m a = Source {}
- type Conduit a m b = Source m a -> Source m b
- type Sink a m r = Source m a -> m r
- returnC :: Monad m => m a -> Source m a
- prod :: Source m (Cont (r -> EitherT r m r) (Source m a)) -> Cont (r -> EitherT r m r) (Source m a)
- close :: Monad m => Source m a
- skip :: Monad m => Source m a
- runSource :: Source m a -> r -> (r -> a -> EitherT r m r) -> EitherT r m r
- lowerSource :: (Monad m, Monoid a) => Source m a -> m a
- source :: (forall r. r -> (r -> a -> EitherT r m r) -> EitherT r m r) -> Source m a
- conduit :: (forall r. r -> (r -> b -> EitherT r m r) -> a -> EitherT r m r) -> Conduit a m b
- 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
- unwrap :: Monad m => EitherT a m a -> m a
- rewrap :: Monad m => (a -> b) -> EitherT a m a -> EitherT b m b
- sink :: forall m a r. Monad m => r -> (r -> a -> EitherT r m r) -> Sink a m r
- awaitForever :: (a -> Source m b) -> Conduit a m b
Documentation
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]
Instances
| MonadTrans Source Source # | |
| MFunctor Source Source # | |
| MMonad Source Source # | |
| (Functor f, MonadFree f m) => MonadFree f (Source m) Source # | |
| MonadError e m => MonadError e (Source m) Source # | |
| MonadReader r m => MonadReader r (Source m) Source # | |
| MonadState s m => MonadState s (Source m) Source # | |
| MonadWriter w m => MonadWriter w (Source m) Source # | |
| Monad (Source m) Source # | |
| Functor (Source m) Source # | |
| Applicative (Source m) Source # | |
| Foldable (Source Identity) Source # | |
| Monad m => MonadPlus (Source m) Source # | |
| MonadIO m => MonadIO (Source m) Source # | |
| Monad m => Alternative (Source m) Source # | |
| MonadThrow m => MonadThrow (Source m) Source # | |
| MonadCatch m => MonadCatch (Source m) Source # | |
| MonadMask m => MonadMask (Source m) Source # | |
| Monad m => Semigroup (Source m a) Source # | |
| Monad m => Monoid (Source m a) Source # | |
type Conduit a m b = Source m a -> Source m b Source #
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.
prod :: Source m (Cont (r -> EitherT r m r) (Source m a)) -> Cont (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 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.
awaitForever :: (a -> Source m b) -> Conduit a m b Source #