machines-0.6.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

Minimal complete definition

auto

Methods

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

Instances

Automaton (->) Source # 

Methods

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

Automaton Is Source # 

Methods

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

Automaton Moore Source # 

Methods

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

Automaton Mealy Source # 

Methods

auto :: Mealy a b -> Process 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.

process L :: Process a c -> Tee a b c
process R :: Process b c -> Tee a b c
process 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.

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.

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.

dropping :: Int -> Process a a Source #

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

taking :: Int -> Process a a Source #

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

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

A Process that drops elements while a predicate holds

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

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

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.

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.

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

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

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

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.

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

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

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

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

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

Break each input into pieces that are fed downstream individually.

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 :: Monad m => (a -> m b) -> ProcessT m a b Source #

Apply a monadic function to each element of a ProcessT.

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

Skip all but the final element of the input

final :: Process a a

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

finalOr :: a -> Process a a

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

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

Apply a function to all values coming from the input

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.