machines-0.7.1: Networked stream transducers

Copyright(C) 2012 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
PortabilityRank 2 Types, GADTs
Safe HaskellNone
LanguageHaskell2010

Data.Machine.Process

Contents

Description

 
Synopsis

Processes

type Process a b = Machine (Is a) b Source #

A Process a b is a stream transducer that can consume values of type a from its input, and produce values of type b for its output.

type ProcessT m a b = MachineT m (Is a) b Source #

A ProcessT m a b is a stream transducer that can consume values of type a from its input, and produce values of type b and has side-effects in the Monad m.

class Automaton k where Source #

An Automaton can be automatically lifted into a Process

Methods

auto :: k a b -> Process a b Source #

Instances
Automaton Is Source # 
Instance details

Defined in Data.Machine.Process

Methods

auto :: Is a b -> Process a b Source #

Automaton Moore Source # 
Instance details

Defined in Data.Machine.Moore

Methods

auto :: Moore a b -> Process a b Source #

Automaton Mealy Source # 
Instance details

Defined in Data.Machine.Mealy

Methods

auto :: Mealy a b -> Process a b Source #

Automaton ((->) :: Type -> Type -> Type) Source # 
Instance details

Defined in Data.Machine.Process

Methods

auto :: (a -> b) -> Process a b Source #

class AutomatonM x where Source #

Methods

autoT :: Monad m => x m a b -> ProcessT m a b Source #

Instances
AutomatonM Kleisli Source # 
Instance details

Defined in Data.Machine.Process

Methods

autoT :: Monad m => Kleisli m a b -> ProcessT m a b Source #

AutomatonM MealyT Source # 
Instance details

Defined in Data.Machine.MealyT

Methods

autoT :: Monad m => MealyT m a b -> ProcessT m a b Source #

AutomatonM MooreT Source # 
Instance details

Defined in Data.Machine.MooreT

Methods

autoT :: Monad m => MooreT m a b -> ProcessT m a b Source #

process :: Monad m => (forall a. k a -> i -> a) -> MachineT m k o -> ProcessT m i o Source #

Convert a machine into a process, with a little bit of help.

choose :: T a b x -> (a, b) -> x
choose t = case t of
  L -> fst
  R -> snd

process choose :: Tee a b c -> Process (a, b) c
process choose :: Tee a b c -> Process (a, b) c
process (const id) :: Process a b -> Process a b

Common Processes

(<~) :: Monad m => ProcessT m b c -> MachineT m k b -> MachineT m k c infixr 9 Source #

Build a new Machine by adding a Process to the output of an old Machine

(<~) :: Process b c -> Process a b -> Process a c
(<~) :: Process c d -> Tee a b c -> Tee a b d
(<~) :: Process b c -> Machine k b -> Machine k c

(~>) :: Monad m => MachineT m k b -> ProcessT m b c -> MachineT m k c infixl 9 Source #

Flipped (<~).

echo :: Process a a Source #

The trivial Process that simply repeats each input it receives.

This can be constructed from a plan with

echo :: Process a a
echo = repeatedly $ do
  i <- await
  yield i

Examples:

>>> run $ echo <~ source [1..5]
[1,2,3,4,5]

supply :: forall f m a b. (Foldable f, Monad m) => f a -> ProcessT m a b -> ProcessT m a b Source #

Feed a Process some input.

Examples:

>>> run $ supply [1,2,3] echo <~ source [4..6]
[1,2,3,4,5,6]

prepended :: Foldable f => f a -> Process a a Source #

A Process that prepends the elements of a Foldable onto its input, then repeats its input from there.

filtered :: (a -> Bool) -> Process a a Source #

A Process that only passes through inputs that match a predicate.

This can be constructed from a plan with

filtered :: (a -> Bool) -> Process a a
filtered p = repeatedly $ do
  i <- await
  when (p i) $ yield i

Examples:

>>> run $ filtered even <~ source [1..5]
[2,4]

dropping :: Int -> Process a a Source #

A Process that drops the first n, then repeats the rest.

This can be constructed from a plan with

dropping n = before echo $ replicateM_ n await

Examples:

>>> run $ dropping 3 <~ source [1..5]
[4,5]

taking :: Int -> Process a a Source #

A Process that passes through the first n elements from its input then stops

This can be constructed from a plan with

taking n = construct . replicateM_ n $ await >>= yield

Examples:

>>> run $ taking 3 <~ source [1..5]
[1,2,3]

droppingWhile :: (a -> Bool) -> Process a a Source #

A Process that drops elements while a predicate holds

This can be constructed from a plan with

droppingWhile :: (a -> Bool) -> Process a a
droppingWhile p = before echo loop where
  loop = await >>= v -> if p v then loop else yield v

Examples:

>>> run $ droppingWhile (< 3) <~ source [1..5]
[3,4,5]

takingWhile :: (a -> Bool) -> Process a a Source #

A Process that passes through elements until a predicate ceases to hold, then stops

This can be constructed from a plan with

takingWhile :: (a -> Bool) -> Process a a
takingWhile p = repeatedly $ await >>= v -> if p v then yield v else stop

Examples:

>>> run $ takingWhile (< 3) <~ source [1..5]
[1,2]

takingJusts :: Process (Maybe a) a Source #

A Process that passes through elements unwrapped from Just until a Nothing is found, then stops.

This can be constructed from a plan with

takingJusts :: Process (Maybe a) a
takingJusts = repeatedly $ await >>= maybe stop yield

Examples:

>>> run $ takingJusts <~ source [Just 1, Just 2, Nothing, Just 3, Just 4]
[1,2]

buffered :: Int -> Process a [a] Source #

Chunk up the input into n element lists.

Avoids returning empty lists and deals with the truncation of the final group.

An approximation of this can be constructed from a plan with

buffered :: Int -> Process a [a]
buffered = repeatedly . go [] where
  go acc 0 = yield (reverse acc)
  go acc n = do
    i await <| yield (reverse acc) *> stop
    go (i:acc) $! n-1

Examples:

>>> run $ buffered 3 <~ source [1..6]
[[1,2,3],[4,5,6]]
>>> run $ buffered 3 <~ source [1..5]
[[1,2,3],[4,5]]
>>> run $ buffered 3 <~ source []
[]

flattened :: Foldable f => Process (f a) a Source #

Break each input into pieces that are fed downstream individually.

Alias for asParts

fold :: Category k => (a -> b -> a) -> a -> Machine (k b) a Source #

Construct a Process from a left-folding operation.

Like scan, but only yielding the final value.

It may be useful to consider this alternative signature

fold :: (a -> b -> a) -> a -> Process b a

This can be constructed from a plan with

fold :: Category k => (a -> b -> a) -> a -> Machine (k b) a
fold func seed = construct $ go seed where
  go cur = do
    next await <| yield cur *> stop
    go $! func cur next

Examples:

>>> run $ fold (+) 0 <~ source [1..5]
[15]
>>> run $ fold (\a _ -> a + 1) 0 <~ source [1..5]
[5]

fold1 :: Category k => (a -> a -> a) -> Machine (k a) a Source #

fold1 is a variant of fold that has no starting value argument

This can be constructed from a plan with

fold1 :: Category k => (a -> a -> a) -> Machine (k a) a
fold1 func = construct $ await >>= go where
  go cur = do
    next await <| yield cur *> stop
    go $! func cur next

Examples:

>>> run $ fold1 (+) <~ source [1..5]
[15]

scan :: Category k => (a -> b -> a) -> a -> Machine (k b) a Source #

Construct a Process from a left-scanning operation.

Like fold, but yielding intermediate values.

It may be useful to consider this alternative signature

scan :: (a -> b -> a) -> a -> Process b a

For stateful scan use auto with Data.Machine.Mealy machine. This can be constructed from a plan with

scan :: Category k => (a -> b -> a) -> a -> Machine (k b) a
scan func seed = construct $ go seed where
  go cur = do
    yield cur
    next <- await
    go $! func cur next

Examples:

>>> run $ scan (+) 0 <~ source [1..5]
[0,1,3,6,10,15]
>>> run $ scan (\a _ -> a + 1) 0 <~ source [1..5]
[0,1,2,3,4,5]

scan1 :: Category k => (a -> a -> a) -> Machine (k a) a Source #

scan1 is a variant of scan that has no starting value argument

This can be constructed from a plan with

scan1 :: Category k => (a -> a -> a) -> Machine (k a) a
scan1 func = construct $ await >>= go where
  go cur = do
    yield cur
    next <- await
    go $! func cur next

Examples:

>>> run $ scan1 (+) <~ source [1..5]
[1,3,6,10,15]

scanMap :: (Category k, Monoid b) => (a -> b) -> Machine (k a) b Source #

Like scan only uses supplied function to map and uses Monoid for associative operation

Examples:

>>> run $ mapping getSum <~ scanMap Sum <~ source [1..5]
[0,1,3,6,10,15]

asParts :: Foldable f => Process (f a) a Source #

Break each input into pieces that are fed downstream individually.

This can be constructed from a plan with

asParts :: Foldable f => Process (f a) a
asParts = repeatedly $ await >>= traverse_ yield

Examples:

>>> run $ asParts <~ source [[1..3],[4..6]]
[1,2,3,4,5,6]

sinkPart_ :: Monad m => (a -> (b, c)) -> ProcessT m c Void -> ProcessT m a b Source #

sinkPart_ toParts sink creates a process that uses the toParts function to break input into a tuple of (passAlong, sinkPart) for which the second projection is given to the supplied sink ProcessT (that produces no output) while the first projection is passed down the pipeline.

autoM :: (Category k, Monad m) => (a -> m b) -> MachineT m (k a) b Source #

Apply a monadic function to each element of a ProcessT.

This can be constructed from a plan with

autoM :: Monad m => (a -> m b) -> ProcessT m a b
autoM :: (Category k, Monad m) => (a -> m b) -> MachineT m (k a) b
autoM f = repeatedly $ await >>= lift . f >>= yield

Examples:

>>> runT $ autoM Left <~ source [3, 4]
Left 3
>>> runT $ autoM Right <~ source [3, 4]
Right [3,4]

final :: Category k => Machine (k a) a Source #

Skip all but the final element of the input

This can be constructed from a plan with

final :: Process a a
final :: Category k => Machine (k a) a
final = construct $ await >>= go where
  go prev = do
    next await <| yield prev *> stop
    go next

Examples:

>>> runT $ final <~ source [1..10]
[10]
>>> runT $ final <~ source []
[]

finalOr :: Category k => a -> Machine (k a) a Source #

Skip all but the final element of the input. If the input is empty, the default value is emitted

This can be constructed from a plan with

finalOr :: a -> Process a a
finalOr :: Category k => a -> Machine (k a) a
finalOr = construct . go where
  go prev = do
    next await <| yield prev *> stop
    go next

Examples:

>>> runT $ finalOr (-1) <~ source [1..10]
[10]
>>> runT $ finalOr (-1) <~ source []
[-1]

intersperse :: Category k => a -> Machine (k a) a Source #

Intersperse an element between the elements of the input

intersperse :: a -> Process a a

largest :: (Category k, Ord a) => Machine (k a) a Source #

Return the maximum value from the input

smallest :: (Category k, Ord a) => Machine (k a) a Source #

Return the minimum value from the input

sequencing :: (Category k, Monad m) => MachineT m (k (m a)) a Source #

Convert a stream of actions to a stream of values

This can be constructed from a plan with

sequencing :: Monad m => (a -> m b) -> ProcessT m a b
sequencing :: (Category k, Monad m) => MachineT m (k (m a)) a
sequencing = repeatedly $ do
  ma <- await
  a  <- lift ma
  yield a

Examples:

>>> runT $ sequencing <~ source [Just 3, Nothing]
Nothing
>>> runT $ sequencing <~ source [Just 3, Just 4]
Just [3,4]

mapping :: Category k => (a -> b) -> Machine (k a) b Source #

Apply a function to all values coming from the input

This can be constructed from a plan with

mapping :: Category k => (a -> b) -> Machine (k a) b
mapping f = repeatedly $ await >>= yield . f

Examples:

>>> runT $ mapping (*2) <~ source [1..3]
[2,4,6]

traversing :: (Category k, Monad m) => (a -> m b) -> MachineT m (k a) b Source #

Apply an effectful to all values coming from the input.

Alias to autoM.

reading :: (Category k, Read a) => Machine (k String) a Source #

Parse Readable values, only emitting the value if the parse succceeds. This Machine stops at first parsing error

showing :: (Category k, Show a) => Machine (k a) String Source #

Convert Showable values to Strings

strippingPrefix :: (Eq b, Monad m) => MachineT m (k a) b -> MachineT m (k a) b -> MachineT m (k a) b Source #

strippingPrefix mp mb Drops the given prefix from mp. It stops if mb did not start with the prefix given, or continues streaming after the prefix, if mb did.