streamly-0.9.0: Streaming, dataflow programming and declarative concurrency
Copyright(c) 2019 Composewell Technologies
LicenseBSD-3-Clause
Maintainerstreamly@composewell.com
Stabilityexperimental
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Streamly.Internal.Data.Stream.IsStream.Lift

Description

Deprecated: Please use "Streamly.Data.Stream.*" instead.

Synopsis

Generalize Inner Monad

hoist :: (Monad m, Monad n) => (forall x. m x -> n x) -> SerialT m a -> SerialT n a Source #

Transform the inner monad of a stream using a natural transformation.

Internal

generally :: (IsStream t, Monad m) => t Identity a -> t m a Source #

Generalize the inner monad of the stream from Identity to any monad.

Internal

Transform Inner Monad

liftInner :: (Monad m, IsStream t, MonadTrans tr, Monad (tr m)) => t m a -> t (tr m) a Source #

Lift the inner monad m of a stream t m a to tr m using the monad transformer tr.

Since: 0.8.0

usingReaderT :: (Monad m, IsStream t) => m r -> (t (ReaderT r m) a -> t (ReaderT r m) a) -> t m a -> t m a Source #

Run a stream transformation using a given environment.

See also: map

Internal

runReaderT :: (IsStream t, Monad m) => m s -> t (ReaderT s m) a -> t m a Source #

Evaluate the inner monad of a stream as ReaderT.

Since: 0.8.0

evalStateT :: Monad m => m s -> SerialT (StateT s m) a -> SerialT m a Source #

Evaluate the inner monad of a stream as StateT.

This is supported only for SerialT as concurrent state updation may not be safe.

evalStateT s = Stream.map snd . Stream.runStateT s

Internal

usingStateT :: Monad m => m s -> (SerialT (StateT s m) a -> SerialT (StateT s m) a) -> SerialT m a -> SerialT m a Source #

Run a stateful (StateT) stream transformation using a given state.

This is supported only for SerialT as concurrent state updation may not be safe.

usingStateT s f = evalStateT s . f . liftInner

See also: scanl'

Internal

runStateT :: Monad m => m s -> SerialT (StateT s m) a -> SerialT m (s, a) Source #

Evaluate the inner monad of a stream as StateT and emit the resulting state and value pair after each step.

This is supported only for SerialT as concurrent state updation may not be safe.

Since: 0.8.0