pipes-group-1.0.0: Group streams into substreams

Safe HaskellNone

Pipes.Group

Contents

Description

Element-agnostic grouping utilities for pipes

See Pipes.Group.Tutorial for an extended tutorial

Synopsis

Lenses

groupsBy :: Monad m => (a -> a -> Bool) -> Lens' (Producer a m x) (FreeT (Producer a m) m x)Source

groupsBy splits a Producer into a FreeT of Producers grouped using the given equality predicate

groups :: (Monad m, Eq a) => Lens' (Producer a m x) (FreeT (Producer a m) m x)Source

Like groupsBy, where the equality predicate is (==)

chunksOf :: Monad m => Int -> Lens' (Producer a m x) (FreeT (Producer a m) m x)Source

chunksOf is an splits a Producer into a FreeT of Producers of fixed length

Transformations

takes :: (Functor f, Monad m) => Int -> FreeT f m () -> FreeT f m ()Source

(takes n) only keeps the first n functor layers of a FreeT

You can think of this as:

 takes
     :: (Functor f, Monad m)
     => Int -> FreeT (Producer a m) m () -> FreeT (Producer a m) m ()

takes' :: Monad m => Int -> FreeT (Producer a m) m x -> FreeT (Producer a m) m xSource

(takes' n) only keeps the first n Producers of a FreeT

takes' differs from takes by draining unused Producers in order to preserve the return value. This makes it a suitable argument for maps.

drops :: Monad m => Int -> FreeT (Producer a m) m x -> FreeT (Producer a m) m xSource

(drops n) peels off the first n Producer layers of a FreeT

Use carefully: the peeling off is not free. This runs the first n layers, just discarding everything they produce.

maps :: (Monad m, Functor g) => (forall r. f r -> g r) -> FreeT f m x -> FreeT g m xSource

Transform each individual functor layer of a FreeT

You can think of this as:

 maps
     :: (forall r . Producer a m r -> Producer b m r)
     -> FreeT (Producer a m) m x -> FreeT (Producer b m) m x

This is just a synonym for transFreeT

individually :: (Monad m, Functor g) => Setter (FreeT f m x) (FreeT g m x) (f (FreeT f m x)) (g (FreeT f m x))Source

Lens to transform each individual functor layer of a FreeT

 over individually = maps  -- ... with a less general type

Joiners

concats :: Monad m => FreeT (Producer a m) m x -> Producer a m xSource

Join a FreeT-delimited stream of Producers into a single Producer

intercalates :: Monad m => Producer a m () -> FreeT (Producer a m) m x -> Producer a m xSource

Join a FreeT-delimited stream of Producers into a single Producer by intercalating a Producer in between them

Folds

These folds are designed to be compatible with the foldl library. See the purely and impurely functions from that library for more details.

For example, to count the number of Producer layers in a FreeT, you can write:

 import Control.Applicative (pure)
 import qualified Control.Foldl as L
 import Pipes.Group
 import qualified Pipes.Prelude as P

 count :: Monad m => FreeT (Producer a m) m () -> m Int
 count = P.sum . L.purely folds (pure 1)

foldsSource

Arguments

:: Monad m 
=> (x -> a -> x)

Step function

-> x

Initial accumulator

-> (x -> b)

Extraction function

-> FreeT (Producer a m) m r 
-> Producer b m r 

Fold each Producer of a FreeT

 purely folds
     :: Monad m => Fold a b -> FreeT (Producer a m) m r -> Producer b m r

foldsMSource

Arguments

:: Monad m 
=> (x -> a -> m x)

Step function

-> m x

Initial accumulator

-> (x -> m b)

Extraction function

-> FreeT (Producer a m) m r 
-> Producer b m r 

Fold each Producer of a FreeT, monadically

 impurely foldsM
     :: Monad m => FoldM a b -> FreeT (Producer a m) m r -> Producer b m r

Re-exports

module Pipes