rhine-0.1.1.0: Functional Reactive Programming with type-level clocks

Safe HaskellNone
LanguageHaskell2010

FRP.Rhine.Schedule

Contents

Synopsis

The schedule type

data Schedule m cl1 cl2 Source #

A schedule implements a combination of two clocks. It outputs a time stamp and an Either value, which specifies which of the two subclocks has ticked.

Constructors

TimeDomainOf cl1 ~ TimeDomainOf cl2 => Schedule 

Fields

Utilities to create new schedules from existing ones

hoistSchedule :: (Monad m1, Monad m2) => (forall a. m1 a -> m2 a) -> Schedule m1 cl1 cl2 -> Schedule m2 cl1 cl2 Source #

Lift a schedule along a monad morphism.

flipSchedule :: Monad m => Schedule m cl1 cl2 -> Schedule m cl2 cl1 Source #

Swaps the clocks for a given schedule.

Composite clocks

data SequentialClock m cl1 cl2 Source #

Two clocks can be combined with a schedule as a clock for an asynchronous sequential composition of signal functions.

Constructors

(TimeDomainOf cl1 ~ TimeDomainOf cl2) => SequentialClock 

Fields

Instances

(Monad m, Clock m cl1, Clock m cl2) => Clock m (SequentialClock m cl1 cl2) Source # 

Associated Types

type TimeDomainOf (SequentialClock m cl1 cl2) :: * Source #

type Tag (SequentialClock m cl1 cl2) :: * Source #

Methods

startClock :: SequentialClock m cl1 cl2 -> m (MSF m () (TimeDomainOf (SequentialClock m cl1 cl2), Tag (SequentialClock m cl1 cl2)), TimeDomainOf (SequentialClock m cl1 cl2)) Source #

type TimeDomainOf (SequentialClock m cl1 cl2) Source # 
type Tag (SequentialClock m cl1 cl2) Source # 
type Tag (SequentialClock m cl1 cl2) = Either (Tag cl1) (Tag cl2)

data ParallelClock m cl1 cl2 Source #

Two clocks can be combined with a schedule as a clock for an asynchronous parallel composition of signal functions.

Constructors

(TimeDomainOf cl1 ~ TimeDomainOf cl2) => ParallelClock 

Fields

Instances

(Monad m, Clock m cl1, Clock m cl2) => Clock m (ParallelClock m cl1 cl2) Source # 

Associated Types

type TimeDomainOf (ParallelClock m cl1 cl2) :: * Source #

type Tag (ParallelClock m cl1 cl2) :: * Source #

Methods

startClock :: ParallelClock m cl1 cl2 -> m (MSF m () (TimeDomainOf (ParallelClock m cl1 cl2), Tag (ParallelClock m cl1 cl2)), TimeDomainOf (ParallelClock m cl1 cl2)) Source #

type TimeDomainOf (ParallelClock m cl1 cl2) Source # 
type TimeDomainOf (ParallelClock m cl1 cl2) = TimeDomainOf cl1
type Tag (ParallelClock m cl1 cl2) Source # 
type Tag (ParallelClock m cl1 cl2) = Either (Tag cl1) (Tag cl2)

Navigating the clock tree

type family Leftmost cl where ... Source #

The clock that represents the rate at which data enters the system.

Equations

Leftmost (SequentialClock m cl1 cl2) = Leftmost cl1 
Leftmost (ParallelClock m cl1 cl2) = ParallelClock m (Leftmost cl1) (Leftmost cl2) 
Leftmost cl = cl 

type family Rightmost cl where ... Source #

The clock that represents the rate at which data leaves the system.

Equations

Rightmost (SequentialClock m cl1 cl2) = Rightmost cl2 
Rightmost (ParallelClock m cl1 cl2) = ParallelClock m (Rightmost cl1) (Rightmost cl2) 
Rightmost cl = cl 

data LastTime cl where Source #

A tree representing possible last times to which the constituents of a clock may have ticked.

Constructors

SequentialLastTime :: LastTime cl1 -> LastTime cl2 -> LastTime (SequentialClock m cl1 cl2) 
ParallelLastTime :: LastTime cl1 -> LastTime cl2 -> LastTime (ParallelClock m cl1 cl2) 
LeafLastTime :: TimeDomainOf cl -> LastTime cl 

data ParClockInclusion clS cl where Source #

An inclusion of a clock into a tree of parallel compositions of clocks.

parClockTagInclusion :: ParClockInclusion clS cl -> Tag clS -> Tag cl Source #

Generates a tag for the composite clock from a tag of a leaf clock, given a parallel clock inclusion.