Copyright | (c) 2019 Composewell Technologies |
---|---|
License | BSD3 |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
An unfold is akin to a reader. It is the streaming equivalent of a reader.
The argument a
is the environment of the reader. That's the reason the
default unfolds in various modules are named "reader".
Synopsis
- data Unfold m a b = forall s. Unfold (s -> m (Step s b)) (a -> m s)
- mkUnfoldM :: (s -> m (Step s b)) -> (a -> m s) -> Unfold m a b
- mkUnfoldrM :: Applicative m => (a -> m (Step a b)) -> Unfold m a b
- unfoldrM :: Applicative m => (a -> m (Maybe (b, a))) -> Unfold m a b
- unfoldr :: Applicative m => (a -> Maybe (b, a)) -> Unfold m a b
- functionM :: Applicative m => (a -> m b) -> Unfold m a b
- function :: Applicative m => (a -> b) -> Unfold m a b
- identity :: Applicative m => Unfold m a a
- fromEffect :: Applicative m => m b -> Unfold m a b
- fromPure :: Applicative m => b -> Unfold m a b
- fromList :: Applicative m => Unfold m [a] a
- 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
- map :: Functor m => (b -> c) -> Unfold m a b -> Unfold m a c
- map2 :: Functor m => (a -> b -> c) -> Unfold m a b -> Unfold m a c
- mapM :: Monad m => (b -> m c) -> Unfold m a b -> Unfold m a c
- mapM2 :: Monad m => (a -> b -> m c) -> Unfold m a b -> Unfold m a c
- both :: a -> Unfold m a b -> Unfold m Void b
- first :: a -> Unfold m (a, b) c -> Unfold m b c
- second :: b -> Unfold m (a, b) c -> Unfold m a c
- takeWhileMWithInput :: Monad m => (a -> b -> m Bool) -> Unfold m a b -> Unfold m a b
- 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
- data ConcatState s1 s2
- = ConcatOuter s1
- | ConcatInner s1 s2
- many :: Monad m => Unfold m b c -> Unfold m a b -> Unfold m a c
- many2 :: Monad m => Unfold m (a, b) c -> Unfold m a b -> Unfold m a c
- manyInterleave :: Monad m => Unfold m a b -> Unfold m c a -> Unfold m c b
- crossApplySnd :: Unfold m a b -> Unfold m a c -> Unfold m a c
- crossApplyFst :: Unfold m a b -> Unfold m a c -> Unfold m a b
- crossWithM :: Monad m => (b -> c -> m d) -> Unfold m a b -> Unfold m a c -> Unfold m a d
- crossWith :: Monad m => (b -> c -> d) -> Unfold m a b -> Unfold m a c -> Unfold m a d
- cross :: Monad m => Unfold m a b -> Unfold m a c -> Unfold m a (b, c)
- crossApply :: Monad m => Unfold m a (b -> c) -> Unfold m a b -> Unfold m a c
- concatMapM :: Monad m => (b -> m (Unfold m a c)) -> Unfold m a b -> Unfold m a c
- concatMap :: Monad m => (b -> Unfold m a c) -> Unfold m a b -> Unfold m a c
- bind :: Monad m => Unfold m a b -> (b -> Unfold m a c) -> Unfold m a c
- zipWithM :: Monad m => (b -> c -> m d) -> Unfold m a b -> Unfold m a c -> Unfold m a d
- zipWith :: Monad m => (b -> c -> d) -> Unfold m a b -> Unfold m a c -> Unfold m a d
Setup
To execute the code examples provided in this module in ghci, please run the following commands first.
>>>
:m
>>>
import Streamly.Data.Unfold (Unfold)
>>>
import qualified Streamly.Data.Fold as Fold
>>>
import qualified Streamly.Data.Stream as Stream
>>>
import qualified Streamly.Data.Unfold as Unfold
For APIs that have not been released yet.
>>>
import qualified Streamly.Internal.Data.Unfold as Unfold
General Notes
What makes streams less efficient is also what makes them more convenient to use and powerful. The stream data type (Stream m a) bundles the state along with the stream generator function making it opaque, whereas an unfold exposes the state (Unfold m s a) to the user. This allows the Unfold to be unfolded (inlined) inside a nested loop without having to bundle the state and the generator together, the stream state can be saved and passed independent of the generator function. On the other hand in a stream type we have to bundle the stream state and the generator function together to save the stream. This makes it inefficient because it requires boxing and constructor allocation. However, this makes streams more convenient as we do not need to pass around the state/seed separately.
Unfold Type:
The order of arguments allows Category
and Arrow
instances but precludes
contravariant and contra-applicative.
Unfolds and Streams
An Unfold
type is the same as the direct style Stream
type except that
it uses an inject function to determine the initial state of the stream
based on an input. A stream is a special case of Unfold when the static
input is unit or Void.
This allows an important optimization to occur in several cases, making the
Unfold
a more efficient abstraction. Consider the concatMap
and
unfoldMany
operations, the latter is more efficient. concatMap
generates a new stream object from each element in the stream by applying
the supplied function to the element, the stream object includes the "step"
function as well as the initial "state" of the stream. Since the stream is
generated dynamically the compiler does not know the step function or the
state type statically at compile time, therefore, it cannot inline it. On
the other hand in case of unfoldMany
the compiler has visibility into
the unfold's state generation function, therefore, the compiler knows all
the types statically and it can inline the inject as well as the step
functions, generating efficient code. Essentially, the stream is not opaque
to the consumer in case of unfolds, the consumer knows how to generate the
stream from a seed using a known "inject" and "step" functions.
A Stream is like a data object whereas unfold is like a function. Being
function like, an Unfold is an instance of Category
and Arrow
type
classes.
Unfolds and Folds
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.
Reader:
An unfold acts as a reader (see Reader
monad). The input to an unfold acts
as the read-only environment. The environment can be extracted using the
identity
unfold (equivalent to ask
) and transformed using lmap
.
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
.
Basic Constructors
mkUnfoldM :: (s -> m (Step s b)) -> (a -> m s) -> Unfold m a b Source #
Make an unfold from step
and inject
functions.
Pre-release
mkUnfoldrM :: Applicative m => (a -> m (Step a b)) -> Unfold m a b Source #
unfoldrM :: Applicative m => (a -> m (Maybe (b, a))) -> Unfold m a b Source #
Build a stream by unfolding a monadic step function starting from a seed.
The step function returns the next element in the stream and the next seed
value. When it is done it returns Nothing
and the stream ends.
unfoldr :: Applicative m => (a -> Maybe (b, a)) -> Unfold m a b Source #
Like unfoldrM
but uses a pure step function.
>>>
:{
f [] = Nothing f (x:xs) = Just (x, xs) :}
>>>
Unfold.fold Fold.toList (Unfold.unfoldr f) [1,2,3]
[1,2,3]
functionM :: Applicative m => (a -> m b) -> Unfold m a b Source #
Lift a monadic function into an unfold. The unfold generates a singleton stream.
function :: Applicative m => (a -> b) -> Unfold m a b Source #
Lift a pure function into an unfold. The unfold generates a singleton stream.
function f = functionM $ return . f
identity :: Applicative m => Unfold m a a Source #
Identity unfold. The unfold generates a singleton stream having the input as the only element.
identity = function Prelude.id
Pre-release
From Values
fromEffect :: Applicative m => m b -> Unfold m a b Source #
The unfold discards its input and generates a function stream using the supplied monadic action.
Pre-release
fromPure :: Applicative m => b -> Unfold m a b Source #
Discards the unfold input and always returns the argument of fromPure
.
fromPure = fromEffect . pure
Pre-release
From Containers
fromList :: Applicative m => Unfold m [a] a Source #
Convert a list of pure values to a Stream
Transformations
lmap :: (a -> c) -> Unfold m c b -> Unfold m a b Source #
Map a function on the input argument of the Unfold
.
>>>
u = Unfold.lmap (fmap (+1)) Unfold.fromList
>>>
Unfold.fold Fold.toList u [1..5]
[2,3,4,5,6]
lmap f = Unfold.many (Unfold.function f)
lmapM :: Monad m => (a -> m c) -> Unfold m c b -> Unfold m a b Source #
Map an action on the input argument of the Unfold
.
lmapM f = Unfold.many (Unfold.functionM f)
map :: Functor m => (b -> c) -> Unfold m a b -> Unfold m a c Source #
Map a function on the output of the unfold (the type b
).
>>>
map f = Unfold.map2 (const f)
Pre-release
map2 :: Functor m => (a -> b -> c) -> Unfold m a b -> Unfold m a c Source #
>>>
map2 f = Unfold.mapM2 (\a b -> pure (f a b))
Note that the seed may mutate (e.g. if the seed is a Handle or IORef) as stream is generated from it, so we need to be careful when reusing the seed while the stream is being generated from it.
mapM :: Monad m => (b -> m c) -> Unfold m a b -> Unfold m a c Source #
Apply a monadic function to each element of the stream and replace it with the output of the resulting action.
>>>
mapM f = Unfold.mapM2 (const f)
both :: a -> Unfold m a b -> Unfold m Void b Source #
Supply the seed to an unfold closing the input end of the unfold.
both a = Unfold.lmap (Prelude.const a)
Pre-release
first :: a -> Unfold m (a, b) c -> 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.
first a = Unfold.lmap (a, )
Pre-release
second :: b -> Unfold m (a, b) c -> 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.
second b = Unfold.lmap (, b)
Pre-release
Trimming
takeWhileM :: Monad m => (b -> m Bool) -> Unfold m a b -> Unfold m a b Source #
Same as takeWhile
but with a monadic predicate.
takeWhile :: Monad m => (b -> Bool) -> Unfold m a b -> Unfold m a b Source #
End the stream generated by the Unfold
as soon as the predicate fails
on an element.
Nesting
data ConcatState s1 s2 Source #
ConcatOuter s1 | |
ConcatInner s1 s2 |
many :: Monad m => Unfold m b c -> Unfold m a b -> Unfold m a c Source #
Apply the first unfold to each output element of the second unfold and flatten the output in a single stream.
>>>
many u = Unfold.many2 (Unfold.lmap snd u)
manyInterleave :: Monad m => Unfold m a b -> Unfold m c a -> Unfold m c b Source #
unfoldManyInterleave
for
documentation and notes.
This is almost identical to unfoldManyInterleave in StreamD module.
The many
combinator is in fact manyAppend
to be more explicit in naming.
Internal
crossApplySnd :: Unfold m a b -> Unfold m a c -> Unfold m a c Source #
Outer product discarding the first element.
Unimplemented
crossApplyFst :: Unfold m a b -> Unfold m a c -> Unfold m a b Source #
Outer product discarding the second element.
Unimplemented
crossWithM :: Monad m => (b -> c -> m d) -> Unfold m a b -> Unfold m a c -> Unfold m a d Source #
Create a cross product (vector product or cartesian product) of the output streams of two unfolds using a monadic combining function.
>>>
f1 f u = Unfold.mapM2 (\(_, c) b -> f b c) (Unfold.lmap fst u)
>>>
crossWithM f u = Unfold.many2 (f1 f u)
Pre-release
crossWith :: Monad m => (b -> c -> d) -> Unfold m a b -> Unfold m a c -> Unfold m a d Source #
Like crossWithM
but uses a pure combining function.
crossWith f = crossWithM (\b c -> return $ f b c)
>>>
u1 = Unfold.lmap fst Unfold.fromList
>>>
u2 = Unfold.lmap snd Unfold.fromList
>>>
u = Unfold.crossWith (,) u1 u2
>>>
Unfold.fold Fold.toList u ([1,2,3], [4,5,6])
[(1,4),(1,5),(1,6),(2,4),(2,5),(2,6),(3,4),(3,5),(3,6)]
cross :: Monad m => Unfold m a b -> Unfold m a c -> Unfold m a (b, c) Source #
See crossWith
.
Definition:
>>>
cross = Unfold.crossWith (,)
To create a cross product of the streams generated from a tuple we can write:
>>>
:{
cross :: Monad m => Unfold m a b -> Unfold m c d -> Unfold m (a, c) (b, d) cross u1 u2 = Unfold.cross (Unfold.lmap fst u1) (Unfold.lmap snd u2) :}
Pre-release
concatMapM :: Monad m => (b -> m (Unfold m a c)) -> Unfold m a b -> Unfold m a c Source #
Map an unfold generating action to each element of an unfold and flatten the results into a single stream.
zipWithM :: Monad m => (b -> c -> m d) -> Unfold m a b -> Unfold m a c -> Unfold m a d Source #
Distribute the input to two unfolds and then zip the outputs to a single stream using a monadic zip function.
Stops as soon as any of the unfolds stops.
Pre-release
zipWith :: Monad m => (b -> c -> d) -> Unfold m a b -> Unfold m a c -> Unfold m a d Source #
Like zipWithM
but with a pure zip function.
>>>
square = fmap (\x -> x * x) Unfold.fromList
>>>
cube = fmap (\x -> x * x * x) Unfold.fromList
>>>
u = Unfold.zipWith (,) square cube
>>>
Unfold.fold Fold.toList u [1..5]
[(1,1),(4,8),(9,27),(16,64),(25,125)]
zipWith f = zipWithM (\a b -> return $ f a b)