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

FRP.Rhine.Clock

Description

Clocks are the central new notion in Rhine. There are clock types (instances of the Clock type class) and their values.

This module provides the Clock type class, several utilities, and certain general constructions of Clocks, such as clocks lifted along monad morphisms or time rescalings.

Synopsis

Documentation

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.

Associated Types

type Time cl Source #

The time domain, i.e. type of the time stamps the clock creates.

type Tag cl Source #

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.

Methods

initClock Source #

Arguments

:: 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

Instances details
MonadIO m => Clock m Busy Source # 
Instance details

Defined in FRP.Rhine.Clock.Realtime.Busy

Associated Types

type Time Busy Source #

type Tag Busy Source #

MonadIO m => Clock m Never Source # 
Instance details

Defined in FRP.Rhine.Clock.Realtime.Never

Associated Types

type Time Never Source #

type Tag Never Source #

MonadIO m => Clock m StdinClock Source # 
Instance details

Defined in FRP.Rhine.Clock.Realtime.Stdin

Associated Types

type Time StdinClock Source #

type Tag StdinClock Source #

Monad m => Clock m Trivial Source # 
Instance details

Defined in FRP.Rhine.Clock.Trivial

Associated Types

type Time Trivial Source #

type Tag Trivial Source #

Clock IO (Millisecond n) Source # 
Instance details

Defined in FRP.Rhine.Clock.Realtime.Millisecond

Associated Types

type Time (Millisecond n) Source #

type Tag (Millisecond n) Source #

(Monad m, PureAudioClockRate rate) => Clock m (PureAudioClock rate) Source # 
Instance details

Defined in FRP.Rhine.Clock.Realtime.Audio

Associated Types

type Time (PureAudioClock rate) Source #

type Tag (PureAudioClock rate) Source #

(Exception e, Clock IO cl, MonadIO eio, MonadError e eio) => Clock eio (ExceptClock cl e) Source # 
Instance details

Defined in FRP.Rhine.Clock.Except

Associated Types

type Time (ExceptClock cl e) Source #

type Tag (ExceptClock cl e) Source #

Methods

initClock :: ExceptClock cl e -> RunningClockInit eio (Time (ExceptClock cl e)) (Tag (ExceptClock cl e)) Source #

(Monad m, TimeDomain time, Clock m cl) => Clock m (RescaledClock cl time) Source # 
Instance details

Defined in FRP.Rhine.Clock

Associated Types

type Time (RescaledClock cl time) Source #

type Tag (RescaledClock cl time) Source #

Methods

initClock :: RescaledClock cl time -> RunningClockInit m (Time (RescaledClock cl time)) (Tag (RescaledClock cl time)) Source #

(MonadIO m, KnownNat bufferSize, AudioClockRate rate) => Clock m (AudioClock rate bufferSize) Source # 
Instance details

Defined in FRP.Rhine.Clock.Realtime.Audio

Associated Types

type Time (AudioClock rate bufferSize) Source #

type Tag (AudioClock rate bufferSize) Source #

Methods

initClock :: AudioClock rate bufferSize -> RunningClockInit m (Time (AudioClock rate bufferSize)) (Tag (AudioClock rate bufferSize)) Source #

(Monad m, Clock m cl) => Clock m (SelectClock cl a) Source # 
Instance details

Defined in FRP.Rhine.Clock.Select

Associated Types

type Time (SelectClock cl a) Source #

type Tag (SelectClock cl a) Source #

(TimeDomain (Time cl), Clock (ScheduleT (Diff (Time cl)) m) cl, Monad m) => Clock m (UnscheduleClock m cl) Source # 
Instance details

Defined in FRP.Rhine.Clock.Unschedule

Associated Types

type Time (UnscheduleClock m cl) Source #

type Tag (UnscheduleClock m cl) Source #

(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 #

(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 #

(Monad m, TimeDomain time, Clock m cl) => Clock m (RescaledClockM m cl time) Source # 
Instance details

Defined in FRP.Rhine.Clock

Associated Types

type Time (RescaledClockM m cl time) Source #

type Tag (RescaledClockM m cl time) Source #

Methods

initClock :: RescaledClockM m cl time -> RunningClockInit m (Time (RescaledClockM m cl time)) (Tag (RescaledClockM m cl time)) Source #

(Time cl1 ~ Time cl2, Clock (ExceptT e m) cl1, Clock m cl2, Monad m) => Clock m (CatchClock cl1 e cl2) Source # 
Instance details

Defined in FRP.Rhine.Clock.Except

Associated Types

type Time (CatchClock cl1 e cl2) Source #

type Tag (CatchClock cl1 e cl2) Source #

Methods

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

(Monad m1, Monad m2, Clock m1 cl) => Clock m2 (HoistClock m1 m2 cl) Source # 
Instance details

Defined in FRP.Rhine.Clock

Associated Types

type Time (HoistClock m1 m2 cl) Source #

type Tag (HoistClock m1 m2 cl) Source #

Methods

initClock :: HoistClock m1 m2 cl -> RunningClockInit m2 (Time (HoistClock m1 m2 cl)) (Tag (HoistClock m1 m2 cl)) Source #

(Monad m, TimeDomain time, Clock m cl) => Clock m (RescaledClockS m cl time tag) Source # 
Instance details

Defined in FRP.Rhine.Clock

Associated Types

type Time (RescaledClockS m cl time tag) Source #

type Tag (RescaledClockS m cl time tag) Source #

Methods

initClock :: RescaledClockS m cl time tag -> RunningClockInit m (Time (RescaledClockS m cl time tag)) (Tag (RescaledClockS m cl time tag)) Source #

(TimeDomain time, MonadError e m) => Clock m (Single m time tag e) Source # 
Instance details

Defined in FRP.Rhine.Clock.Except

Associated Types

type Time (Single m time tag e) Source #

type Tag (Single m time tag e) Source #

Methods

initClock :: Single m time tag e -> RunningClockInit m (Time (Single m time tag e)) (Tag (Single m time tag e)) Source #

(MonadSchedule m, Monad m) => Clock (ScheduleT Integer m) (FixedStep n) Source # 
Instance details

Defined in FRP.Rhine.Clock.FixedStep

Associated Types

type Time (FixedStep n) Source #

type Tag (FixedStep n) Source #

(Monad m, NonemptyNatList v) => Clock (ScheduleT Integer m) (Periodic v) Source # 
Instance details

Defined in FRP.Rhine.Clock.Periodic

Associated Types

type Time (Periodic v) Source #

type Tag (Periodic v) Source #

MonadIO m => Clock (EventChanT event m) (EventClock event) Source # 
Instance details

Defined in FRP.Rhine.Clock.Realtime.Event

Associated Types

type Time (EventClock event) Source #

type Tag (EventClock event) Source #

Methods

initClock :: EventClock event -> RunningClockInit (EventChanT event m) (Time (EventClock event)) (Tag (EventClock event)) Source #

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.

data HoistClock m1 m2 cl Source #

Applying a monad morphism yields a new clock.

Constructors

HoistClock 

Fields

Instances

Instances details
(Monad m1, Monad m2, Clock m1 cl) => Clock m2 (HoistClock m1 m2 cl) Source # 
Instance details

Defined in FRP.Rhine.Clock

Associated Types

type Time (HoistClock m1 m2 cl) Source #

type Tag (HoistClock m1 m2 cl) Source #

Methods

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 # 
Instance details

Defined in FRP.Rhine.Clock.Proxy

type Tag (HoistClock m1 m2 cl) Source # 
Instance details

Defined in FRP.Rhine.Clock

type Tag (HoistClock m1 m2 cl) = Tag cl
type Time (HoistClock m1 m2 cl) Source # 
Instance details

Defined in FRP.Rhine.Clock

type Time (HoistClock m1 m2 cl) = Time cl

data TimeInfo cl Source #

An annotated, rich time stamp.

Constructors

TimeInfo 

Fields

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.

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.

data RescaledClock cl time Source #

Applying a morphism of time domains yields a new clock.

Constructors

RescaledClock 

Fields

Instances

Instances details
(Monad m, TimeDomain time, Clock m cl) => Clock m (RescaledClock cl time) Source # 
Instance details

Defined in FRP.Rhine.Clock

Associated Types

type Time (RescaledClock cl time) Source #

type Tag (RescaledClock cl time) Source #

Methods

initClock :: RescaledClock cl time -> RunningClockInit m (Time (RescaledClock cl time)) (Tag (RescaledClock cl time)) Source #

GetClockProxy cl => GetClockProxy (RescaledClock cl time) Source # 
Instance details

Defined in FRP.Rhine.Clock.Proxy

type Tag (RescaledClock cl time) Source # 
Instance details

Defined in FRP.Rhine.Clock

type Tag (RescaledClock cl time) = Tag cl
type Time (RescaledClock cl time) Source # 
Instance details

Defined in FRP.Rhine.Clock

type Time (RescaledClock cl time) = time

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.

Constructors

RescaledClockM 

Fields

Instances

Instances details
(Monad m, TimeDomain time, Clock m cl) => Clock m (RescaledClockM m cl time) Source # 
Instance details

Defined in FRP.Rhine.Clock

Associated Types

type Time (RescaledClockM m cl time) Source #

type Tag (RescaledClockM m cl time) Source #

Methods

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 # 
Instance details

Defined in FRP.Rhine.Clock.Proxy

type Tag (RescaledClockM m cl time) Source # 
Instance details

Defined in FRP.Rhine.Clock

type Tag (RescaledClockM m cl time) = Tag cl
type Time (RescaledClockM m cl time) Source # 
Instance details

Defined in FRP.Rhine.Clock

type Time (RescaledClockM m cl time) = time

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.

Constructors

RescaledClockS 

Fields

  • unscaledClockS :: cl

    The clock before the rescaling

  • rescaleS :: RescalingSInit m cl time tag

    The rescaling stream function, and rescaled initial time, depending on the initial time before rescaling

Instances

Instances details
(Monad m, TimeDomain time, Clock m cl) => Clock m (RescaledClockS m cl time tag) Source # 
Instance details

Defined in FRP.Rhine.Clock

Associated Types

type Time (RescaledClockS m cl time tag) Source #

type Tag (RescaledClockS m cl time tag) Source #

Methods

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 # 
Instance details

Defined in FRP.Rhine.Clock.Proxy

Methods

getClockProxy :: ClockProxy (RescaledClockS m cl time tag) Source #

type Tag (RescaledClockS m cl time tag) Source # 
Instance details

Defined in FRP.Rhine.Clock

type Tag (RescaledClockS m cl time tag) = tag
type Time (RescaledClockS m cl time tag) Source # 
Instance details

Defined in FRP.Rhine.Clock

type Time (RescaledClockS m cl time tag) = time

type LiftClock m t cl = HoistClock m (t m) cl Source #

Lift a clock type into a monad transformer.

type IOClock m cl = HoistClock IO m cl Source #

Lift a clock type into MonadIO.

retag :: Time cl1 ~ Time cl2 => (Tag cl1 -> Tag cl2) -> TimeInfo cl1 -> TimeInfo cl2 Source #

A utility that changes the tag of a TimeInfo.

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.

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.

liftClock :: (Monad m, MonadTrans t) => cl -> LiftClock m t cl Source #

Lift a clock value into a monad transformer.

ioClock :: MonadIO m => cl -> IOClock m cl Source #

Lift a clock value into MonadIO.