machines-0.7.1: Networked stream transducers

Safe HaskellNone
LanguageHaskell2010

Data.Machine.Group.General

Contents

Description

Split up input streams into groups with separator values and process the groups with their own MachineT.

Synopsis

Documentation

groupingOn :: Monad m => i -> (a -> a -> Maybe i) -> (i -> ProcessT m a b) -> ProcessT m a b Source #

Using a function to signal group changes, run a machine independently over each group with the value returned provided.

groupingOn_ :: Monad m => (a -> a -> Bool) -> ProcessT m a b -> ProcessT m a b Source #

Using a function to signal group changes, run a machine independently over each group.

groupingN :: Monad m => Int -> (Int -> ProcessT m a b) -> ProcessT m a b Source #

Run a machine repeatedly over n-element segments of the stream, providing an incrementing value to each run.

Tagging a stream

taggedState :: Monad m => s -> (a -> s -> (Maybe i, s)) -> ProcessT m a (Either i a) Source #

Mark a transition point between two groups when a state passing function returns a Just i. Examples

>>> runT $ supply [1,3,3,2] (taggedState (-1) (\x y -> (even x <$ guard (x /= y), x)))
[Left False,Right 1,Left False,Right 3,Right 3,Left True,Right 2]

taggedM :: Monad m => (a -> m (Maybe i)) -> ProcessT m a (Either i a) Source #

Mark a transition point between two groups when an action returns a Just i. Could be useful for breaking up a stream based on time passed. Examples

>>> let f x = do{ y <- ask; return (even x <$ guard (x > y)) }
>>> flip runReader 1 . runT $ supply [1,3,3,2] (taggedM f)
[Right 1,Left False,Right 3,Left False,Right 3,Left True,Right 2]

taggedOn :: Monad m => (a -> a -> Maybe i) -> ProcessT m a (Either i a) Source #

Mark a transition point between two groups as a function of adjacent elements, and insert the value returned as the separator. Examples

>>> runT $ supply [1,3,3,2] (taggedOn (\x y -> (x < y) <$ guard (x /= y)))
[Right 1,Left True,Right 3,Right 3,Left False,Right 2]

taggedOnM :: Monad m => (a -> a -> m (Maybe i)) -> ProcessT m a (Either i a) Source #

Mark a transition point between two groups using an action on adjacent elements, and insert the value returned as the separator. Examples

>>> let f x y = do{ z <- ask; return ((x + y <$ guard (z < x + y))) }
>>> flip runReader 5 . runT $ supply [1..5] (taggedOnM f)
[Right 1,Right 2,Right 3,Left 7,Right 4,Left 9,Right 5]

taggedOn_ :: Monad m => (a -> a -> Bool) -> ProcessT m a (Either () a) Source #

Mark a transition point between two groups as a function of adjacent elements. Examples

>>> runT $ supply [1,2,2] (taggedOn_ (==))
[Right 1,Left (),Right 2,Right 2]

taggedAt :: Monad m => Int -> s -> (s -> s) -> ProcessT m a (Either s a) Source #

Mark a transition point between two groups at every n values, stepping the separator by a function. Examples

>>> runT $ supply [1..5] (taggedAt 2 True not)
[Right 1,Right 2,Left True,Right 3,Right 4,Left False,Right 5]

taggedAt_ :: Monad m => Int -> ProcessT m a (Either () a) Source #

Mark a transition point between two groups at every n values. Examples

>>> runT $ supply [1..5] (taggedAt_ 2)
[Right 1,Right 2,Left (),Right 3,Right 4,Left (),Right 5]

taggedCount :: Monad m => Int -> ProcessT m a (Either Int a) Source #

Mark a transition point between two groups at every n values, using the counter as the separator. Examples

>>> runT $ supply [1..5] (taggedCount 2)
[Right 1,Right 2,Left 1,Right 3,Right 4,Left 2,Right 5]

Reset a machine for each group

partitioning :: Monad m => i -> (i -> ProcessT m a b) -> ProcessT m (Either i a) b Source #

Run a machine multiple times over partitions of the input stream specified by Left i values, passing the is to each MachineT run. Examples

>>> let input = [Right 1, Right 2,Left 1, Right 3,Left 2, Right 4]
>>> runT $ supply input (partitioning 0 (\x -> mapping (\y -> (x,y))))
[(0,1),(0,2),(1,3),(2,4)]

partitioning_ :: Monad m => ProcessT m a b -> ProcessT m (Either () a) b Source #

Run a machine multiple times over partitions of the input stream specified by Left () values. Examples

>>> let input = [Right 1,Left (),Right 3,Right 4,Left ()]
>>> runT $ supply input (partitioning_ (fold (flip (:)) []))
[[1],[4,3],[]]

Helpers

starve :: Monad m => MachineT m k0 b -> MachineT m k b -> MachineT m k b Source #

Run a machine with no input until it stops, then behave as another machine.

awaitUntil :: Monad m => (a -> Bool) -> (a -> ProcessT m a b) -> ProcessT m a b Source #

Read inputs until a condition is met, then behave as cont with input matching condition as first input of cont. If await fails, stop.