rhine-0.5.1.0: Functional Reactive Programming with type-level clocks

Safe HaskellNone
LanguageHaskell2010

FRP.Rhine.ClSF.Util

Contents

Description

Utilities to create ClSFs. The fundamental effect that ClSFs have is reading the time information of the clock. It can be used for many purposes, for example digital signal processing.

Synopsis

Read time information

timeInfo :: Monad m => ClSF m cl a (TimeInfo cl) Source #

Read the environment variable, i.e. the TimeInfo.

timeInfoOf :: Monad m => (TimeInfo cl -> b) -> ClSF m cl a b Source #

Utility to apply functions to the current TimeInfo, such as record selectors: printAbsoluteTime :: ClSF IO cl () () printAbsoluteTime = timeInfoOf absolute >>> arrMCl print

sinceLastS :: Monad m => ClSF m cl a (Diff (Time cl)) Source #

Continuously return the time difference since the last tick.

sinceInitS :: Monad m => ClSF m cl a (Diff (Time cl)) Source #

Continuously return the time difference since clock initialisation.

absoluteS :: Monad m => ClSF m cl a (Time cl) Source #

Continuously return the absolute time.

tagS :: Monad m => ClSF m cl a (Tag cl) Source #

Continuously return the tag of the current tick.

sinceStart :: (Monad m, TimeDomain time) => BehaviourF m time a (Diff time) Source #

Calculate the time passed since this ClSF was instantiated. This is _not_ the same as sinceInitS, which measures the time since clock initialisation.

For example, the following gives a sawtooth signal:

sawtooth = safely $ do
  try $ sinceStart >>> proc time -> do
    throwOn () -time 1
    returnA    -< time
  safe sawtooth

If you replace sinceStart by sinceInitS, it will usually hang after one second, since it doesn't reset after restarting the sawtooth.

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

clsf1 >-> clsf2 @@ clA ||@ sched @|| clsf3 >-> clsf4 @@ clB

The type signature specialises e.g. to

(>->) :: Monad m => ClSF m cl a b -> ClSF m cl b c -> ClSF m cl a c

(<-<) :: Category cat => cat b c -> cat a b -> cat a c infixl 6 Source #

Alias for <<<.

arr_ :: Arrow a => b -> a c b Source #

Output a constant value. Specialises e.g. to this type signature:

arr_ :: Monad m => b -> ClSF m cl a b

clId :: Monad m => ClSF m cl a a Source #

The identity synchronous stream function.

Basic signal processing components

Integration and differentiation

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.

threePointDerivativeFrom Source #

Arguments

:: (Monad m, VectorSpace v, Groundfield v ~ Diff td) 
=> v

The initial position

-> BehaviorF m td v v 

Like derivativeFrom, but uses three samples to compute the derivative. Consequently, it is delayed by one sample.

threePointDerivative :: (Monad m, VectorSpace v, Groundfield v ~ Diff td) => BehaviorF m td v v Source #

Like threePointDerivativeFrom, but with the initial position initialised to zeroVector.

Averaging and filters

weightedAverageFrom Source #

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.

averageFrom Source #

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 constant t. (Equivalently, it filters out frequencies above 1 / (2 * pi * t).)

average Source #

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.

averageLinFrom Source #

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.

averageLin Source #

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.

First-order filters

lowPass :: (Monad m, VectorSpace v, Floating (Groundfield v), Groundfield v ~ Diff td) => Diff td -> BehaviourF m td v v Source #

Alias for average.

highPass Source #

Arguments

:: (Monad m, VectorSpace v, Floating (Groundfield v), Groundfield v ~ Diff td) 
=> Diff td

The time constant t

-> BehaviourF m td v v 

Filters out frequencies below 1 / (2 * pi * t).

bandPass Source #

Arguments

:: (Monad m, VectorSpace v, Floating (Groundfield v), Groundfield v ~ Diff td) 
=> Diff td

The time constant t

-> BehaviourF m td v v 

Filters out frequencies other than 1 / (2 * pi * t).

bandStop Source #

Arguments

:: (Monad m, VectorSpace v, Floating (Groundfield v), Groundfield v ~ Diff td) 
=> Diff td

The time constant t

-> BehaviourF m td v v 

Filters out the frequency 1 / (2 * pi * t).

Delays

keepFirst :: Monad m => ClSF m cl a a Source #

Remembers and indefinitely outputs ("holds") the first input value.

historySince Source #

Arguments

:: (Monad m, Ord (Diff (Time cl)), TimeDomain (Time cl)) 
=> Diff (Time cl)

The size of the time window

-> ClSF m cl a (Seq (TimeInfo cl, a)) 

Remembers all input values that arrived within a given time window. New values are appended left.

delayBy Source #

Arguments

:: (Monad m, Ord (Diff (Time cl)), TimeDomain (Time cl)) 
=> Diff (Time cl)

The time span to delay the signal

-> ClSF m cl a a 

Delay a signal by certain time span.

Timers

timer :: (Monad m, TimeDomain td, Ord (Diff td)) => Diff td -> BehaviorF (ExceptT () m) td a (Diff td) Source #

Throws an exception after the specified time difference, outputting the time passed since the timer was instantiated.

timer_ :: (Monad m, TimeDomain td, Ord (Diff td)) => Diff td -> BehaviorF (ExceptT () m) td a () Source #

Like timer_, but doesn't output the remaining time at all.

scaledTimer :: (Monad m, TimeDomain td, Fractional (Diff td), Ord (Diff td)) => Diff td -> BehaviorF (ExceptT () m) td a (Diff td) Source #

Like timer, but divides the remaining time by the total time.

To be ported to Dunai

lastS :: Monad m => a -> MSF m (Maybe a) a Source #

Remembers the last Just value, defaulting to the given initialisation value.