rhine-1.0: Functional Reactive Programming with type-level clocks
Safe HaskellSafe-Inferred
LanguageHaskell2010

FRP.Rhine.Schedule

Description

The MonadSchedule class from the monad-schedule package is the compatibility mechanism between two different clocks. It implements a concurrency abstraction that allows the clocks to run at the same time, independently. Several such clocks running together form composite clocks, such as ParallelClock and SequentialClock. This module defines these composite clocks, and utilities to work with them.

Synopsis

Scheduling

scheduleList :: (Monad m, MonadSchedule m) => NonEmpty (MSF m a b) -> MSF m a (NonEmpty b) Source #

runningSchedule :: (Monad m, MonadSchedule m, Clock m cl1, Clock m cl2, Time cl1 ~ Time cl2) => cl1 -> cl2 -> RunningClock m (Time cl1) (Tag cl1) -> RunningClock m (Time cl2) (Tag cl2) -> RunningClock m (Time cl1) (Either (Tag cl1) (Tag cl2)) Source #

Two clocks in the ScheduleT monad transformer can always be canonically scheduled. Indeed, this is the purpose for which ScheduleT was defined.

initSchedule :: (Time cl1 ~ Time cl2, Monad m, MonadSchedule m, Clock m cl1, Clock m cl2) => cl1 -> cl2 -> RunningClockInit m (Time cl1) (Either (Tag cl1) (Tag 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.

Composite clocks

Sequentially combined clocks

data SequentialClock cl1 cl2 Source #

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

Constructors

Time cl1 ~ Time cl2 => SequentialClock 

Fields

Instances

Instances details
(Monad m, MonadSchedule m, Clock m cl1, Clock m cl2) => Clock m (SequentialClock cl1 cl2) Source # 
Instance details

Defined in FRP.Rhine.Schedule

Associated Types

type Time (SequentialClock cl1 cl2) Source #

type Tag (SequentialClock cl1 cl2) Source #

(GetClockProxy cl1, GetClockProxy cl2) => GetClockProxy (SequentialClock cl1 cl2) Source # 
Instance details

Defined in FRP.Rhine.Clock.Proxy

type Tag (SequentialClock cl1 cl2) Source # 
Instance details

Defined in FRP.Rhine.Schedule

type Tag (SequentialClock cl1 cl2) = Either (Tag cl1) (Tag cl2)
type Time (SequentialClock cl1 cl2) Source # 
Instance details

Defined in FRP.Rhine.Schedule

type Time (SequentialClock cl1 cl2) = Time cl1

type SeqClock cl1 cl2 = SequentialClock cl1 cl2 Source #

Abbrevation synonym.

Parallelly combined clocks

data ParallelClock cl1 cl2 Source #

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

Constructors

Time cl1 ~ Time cl2 => ParallelClock 

Fields

Instances

Instances details
(Monad m, MonadSchedule m, Clock m cl1, Clock m cl2) => Clock m (ParallelClock cl1 cl2) Source # 
Instance details

Defined in FRP.Rhine.Schedule

Associated Types

type Time (ParallelClock cl1 cl2) Source #

type Tag (ParallelClock cl1 cl2) Source #

Methods

initClock :: ParallelClock cl1 cl2 -> RunningClockInit m (Time (ParallelClock cl1 cl2)) (Tag (ParallelClock cl1 cl2)) Source #

(GetClockProxy cl1, GetClockProxy cl2) => GetClockProxy (ParallelClock cl1 cl2) Source # 
Instance details

Defined in FRP.Rhine.Clock.Proxy

type Tag (ParallelClock cl1 cl2) Source # 
Instance details

Defined in FRP.Rhine.Schedule

type Tag (ParallelClock cl1 cl2) = Either (Tag cl1) (Tag cl2)
type Time (ParallelClock cl1 cl2) Source # 
Instance details

Defined in FRP.Rhine.Schedule

type Time (ParallelClock cl1 cl2) = Time cl1

type ParClock cl1 cl2 = ParallelClock cl1 cl2 Source #

Abbrevation synonym.

Navigating the clock tree

type family In cl where ... Source #

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

Equations

In (SequentialClock cl1 cl2) = In cl1 
In (ParallelClock cl1 cl2) = ParallelClock (In cl1) (In cl2) 
In cl = cl 

type family Out cl where ... Source #

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

Equations

Out (SequentialClock cl1 cl2) = Out cl2 
Out (ParallelClock cl1 cl2) = ParallelClock (Out cl1) (Out cl2) 
Out 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 cl1 cl2) 
ParallelLastTime :: LastTime cl1 -> LastTime cl2 -> LastTime (ParallelClock cl1 cl2) 
LeafLastTime :: Time 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.