| Copyright | (c) 2019 Composewell Technologies | 
|---|---|
| License | BSD3 | 
| Maintainer | streamly@composewell.com | 
| Stability | experimental | 
| Portability | GHC | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Streamly.Internal.Data.Unfold.Type
Description
To run the examples in this module:
>>>import qualified Streamly.Prelude as Stream>>>import qualified Streamly.Data.Fold as Fold>>>import qualified Streamly.Internal.Data.Unfold as Unfold
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
- 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
- supply :: a -> Unfold m a b -> Unfold m Void b
- supplyFirst :: a -> Unfold m (a, b) c -> Unfold m b c
- supplySecond :: 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 a b -> Unfold m b c -> Unfold m a c
- manyInterleave :: Monad m => Unfold m a b -> Unfold m c a -> Unfold m c b
- apSequence :: Unfold m a b -> Unfold m a c -> Unfold m a c
- apDiscardSnd :: 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)
- apply :: 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
Documentation
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
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.
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
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
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
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
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)
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
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).
Pre-release
supply :: a -> Unfold m a b -> Unfold m Void b Source #
Supply the seed to an unfold closing the input end of the unfold.
supply a = Unfold.lmap (Prelude.const a)
Pre-release
supplyFirst :: 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.
supplyFirst a = Unfold.lmap (a, )
Pre-release
supplySecond :: 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.
supplySecond 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.
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
Nesting
data ConcatState s1 s2 Source #
Constructors
| ConcatOuter s1 | |
| ConcatInner s1 s2 | 
many :: 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.
Since: 0.8.0
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
apSequence :: Unfold m a b -> Unfold m a c -> Unfold m a c Source #
Outer product discarding the first element.
Unimplemented
apDiscardSnd :: 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.
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)]
Since: 0.8.0
cross :: Monad m => Unfold m a b -> Unfold m a c -> Unfold m a (b, c) Source #
See crossWith.
cross = crossWith (,)
To cross the streams from a tuple we can write:
crossProduct :: Monad m => Unfold m a b -> Unfold m c d -> Unfold m (a, c) (b, d) crossProduct u1 u2 = cross (lmap fst u1) (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)
Since: 0.8.0