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

FRP.Rhine.Clock.FixedStep

Description

Implements pure clocks ticking at every multiple of a fixed number of steps, and a deterministic schedule for such clocks.

Synopsis

Documentation

data FixedStep (n :: Nat) where Source #

A pure (side effect free) clock with fixed step size, i.e. ticking at multiples of n. The tick rate is in the type signature, which prevents composition of signals at different rates.

Constructors

FixedStep :: KnownNat n => FixedStep n 

Instances

Instances details
GetClockProxy (FixedStep n) Source # 
Instance details

Defined in FRP.Rhine.Clock.FixedStep

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

type Tag (FixedStep n) Source # 
Instance details

Defined in FRP.Rhine.Clock.FixedStep

type Tag (FixedStep n) = ()
type Time (FixedStep n) Source # 
Instance details

Defined in FRP.Rhine.Clock.FixedStep

stepsize :: FixedStep n -> Integer Source #

Extract the type-level natural number as an integer.

type Count = FixedStep 1 Source #

A singleton clock that counts the ticks.

downsampleFixedStep :: (KnownNat n, Monad m) => ResamplingBuffer m (FixedStep k) (FixedStep (n * k)) a (Vector n a) Source #

Resample into a FixedStep clock that ticks n times slower, by collecting all values into a vector.