pipes-group-1.0.4: Group streams into substreams

Safe HaskellSafe
LanguageHaskell2010

Pipes.Group

Contents

Description

Element-agnostic grouping utilities for pipes

See Pipes.Group.Tutorial for an extended tutorial

Some type signatures below refer to the aliases below, which are not used in this library, but are included to simplify the documentation.

type Groups         a m x = FreeT (Producer a m) m x
type Splitter       a m x = Producer a m x -> Groups a m x
type Transformation a m x = Groups a m x -> Groups a m x
type Joiner         a m x = Groups a m x -> Producer a m x

Synopsis

Lenses

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

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

     groups :: Monad m => Lens' (Producer a m x) (Groups a m x)
view groups :: Monad m => Splitter a m x
set  groups :: Monad m => Groups a m x -> Producer a m x -> Producer a m x
over groups :: Monad m => Transformation a m x -> Producer a m x -> Producer a m x
>>> import Lens.Family (view)
>>> import Pipes (yield, each)
>>> import Pipes.Prelude (toList)
>>> (toList . intercalates (yield '|') . view groups) (each "12233345")
"1|22|333|4|5"

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

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

      groupsBy p  :: Monad m => Lens' (Producer a m x) (Groups a m x)
view (groupsBy p) :: Monad m => Splitter a m x
set  (groupsBy p) :: Monad m => Groups a m x -> Producer a m x -> Producer a m x
over (groupsBy p) :: Monad m => Transformation a m x -> Producer a m x -> Producer a m x
>>> import Lens.Family (view)
>>> import Pipes (yield, each)
>>> import Pipes.Prelude (toList)
>>> (toList . intercalates (yield '|') . view (groupsBy (==))) (each "12233345")
"1|22|333|4|5"

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

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

This differs from groupsBy by comparing successive elements for equality instead of comparing each element to the first member of the group

>>> import Lens.Family (view)
>>> import Pipes (yield, each)
>>> import Pipes.Prelude (toList)
>>> let cmp c1 c2 = succ c1 == c2
>>> (toList . intercalates (yield '|') . view (groupsBy' cmp)) (each "12233345")
"12|23|3|345"
>>> (toList . intercalates (yield '|') . view (groupsBy  cmp)) (each "12233345")
"122|3|3|34|5"
      groupsBy' p  :: Monad m => Lens' (Producer a m x) (Groups a m x)
view (groupsBy' p) :: Monad m => Splitter a m x
set  (groupsBy' p) :: Monad m => Groups a m x -> Producer a m x -> Producer a m x
over (groupsBy' p) :: Monad m => Transformation a m x -> Producer a m x -> Producer a m x

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

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

      chunksOf n  :: Monad m => Lens' (Producer a m x) (Groups a m x)
view (chunksOf n) :: Monad m => Splitter a m x
set  (chunksOf n) :: Monad m => Groups a m x -> Producer a m x -> Producer a m x
over (chunksOf n) :: Monad m => Transformation a m x -> Producer a m x -> Producer a m x
>>> import Lens.Family (view)
>>> import Pipes (yield, each)
>>> import Pipes.Prelude (toList)
>>> (toList . intercalates (yield '|') . view (chunksOf 3)) (each "12233345")
"122|333|45"

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

takes :: Monad m => Int -> Groups a m () -> Groups a m ()
>>> import Lens.Family (view)
>>> import Pipes (yield, each)
>>> import Pipes.Prelude (toList)
>>> (toList . intercalates (yield '|') . takes 3 . view groups) (each "12233345")
"1|22|333"

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

(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.

takes' :: Monad m => Int -> Transformation a m x

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

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

drops :: Monad m => Int -> Transformation a m x
>>> import Lens.Family (view)
>>> import Pipes (yield, each)
>>> import Pipes.Prelude (toList)
>>> (toList . intercalates (yield '|') . drops 3 . view groups) (each "12233345")
"4|5"

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 x Source #

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) is equivalent to maps, but with a less general type.

type Group a m x = Producer a m (Groups a m x)

set  individually :: Monad m => Group a m x -> Transformation a m x
over individually :: Monad m => (Group a m x -> Group a m x) -> Transformation a m x

Joiners

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

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

concats :: Monad m => Joiner a m x

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

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

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

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)

folds Source #

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 -> Groups a m r -> Producer b m r

foldsM Source #

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 -> Groups a m r -> Producer b m r

Re-exports

module Pipes