machines-0.1.1: Networked stream transducers

Portabilityrank-2, GADTs
Stabilityprovisional
MaintainerEdward Kmett <ekmett@gmail.com>
Safe HaskellSafe-Infered

Data.Machine.Type

Contents

Description

 

Synopsis

Machines

newtype MachineT m k i 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 i o (MachineT m k i o))
 

Instances

(~ (* -> * -> *) k Is, Monad m) => Category (MachineT m k)

Eventually this will probably revert to instance Monad m => Category (MachineT m Is)

(Monad m, Profunctor k) => Profunctor (MachineT m k) 
Monad m => Functor (MachineT m k i) 
~ (* -> *) m Identity => Foldable (MachineT m k i)

This permits toList to be used on a Machine.

data Step k i o r Source

This is the base functor for a Machine or MachineT.

Note: Machines are usually constructed from Plan, so this does not need to be CPS'd.

Constructors

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

Instances

Functor (Step k i o) 

type Machine k i o = forall m. Monad m => MachineT m k i oSource

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 a b -> m ()Source

Stop feeding input into model, taking only the effects.

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

Stop feeding input into model and extract an answer

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

Run a pure machine and extract an answer.

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

Pack a Step of a Machine into a Machine.

Building machines from plans

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

Compile a machine to a model.

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

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 i o -> PlanT k i o m a -> MachineT m k i oSource

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

Reshaping machines

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

Connect different kinds of machines.

fit id = id
 fit id :: Process a b -> Process a b

pass :: k i o -> Machine k i oSource

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 a bSource

This is a stopped Machine