| Portability | Rank 2 Types, GADTs | 
|---|---|
| Stability | provisional | 
| Maintainer | Edward Kmett <ekmett@gmail.com> | 
| Safe Haskell | None | 
Data.Machine.Process
Contents
Description
- type Process a b = Machine (Is a) b
 - type ProcessT m a b = MachineT m (Is a) b
 - class Automaton k where
 - process :: Monad m => (forall a. k a -> i -> a) -> MachineT m k o -> ProcessT m i o
 - (<~) :: Monad m => ProcessT m b c -> MachineT m k b -> MachineT m k c
 - (~>) :: Monad m => MachineT m k b -> ProcessT m b c -> MachineT m k c
 - echo :: Process a a
 - supply :: Monad m => [a] -> ProcessT m a b -> ProcessT m a b
 - prepended :: Foldable f => f a -> Process a a
 - filtered :: (a -> Bool) -> Process a a
 - dropping :: Int -> Process a a
 - taking :: Int -> Process a a
 - droppingWhile :: (a -> Bool) -> Process a a
 - takingWhile :: (a -> Bool) -> Process a a
 - buffered :: Int -> Process a [a]
 
Processes
type Process a b = Machine (Is a) bSource
A  is a stream transducer that can consume values of type Process a ba
 from its input, and produce values of type b for its output.
Common Processes
filtered :: (a -> Bool) -> Process a aSource
A Process that only passes through inputs that match a predicate.
taking :: Int -> Process a aSource
A Process that passes through the first n elements from its input then stops
droppingWhile :: (a -> Bool) -> Process a aSource
A Process that drops elements while a predicate holds
takingWhile :: (a -> Bool) -> Process a aSource
A Process that passes through elements until a predicate ceases to hold, then stops