machines-0.4: Networked stream transducers

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

Data.Machine.Type

Contents

Description

 

Synopsis

Machines

newtype MachineT m k o Source

A MachineT reads from a number of inputs and may yield results before stopping with monadic side-effects.

Constructors

MachineT 

Fields

runMachineT :: m (Step k o (MachineT m k o))
 

Instances

Monad m => Functor (MachineT m k) 
(Monad m, Appliance k) => Applicative (MachineT m k) 
(~) (* -> *) m Identity => Foldable (MachineT m k)

This permits toList to be used on a Machine.

Monad m => Pointed (MachineT m k) 

data Step k o r Source

This is the base functor for a Machine or MachineT.

Note: A Machine is usually constructed from Plan, so it does not need to be CPS'd.

Constructors

Stop 
Yield o r 
forall t . Await (t -> r) (k t) r 

Instances

Functor (Step k o) 

type Machine k o = forall m. Monad m => MachineT m k o Source

A Machine reads from a number of inputs and may yield results before stopping.

A Machine can be used as a MachineT m for any Monad m.

runT_ :: Monad m => MachineT m k b -> m () Source

Stop feeding input into model, taking only the effects.

runT :: Monad m => MachineT m k b -> m [b] Source

Stop feeding input into model and extract an answer

run :: MachineT Identity k b -> [b] Source

Run a pure machine and extract an answer.

encased :: Monad m => Step k o (MachineT m k o) -> MachineT m k o Source

Pack a Step of a Machine into a Machine.

Building machines from plans

construct :: Monad m => PlanT k o m a -> MachineT m k o Source

Compile a machine to a model.

repeatedly :: Monad m => PlanT k o m a -> MachineT m k o Source

Generates a model that runs a machine until it stops, then start it up again.

repeatedly m = construct (forever m)

before :: Monad m => MachineT m k o -> PlanT k o m a -> MachineT m k o Source

Evaluate a machine until it stops, and then yield answers according to the supplied model.

Deconstructing machines back into plans

deconstruct :: Monad m => MachineT m k (Either a o) -> PlanT k o m a Source

tagDone :: Monad m => (o -> Bool) -> MachineT m k o -> MachineT m k (Either o o) Source

Use a predicate to mark a yielded value as the terminal value of this Machine. This is useful in combination with deconstruct to combine Plans.

finishWith :: Monad m => (o -> Maybe r) -> MachineT m k o -> MachineT m k (Either r o) Source

Use a function to produce and mark a yielded value as the terminal value of a Machine. All yielded values for which the given function returns Nothing are yielded down the pipeline, but the first value for which the function returns a Just value will be returned by a Plan created via deconstruct.

Reshaping machines

fit :: Monad m => (forall a. k a -> k' a) -> MachineT m k o -> MachineT m k' o Source

Connect different kinds of machines.

fit id = id

fitM :: (Monad m, Monad m') => (forall a. m a -> m' a) -> MachineT m k o -> MachineT m' k o Source

pass :: k o -> Machine k o Source

Given a handle, ignore all other inputs and just stream input from that handle.

pass id :: Process a a
pass L  :: Tee a b a
pass R  :: Tee a b b
pass X  :: Wye a b a
pass Y  :: Wye a b b
pass Z  :: Wye a b (Either a b)

stopped :: Machine k b Source

This is a stopped Machine

Applicative Machines

class Appliance k where Source

An input type that supports merging requests from multiple machines.

Methods

applied :: Monad m => MachineT m k (a -> b) -> MachineT m k a -> MachineT m k b Source