pipes-interleave-0.2.2: Interleave and merge streams of elements

Safe HaskellSafe
LanguageHaskell2010

Pipes.Interleave

Synopsis

Documentation

interleave Source

Arguments

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

ordering on elements

-> [Producer a m ()]

element producers

-> Producer a m () 

Interleave elements from a set of Producers such that the interleaved stream is increasing with respect to the given ordering.

>>> toList $ interleave compare [each [1,3..10], each [1,5..20]]
[1,1,3,5,5,7,9,9,13,17]

combine Source

Arguments

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

equality test

-> (a -> a -> a)

combine operation

-> Producer a m r 
-> Producer a m r 

Given a stream of increasing elements, combine those equal under the given equality relation

>>> let append (k,v) (_,v') = return (k, v+v')
>>> toList $ combine ((==) `on` fst) append (each [(1,1), (1,4), (2,3), (3,10)])
[(1,5),(2,3),(3,10)]

combineM Source

Arguments

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

equality test

-> (a -> a -> m a)

combine operation

-> Producer a m r 
-> Producer a m r 

combine with monadic side-effects in combine operation.

merge Source

Arguments

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

ordering on elements

-> (a -> a -> a)

combine operation

-> [Producer a m ()]

producers of elements

-> Producer a m () 

Equivalent to combine composed with interleave

>>> let append (k,v) (_,v') = return (k, v+v')
>>> let producers = [ each [(i,2) | i <- [1,3..10]], each [(i,10) | i <- [1,5..20]] ] :: [Producer (Int,Int) Identity ()]
>>> toList $ merge (compare `on` fst) append producers
[(1,12),(3,2),(5,12),(7,2),(9,12),(13,10),(17,10)]

mergeM Source

Arguments

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

ordering on elements

-> (a -> a -> m a)

combine operation

-> [Producer a m ()]

producers of elements

-> Producer a m () 

Merge with monadic side-effects in combine operation.

groupBy Source

Arguments

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

equality test

-> Producer a m r 
-> Producer [a] m r 

Split stream into groups of equal elements. Note that this is a non-local operation: if the Producer generates a large run of equal elements, all of them will remain in memory until the run ends.

>>> toList $ groupBy ((==) `on` fst) (each [(1,1), (1,4), (2,3), (3,10)])
[[(1,1),(1,4)],[(2,3)],[(3,10)]]