Copyright | (c) 2019 Composewell Technologies |
---|---|
License | BSD3 |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Streams forcing a closed control flow loop can be categorized under two types, unfolds and folds, both of these are duals of each other.
Unfold streams are really generators of a sequence of elements, we can also call them pull style streams. These are lazy producers of streams. On each evaluation the producer generates the next element. A consumer can therefore pull elements from the stream whenever it wants to. A stream consumer can multiplex pull streams by pulling elements from the chosen streams, therefore, pull streams allow merging or multiplexing. On the other hand, with this representation we cannot split or demultiplex a stream. So really these are stream sources that can be generated from a seed and can be merged or zipped into a single stream.
The dual of Unfolds are Folds. Folds can also be called as push style streams or reducers. These are strict consumers of streams. We keep pushing elements to a fold and we can extract the result at any point. A driver can choose which fold to push to and can also push the same element to multiple folds. Therefore, folds allow splitting or demultiplexing a stream. On the other hand, we cannot merge streams using this representation. So really these are stream consumers that reduce the stream to a single value, these consumers can be composed such that a stream can be split over multiple consumers.
Performance:
Composing a tree or graph of computations with unfolds can be much more efficient compared to composing with the Monad instance. The reason is that unfolds allow the compiler to statically know the state and optimize it using stream fusion whereas it is not possible with the monad bind because the state is determined dynamically.
Synopsis
- data Unfold m a b
- lmap :: (a -> c) -> Unfold m c b -> Unfold m a b
- lmapM :: Monad m => (a -> m c) -> Unfold m c b -> Unfold m a b
- supply :: Unfold m a b -> a -> Unfold m Void b
- supplyFirst :: Unfold m (a, b) c -> a -> Unfold m b c
- supplySecond :: Unfold m (a, b) c -> b -> Unfold m a c
- discardFirst :: Unfold m a b -> Unfold m (c, a) b
- discardSecond :: Unfold m a b -> Unfold m (a, c) b
- swap :: Unfold m (a, c) b -> Unfold m (c, a) b
- fold :: Monad m => Unfold m a b -> Fold m b c -> a -> m c
- fromStream :: (IsStream t, Monad m) => t m b -> Unfold m Void b
- fromStream1 :: (IsStream t, Monad m) => (a -> t m b) -> Unfold m a b
- fromStream2 :: (IsStream t, Monad m) => (a -> b -> t m c) -> Unfold m (a, b) c
- nilM :: Monad m => (a -> m c) -> Unfold m a b
- consM :: Monad m => (a -> m b) -> Unfold m a b -> Unfold m a b
- effect :: Monad m => m b -> Unfold m Void b
- singletonM :: Monad m => (a -> m b) -> Unfold m a b
- singleton :: Monad m => (a -> b) -> Unfold m a b
- identity :: Monad m => Unfold m a a
- const :: Monad m => m b -> Unfold m a b
- replicateM :: Monad m => Int -> Unfold m a a
- repeatM :: Monad m => Unfold m a a
- fromList :: Monad m => Unfold m [a] a
- fromListM :: Monad m => Unfold m [m a] a
- enumerateFromStepIntegral :: (Integral a, Monad m) => Unfold m (a, a) a
- enumerateFromToIntegral :: (Monad m, Integral a) => a -> Unfold m a a
- enumerateFromIntegral :: (Monad m, Integral a, Bounded a) => Unfold m a a
- map :: Monad m => (b -> c) -> Unfold m a b -> Unfold m a c
- mapM :: Monad m => (b -> m c) -> Unfold m a b -> Unfold m a c
- mapMWithInput :: Monad m => (a -> b -> m c) -> Unfold m a b -> Unfold m a c
- takeWhileM :: Monad m => (b -> m Bool) -> Unfold m a b -> Unfold m a b
- takeWhile :: Monad m => (b -> Bool) -> Unfold m a b -> Unfold m a b
- take :: Monad m => Int -> Unfold m a b -> Unfold m a b
- filter :: Monad m => (b -> Bool) -> Unfold m a b -> Unfold m a b
- filterM :: Monad m => (b -> m Bool) -> Unfold m a b -> Unfold m a b
- zipWithM :: Monad m => (a -> b -> m c) -> Unfold m x a -> Unfold m y b -> Unfold m (x, y) c
- zipWith :: Monad m => (a -> b -> c) -> Unfold m x a -> Unfold m y b -> Unfold m (x, y) c
- teeZipWith :: Monad m => (a -> b -> c) -> Unfold m x a -> Unfold m x b -> Unfold m x c
- concat :: Monad m => Unfold m a b -> Unfold m b c -> Unfold m a c
- concatMapM :: Monad m => (b -> m (Unfold m () c)) -> Unfold m a b -> Unfold m a c
- outerProduct :: Monad m => Unfold m a b -> Unfold m c d -> Unfold m (a, c) (b, d)
- gbracket :: Monad m => (a -> m c) -> (forall s. m s -> m (Either e s)) -> (c -> m d) -> Unfold m (c, e) b -> Unfold m c b -> Unfold m a b
- gbracketIO :: (MonadIO m, MonadBaseControl IO m) => (a -> m c) -> (forall s. m s -> m (Either e s)) -> (c -> m d) -> Unfold m (c, e) b -> Unfold m c b -> Unfold m a b
- before :: Monad m => (a -> m c) -> Unfold m a b -> Unfold m a b
- after :: Monad m => (a -> m c) -> Unfold m a b -> Unfold m a b
- afterIO :: (MonadIO m, MonadBaseControl IO m) => (a -> m c) -> Unfold m a b -> Unfold m a b
- onException :: MonadCatch m => (a -> m c) -> Unfold m a b -> Unfold m a b
- finally :: MonadCatch m => (a -> m c) -> Unfold m a b -> Unfold m a b
- finallyIO :: (MonadAsync m, MonadCatch m) => (a -> m c) -> Unfold m a b -> Unfold m a b
- bracket :: MonadCatch m => (a -> m c) -> (c -> m d) -> Unfold m c b -> Unfold m a b
- bracketIO :: (MonadAsync m, MonadCatch m) => (a -> m c) -> (c -> m d) -> Unfold m c b -> Unfold m a b
- handle :: (MonadCatch m, Exception e) => Unfold m e b -> Unfold m a b -> Unfold m a b
Unfold Type
An Unfold m a b
is a generator of a stream of values of type b
from a
seed of type a
in Monad
m
.
Since: 0.7.0
Operations on Input
supply :: Unfold m a b -> a -> Unfold m Void b Source #
Supply the seed to an unfold closing the input end of the unfold.
Internal
supplyFirst :: Unfold m (a, b) c -> a -> Unfold m b c Source #
Supply the first component of the tuple to an unfold that accepts a tuple as a seed resulting in a fold that accepts the second component of the tuple as a seed.
Internal
supplySecond :: Unfold m (a, b) c -> b -> Unfold m a c Source #
Supply the second component of the tuple to an unfold that accepts a tuple as a seed resulting in a fold that accepts the first component of the tuple as a seed.
Internal
discardFirst :: Unfold m a b -> Unfold m (c, a) b Source #
Convert an Unfold
into an unfold accepting a tuple as an argument,
using the argument of the original fold as the second element of tuple and
discarding the first element of the tuple.
Internal
discardSecond :: Unfold m a b -> Unfold m (a, c) b Source #
Convert an Unfold
into an unfold accepting a tuple as an argument,
using the argument of the original fold as the first element of tuple and
discarding the second element of the tuple.
Internal
swap :: Unfold m (a, c) b -> Unfold m (c, a) b Source #
Convert an Unfold
that accepts a tuple as an argument into an unfold
that accepts a tuple with elements swapped.
Internal
Operations on Output
Unfolds
nilM :: Monad m => (a -> m c) -> Unfold m a b Source #
Lift a monadic function into an unfold generating a nil stream with a side effect.
consM :: Monad m => (a -> m b) -> Unfold m a b -> Unfold m a b Source #
Prepend a monadic single element generator function to an Unfold
.
Internal
effect :: Monad m => m b -> Unfold m Void b Source #
Lift a monadic effect into an unfold generating a singleton stream.
singletonM :: Monad m => (a -> m b) -> Unfold m a b Source #
Lift a monadic function into an unfold generating a singleton stream.
singleton :: Monad m => (a -> b) -> Unfold m a b Source #
Lift a pure function into an unfold generating a singleton stream.
identity :: Monad m => Unfold m a a Source #
Identity unfold. Generates a singleton stream with the seed as the only element in the stream.
identity = singletonM return
replicateM :: Monad m => Int -> Unfold m a a Source #
Generates a stream replicating the seed n
times.
enumerateFromStepIntegral :: (Integral a, Monad m) => Unfold m (a, a) a Source #
Can be used to enumerate unbounded integrals. This does not check for overflow or underflow for bounded integrals.
Transformations
Filtering
Zipping
zipWithM :: Monad m => (a -> b -> m c) -> Unfold m x a -> Unfold m y b -> Unfold m (x, y) c Source #
teeZipWith :: Monad m => (a -> b -> c) -> Unfold m x a -> Unfold m x b -> Unfold m x c Source #
Distribute the input to two unfolds and then zip the outputs to a single stream.
S.mapM_ print $ S.concatUnfold (UF.teeZipWith (,) UF.identity (UF.singleton sqrt)) $ S.fromList [1..10]
Internal
Nesting
concat :: Monad m => Unfold m a b -> Unfold m b c -> Unfold m a c Source #
Apply the second unfold to each output element of the first unfold and flatten the output in a single stream.
Internal
concatMapM :: Monad m => (b -> m (Unfold m () c)) -> Unfold m a b -> Unfold m a c Source #
Map an unfold generating action to each element of an unfold and flattern the results into a single stream.
outerProduct :: Monad m => Unfold m a b -> Unfold m c d -> Unfold m (a, c) (b, d) Source #
Create an outer product (vector product or cartesian product) of the output streams of two unfolds.
Exceptions
:: Monad m | |
=> (a -> m c) | before |
-> (forall s. m s -> m (Either e s)) | try (exception handling) |
-> (c -> m d) | after, on normal stop |
-> Unfold m (c, e) b | on exception |
-> Unfold m c b | unfold to run |
-> Unfold m a b |
The most general bracketing and exception combinator. All other combinators can be expressed in terms of this combinator. This can also be used for cases which are not covered by the standard combinators.
Internal
:: (MonadIO m, MonadBaseControl IO m) | |
=> (a -> m c) | before |
-> (forall s. m s -> m (Either e s)) | try (exception handling) |
-> (c -> m d) | after, on normal stop, or GC |
-> Unfold m (c, e) b | on exception |
-> Unfold m c b | unfold to run |
-> Unfold m a b |
The most general bracketing and exception combinator. All other combinators can be expressed in terms of this combinator. This can also be used for cases which are not covered by the standard combinators.
Internal
before :: Monad m => (a -> m c) -> Unfold m a b -> Unfold m a b Source #
Run a side effect before the unfold yields its first element.
Internal
after :: Monad m => (a -> m c) -> Unfold m a b -> Unfold m a b Source #
Run a side effect whenever the unfold stops normally.
Prefer afterIO over this as the after
action in this combinator is not
executed if the unfold is partially evaluated lazily and then garbage
collected.
Internal
afterIO :: (MonadIO m, MonadBaseControl IO m) => (a -> m c) -> Unfold m a b -> Unfold m a b Source #
Run a side effect whenever the unfold stops normally or is garbage collected after a partial lazy evaluation.
Internal
onException :: MonadCatch m => (a -> m c) -> Unfold m a b -> Unfold m a b Source #
Run a side effect whenever the unfold aborts due to an exception.
Internal
finally :: MonadCatch m => (a -> m c) -> Unfold m a b -> Unfold m a b Source #
Run a side effect whenever the unfold stops normally or aborts due to an exception.
Prefer finallyIO over this as the after
action in this combinator is not
executed if the unfold is partially evaluated lazily and then garbage
collected.
Internal
finallyIO :: (MonadAsync m, MonadCatch m) => (a -> m c) -> Unfold m a b -> Unfold m a b Source #
Run a side effect whenever the unfold stops normally, aborts due to an exception or if it is garbage collected after a partial lazy evaluation.
Internal
bracket :: MonadCatch m => (a -> m c) -> (c -> m d) -> Unfold m c b -> Unfold m a b Source #
bracket before after between
runs the before
action and then unfolds
its output using the between
unfold. When the between
unfold is done or
if an exception occurs then the after
action is run with the output of
before
as argument.
Prefer bracketIO over this as the after
action in this combinator is not
executed if the unfold is partially evaluated lazily and then garbage
collected.
Internal
bracketIO :: (MonadAsync m, MonadCatch m) => (a -> m c) -> (c -> m d) -> Unfold m c b -> Unfold m a b Source #
bracket before after between
runs the before
action and then unfolds
its output using the between
unfold. When the between
unfold is done or
if an exception occurs then the after
action is run with the output of
before
as argument. The after action is also executed if the unfold is
paritally evaluated and then garbage collected.
Internal