Copyright | (c) 2021 Composewell Technologies |
---|---|
License | BSD-3-Clause |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
A Producer
is an Unfold
with an extract
function added to extract
the state. It is more powerful but less general than an Unfold.
A Producer
represents steps of a loop generating a sequence of elements.
While unfolds are closed representation of imperative loops with some opaque
internal state, producers are open loops with the state being accessible to
the user.
Unlike an unfold, which runs a loop till completion, a producer can be stopped in the middle, its state can be extracted, examined, changed, and then it can be resumed later from the stopped state.
A producer can be used in places where a CPS stream would otherwise be needed, because the state of the loop can be passed around. However, it can be much more efficient than CPS because it allows stream fusion and unecessary function calls can be avoided.
Synopsis
- data Source a b
- source :: Maybe a -> Source a b
- unread :: [b] -> Source a b -> Source a b
- isEmpty :: Source a b -> Bool
- producer :: Monad m => Producer m a b -> Producer m (Source a b) b
- parse :: Monad m => Parser a m b -> Producer m (Source s a) a -> Source s a -> m (Either ParseError b, Source s a)
- parseMany :: Monad m => Parser a m b -> Producer m (Source x a) a -> Producer m (Source x a) (Either ParseError b)
- parseManyD :: Monad m => Parser a m b -> Producer m (Source x a) a -> Producer m (Source x a) (Either ParseError b)
- data Producer m a b = forall s. Producer (s -> m (Step s b)) (a -> m s) (s -> m a)
- nil :: Monad m => Producer m a b
- nilM :: Monad m => (a -> m c) -> Producer m a b
- unfoldrM :: Monad m => (a -> m (Maybe (b, a))) -> Producer m a b
- fromList :: Monad m => Producer m [a] a
- translate :: Functor m => (a -> c) -> (c -> a) -> Producer m c b -> Producer m a b
- lmap :: (a -> a) -> Producer m a b -> Producer m a b
- data NestedLoop s1 s2
- concat :: Monad m => Producer m a b -> Producer m b c -> Producer m (NestedLoop a b) c
- simplify :: Producer m a b -> Unfold m a b
- fromStreamD :: Monad m => Producer m (Stream m a) a
Documentation
A seed with a buffer. It allows us to unread
or return some data
after reading it. Useful in backtracked parsing.
Creation
source :: Maybe a -> Source a b Source #
Make a source from a seed value. The buffer would start as empty.
Pre-release
Transformation
unread :: [b] -> Source a b -> Source a b Source #
Return some unused data back to the source. The data is prepended (or consed) to the source.
Pre-release
Consumption
producer :: Monad m => Producer m a b -> Producer m (Source a b) b Source #
Convert a producer to a producer from a buffered source. Any buffered data is read first and then the seed is unfolded.
Pre-release
Parsing
parse :: Monad m => Parser a m b -> Producer m (Source s a) a -> Source s a -> m (Either ParseError b, Source s a) Source #
parseMany :: Monad m => Parser a m b -> Producer m (Source x a) a -> Producer m (Source x a) (Either ParseError b) Source #
Apply a parser repeatedly on a buffered source producer to generate a producer of parsed values.
Pre-release
parseManyD :: Monad m => Parser a m b -> Producer m (Source x a) a -> Producer m (Source x a) (Either ParseError b) Source #
Type
A Producer m a b
is a generator of a stream of values of type b
from a
seed of type a
in Monad
m
.
Pre-release
Producers
fromList :: Monad m => Producer m [a] a Source #
Convert a list of pure values to a Stream
Pre-release
Mapping
translate :: Functor m => (a -> c) -> (c -> a) -> Producer m c b -> Producer m a b Source #
Interconvert the producer between two interconvertible input types.
Pre-release
lmap :: (a -> a) -> Producer m a b -> Producer m a b Source #
Map the producer input to another value of the same type.
Pre-release
Nesting
concat :: Monad m => Producer m a b -> Producer m b c -> Producer m (NestedLoop a b) c Source #
Apply the second unfold to each output element of the first unfold and flatten the output in a single stream.
Pre-release