| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
FRP.Rhine.SyncSF
Contents
Synopsis
- type SyncSF m cl a b = MSF (ReaderT (TimeInfo cl) m) a b
- type SyncSignal m cl a = SyncSF m cl () a
- type Behaviour m td a = forall cl. td ~ TimeDomainOf cl => SyncSignal m cl a
- type Behavior m td a = Behaviour m td a
- type BehaviourF m td a b = forall cl. td ~ TimeDomainOf cl => SyncSF m cl a b
- type BehaviorF m td a b = BehaviourF m td a b
- hoistSyncSF :: (Monad m1, Monad m2) => (forall c. m1 c -> m2 c) -> SyncSF m1 cl a b -> SyncSF m2 (HoistClock m1 m2 cl) a b
- timeless :: Monad m => MSF m a b -> SyncSF m cl a b
- arrMSync :: Monad m => (a -> m b) -> SyncSF m cl a b
- arrMSync_ :: Monad m => m b -> SyncSF m cl a b
- timeInfo :: Monad m => SyncSF m cl a (TimeInfo cl)
- timeInfoOf :: Monad m => (TimeInfo cl -> b) -> SyncSF m cl a b
- (>->) :: Category cat => cat a b -> cat b c -> cat a c
- (<-<) :: Category cat => cat b c -> cat a b -> cat a c
- arr_ :: Arrow a => b -> a c b
- syncId :: Monad m => SyncSF m cl a a
- integralFrom :: (Monad m, VectorSpace v, Groundfield v ~ Diff td) => v -> BehaviorF m td v v
- integral :: (Monad m, VectorSpace v, Groundfield v ~ Diff td) => BehaviorF m td v v
- derivativeFrom :: (Monad m, VectorSpace v, Groundfield v ~ Diff td) => v -> BehaviorF m td v v
- derivative :: (Monad m, VectorSpace v, Groundfield v ~ Diff td) => BehaviorF m td v v
- weightedAverageFrom :: (Monad m, VectorSpace v, Groundfield v ~ Diff td) => v -> BehaviorF m td (v, Groundfield v) v
- averageFrom :: (Monad m, VectorSpace v, Floating (Groundfield v), Groundfield v ~ Diff td) => v -> Diff td -> BehaviorF m td v v
- average :: (Monad m, VectorSpace v, Floating (Groundfield v), Groundfield v ~ Diff td) => Diff td -> BehaviourF m td v v
- averageLinFrom :: (Monad m, VectorSpace v, Groundfield v ~ Diff td) => v -> Diff td -> BehaviourF m td v v
- averageLin :: (Monad m, VectorSpace v, Groundfield v ~ Diff td) => Diff td -> BehaviourF m td v v
Synchronous signal functions and behaviours
type SyncSF m cl a b = MSF (ReaderT (TimeInfo cl) m) a b Source #
A (synchronous) monadic stream function
   with the additional side effect of being time-aware,
   that is, reading the current TimeInfo of the clock cl.
type SyncSignal m cl a = SyncSF m cl () a Source #
A synchronous signal is a SyncSF with no input required.
   It produces its output on its own.
type Behaviour m td a = forall cl. td ~ TimeDomainOf cl => SyncSignal m cl a Source #
A (side-effectful) behaviour is a time-aware stream
   that doesn't depend on a particular clock.
   td denotes the TimeDomain.
type BehaviourF m td a b = forall cl. td ~ TimeDomainOf cl => SyncSF m cl a b Source #
A (side-effectful) behaviour function is a time-aware synchronous stream
   function that doesn't depend on a particular clock.
   td denotes the TimeDomain.
type BehaviorF m td a b = BehaviourF m td a b Source #
Compatibility to U.S. american spelling.
Utilities to create SyncSFs from simpler data
hoistSyncSF :: (Monad m1, Monad m2) => (forall c. m1 c -> m2 c) -> SyncSF m1 cl a b -> SyncSF m2 (HoistClock m1 m2 cl) a b Source #
Hoist a SyncSF along a monad morphism.
timeless :: Monad m => MSF m a b -> SyncSF m cl a b Source #
A monadic stream function without dependency on time
   is a SyncSF for any clock.
arrMSync :: Monad m => (a -> m b) -> SyncSF m cl a b Source #
Utility to lift Kleisli arrows directly to SyncSFs.
timeInfo :: Monad m => SyncSF m cl a (TimeInfo cl) Source #
Read the environment variable, i.e. the TimeInfo.
timeInfoOf :: Monad m => (TimeInfo cl -> b) -> SyncSF m cl a b Source #
Utility to apply functions to the current TimeInfo,
such as record selectors:
printAbsoluteTime :: SyncSF IO cl () ()
printAbsoluteTime = timeInfoOf absolute >>> arrMSync print
Useful aliases
(>->) :: Category cat => cat a b -> cat b c -> cat a c infixr 6 Source #
Alias for >>> (sequential composition)
with higher operator precedence, designed to work with the other operators, e.g.:
syncsf1 >-> syncsf2 @@ clA **@ sched @** syncsf3 >-> syncsf4 @@ clB
The type signature specialises e.g. to
(>->) :: Monad m => SyncSF m cl a b -> SyncSF m cl b c -> SyncSF m cl a c
arr_ :: Arrow a => b -> a c b Source #
Output a constant value. Specialises e.g. to this type signature:
arr_ :: Monad m => b -> SyncSF m cl a b
Basic signal processing components
integralFrom :: (Monad m, VectorSpace v, Groundfield v ~ Diff td) => v -> BehaviorF m td v v Source #
The output of integralFrom v0 is the numerical Euler integral
   of the input, with initial offset v0.
integral :: (Monad m, VectorSpace v, Groundfield v ~ Diff td) => BehaviorF m td v v Source #
Euler integration, with zero initial offset.
derivativeFrom :: (Monad m, VectorSpace v, Groundfield v ~ Diff td) => v -> BehaviorF m td v v Source #
The output of derivativeFrom v0 is the numerical derivative of the input,
   with a Newton difference quotient.
   The input is initialised with v0.
derivative :: (Monad m, VectorSpace v, Groundfield v ~ Diff td) => BehaviorF m td v v Source #
Numerical derivative with input initialised to zero.
Arguments
| :: (Monad m, VectorSpace v, Groundfield v ~ Diff td) | |
| => v | The initial position | 
| -> BehaviorF m td (v, Groundfield v) v | 
A weighted moving average signal function. The output is the average of the first input, weighted by the second input (which is assumed to be always between 0 and 1). The weight is applied to the average of the last tick, so a weight of 1 simply repeats the past value unchanged, whereas a weight of 0 outputs the current value.
Arguments
| :: (Monad m, VectorSpace v, Floating (Groundfield v), Groundfield v ~ Diff td) | |
| => v | The initial position | 
| -> Diff td | The time scale on which the signal is averaged | 
| -> BehaviorF m td v v | 
An exponential moving average, or low pass. It will average out, or filter, all features below a given time scale.
Arguments
| :: (Monad m, VectorSpace v, Floating (Groundfield v), Groundfield v ~ Diff td) | |
| => Diff td | The time scale on which the signal is averaged | 
| -> BehaviourF m td v v | 
An average, or low pass, initialised to zero.
Arguments
| :: (Monad m, VectorSpace v, Groundfield v ~ Diff td) | |
| => v | The initial position | 
| -> Diff td | The time scale on which the signal is averaged | 
| -> BehaviourF m td v v | 
A linearised version of averageFrom.
   It is more efficient, but only accurate
   if the supplied time scale is much bigger
   than the average time difference between two ticks.
Arguments
| :: (Monad m, VectorSpace v, Groundfield v ~ Diff td) | |
| => Diff td | The time scale on which the signal is averaged | 
| -> BehaviourF m td v v | 
Linearised version of average.