Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
An optimization layer on Data.Stream.
Since both variants are semantically the same, not the full API of Data.Stream is replicated here.
Synopsis
- data OptimizedStreamT m a
- toStreamT :: Functor m => OptimizedStreamT m b -> StreamT m b
- hoist' :: (forall x. m1 x -> m2 x) -> OptimizedStreamT m1 a -> OptimizedStreamT m2 a
- mapOptimizedStreamT :: (Functor m, Functor n) => (forall s. m (Result s a) -> n (Result s b)) -> OptimizedStreamT m a -> OptimizedStreamT n b
- withOptimized :: Monad n => (forall m. Monad m => StreamT m a -> StreamT m b) -> OptimizedStreamT n a -> OptimizedStreamT n b
- handleOptimized :: Functor m => (StreamT m a -> StreamT n b) -> OptimizedStreamT m a -> OptimizedStreamT n b
- reactimate :: Monad m => OptimizedStreamT m () -> m void
- constM :: m a -> OptimizedStreamT m a
- stepOptimizedStream :: Functor m => OptimizedStreamT m a -> m (Result (OptimizedStreamT m a) a)
- toFinal :: Functor m => OptimizedStreamT m a -> Final m a
- fromFinal :: Final m a -> OptimizedStreamT m a
- concatS :: Monad m => OptimizedStreamT m [a] -> OptimizedStreamT m a
- exceptS :: Monad m => OptimizedStreamT (ExceptT e m) b -> OptimizedStreamT m (Either e b)
- applyExcept :: Monad m => OptimizedStreamT (ExceptT (e1 -> e2) m) a -> OptimizedStreamT (ExceptT e1 m) a -> OptimizedStreamT (ExceptT e2 m) a
- selectExcept :: Monad m => OptimizedStreamT (ExceptT (Either e1 e2) m) a -> OptimizedStreamT (ExceptT (e1 -> e2) m) a -> OptimizedStreamT (ExceptT e2 m) a
Documentation
data OptimizedStreamT m a Source #
An optimized version of StreamT
which has an extra constructor for stateless streams.
In most cases, using OptimizedStreamT
is preferable over StreamT
,
because building up bigger programs with StreamT
will build up big accumulations of trivial states.
The API of OptimizedStreamT
only keeps the nontrivial parts of the state.
Semantically, both types are the same.
Stateful (StreamT m a) | Embed a |
Stateless (m a) | A stateless stream is simply an action in a monad which is performed repetitively. |
Instances
toStreamT :: Functor m => OptimizedStreamT m b -> StreamT m b Source #
Remove the optimization layer.
For stateful streams, this is just the identity.
A stateless stream is encoded as a stream with state ()
.
hoist' :: (forall x. m1 x -> m2 x) -> OptimizedStreamT m1 a -> OptimizedStreamT m2 a Source #
mapOptimizedStreamT :: (Functor m, Functor n) => (forall s. m (Result s a) -> n (Result s b)) -> OptimizedStreamT m a -> OptimizedStreamT n b Source #
Change the output type and effect of a stream without changing its state type.
withOptimized :: Monad n => (forall m. Monad m => StreamT m a -> StreamT m b) -> OptimizedStreamT n a -> OptimizedStreamT n b Source #
Map a monad-independent morphism of streams to optimized streams.
In contrast to handleOptimized
, the stream morphism must be independent of the monad.
handleOptimized :: Functor m => (StreamT m a -> StreamT n b) -> OptimizedStreamT m a -> OptimizedStreamT n b Source #
Map a morphism of streams to optimized streams.
In contrast to withOptimized
, the monad type is allowed to change.
reactimate :: Monad m => OptimizedStreamT m () -> m void Source #
Run a stream with trivial output.
See reactimate
.
constM :: m a -> OptimizedStreamT m a Source #
A stateless stream.
This function is typically preferable over constM
,
since the optimized version doesn't create a state type.
stepOptimizedStream :: Functor m => OptimizedStreamT m a -> m (Result (OptimizedStreamT m a) a) Source #
Perform one step of a stream, resulting in an updated stream and an output value.
toFinal :: Functor m => OptimizedStreamT m a -> Final m a Source #
Translate to the final encoding of streams.
This will typically be a performance penalty.
fromFinal :: Final m a -> OptimizedStreamT m a Source #
Translate a stream from final encoding to stateful, initial encoding. The internal state is the stream itself.
concatS :: Monad m => OptimizedStreamT m [a] -> OptimizedStreamT m a Source #
See concatS
.
exceptS :: Monad m => OptimizedStreamT (ExceptT e m) b -> OptimizedStreamT m (Either e b) Source #
See exceptS
.
applyExcept :: Monad m => OptimizedStreamT (ExceptT (e1 -> e2) m) a -> OptimizedStreamT (ExceptT e1 m) a -> OptimizedStreamT (ExceptT e2 m) a Source #
See applyExcept
.
selectExcept :: Monad m => OptimizedStreamT (ExceptT (Either e1 e2) m) a -> OptimizedStreamT (ExceptT (e1 -> e2) m) a -> OptimizedStreamT (ExceptT e2 m) a Source #
See selectExcept
.