| Safe Haskell | None |
|---|
Data.Conduit.Extra.ZipConduit
- newtype ZipConduit i o m r = ZipConduit {
- getZipConduit :: ConduitM i o m r
- sequenceConduits :: (Traversable f, Monad m) => f (ConduitM i o m r) -> ConduitM i o m (f r)
Documentation
newtype ZipConduit i o m r Source
Provides an alternative Applicative instance for ConduitM. In this instance,
every incoming value is provided to all ConduitMs, and output is coalesced together.
Leftovers from individual ConduitMs will be used within that component, and then discarded
at the end of their computation. Output and finalizers will both be handled in a left-biased manner.
As an example, take the following program:
main :: IO ()
main = do
let src = mapM_ yield [1..3 :: Int]
conduit1 = CL.map (+1)
conduit2 = CL.concatMap (replicate 2)
conduit = getZipConduit $ ZipConduit conduit1 <* ZipConduit conduit2
sink = CL.mapM_ print
src $$ conduit =$ sink
It will produce the output: 2, 1, 1, 3, 2, 2, 4, 3, 3
Since 0.1.5
Constructors
| ZipConduit | |
Fields
| |
Instances
| Monad m => Functor (ZipConduit i o m) | |
| Monad m => Applicative (ZipConduit i o m) |
sequenceConduits :: (Traversable f, Monad m) => f (ConduitM i o m r) -> ConduitM i o m (f r)Source
Provide identical input to all of the Conduits and combine their outputs
into a single stream.
Implemented on top of ZipConduit, see that data type for more details.
Since 0.1.5