| Copyright | (c) 2019 Composewell Technologies | 
|---|---|
| License | BSD3 | 
| Maintainer | streamly@composewell.com | 
| Stability | released | 
| Portability | GHC | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Streamly.Data.Unfold
Description
Fast, composable stream producers with ability to terminate, supporting
 nested stream fusion. Nested stream operations like
 concatMap in the Streamly.Data.Stream module do not
 fuse, however, the unfoldMany operation, using the
 Unfold type, is a fully fusible alternative to
 concatMap.
Please refer to Streamly.Internal.Data.Unfold for more functions that have not yet been released.
Exception combinators are not exposed, we would like to encourage the use of
 Stream type instead whenever exception handling is required. We can
 consider exposing the unfold exception functions if there is a compelling
 use case to use unfolds instead of stream.
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 :: Applicative m => Unfold m (m a) a
- replicateM :: Applicative m => Unfold m (Int, m a) a
- iterateM :: Applicative m => (a -> m a) -> Unfold m (m a) a
- fromList :: Applicative m => Unfold m [a] a
- fromListM :: Applicative m => Unfold m [m a] a
- fromStream :: Applicative m => Unfold m (Stream 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 :: Applicative 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 :: Applicative 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 b c -> Unfold m a b -> Unfold m a c
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
Overview
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.
For example, the fromList Unfold generates a stream of values from a
 supplied list.  Unfolds can be converted to Stream
 using the unfold operation.
>>>stream = Stream.unfold Unfold.fromList [1..100]>>>Stream.fold Fold.sum stream5050
The input seed of an unfold can be transformed using lmap:
>>>u = Unfold.lmap (fmap (+1)) Unfold.fromList>>>Stream.fold Fold.toList $ Stream.unfold u [1..5][2,3,4,5,6]
Output stream of an Unfold 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.fold Fold.toList $ Stream.unfold u [1..100][1,2]
Unfolds can be nested efficiently. For example, to implement nested looping:
>>>u1 = Unfold.lmap fst Unfold.fromList>>>u2 = Unfold.lmap snd Unfold.fromList>>>u = Unfold.crossWith (,) u1 u2>>>Stream.fold Fold.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)]
Unfold u1 generates a stream from the first list in the input tuple,
 u2 generates another stream from the second list. The combines Unfold
 u nests the two streams i.e. for each element in first stream, for each
 element in second stream apply the supplied function (i.e. (,)) to the
 pair of elements.
This is the equivalent of the nested looping construct from imperative languages, also known as the cross product of two streams in functional parlance.
Please see Streamly.Internal.Data.Unfold for additional Pre-release
 functions.
Creating New Unfolds
There are many commonly used unfolds provided in this module. However, you
 can always create your own as well.  An Unfold is just a data
 representation of a stream generator function. It consists of an inject
 function which covnerts the supplied seed into an internal state of the
 unfold, and a step function which takes the state and generates the next
 output in the stream. For those familiar with the list "Data.List.unfoldr"
 function, this is a data representation of the same.
Smart constructor functions are provided in this module for constructing new
 Unfolds. For example, you can use the unfoldr constructor to
 create an Unfold from a pure step function, unfoldr uses id as the
 inject function.
Let's define a simple pure step function:
>>>:{f [] = Nothing f (x:xs) = Just (x, xs) :}
Create an Unfold from the step function:
>>>u = Unfold.unfoldr f
Run the Unfold:
>>>Stream.fold Fold.toList $ Stream.unfold u [1,2,3][1,2,3]
The unfoldr smart constructor is essentially the same as the list
 "Data.List.unfoldr" function. We can use the same step function in both::
>>>Data.List.unfoldr f [1,2,3][1,2,3]
Unfolds vs. Streams
The Unfold abstraction for representing streams was introduced in Streamly
 to provide C like performance for nested looping of streams. Unfold and
 Stream abstractions are similar with the following differences:
- Streamis less efficient than- Unfoldfor nesting.
- Streamis more powerful than- Unfold.
- StreamAPI is more convenient for programming
Unfolds can be easily converted to streams using unfold, however,
 vice versa is not possible. To provide a familiar analogy, Unfold is to
 Stream as Applicative is to Monad.
To demonstrate the efficiency of unfolds, the nested loop example in the previous section can be implemented with concatMap or Monad instance of streams as follows:
 do
     x <- Stream.unfold Unfold.fromList [1,2,3]
     y <- Stream.unfold Unfold.fromList [4,5,6]
     return (x, y)
As you can see, this is more convenient to write than using the crossWith
 unfold combinator. However, this turns out to be many times slower than the
 unfold implementation. The Unfold version is equivalent in performance to
 the C implementation of the same nested loop. Similarly, unfolds can be
 nested with streams using the unfoldMany combinator which is a much more
 efficient alternative to the concatMap operation.
Streams use a hybrid implementation approach using direct style as well as
 CPS. Unfolds do not use CPS, therefore, lack the power that is afforded to
 streams by CPS. The CPS implementation allows infinitely scalable cons and
 append operations in streams. It is also used to implement concurrency in
 streams.
To summarize, unfolds are a high performance solution to the nesting
 problem. Since streams provide a more palatable API for programming, work
 with streams unless you need unfolds for better performance in nesting
 situations. There is little difference in the way in which unfolds and
 streams are written, it is easy to adapt a stream to an unfold. If you are
 writing an unfold you can convert it to stream for free using
 unfold.
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.
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.
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]
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
functionM :: Applicative m => (a -> m b) -> Unfold m a b Source #
Lift a monadic function into an unfold. The unfold generates a singleton stream.
Generators
Generate a monadic stream from a seed.
repeatM :: Applicative m => Unfold m (m a) a Source #
Generates an infinite stream repeating the seed.
replicateM :: Applicative m => Unfold m (Int, m a) a Source #
Given a seed (n, action), generates a stream replicating the action n
 times.
iterateM :: Applicative 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.
From Containers
fromList :: Applicative m => Unfold m [a] a Source #
Convert a list of pure values to a Stream
fromStream :: Applicative m => Unfold m (Stream m a) a Source #
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)
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)
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.
>>>mapM f = Unfold.mapM2 (const f)
Filtering
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.
take :: Applicative 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]
filter :: Monad m => (b -> Bool) -> Unfold m a b -> Unfold m a b Source #
Include only those elements that pass a predicate.
filterM :: Monad m => (b -> m Bool) -> Unfold m a b -> Unfold m a b Source #
Same as filter but with a monadic predicate.
drop :: Applicative m => Int -> Unfold m a b -> Unfold m a b Source #
drop n unf drops n elements from the stream generated by unf.
dropWhile :: Monad m => (b -> Bool) -> Unfold m a b -> Unfold m a b Source #
Similar to dropWhileM but with a pure condition function.
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.
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)
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)]