Safe Haskell | None |
---|
Provides a convenience layer on top of conduit with functions and operators similar to the pipes library.
- (>->) :: forall a b i o m. Monad m => ConduitM i a m () -> ConduitM a o m b -> ConduitM i o m b
- (<-<) :: forall a b i o m. Monad m => ConduitM a o m b -> ConduitM i a m () -> ConduitM i o m b
- runPipe :: forall m b. Monad m => ConduitM () Void m b -> m b
- runPipeR :: forall m b. (MonadBaseControl IO m, Monad m) => ConduitM () Void (ResourceT m) b -> m b
- runEffect :: forall m b. Monad m => ConduitM () Void m b -> m b
- forP :: Monad m => Source m a -> (a -> m ()) -> m ()
- each :: (Monad m, Foldable f) => f a -> Producer m a
- take :: Monad m => Int -> Conduit a m a
- peel :: Monad m => Int -> m [()]
- replicateM :: Monad m => Int -> m a -> Producer m a
- tee :: Monad m => Sink a (ConduitM a a m) b -> ConduitM a a m b
Documentation
(>->) :: forall a b i o m. Monad m => ConduitM i a m () -> ConduitM a o m b -> ConduitM i o m bSource
(<-<) :: forall a b i o m. Monad m => ConduitM a o m b -> ConduitM i a m () -> ConduitM i o m bSource
runPipe :: forall m b. Monad m => ConduitM () Void m b -> m bSource
Run a conduit. This name may be preferable to the overly generic
runEffect
, which pipes uses.
runPipeR :: forall m b. (MonadBaseControl IO m, Monad m) => ConduitM () Void (ResourceT m) b -> m bSource
Like runPipe
, except implies a call to runResourceT
, for running
resource-sensitive pipelines.
forP :: Monad m => Source m a -> (a -> m ()) -> m ()Source
Iterate over all the elements from source, similar to forM
for a monad.
take :: Monad m => Int -> Conduit a m aSource
Take N items from a conduit. Synonym for Conduit's isolate
.
peel :: Monad m => Int -> m [()]Source
Peel off N items from a conduit and return them. Synonym for Conduit's
take
.
replicateM :: Monad m => Int -> m a -> Producer m aSource
Replicate a monadic action a given number of times via a producer.