streamly-0.7.2: Beautiful Streaming, Concurrent and Reactive Composition

Copyright(c) 2018 Harendra Kumar
(c) Roman Leshchinskiy 2008-2010
LicenseBSD3
Maintainerstreamly@composewell.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Streamly.Internal.Data.Stream.StreamD.Type

Contents

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
Functor (Step s) Source # 
Instance details

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

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

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
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 #

fail :: String -> 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 #

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

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

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

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

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

Create a singleton Stream from a pure value.

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

Create a singleton Stream from a monadic action.

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 #

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 #

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

foldlM' :: Monad m => (b -> a -> m b) -> 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 #

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

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

Convert a list of pure values to a Stream

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

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

data GroupState s fs Source #

Constructors

GroupStart s 
GroupBuffer s fs Int 
GroupYield fs (GroupState s fs) 
GroupFinish 

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

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