Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- interleave :: forall a m. (Monad m, Ord a) => [Producer a m ()] -> Producer a m ()
- combine :: (Monad m, Eq a) => (a -> a -> a) -> Producer a m r -> Producer a m r
- combineM :: (Monad m, Eq a) => (a -> a -> m a) -> Producer a m r -> Producer a m r
- merge :: (Monad m, Ord a) => (a -> a -> a) -> [Producer a m ()] -> Producer a m ()
- mergeM :: (Monad m, Ord a) => (a -> a -> m a) -> [Producer a m ()] -> Producer a m ()
- groupBy :: forall a r m. (Monad m, Ord a) => Producer a m r -> Producer [a] m r
- data Entry p a :: * -> * -> * = Entry {}
Documentation
Interleave elements from a set of Producers
such that the interleaved
stream is increasing with respect to the given ordering.
>>>
toList $ interleave [each [1,3..10], each [1,5..20]]
[1,1,3,5,5,7,9,9,13,17]
Given a stream of increasing elements, combine those that are equal.
>>>
let append (Entry k v) (Entry _ v') = Entry k (v+v')
>>>
toList $ combine append (each $ map (uncurry Entry) [(1,1), (1,4), (2,3), (3,10)])
[Entry {priority = 1, payload = 5},Entry {priority = 2, payload = 3},Entry {priority = 3, payload = 10}]
combine
with monadic side-effects in the combine operation.
:: (Monad m, Ord a) | |
=> (a -> a -> a) | combine operation |
-> [Producer a m ()] | producers of elements |
-> Producer a m () |
Equivalent to combine
composed with interleave
>>>
let append (Entry k v) (Entry _ v') = Entry k (v+v')
>>>
let producers = [ each [Entry i 2 | i <- [1,3..10]], each [Entry i 10 | i <- [1,5..20]] ] :: [Producer (Entry Int Int) Identity ()]
>>>
toList $ merge append producers
[(1,12),(3,2),(5,12),(7,2),(9,12),(13,10),(17,10)]
:: (Monad m, Ord a) | |
=> (a -> a -> m a) | combine operation |
-> [Producer a m ()] | producers of elements |
-> Producer a m () |
Merge with monadic side-effects in the combine operation.
groupBy :: forall a r m. (Monad m, Ord a) => Producer a m r -> Producer [a] m r Source #
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 (each [Entry 1 1, Entry 1 4, Entry 2 3, Entry 3 10])
[[Entry {priority = 1, payload = 1},Entry {priority = 1, payload = 4}],[Entry {priority = 2, payload = 3}],[Entry {priority = 3, payload = 10}]]