elerea-2.7.0: A minimalistic FRP library

FRP.Elerea.Clocked

Contents

Description

This version differs from the simple one in adding associated freeze control signals ('clocks') to stateful entities to be able to pause entire subnetworks without having to write all the low-level logic explicitly. The clocks are fixed to signals upon their creation, and the withClock function can be used to specify the common clock for the signals created in a given generator.

A clock signal affects delay elements the following way: if the clock signal is true, the delay works as usual, otherwise it remembers its current output and throws away its current input. If we consider signals to be functions of time (natural numbers), the behaviour of delay can be described by the following function:

 delay x0 s (t_start,clk) t_sample
   | t_start == t_sample = x0
   | t_start < t_sample  = if clk t_sample
                             then s (t_sample-1)
                             else delay x0 s t_start s_clock (t_sample-1)
   | otherwise           = error "stream doesn't exist yet"

A simple example to create counters operating at different rates using the same generator:

 divisibleBy n x = x `mod` n == 0

 counter = stateful 0 (+1)

 drift = do
   time <- counter
   c1 <- withClock (divisibleBy 2 <$> time) counter
   c2 <- withClock (divisibleBy 3 <$> time) counter
   return ((,) <$> c1 <*> c2)

Note that if you want to slow down the drift system defined above, the naive approach might lead to surprising results:

 slowDrift = do
   time <- counter
   withClock (divisibleBy 2 <$> time) drift

The problem is that the clocks are also slowed down, and their spikes double in length. This may or may not be what you want. To overcome this problem, we can define a clock oblivious edge detector to be used within the definition of drift:

 edge = withClock (pure True) . transfer False (\b b' -> b && not b')

 drift = do
   time <- counter
   t2 <- edge (divisibleBy 2 <$> time)
   t3 <- edge (divisibleBy 3 <$> time)
   c1 <- withClock t2 counter
   c2 <- withClock t3 counter
   return ((,) <$> c1 <*> c2)

This works because the withClock function overrides any clock imposed on the generator from outside.

Synopsis

The signal abstraction

data Signal a Source

A signal represents a value changing over time. It can be thought of as a function of type Nat -> a, where the argument is the sampling time, and the Monad instance agrees with the intuition (bind corresponds to extracting the current sample). Signals and the values they carry are denoted the following way in the documentation:

 s = <<s0 s1 s2 ...>>

This says that s is a signal that reads s0 during the first sampling, s1 during the second and so on. You can also think of s as the following function:

 s t_sample = [s0,s1,s2,...] !! t_sample

Signals are constrained to be sampled sequentially, there is no random access. The only way to observe their output is through start.

Instances

data SignalGen a Source

A signal generator is the only source of stateful signals. It can be thought of as a function of type Nat -> a, where the result is an arbitrary data structure that can potentially contain new signals, and the argument is the creation time of these new signals. It exposes the MonadFix interface, which makes it possible to define signals in terms of each other. Unlike the simple variant, the denotation of signal generators differs from that of signals. We will use the following notation for generators:

 g = <|g0 g1 g2 ...|>

Just like signals, generators behave as functions of time, but they can also refer to the clock signal:

 g t_start s_clock = [g0,g1,g2,...] !! t_start

The conceptual difference between the two notions is that signals are passed a sampling time, while generators expect a start time that will be the creation time of all the freshly generated signals in the resulting structure.

Embedding into I/O

startSource

Arguments

:: SignalGen (Signal a)

the generator of the top-level signal

-> IO (IO a)

the computation to sample the signal

Embedding a signal into an IO environment. Repeated calls to the computation returned cause the whole network to be updated, and the current sample of the top-level signal is produced as a result. This is the only way to extract a signal generator outside the network, and it is equivalent to passing zero to the function representing the generator. The clock associated with the top-level signal ticks at every sampling point. In general:

 replicateM n =<< start <|<<x0 x1 x2 x3 ...>> ...|> == take n [x0,x1,x2,x3,...]

Example:

 do
     smp <- start (stateful 3 (+2))
     res <- replicateM 5 smp
     print res

Output:

 [3,5,7,9,11]

externalSource

Arguments

:: a

initial value

-> IO (Signal a, a -> IO ())

the signal and an IO function to feed it

A signal that can be directly fed through the sink function returned. This can be used to attach the network to the outer world. The signal always yields the value last written to the sink. In other words, if the sink is written less frequently than the network sampled, the output remains the same during several samples. If values are pushed in the sink more frequently, only the last one before sampling is visible on the output.

Example:

 do
     (sig,snk) <- external 4
     smp <- start (return sig)
     r1 <- smp
     r2 <- smp
     snk 7
     r3 <- smp
     snk 9
     snk 2
     r4 <- smp
     print [r1,r2,r3,r4]

Output:

 [4,4,7,2]

externalMultiSource

Arguments

:: IO (SignalGen (Signal [a]), a -> IO ())

a generator for the event signal and the associated sink

An event-like signal that can be fed through the sink function returned. The signal carries a list of values fed in since the last sampling (always synchronised to the top-level samplings regardless of any associated clock), i.e. it is constantly [] if the sink is never invoked. The order of elements is reversed, so the last value passed to the sink is the head of the list. Note that unlike external this function only returns a generator to be used within the expression constructing the top-level stream, and this generator can only be used once.

Example:

 do
     (gen,snk) <- externalMulti
     smp <- start gen
     r1 <- smp
     snk 7
     r2 <- smp
     r3 <- smp
     snk 9
     snk 2
     r4 <- smp
     print [r1,r2,r3,r4]

Output:

 [[],[7],[],[2,9]]

Basic building blocks

delaySource

Arguments

:: a

initial output at creation time

-> Signal a

the signal to delay

-> SignalGen (Signal a)

the delayed signal

The delay combinator is the elementary building block for adding state to the signal network by constructing delayed versions of a signal that emit a given value at creation time and the previous output of the signal afterwards.

The clock signal associated to the generator affects delay elements the following way: if the clock signal is true, the delay works as usual, otherwise it remembers its current output and throws away its current input. If we consider signals to be functions of time (natural numbers), the behaviour of delay can be described by the following function:

 delay x0 s t_start s_clock t_sample
   | t_start == t_sample = x0
   | t_start < t_sample  = if s_clock t_sample
                             then s (t_sample-1)
                             else delay x0 s t_start s_clock (t_sample-1)
   | otherwise           = error "stream doesn't exist yet"

The way signal generators are extracted by generator ensures that the error can never happen.

Example (requires the DoRec extension):

 do
     smp <- start $ do
         rec let fib'' = liftA2 (+) fib' fib
             fib' <- delay 1 fib''
             fib <- delay 1 fib'
         return fib
     res <- replicateM 7 smp
     print res

Output:

 [1,1,2,3,5,8,13]

snapshot :: Signal a -> SignalGen aSource

A formal conversion from signals to signal generators, which effectively allows for retrieving the current value of a previously created signal within a generator. This includes both signals defined in an external scope as well as those created earlier in the same generator. It can be modelled by the following function:

 snapshot s t_start s_clock = s t_start

generatorSource

Arguments

:: Signal (SignalGen a)

the signal of generators to run

-> SignalGen (Signal a)

the signal of generated structures

A reactive signal that takes the value to output from a signal generator carried by its input with the sampling time provided as the start time for the generated structure. It is possible to create new signals in the monad, which is the key to defining dynamic data-flow networks.

 generator << <|x00 x01 x02 ...|>
              <|x10 x11 x12 ...|>
              <|x20 x21 x22 ...|>
              ...
           >> = <| <<x00 x11 x22 ...>>
                   <<x00 x11 x22 ...>>
                   <<x00 x11 x22 ...>>
                   ...
                |>

It can be thought of as the following function:

 generator g t_start s_clock t_sample = g t_sample s_clock t_sample

It has to live in the SignalGen monad, because it needs to maintain an internal state to be able to cache the current sample for efficiency reasons. However, this state is not carried between samples, therefore start time doesn't matter and can be ignored. Also, even though it does not make use of the clock itself, part of its job is to distribute it among the newly generated signals.

Refer to the longer example at the bottom of FRP.Elerea.Simple to see how it can be used.

memoSource

Arguments

:: Signal a

the signal to cache

-> SignalGen (Signal a)

a signal observationally equivalent to the argument

Memoising combinator. It can be used to cache results of applicative combinators in case they are used in several places. Unlike in the simple variant, it is not observationally equivalent to return in the SignalGen monad, because it only samples its input signal when the associated clock ticks. The memo combinator can be modelled by the following function:

 memo s t_start s_clock t_sample
   | s_clock t_sample = s t_sample
   | otherwise        = memo s t_start s_clock (t_sample-1)

For instance, if s = f <$> s', then f will be recalculated once for each sampling of s. This can be avoided by writing s <- memo (f <$> s') instead. However, memo incurs a small overhead, therefore it should not be used blindly.

All the functions defined in this module return memoised signals.

untilSource

Arguments

:: Signal Bool

the boolean input signal

-> SignalGen (Signal Bool)

a one-shot signal true only the first time the input is true

A signal that is true exactly once: the first time the input signal is true. Afterwards, it is constantly false, and it holds no reference to the input signal. Note that until always follows the master clock, i.e. the fastest one, therefore it never creates a long spike of True. For instance (assuming the rest of the input is constantly False):

 until <<False False True True False True ...>> =
     <| <<False False True  False False False False False False False ...>>
        << ---  False True  False False False False False False False ...>>
        << ---   ---  True  False False False False False False False ...>>
        << ---   ---   ---  True  False False False False False False ...>>
        << ---   ---   ---   ---  False True  False False False False ...>>
        << ---   ---   ---   ---   ---  True  False False False False ...>>
        << ---   ---   ---   ---   ---   ---  False False False False ...>>
        ...
     |>

It is observationally equivalent to the following expression (which would hold onto s forever):

 until s = global $ do
     step <- transfer False (||) s
     dstep <- delay False step
     memo (liftA2 (/=) step dstep)

Example:

 do
     smp <- start $ do
         cnt <- stateful 0 (+1)
         tick <- until ((>=3) <$> cnt)
         return $ liftA2 (,) cnt tick
     res <- replicateM 6 smp
     print res

Output:

 [(0,False),(1,False),(2,False),(3,True),(4,False),(5,False)]

withClock :: Signal Bool -> SignalGen a -> SignalGen aSource

Override the clock used in a generator. Note that clocks don't interact unless one is used in the definition of the other, i.e. it is possible to provide a fast clock within a generator with a slow associated clock. It is equivalent to the following function:

 withClock s g t_start s_clock = g t_start s

For instance, the following equivalence holds:

 withClock (pure False) (stateful x f) == pure x

global :: SignalGen a -> SignalGen aSource

Equivalent to withClock (pure True), but more efficient.

Derived combinators

statefulSource

Arguments

:: a

initial state

-> (a -> a)

state transformation

-> SignalGen (Signal a) 

A pure stateful signal. The initial state is the first output, and every subsequent state is derived from the preceding one by applying a pure transformation. It is affected by the associated clock like delay: no transformation is performed in the absence of a tick; see the example at the top.

Example:

 do
     smp <- start (stateful "x" ('x':))
     res <- replicateM 5 smp
     print res

Output:

 ["x","xx","xxx","xxxx","xxxxx"]

transferSource

Arguments

:: a

initial internal state

-> (t -> a -> a)

state updater function

-> Signal t

input signal

-> SignalGen (Signal a) 

A stateful transfer function. The current input affects the current output, i.e. the initial state given in the first argument is considered to appear before the first output, and can never be observed, and subsequent states are determined by combining the preceding state with the current output of the input signal using the function supplied. It is affected by the associated clock like delay: no transformation is performed in the absence of a tick; see the example at the top.

Example:

 do
     smp <- start $ do
         cnt <- stateful 1 (+1)
         transfer 10 (+) cnt
     res <- replicateM 5 smp
     print res

Output:

 [11,13,16,20,25]

transfer2Source

Arguments

:: a

initial internal state

-> (t1 -> t2 -> a -> a)

state updater function

-> Signal t1

input signal 1

-> Signal t2

input signal 2

-> SignalGen (Signal a) 

A variation of transfer with two input signals.

transfer3Source

Arguments

:: a

initial internal state

-> (t1 -> t2 -> t3 -> a -> a)

state updater function

-> Signal t1

input signal 1

-> Signal t2

input signal 2

-> Signal t3

input signal 3

-> SignalGen (Signal a) 

A variation of transfer with three input signals.

transfer4Source

Arguments

:: a

initial internal state

-> (t1 -> t2 -> t3 -> t4 -> a -> a)

state updater function

-> Signal t1

input signal 1

-> Signal t2

input signal 2

-> Signal t3

input signal 3

-> Signal t4

input signal 4

-> SignalGen (Signal a) 

A variation of transfer with four input signals.

Signals with side effects

The following combinators are primarily aimed at library implementors who wish build abstractions to effectful libraries on top of Elerea.

execute :: IO a -> SignalGen aSource

An IO action executed in the SignalGen monad. Can be used as liftIO.

effectfulSource

Arguments

:: IO a

the action to be executed repeatedly

-> SignalGen (Signal a) 

A signal that executes a given IO action once at every sampling.

In essence, this combinator provides cooperative multitasking capabilities, and its primary purpose is to assist library writers in wrapping effectful APIs as conceptually pure signals. If there are several effectful signals in the system, their order of execution is undefined and should not be relied on.

Example:

 do
     smp <- start $ do
         ref <- execute $ newIORef 0
         effectful $ do
             x <- readIORef ref
             putStrLn $ "Count: " ++ show x
             writeIORef ref $! x+1
             return ()
     replicateM_ 5 smp

Output:

 Count: 0
 Count: 1
 Count: 2
 Count: 3
 Count: 4

Another example (requires mersenne-random):

 do
     smp <- start $ effectful $ return randomIO :: IO (IO Double)
     res <- replicateM 5 smp
     print res

Output:

 [0.12067753390401374,0.8658877349182655,0.7159264443196786,0.1756941896012891,0.9513646060896676]

effectful1Source

Arguments

:: (t -> IO a)

the action to be executed repeatedly

-> Signal t

parameter signal

-> SignalGen (Signal a) 

A signal that executes a parametric IO action once at every sampling. The parameter is supplied by another signal at every sampling step.

effectful2Source

Arguments

:: (t1 -> t2 -> IO a)

the action to be executed repeatedly

-> Signal t1

parameter signal 1

-> Signal t2

parameter signal 2

-> SignalGen (Signal a) 

Like effectful1, but with two parameter signals.

effectful3Source

Arguments

:: (t1 -> t2 -> t3 -> IO a)

the action to be executed repeatedly

-> Signal t1

parameter signal 1

-> Signal t2

parameter signal 2

-> Signal t3

parameter signal 3

-> SignalGen (Signal a) 

Like effectful1, but with three parameter signals.

effectful4Source

Arguments

:: (t1 -> t2 -> t3 -> t4 -> IO a)

the action to be executed repeatedly

-> Signal t1

parameter signal 1

-> Signal t2

parameter signal 2

-> Signal t3

parameter signal 3

-> Signal t4

parameter signal 4

-> SignalGen (Signal a) 

Like effectful1, but with four parameter signals.