streamly-0.8.3: Dataflow programming and declarative concurrency
Copyright(c) 2019 Composewell Technologies
LicenseBSD-3-Clause
Maintainerstreamly@composewell.com
Stabilityexperimental
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Streamly.Internal.Data.Refold.Type

Description

The Fold type embeds a default initial value, therefore, it is like a Monoid whereas the Refold type has to be supplied with an initial value, therefore, it is more like a Semigroup operation.

Refolds can be appended to each other or to a fold to build the fold incrementally. This is useful in incremental builder like use cases.

See the file splitting example in the streamly-examples repository for an application of the Refold type. The Fold type does not perform as well in this situation.

Refold type is to Fold as Unfold type is to Stream. Unfold provides better optimizaiton than stream in nested operations, similarly, Refold provides better optimization than Fold.

Synopsis

Types

data Refold m c a b Source #

Like Fold except that the initial state of the accmulator can be generated using a dynamically supplied input. This affords better stream fusion optimization in nested fold operations where the initial fold state is determined based on a dynamic value.

Internal

Constructors

forall s. Refold (s -> a -> m (Step s b)) (c -> m (Step s b)) (s -> m b)

Fold step inject extract

Constructors

foldl' :: Monad m => (b -> a -> b) -> Refold m b a b Source #

Make a consumer from a left fold style pure step function.

If your Fold returns only Partial (i.e. never returns a Done) then you can use foldl'* constructors.

See also: Streamly.Prelude.foldl'

Internal

Refolds

Accumulators

sconcat :: (Monad m, Semigroup a) => Refold m a a a Source #

Append the elements of an input stream to a provided starting value.

>>> stream = Stream.map Data.Monoid.Sum $ Stream.enumerateFromTo 1 10
>>> Stream.fold (Fold.fromRefold Refold.sconcat 10) stream
Sum {getSum = 65}
>>> sconcat = Refold.foldl' (<>)

Internal

drainBy :: Monad m => (c -> a -> m b) -> Refold m c a () Source #

Internal

iterate :: Monad m => Refold m b a b -> Refold m b a b Source #

Keep running the same consumer over and over again on the input, feeding the output of the previous run to the next.

Internal

Combinators

lmapM :: Monad m => (a -> m b) -> Refold m c b r -> Refold m c a r Source #

lmapM f fold maps the monadic function f on the input of the fold.

Internal

rmapM :: Monad m => (b -> m c) -> Refold m x a b -> Refold m x a c Source #

Map a monadic function on the output of a fold.

Internal

append :: Monad m => Refold m x a b -> Refold m b a b -> Refold m x a b Source #

Supply the output of the first consumer as input to the second consumer.

Internal

take :: Monad m => Int -> Refold m x a b -> Refold m x a b Source #

Take at most n input elements and fold them using the supplied fold. A negative count is treated as 0.

Internal