Copyright | (c) 2018 Composewell Technologies (c) Roman Leshchinskiy 2008-2010 |
---|---|
License | BSD-3-Clause |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Step s a
- data Stream m a where
- nilM :: Applicative m => m b -> Stream m a
- consM :: Applicative m => m a -> Stream m a -> Stream m a
- uncons :: Monad m => Stream m a -> m (Maybe (a, Stream m a))
- unfold :: Applicative m => Unfold m a b -> a -> Stream m b
- fromPure :: Applicative m => a -> Stream m a
- fromEffect :: Applicative m => m a -> Stream m a
- fromList :: Applicative m => [a] -> Stream m a
- fromStreamK :: Applicative m => Stream m a -> Stream m a
- toStreamK :: Monad m => Stream m a -> Stream m a
- fold :: Monad m => Fold m a b -> Stream m a -> m b
- fold_ :: Monad m => Fold m a b -> Stream m a -> m (b, Stream m a)
- foldOn :: Monad m => Fold m a b -> Stream m a -> Fold m a b
- foldrT :: (Monad m, Monad (t m), MonadTrans t) => (a -> t m b -> t m b) -> t m b -> Stream m a -> t m b
- foldrM :: Monad m => (a -> m b -> m b) -> m b -> Stream m a -> m b
- foldrMx :: Monad m => (a -> m x -> m x) -> m x -> (m x -> m b) -> Stream m a -> m b
- foldr :: Monad m => (a -> b -> b) -> b -> Stream m a -> m b
- foldrS :: Monad m => (a -> Stream m b -> Stream m b) -> Stream m b -> Stream m a -> Stream m b
- foldl' :: Monad m => (b -> a -> b) -> b -> Stream m a -> m b
- foldlM' :: Monad m => (b -> a -> m b) -> m b -> Stream m a -> m b
- foldlx' :: Monad m => (x -> a -> x) -> x -> (x -> b) -> Stream m a -> m b
- foldlMx' :: Monad m => (x -> a -> m x) -> m x -> (x -> m b) -> Stream m a -> m b
- drain :: Monad m => Stream m a -> m ()
- toList :: Monad m => Stream m a -> m [a]
- eqBy :: Monad m => (a -> b -> Bool) -> Stream m a -> Stream m b -> m Bool
- cmpBy :: Monad m => (a -> b -> Ordering) -> Stream m a -> Stream m b -> m Ordering
- map :: Monad m => (a -> b) -> Stream m a -> Stream m b
- mapM :: Monad m => (a -> m b) -> Stream m a -> Stream m b
- take :: Applicative m => Int -> Stream m a -> Stream m a
- takeWhile :: Monad m => (a -> Bool) -> Stream m a -> Stream m a
- takeWhileM :: Monad m => (a -> m Bool) -> Stream m a -> Stream m a
- takeEndBy :: Monad m => (a -> Bool) -> Stream m a -> Stream m a
- takeEndByM :: Monad m => (a -> m Bool) -> Stream m a -> Stream m a
- data ConcatMapUState o i
- = ConcatMapUOuter o
- | ConcatMapUInner o i
- unfoldMany :: Monad m => Unfold m a b -> Stream m a -> Stream m b
- concatMap :: Monad m => (a -> Stream m b) -> Stream m a -> Stream m b
- concatMapM :: Monad m => (a -> m (Stream m b)) -> Stream m a -> Stream m b
- data FoldMany s fs b a
- = FoldManyStart s
- | FoldManyFirst fs s
- | FoldManyLoop s fs
- | FoldManyYield b (FoldMany s fs b a)
- | FoldManyDone
- data FoldManyPost s fs b a
- = FoldManyPostStart s
- | FoldManyPostLoop s fs
- | FoldManyPostYield b (FoldManyPost s fs b a)
- | FoldManyPostDone
- foldMany :: Monad m => Fold m a b -> Stream m a -> Stream m b
- foldManyPost :: Monad m => Fold m a b -> Stream m a -> Stream m b
- refoldMany :: Monad m => Refold m x a b -> m x -> Stream m a -> Stream m b
- chunksOf :: Monad m => Int -> Fold m a b -> Stream m a -> Stream m b
The stream type
A stream consists of a step function that generates the next step given a current state, and the current state.
Instances
MonadTrans Stream Source # | |
Defined in Streamly.Internal.Data.Stream.StreamD.Type | |
Monad m => Monad (Stream m) Source # | |
Functor m => Functor (Stream m) Source # | |
Applicative f => Applicative (Stream f) Source # | |
MonadThrow m => MonadThrow (Stream m) Source # | |
Defined in Streamly.Internal.Data.Stream.StreamD.Type |
Primitives
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
From Values
fromEffect :: Applicative m => m a -> Stream m a Source #
Create a singleton Stream
from a monadic action.
From Containers
Conversions From/To
fromStreamK :: Applicative 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
Running a Fold
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 #
foldrS :: Monad m => (a -> Stream m b -> Stream m b) -> Stream m b -> Stream m a -> Stream m b Source #
Left Folds
Special Folds
To Containers
Multi-stream folds
cmpBy :: Monad m => (a -> b -> Ordering) -> Stream m a -> Stream m b -> m Ordering Source #
Compare two streams lexicographically
Transformations
mapM :: Monad m => (a -> m b) -> Stream m a -> Stream m b Source #
Map a monadic function over a Stream
Nesting
data ConcatMapUState o i Source #
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.
data FoldMany s fs b a Source #
FoldManyStart s | |
FoldManyFirst fs s | |
FoldManyLoop s fs | |
FoldManyYield b (FoldMany s fs b a) | |
FoldManyDone |
data FoldManyPost s fs b a Source #
FoldManyPostStart s | |
FoldManyPostLoop s fs | |
FoldManyPostYield b (FoldManyPost s fs b a) | |
FoldManyPostDone |
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.