Copyright | (C) 2012 Edward Kmett Rúnar Bjarnason Paul Chiusano |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Edward Kmett <ekmett@gmail.com> |
Stability | provisional |
Portability | Rank-2 Types, GADTs |
Safe Haskell | None |
Language | Haskell2010 |
- type Tee a b c = Machine (T a b) c
- type TeeT m a b c = MachineT m (T a b) c
- data T a b c where
- tee :: Monad m => ProcessT m a a' -> ProcessT m b b' -> TeeT m a' b' c -> TeeT m a b c
- teeT :: Monad m => TeeT m a b c -> MachineT m k a -> MachineT m k b -> MachineT m k c
- addL :: Monad m => ProcessT m a b -> TeeT m b c d -> TeeT m a c d
- addR :: Monad m => ProcessT m b c -> TeeT m a c d -> TeeT m a b d
- capL :: Monad m => SourceT m a -> TeeT m a b c -> ProcessT m b c
- capR :: Monad m => SourceT m b -> TeeT m a b c -> ProcessT m a c
- capT :: Monad m => SourceT m a -> SourceT m b -> TeeT m a b c -> SourceT m c
- zipWithT :: (a -> b -> c) -> PlanT (T a b) c m ()
- zipWith :: (a -> b -> c) -> Tee a b c
- zipping :: Tee a b (a, b)
Tees
type Tee a b c = Machine (T a b) c Source #
A Machine
that can read from two input stream in a deterministic manner.
type TeeT m a b c = MachineT m (T a b) c Source #
A Machine
that can read from two input stream in a deterministic manner with monadic side-effects.
tee :: Monad m => ProcessT m a a' -> ProcessT m b b' -> TeeT m a' b' c -> TeeT m a b c Source #
Compose a pair of pipes onto the front of a Tee.
Examples:
>>>
import Data.Machine.Source
>>>
run $ tee (source [1..]) (source ['a'..'c']) zipping
[(1,'a'),(2,'b'),(3,'c')]
teeT :: Monad m => TeeT m a b c -> MachineT m k a -> MachineT m k b -> MachineT m k c Source #
`teeT mt ma mb` Use a Tee
to interleave or combine the outputs of ma
and mb
.
The resulting machine will draw from a single source.
Examples:
>>>
import Data.Machine.Source
>>>
run $ teeT zipping echo echo <~ source [1..5]
[(1,2),(3,4)]
addL :: Monad m => ProcessT m a b -> TeeT m b c d -> TeeT m a c d Source #
Precompose a pipe onto the left input of a tee.
addR :: Monad m => ProcessT m b c -> TeeT m a c d -> TeeT m a b d Source #
Precompose a pipe onto the right input of a tee.
capL :: Monad m => SourceT m a -> TeeT m a b c -> ProcessT m b c Source #
Tie off one input of a tee by connecting it to a known source.
capR :: Monad m => SourceT m b -> TeeT m a b c -> ProcessT m a c Source #
Tie off one input of a tee by connecting it to a known source.
capT :: Monad m => SourceT m a -> SourceT m b -> TeeT m a b c -> SourceT m c Source #
Tie off both inputs to a tee by connecting them to known sources. This is recommended over capping each side separately, as it is far more efficient.
zipWithT :: (a -> b -> c) -> PlanT (T a b) c m () Source #
wait for both the left and the right sides of a T and then merge them with f.