Copyright | (c) 2019 Composewell Technologies |
---|---|
License | BSD3 |
Maintainer | streamly@composewell.com |
Stability | released |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
An Unfold
is a source or a producer of a stream of values. It takes a
seed value as an input and unfolds it into a sequence of values.
>>>
import qualified Streamly.Data.Fold as Fold
>>>
import qualified Streamly.Data.Unfold as Unfold
>>>
import qualified Streamly.Prelude as Stream
For example, the fromList
Unfold generates a stream of values from a
supplied list. Unfolds can be converted to SerialT
stream using the Stream.unfold operation.
>>>
stream = Stream.unfold Unfold.fromList [1..100]
>>>
Stream.sum stream
5050
All the serial stream generation operations in Streamly.Prelude can be expressed using unfolds:
Stream.fromList = Stream.unfold Unfold.fromList [1..100]
Conceptually, an Unfold
is just like "Data.List.unfoldr". Let us write a
step function to unfold a list using "Data.List.unfoldr":
>>>
:{
f [] = Nothing f (x:xs) = Just (x, xs) :}
>>>
Data.List.unfoldr f [1,2,3]
[1,2,3]
Unfold.unfoldr is just the same, it uses the same step function:
>>>
Stream.toList $ Stream.unfold (Unfold.unfoldr f) [1,2,3]
[1,2,3]
The input of an unfold can be transformed using lmap
:
>>>
u = Unfold.lmap (fmap (+1)) Unfold.fromList
>>>
Stream.toList $ Stream.unfold u [1..5]
[2,3,4,5,6]
Unfold
streams can be transformed using transformation combinators. For
example, to retain only the first two elements of an unfold:
>>>
u = Unfold.take 2 Unfold.fromList
>>>
Stream.toList $ Stream.unfold u [1..100]
[1,2]
Multiple unfolds can be combined in several interesting ways. For example, to generate nested looping as in imperative languages (also known as cross product of the two streams):
>>>
u1 = Unfold.lmap fst Unfold.fromList
>>>
u2 = Unfold.lmap snd Unfold.fromList
>>>
u = Unfold.crossWith (,) u1 u2
>>>
Stream.toList $ Stream.unfold 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)]
Nested loops using unfolds provide C like performance due to complete stream fusion.
Please see Streamly.Internal.Data.Unfold for additional Pre-release
functions.
Unfolds vs. Streams
Unfolds' raison d'etre is their efficiency in nested stream operations due
to complete stream fusion. concatMap
or the Monad
instance of streams use stream generation operations of the shape a -> t m
b
and then flatten the resulting stream. This implementation is more
powerful but does not allow for complete stream fusion. Unfolds provide
less powerful but more efficient unfoldMany
, many
and
crossWith
operations as an alternative to a subset of use cases of
concatMap
and Applicative
stream operations.
Streamly.Prelude exports polymorphic stream generation operations that provide the same functionality as unfolds in this module. Since unfolds can be easily converted to streams, several modules in streamly provide only unfolds for serial stream generation. We cannot use unfolds exclusively for stream generation as they do not support concurrency.
Synopsis
- data 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
- function :: Applicative m => (a -> b) -> Unfold m a b
- functionM :: Applicative m => (a -> m b) -> Unfold m a b
- repeatM :: Monad m => Unfold m (m a) a
- replicateM :: Monad m => Int -> Unfold m (m a) a
- iterateM :: Monad m => (a -> m a) -> Unfold m (m a) a
- fromList :: Monad m => Unfold m [a] a
- fromListM :: Monad m => Unfold m [m a] a
- fromStream :: (IsStream t, Monad m) => Unfold m (t 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
- mapM :: Monad m => (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
- drop :: Monad m => Int -> Unfold m a b -> Unfold m a b
- dropWhile :: Monad m => (b -> Bool) -> Unfold m a b -> Unfold m a b
- dropWhileM :: Monad m => (b -> m Bool) -> Unfold m a b -> Unfold m a b
- zipWith :: Monad m => (b -> c -> 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
- many :: Monad m => Unfold m a b -> Unfold m b c -> Unfold m a c
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
Unfolds
Basic Constructors
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.
Since: 0.8.0
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]
Since: 0.8.0
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
Since: 0.8.0
functionM :: Applicative m => (a -> m b) -> Unfold m a b Source #
Lift a monadic function into an unfold. The unfold generates a singleton stream.
Since: 0.8.0
Generators
Generate a monadic stream from a seed.
repeatM :: Monad m => Unfold m (m a) a Source #
Generates an infinite stream repeating the seed.
Since: 0.8.0
replicateM :: Monad m => Int -> Unfold m (m a) a Source #
Generates a stream replicating the seed n
times.
Since: 0.8.0
iterateM :: Monad m => (a -> m a) -> Unfold m (m a) a Source #
Generates an infinite stream starting with the given seed and applying the given function repeatedly.
Since: 0.8.0
From Containers
fromListM :: Monad m => Unfold m [m a] a Source #
Convert a list of monadic values to a Stream
Since: 0.8.0
Combinators
Mapping on Input
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)
Since: 0.8.0
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)
Since: 0.8.0
Mapping on Output
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.
Since: 0.8.0
Filtering
takeWhileM :: Monad m => (b -> m Bool) -> Unfold m a b -> Unfold m a b Source #
Same as takeWhile
but with a monadic predicate.
Since: 0.8.0
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.
Since: 0.8.0
take :: Monad m => Int -> Unfold m a b -> Unfold m a b Source #
>>>
u = Unfold.take 2 Unfold.fromList
>>>
Unfold.fold Fold.toList u [1..100]
[1,2]
Since: 0.8.0
filter :: Monad m => (b -> Bool) -> Unfold m a b -> Unfold m a b Source #
Include only those elements that pass a predicate.
Since: 0.8.0
filterM :: Monad m => (b -> m Bool) -> Unfold m a b -> Unfold m a b Source #
Same as filter
but with a monadic predicate.
Since: 0.8.0
drop :: Monad m => Int -> Unfold m a b -> Unfold m a b Source #
drop n unf
drops n
elements from the stream generated by unf
.
Since: 0.8.0
dropWhile :: Monad m => (b -> Bool) -> Unfold m a b -> Unfold m a b Source #
Similar to dropWhileM
but with a pure condition function.
Since: 0.8.0
dropWhileM :: Monad m => (b -> m Bool) -> Unfold m a b -> Unfold m a b Source #
dropWhileM f unf
drops elements from the stream generated by unf
while
the condition holds true. The condition function f
is monadic in nature.
Since: 0.8.0
Zipping
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)
Since: 0.8.0
Cross Product
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)]
Since: 0.8.0