Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type RunningClock m time tag = Automaton m () (time, tag)
- type RunningClockInit m time tag = m (RunningClock m time tag, time)
- class TimeDomain (Time cl) => Clock m cl where
- data TimeInfo cl = TimeInfo {}
- retag :: Time cl1 ~ Time cl2 => (Tag cl1 -> Tag cl2) -> TimeInfo cl1 -> TimeInfo cl2
- type Rescaling cl time = Time cl -> time
- type RescalingM m cl time = Time cl -> m time
- type RescalingS m cl time tag = Automaton m (Time cl, Tag cl) (time, tag)
- type RescalingSInit m cl time tag = Time cl -> m (RescalingS m cl time tag, time)
- rescaleMToSInit :: Monad m => (time1 -> m time2) -> time1 -> m (Automaton m (time1, tag) (time2, tag), time2)
- data RescaledClock cl time = RescaledClock {
- unscaledClock :: cl
- rescale :: Rescaling cl time
- data RescaledClockM m cl time = RescaledClockM {
- unscaledClockM :: cl
- rescaleM :: RescalingM m cl time
- rescaledClockToM :: Monad m => RescaledClock cl time -> RescaledClockM m cl time
- data RescaledClockS m cl time tag = RescaledClockS {
- unscaledClockS :: cl
- rescaleS :: RescalingSInit m cl time tag
- rescaledClockMToS :: Monad m => RescaledClockM m cl time -> RescaledClockS m cl time (Tag cl)
- rescaledClockToS :: Monad m => RescaledClock cl time -> RescaledClockS m cl time (Tag cl)
- data HoistClock m1 m2 cl = HoistClock {
- unhoistedClock :: cl
- monadMorphism :: forall a. m1 a -> m2 a
- type LiftClock m t cl = HoistClock m (t m) cl
- liftClock :: (Monad m, MonadTrans t) => cl -> LiftClock m t cl
- type IOClock m cl = HoistClock IO m cl
- ioClock :: MonadIO m => cl -> IOClock m cl
The Clock
type class
type RunningClock m time tag = Automaton m () (time, tag) Source #
A clock creates a stream of time stamps and additional information,
possibly together with side effects in a monad m
that cause the environment to wait until the specified time is reached.
type RunningClockInit m time tag = m (RunningClock m time tag, time) Source #
When initialising a clock, the initial time is measured (typically by means of a side effect), and a running clock is returned.
class TimeDomain (Time cl) => Clock m cl where Source #
Since we want to leverage Haskell's type system to annotate signal networks by their clocks,
each clock must be an own type, cl
.
Different values of the same clock type should tick at the same speed,
and only differ in implementation details.
Often, clocks are singletons.
The time domain, i.e. type of the time stamps the clock creates.
Additional information that the clock may output at each tick, e.g. if a realtime promise was met, if an event occurred, if one of its subclocks (if any) ticked.
:: cl | The clock value, containing e.g. settings or device parameters |
-> RunningClockInit m (Time cl) (Tag cl) | The stream of time stamps, and the initial time |
The method that produces to a clock value a running clock, i.e. an effectful stream of tagged time stamps together with an initialisation time.
Instances
Auxiliary definitions and utilities
An annotated, rich time stamp.
retag :: Time cl1 ~ Time cl2 => (Tag cl1 -> Tag cl2) -> TimeInfo cl1 -> TimeInfo cl2 Source #
A utility that changes the tag of a TimeInfo
.
Certain universal building blocks to produce new clocks from given ones
Rescalings of time domains
type Rescaling cl time = Time cl -> time Source #
A pure morphism of time domains is just a function.
type RescalingM m cl time = Time cl -> m time Source #
An effectful morphism of time domains is a Kleisli arrow. It can use a side effect to rescale a point in one time domain into another one.
type RescalingS m cl time tag = Automaton m (Time cl, Tag cl) (time, tag) Source #
An effectful, stateful morphism of time domains is an Automaton
that uses side effects to rescale a point in one time domain
into another one.
type RescalingSInit m cl time tag = Time cl -> m (RescalingS m cl time tag, time) Source #
Like RescalingS
, but allows for an initialisation
of the rescaling morphism, together with the initial time.
rescaleMToSInit :: Monad m => (time1 -> m time2) -> time1 -> m (Automaton m (time1, tag) (time2, tag), time2) Source #
Convert an effectful morphism of time domains into a stateful one with initialisation.
Think of its type as RescalingM m cl time -> RescalingSInit m cl time tag
,
although this type is ambiguous.
Applying rescalings to clocks
data RescaledClock cl time Source #
Applying a morphism of time domains yields a new clock.
RescaledClock | |
|
Instances
(Monad m, TimeDomain time, Clock m cl) => Clock m (RescaledClock cl time) Source # | |
Defined in FRP.Rhine.Clock type Time (RescaledClock cl time) Source # type Tag (RescaledClock cl time) Source # initClock :: RescaledClock cl time -> RunningClockInit m (Time (RescaledClock cl time)) (Tag (RescaledClock cl time)) Source # | |
GetClockProxy cl => GetClockProxy (RescaledClock cl time) Source # | |
Defined in FRP.Rhine.Clock.Proxy getClockProxy :: ClockProxy (RescaledClock cl time) Source # | |
type Tag (RescaledClock cl time) Source # | |
Defined in FRP.Rhine.Clock | |
type Time (RescaledClock cl time) Source # | |
Defined in FRP.Rhine.Clock |
data RescaledClockM m cl time Source #
Instead of a mere function as morphism of time domains, we can transform one time domain into the other with an effectful morphism.
RescaledClockM | |
|
Instances
(Monad m, TimeDomain time, Clock m cl) => Clock m (RescaledClockM m cl time) Source # | |
Defined in FRP.Rhine.Clock type Time (RescaledClockM m cl time) Source # type Tag (RescaledClockM m cl time) Source # initClock :: RescaledClockM m cl time -> RunningClockInit m (Time (RescaledClockM m cl time)) (Tag (RescaledClockM m cl time)) Source # | |
GetClockProxy cl => GetClockProxy (RescaledClockM m cl time) Source # | |
Defined in FRP.Rhine.Clock.Proxy getClockProxy :: ClockProxy (RescaledClockM m cl time) Source # | |
type Tag (RescaledClockM m cl time) Source # | |
Defined in FRP.Rhine.Clock | |
type Time (RescaledClockM m cl time) Source # | |
Defined in FRP.Rhine.Clock |
rescaledClockToM :: Monad m => RescaledClock cl time -> RescaledClockM m cl time Source #
A RescaledClock
is trivially a RescaledClockM
.
data RescaledClockS m cl time tag Source #
Instead of a mere function as morphism of time domains, we can transform one time domain into the other with an automaton.
RescaledClockS | |
|
Instances
(Monad m, TimeDomain time, Clock m cl) => Clock m (RescaledClockS m cl time tag) Source # | |
Defined in FRP.Rhine.Clock type Time (RescaledClockS m cl time tag) Source # type Tag (RescaledClockS m cl time tag) Source # initClock :: RescaledClockS m cl time tag -> RunningClockInit m (Time (RescaledClockS m cl time tag)) (Tag (RescaledClockS m cl time tag)) Source # | |
GetClockProxy cl => GetClockProxy (RescaledClockS m cl time tag) Source # | |
Defined in FRP.Rhine.Clock.Proxy getClockProxy :: ClockProxy (RescaledClockS m cl time tag) Source # | |
type Tag (RescaledClockS m cl time tag) Source # | |
Defined in FRP.Rhine.Clock | |
type Time (RescaledClockS m cl time tag) Source # | |
Defined in FRP.Rhine.Clock |
rescaledClockMToS :: Monad m => RescaledClockM m cl time -> RescaledClockS m cl time (Tag cl) Source #
A RescaledClockM
is trivially a RescaledClockS
.
rescaledClockToS :: Monad m => RescaledClock cl time -> RescaledClockS m cl time (Tag cl) Source #
A RescaledClock
is trivially a RescaledClockS
.
data HoistClock m1 m2 cl Source #
Applying a monad morphism yields a new clock.
HoistClock | |
|
Instances
(Monad m1, Monad m2, Clock m1 cl) => Clock m2 (HoistClock m1 m2 cl) Source # | |
Defined in FRP.Rhine.Clock type Time (HoistClock m1 m2 cl) Source # type Tag (HoistClock m1 m2 cl) Source # initClock :: HoistClock m1 m2 cl -> RunningClockInit m2 (Time (HoistClock m1 m2 cl)) (Tag (HoistClock m1 m2 cl)) Source # | |
GetClockProxy cl => GetClockProxy (HoistClock m1 m2 cl) Source # | |
Defined in FRP.Rhine.Clock.Proxy getClockProxy :: ClockProxy (HoistClock m1 m2 cl) Source # | |
type Tag (HoistClock m1 m2 cl) Source # | |
Defined in FRP.Rhine.Clock | |
type Time (HoistClock m1 m2 cl) Source # | |
Defined in FRP.Rhine.Clock |
type LiftClock m t cl = HoistClock m (t m) cl Source #
Lift a clock type into a monad transformer.