automaton-1.3: Effectful streams and automata in initial encoding
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Stream.Optimized

Description

An optimization layer on Data.Stream.

Since both variants are semantically the same, not the full API of Data.Stream is replicated here.

Synopsis

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.

Constructors

Stateful (StreamT m a)

Embed a StreamT. Take care only to use this constructor on streams with nontrivial state.

Stateless (m a)

A stateless stream is simply an action in a monad which is performed repetitively.

Instances

Instances details
MFunctor OptimizedStreamT Source # 
Instance details

Defined in Data.Stream.Optimized

Methods

hoist :: forall m n (b :: k). Monad m => (forall a. m a -> n a) -> OptimizedStreamT m b -> OptimizedStreamT n b #

Alternative m => Alternative (OptimizedStreamT m) Source # 
Instance details

Defined in Data.Stream.Optimized

Applicative m => Applicative (OptimizedStreamT m) Source #

Only builds up tuples of states if both streams are stateful.

Instance details

Defined in Data.Stream.Optimized

Functor m => Functor (OptimizedStreamT m) Source # 
Instance details

Defined in Data.Stream.Optimized

Methods

fmap :: (a -> b) -> OptimizedStreamT m a -> OptimizedStreamT m b #

(<$) :: a -> OptimizedStreamT m b -> OptimizedStreamT m a #

Selective m => Selective (OptimizedStreamT m) Source # 
Instance details

Defined in Data.Stream.Optimized

Methods

select :: OptimizedStreamT m (Either a b) -> OptimizedStreamT m (a -> b) -> OptimizedStreamT m b #

Align m => Align (OptimizedStreamT m) Source # 
Instance details

Defined in Data.Stream.Optimized

Methods

nil :: OptimizedStreamT m a #

Semialign m => Semialign (OptimizedStreamT m) Source # 
Instance details

Defined in Data.Stream.Optimized

(Applicative m, Floating a) => Floating (OptimizedStreamT m a) Source # 
Instance details

Defined in Data.Stream.Optimized

(Applicative m, Num a) => Num (OptimizedStreamT m a) Source # 
Instance details

Defined in Data.Stream.Optimized

(Applicative m, Fractional a) => Fractional (OptimizedStreamT m a) Source # 
Instance details

Defined in Data.Stream.Optimized

(VectorSpace v s, Eq s, Floating s, Applicative m) => VectorSpace (OptimizedStreamT m v) (OptimizedStreamT m s) Source # 
Instance details

Defined in Data.Stream.Optimized

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 #

Like hoist, but without the Monad m2 constraint.

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.