streamly-0.8.0: Dataflow programming and declarative concurrency
Copyright(c) 2018 Composewell Technologies
(c) Roman Leshchinskiy 2008-2010
LicenseBSD-3-Clause
Maintainerstreamly@composewell.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Streamly.Internal.Data.Stream.StreamD.Type

Description

 
Synopsis

The stream type

data Step s a Source #

A stream is a succession of Steps. A Yield produces a single value and the next state of the stream. Stop indicates there are no more values in the stream.

Constructors

Yield a s 
Skip s 
Stop 

Instances

Instances details
Functor (Step s) Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Step

Methods

fmap :: (a -> b) -> Step s a -> Step s b #

(<$) :: a -> Step s b -> Step s a #

data Stream m a Source #

A stream consists of a step function that generates the next step given a current state, and the current state.

Constructors

forall s. UnStream (State Stream m a -> s -> m (Step s a)) s 

Bundled Patterns

pattern Stream :: (State Stream m a -> s -> m (Step s a)) -> s -> Stream m a 

Instances

Instances details
MonadTrans Stream Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Type

Methods

lift :: Monad m => m a -> Stream m a #

Monad m => Monad (Stream m) Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Type

Methods

(>>=) :: Stream m a -> (a -> Stream m b) -> Stream m b #

(>>) :: Stream m a -> Stream m b -> Stream m b #

return :: a -> Stream m a #

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

Defined in Streamly.Internal.Data.Stream.StreamD.Type

Methods

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

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

Applicative f => Applicative (Stream f) Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Type

Methods

pure :: a -> Stream f a #

(<*>) :: Stream f (a -> b) -> Stream f a -> Stream f b #

liftA2 :: (a -> b -> c) -> Stream f a -> Stream f b -> Stream f c #

(*>) :: Stream f a -> Stream f b -> Stream f b #

(<*) :: Stream f a -> Stream f b -> Stream f a #

MonadThrow m => MonadThrow (Stream m) Source # 
Instance details

Defined in Streamly.Internal.Data.Stream.StreamD.Type

Methods

throwM :: Exception e => e -> Stream m a #

Primitives

nilM :: Monad m => m b -> Stream m a Source #

An empty Stream with a side effect.

consM :: Monad m => m a -> Stream m a -> Stream m a Source #

uncons :: Monad m => Stream m a -> m (Maybe (a, Stream m a)) Source #

Does not fuse, has the same performance as the StreamK version.

From Unfold

unfold :: Monad m => Unfold m a b -> a -> Stream m b Source #

Convert an Unfold into a Stream by supplying it a seed.

From Values

fromPure :: Applicative m => a -> Stream m a Source #

Create a singleton Stream from a pure value.

fromEffect :: Monad m => m a -> Stream m a Source #

Create a singleton Stream from a monadic action.

From Containers

fromList :: Applicative m => [a] -> Stream m a Source #

Convert a list of pure values to a Stream

Conversions From/To

fromStreamK :: Monad m => Stream m a -> Stream m a Source #

Convert a CPS encoded StreamK to direct style step encoded StreamD

toStreamK :: Monad m => Stream m a -> Stream m a Source #

Convert a direct style step encoded StreamD to a CPS encoded StreamK

toStreamD :: (IsStream t, Monad m) => t m a -> Stream m a Source #

fromStreamD :: (IsStream t, Monad m) => Stream m a -> t m a Source #

Running a Fold

fold :: Monad m => Fold m a b -> Stream m a -> m b Source #

fold_ :: Monad m => Fold m a b -> Stream m a -> m (b, Stream m a) Source #

Right Folds

foldrT :: (Monad m, Monad (t m), MonadTrans t) => (a -> t m b -> t m b) -> t m b -> Stream m a -> t m b Source #

foldrM :: Monad m => (a -> m b -> m b) -> m b -> Stream m a -> m b Source #

foldrMx :: Monad m => (a -> m x -> m x) -> m x -> (m x -> m b) -> Stream m a -> m b Source #

foldr :: Monad m => (a -> b -> b) -> b -> Stream m a -> m b Source #

foldrS :: Monad m => (a -> Stream m b -> Stream m b) -> Stream m b -> Stream m a -> Stream m b Source #

Left Folds

foldl' :: Monad m => (b -> a -> b) -> b -> Stream m a -> m b Source #

foldlM' :: Monad m => (b -> a -> m b) -> m b -> Stream m a -> m b Source #

foldlx' :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream m a -> m b Source #

foldlMx' :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Stream m a -> m b Source #

To Containers

toList :: Monad m => Stream m a -> m [a] Source #

Multi-stream folds

eqBy :: Monad m => (a -> b -> Bool) -> Stream m a -> Stream m b -> m Bool Source #

cmpBy :: Monad m => (a -> b -> Ordering) -> Stream m a -> Stream m b -> m Ordering Source #

Compare two streams lexicographically

Transformations

map :: Monad m => (a -> b) -> Stream m a -> Stream m b Source #

mapM :: Monad m => (a -> m b) -> Stream m a -> Stream m b Source #

Map a monadic function over a Stream

take :: Monad m => Int -> Stream m a -> Stream m a Source #

takeWhile :: Monad m => (a -> Bool) -> Stream m a -> Stream m a Source #

takeWhileM :: Monad m => (a -> m Bool) -> Stream m a -> Stream m a Source #

Nesting

unfoldMany :: Monad m => Unfold m a b -> Stream m a -> Stream m b Source #

unfoldMany unfold stream uses unfold to map the input stream elements to streams and then flattens the generated streams into a single output stream.

concatMap :: Monad m => (a -> Stream m b) -> Stream m a -> Stream m b Source #

concatMapM :: Monad m => (a -> m (Stream m b)) -> Stream m a -> Stream m b Source #

data FoldMany s fs b a Source #

Constructors

FoldManyStart s 
FoldManyFirst fs s 
FoldManyLoop s fs 
FoldManyYield b (FoldMany s fs b a) 
FoldManyDone 

foldMany :: Monad m => Fold m a b -> Stream m a -> Stream m b Source #

Apply a fold multiple times until the stream ends. If the stream is empty the output would be empty.

foldMany f = parseMany (fromFold f)

A terminating fold may terminate even without accepting a single input. So we run the fold's initial action before evaluating the stream. However, this means that if later the stream does not yield anything we have to discard the fold's initial result which could have generated an effect.

foldManyPost :: Monad m => Fold m a b -> Stream m a -> Stream m b Source #

Like foldMany but with the following differences:

  • If the stream is empty the default value of the fold would still be emitted in the output.
  • At the end of the stream if the last application of the fold did not receive any input it would still yield the default fold accumulator as the last value.

groupsOf2 :: Monad m => Int -> m c -> Fold2 m c a b -> Stream m a -> Stream m b Source #

chunksOf :: Monad m => Int -> Fold m a b -> Stream m a -> Stream m b Source #