euphoria-0.6.0.1: Dynamic network FRP with events and continuous values

Safe HaskellNone
LanguageHaskell98

FRP.Euphoria.Signal

Contents

Description

Re-exported and renamed definitions from FRP.Elerea.Simple.

Synopsis

Re-exports

data Signal a :: * -> *

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

Monad Signal 
Functor Signal 
Applicative Signal 
Apply Signal Event Source 
Bounded t => Bounded (Signal t) 
Enum t => Enum (Signal t) 
Eq (Signal a)

Equality test is impossible.

Floating t => Floating (Signal t) 
Fractional t => Fractional (Signal t) 
Integral t => Integral (Signal t) 
Num t => Num (Signal t) 
Ord t => Ord (Signal t) 
Real t => Real (Signal t) 
Show (Signal a)

The Show instance is only defined for the sake of Num...

SignalSet (Signal a) Source 
EasyApply (Signal (a -> b)) (Event a) (Event b) Source 

data SignalGen a :: * -> *

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. The denotation of signal generators happens to be the same as that of signals, but this partly accidental (it does not hold in the other variants), so we will use a separate notation for generators:

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

Just like signals, generators behave as functions of time:

g t_start = [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.

execute :: IO a -> SignalGen a

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

external

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]

start

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

MonadSignalGen

Renamed functions

delayS :: MonadSignalGen m => a -> Signal a -> m (Signal a) Source

Same as delay

delayS sig returns a Signal whose value is equal to the value of sig in the previous step. This function does not introduce a direct dependency; for example it is ok if sig depends on the resulting signal of the call.

generatorS :: MonadSignalGen m => Signal (SignalGen a) -> m (Signal a) Source

Same as generator

generatorS net runs the SignalGen action specified by net each step. generatorS returns a signal that contains the value returned by the action in this step.

snapshotS :: MonadSignalGen m => Signal a -> m a Source

Same as snapshot

snapshotS sig returns the current value of sig.

memoS :: MonadSignalGen m => Signal a -> m (Signal a) Source

Same as memo

memoS sig returns a memoized version of sig. The returned signal can be used any number of times without the risk of duplicated computation.

transferS :: MonadSignalGen m => a -> (t -> a -> a) -> Signal t -> m (Signal a) Source