foldl-transduce-0.1.2.1: Transducers for foldl folds.

Safe HaskellSafe
LanguageHaskell98

Control.Foldl.Transduce

Contents

Description

This module builds on module Control.Foldl, adding stateful transducers and grouping operations.

Synopsis

Transducer types

type Transduction a b = forall x. Fold b x -> Fold a x Source

A (possibly stateful) transformation on the inputs of a Fold.

Functions constructed with combinators like premap or handles from Control.Foldl also typecheck as a Transduction.

type Transduction' a b r = forall x. Fold b x -> Fold a (r, x) Source

A more general from of Transduction that adds new information to the return value of the Fold.

data Transducer i o r Source

Representation of a stateful Transduction with step function, an initial accumulator, and a extraction function that returns a summary value of type r. Both the step function and the extraction function may send output downstream.

Constructors

forall x . Transducer (x -> i -> (x, [o])) x (x -> (r, [o])) 

type TransductionM m a b = forall x. Monad m => FoldM m b x -> FoldM m a x Source

type TransductionM' m a b r = forall x. FoldM m b x -> FoldM m a (r, x) Source

data TransducerM m i o r Source

Like Transducer, but monadic.

Constructors

forall x . TransducerM (x -> i -> m (x, [o])) (m x) (x -> m (r, [o])) 

Instances

Applying transducers

transduce :: Transducer i o r -> Transduction i o Source

Apply a Transducer to a Fold, discarding the return value of the Transducer.

>>> L.fold (transduce (Transducer (\_ i -> ((),[i])) () (\_ -> ('r',[]))) L.list) [1..7]
[1,2,3,4,5,6,7]

transduce' :: Transducer i o x -> Transduction' i o x Source

Generalized version of transduce that preserves the return value of the Transducer.

>>> L.fold (transduce' (Transducer (\_ i -> ((),[i])) () (\_ -> ('r',[]))) L.list) [1..7]
('r',[1,2,3,4,5,6,7])

Transducers

surround :: (Foldable p, Foldable s) => p a -> s a -> Transducer a a () Source

Adds a prefix and a suffix to the stream arriving into a Fold.

>>> L.fold (transduce (surround "prefix" "suffix") L.list) "middle"
"prefixmiddlesuffix"

surroundIO :: (Foldable p, Foldable s, MonadIO m) => m (p a) -> m (s a) -> TransducerM m a a () Source

Like surround, but the prefix and suffix are obtained using a IO action.

>>> L.foldM (transduceM (surroundIO (return "prefix") (return "suffix")) (L.generalize L.list)) "middle"
"prefixmiddlesuffix"

Transducer utilities

generalizeTransducer :: Monad m => Transducer i o r -> TransducerM m i o r Source

Generalize a Transducer to a TransducerM.

foldify :: Transducer i o r -> Fold i r Source

Transforms a Transducer into a Fold by forgetting about the data sent downstream.

foldifyM :: Functor m => TransducerM m i o r -> FoldM m i r Source

chokepoint :: Fold i b -> Transducer i b () Source

Transforms a Fold into a Transducer that sends the return value of the Fold downstream when upstream closes.

chokepointM :: Applicative m => FoldM m i b -> TransducerM m i b () Source

hoistTransducer :: Monad m => (forall a. m a -> n a) -> TransducerM m i o r -> TransducerM n i o r Source

Changes the base monad used by a TransducerM.

hoistFold :: Monad m => (forall a. m a -> n a) -> FoldM m i r -> FoldM n i r Source

Changes the base monad used by a FoldM.

Splitter types

data Splitter i Source

A procedure for splitting a stream into delimited segments. It is composed of a step function, an initial state, and a done function that may flush some accumulated output downstream.

The step function returns a triplet of:

  • The new internal state.
  • Output that continues the last segment detected in the previous step.
  • A list of lists containing new segments detected in the current step. If the list is empty, that means no splitting has taken place in the current step.

Constructors

forall x . Splitter (x -> i -> (x, [i], [[i]])) x (x -> [i]) 

Working with groups

groups :: Splitter i -> Transduction i b -> Transduction i b Source

Applies a Transduction to all groups detected by a Splitter, returning a Transduction that works over the undivided stream of inputs.

>>> L.fold (groups (chunksOf 2) (transduce (surround "<" ">")) L.list) "aabbccdd"
"<aa><bb><cc><dd>"

groups' Source

Arguments

:: Splitter i 
-> Fold u v

for aggregating the u values produced for each group

-> Transduction' i a u 
-> Transduction' i a v

the resulting Fold will return a summary v of the stream

Generalized version of groups that obtains a summary value for each group, aggregates them into a summary value for the whole stream, and puts that information in the final result.

In practice, this function behaves like a combinaton of groups and folds that works in a single pass.

>>> L.fold (groups' (chunksOf 2) L.list (\f -> transduce (surround "<" ">") (liftA2 (,) L.list f)) L.list) "aabbccdd"
(["<aa>","<bb>","<cc>","<dd>"],"<aa><bb><cc><dd>")

groupsM' :: Monad m => Splitter i -> FoldM m u v -> TransductionM' m i a u -> TransductionM' m i a v Source

folds :: Splitter i -> Fold i b -> Transduction i b Source

Summarizes each group detected by a Splitter using a Fold, returning a Transduction that allows a Fold to accept the original ungrouped input.

foldsM :: Splitter i -> FoldM m i b -> TransductionM m i b Source

Splitters

chunksOf :: Int -> Splitter a Source

Splits a stream into chunks of fixed size.

>>> L.fold (folds (chunksOf 2) L.list L.list) [1..7]
[[1,2],[3,4],[5,6],[7]]
>>> L.fold (groups (chunksOf 2) (transduce (surround [] [0])) L.list) [1..7]
[1,2,0,3,4,0,5,6,0,7,0]

Re-exports