Safe Haskell | None |
---|---|
Language | Haskell2010 |
Schedule
s are the compatibility mechanism between two different clocks.
A schedule' implements the the universal clocks such that those two given clocks
are its subclocks.
This module defines the Schedule
type and certain general constructions of schedules,
such as lifting along monad morphisms or time domain morphisms.
It also supplies (sequential and parallel) compositions of clocks.
Specific implementations of schedules are found in submodules.
Synopsis
- data Schedule m cl1 cl2 = Time cl1 ~ Time cl2 => Schedule {
- initSchedule :: cl1 -> cl2 -> RunningClockInit m (Time cl1) (Either (Tag cl1) (Tag cl2))
- hoistSchedule :: (Monad m1, Monad m2) => (forall a. m1 a -> m2 a) -> Schedule m1 cl1 cl2 -> Schedule m2 cl1 cl2
- flipSchedule :: Monad m => Schedule m cl1 cl2 -> Schedule m cl2 cl1
- rescaledSchedule :: Monad m => Schedule m cl1 cl2 -> Schedule m (RescaledClock cl1 time) (RescaledClock cl2 time)
- rescaledScheduleS :: Monad m => Schedule m cl1 cl2 -> Schedule m (RescaledClockS m cl1 time tag1) (RescaledClockS m cl2 time tag2)
- readerSchedule :: (Monad m, Clock (ReaderT r m) cl1, Clock (ReaderT r m) cl2, Time cl1 ~ Time cl2) => Schedule m (HoistClock (ReaderT r m) m cl1) (HoistClock (ReaderT r m) m cl2) -> Schedule (ReaderT r m) cl1 cl2
- data SequentialClock m cl1 cl2 = Time cl1 ~ Time cl2 => SequentialClock {
- sequentialCl1 :: cl1
- sequentialCl2 :: cl2
- sequentialSchedule :: Schedule m cl1 cl2
- type SeqClock m cl1 cl2 = SequentialClock m cl1 cl2
- schedSeq1 :: (Monad m, Semigroup cl1) => Schedule m cl1 (SequentialClock m cl1 cl2)
- schedSeq2 :: (Monad m, Semigroup cl2, Time cl1 ~ Time cl2) => Schedule m (SequentialClock m cl1 cl2) cl2
- data ParallelClock m cl1 cl2 = Time cl1 ~ Time cl2 => ParallelClock {
- parallelCl1 :: cl1
- parallelCl2 :: cl2
- parallelSchedule :: Schedule m cl1 cl2
- type ParClock m cl1 cl2 = ParallelClock m cl1 cl2
- schedPar1 :: (Monad m, Semigroup cl1) => Schedule m cl1 (ParallelClock m cl1 cl2)
- schedPar1' :: (Monad m, Semigroup cl1) => Schedule m cl1 (ParallelClock m cl1 cl2)
- schedPar2 :: (Monad m, Semigroup cl2, Time cl1 ~ Time cl2) => Schedule m (ParallelClock m cl1 cl2) cl2
- schedPar2' :: (Monad m, Semigroup cl2, Time cl1 ~ Time cl2) => Schedule m (ParallelClock m cl1 cl2) cl2
- type family In cl where ...
- type family Out cl where ...
- data LastTime cl where
- SequentialLastTime :: LastTime cl1 -> LastTime cl2 -> LastTime (SequentialClock m cl1 cl2)
- ParallelLastTime :: LastTime cl1 -> LastTime cl2 -> LastTime (ParallelClock m cl1 cl2)
- LeafLastTime :: Time cl -> LastTime cl
- data ParClockInclusion clS cl where
- ParClockInL :: ParClockInclusion (ParallelClock m clL clR) cl -> ParClockInclusion clL cl
- ParClockInR :: ParClockInclusion (ParallelClock m clL clR) cl -> ParClockInclusion clR cl
- ParClockRefl :: ParClockInclusion cl cl
- parClockTagInclusion :: ParClockInclusion clS cl -> Tag clS -> Tag cl
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.
Time cl1 ~ Time cl2 => Schedule | |
|
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.
rescaledSchedule :: Monad m => Schedule m cl1 cl2 -> Schedule m (RescaledClock cl1 time) (RescaledClock cl2 time) Source #
If a schedule works for two clocks, a rescaling of the clocks also applies to the schedule.
rescaledScheduleS :: Monad m => Schedule m cl1 cl2 -> Schedule m (RescaledClockS m cl1 time tag1) (RescaledClockS m cl2 time tag2) Source #
As rescaledSchedule
, with a stateful rescaling
readerSchedule :: (Monad m, Clock (ReaderT r m) cl1, Clock (ReaderT r m) cl2, Time cl1 ~ Time cl2) => Schedule m (HoistClock (ReaderT r m) m cl1) (HoistClock (ReaderT r m) m cl2) -> Schedule (ReaderT r m) cl1 cl2 Source #
Lifts a schedule into the ReaderT
transformer,
supplying the same environment to its scheduled clocks.
Composite clocks
Sequentially combined 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 networks.
Time cl1 ~ Time cl2 => SequentialClock | |
|
Instances
(Monad m, Clock m cl1, Clock m cl2) => Clock m (SequentialClock m cl1 cl2) Source # | |
Defined in FRP.Rhine.Schedule type Time (SequentialClock m cl1 cl2) Source # type Tag (SequentialClock m cl1 cl2) Source # initClock :: SequentialClock m cl1 cl2 -> RunningClockInit m (Time (SequentialClock m cl1 cl2)) (Tag (SequentialClock m cl1 cl2)) Source # | |
(GetClockProxy cl1, GetClockProxy cl2) => GetClockProxy (SequentialClock m cl1 cl2) Source # | |
Defined in FRP.Rhine.Clock.Proxy getClockProxy :: ClockProxy (SequentialClock m cl1 cl2) Source # | |
type Time (SequentialClock m cl1 cl2) Source # | |
Defined in FRP.Rhine.Schedule | |
type Tag (SequentialClock m cl1 cl2) Source # | |
Defined in FRP.Rhine.Schedule |
type SeqClock m cl1 cl2 = SequentialClock m cl1 cl2 Source #
Abbrevation synonym.
schedSeq1 :: (Monad m, Semigroup cl1) => Schedule m cl1 (SequentialClock m cl1 cl2) Source #
cl1
is a subclock of SequentialClock m cl1 cl2
,
therefore it is always possible to schedule these two clocks deterministically.
The left subclock of the combined clock always ticks instantly after cl1
.
schedSeq2 :: (Monad m, Semigroup cl2, Time cl1 ~ Time cl2) => Schedule m (SequentialClock m cl1 cl2) cl2 Source #
As schedSeq1
, but for the right subclock.
The right subclock of the combined clock always ticks instantly before cl2
.
Parallelly combined clocks
data ParallelClock m cl1 cl2 Source #
Two clocks can be combined with a schedule as a clock for an asynchronous parallel composition of signal networks.
Time cl1 ~ Time cl2 => ParallelClock | |
|
Instances
(Monad m, Clock m cl1, Clock m cl2) => Clock m (ParallelClock m cl1 cl2) Source # | |
Defined in FRP.Rhine.Schedule type Time (ParallelClock m cl1 cl2) Source # type Tag (ParallelClock m cl1 cl2) Source # initClock :: ParallelClock m cl1 cl2 -> RunningClockInit m (Time (ParallelClock m cl1 cl2)) (Tag (ParallelClock m cl1 cl2)) Source # | |
(GetClockProxy cl1, GetClockProxy cl2) => GetClockProxy (ParallelClock m cl1 cl2) Source # | |
Defined in FRP.Rhine.Clock.Proxy getClockProxy :: ClockProxy (ParallelClock m cl1 cl2) Source # | |
type Time (ParallelClock m cl1 cl2) Source # | |
Defined in FRP.Rhine.Schedule | |
type Tag (ParallelClock m cl1 cl2) Source # | |
Defined in FRP.Rhine.Schedule |
type ParClock m cl1 cl2 = ParallelClock m cl1 cl2 Source #
Abbrevation synonym.
schedPar1 :: (Monad m, Semigroup cl1) => Schedule m cl1 (ParallelClock m cl1 cl2) Source #
Like schedSeq1
, but for parallel clocks.
The left subclock of the combined clock always ticks instantly after cl1
.
schedPar1' :: (Monad m, Semigroup cl1) => Schedule m cl1 (ParallelClock m cl1 cl2) Source #
Like schedPar1
,
but the left subclock of the combined clock always ticks instantly before cl1
.
schedPar2 :: (Monad m, Semigroup cl2, Time cl1 ~ Time cl2) => Schedule m (ParallelClock m cl1 cl2) cl2 Source #
Like schedPar1
, but for the right subclock.
The right subclock of the combined clock always ticks instantly before cl2
.
schedPar2' :: (Monad m, Semigroup cl2, Time cl1 ~ Time cl2) => Schedule m (ParallelClock m cl1 cl2) cl2 Source #
Like schedPar1
,
but the right subclock of the combined clock always ticks instantly after cl2
.
Navigating the clock tree
type family In cl where ... Source #
The clock that represents the rate at which data enters the system.
In (SequentialClock m cl1 cl2) = In cl1 | |
In (ParallelClock m cl1 cl2) = ParallelClock m (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.
Out (SequentialClock m cl1 cl2) = Out cl2 | |
Out (ParallelClock m cl1 cl2) = ParallelClock m (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.
SequentialLastTime :: LastTime cl1 -> LastTime cl2 -> LastTime (SequentialClock m cl1 cl2) | |
ParallelLastTime :: LastTime cl1 -> LastTime cl2 -> LastTime (ParallelClock m 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.
ParClockInL :: ParClockInclusion (ParallelClock m clL clR) cl -> ParClockInclusion clL cl | |
ParClockInR :: ParClockInclusion (ParallelClock m clL clR) cl -> ParClockInclusion clR cl | |
ParClockRefl :: ParClockInclusion cl cl |
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.