WidgetRattus-0.4: An asynchronous modal FRP language for GUI programming
Safe HaskellSafe-Inferred
LanguageHaskell2010

WidgetRattus.Signal

Description

Programming with signals.

Synopsis

Documentation

map :: Box (a -> b) -> Sig a -> Sig b Source #

Apply a function to the value of a signal.

mapAwait :: Box (a -> b) -> O (Sig a) -> O (Sig b) Source #

A version of map for delayed signals.

switch :: Sig a -> O (Sig a) -> Sig a Source #

This function allows to switch from one signal to another one dynamically. The signal defined by switch xs ys first behaves like xs, but as soon as ys produces a new value, switch xs ys behaves like ys.

Example:

          xs: 1 2 3 4 5   6 7 8   9
          ys:         1 2   3 4 5 6

switch xs ys: 1 2 3 1 2 4   3 4 5 6

switchS :: Stable a => Sig a -> O (a -> Sig a) -> Sig a Source #

This function is similar to switch, but the (future) second signal may depend on the last value of the first signal.

switchR :: Stable a => Sig a -> O (Sig (a -> Sig a)) -> Sig a Source #

Variant of switchS that repeatedly switches. The output signal switch xs ys first behaves like xs, but whenever ys produces a value f, the signal switches to f v where v is the previous value of the output signal.

switchS can be considered a special case of switchR that only makes a single switch. That is we have the following:

switchS xs ys = switchR (delay (const (adv xs))) ys

trigger :: (Stable b, Stable c) => Box (a -> b -> c) -> Sig a -> Sig b -> Sig c Source #

This function is a variant of zipWith. Whereas zipWith f xs ys produces a new value whenever xs or ys produce a new value, trigger f xs ys only produces a new value when xs produces a new value, otherwise it just repeats the previous value.

Example:

                     xs:  1     0 5 2
                     ys:  1 2 3     2

zipWith (box (+)) xs ys:  2 3 4 3 8 4
trigger (box (+)) xy ys:  2 2 2 3 8 4

triggerAwait :: (Stable b, Stable c) => Box (a -> b -> c) -> c -> O (Sig a) -> Sig b -> Sig c Source #

This function is a variant of trigger that works on a delayed input signal. To this end, triggerAwait takes an additional argument that is the initial value of output signal.

Example:

                            xs:    1     0 5 2
                            ys:  5 1 2 3     2

triggerAwait (box (+)) 0 xy ys:  0 2 2 2 3 8 4

triggerM :: Stable b => Box (a -> b -> Maybe' c) -> Sig a -> Sig b -> Sig (Maybe' c) Source #

This function is a variant of trigger that only produces a value when the first signal ticks; otherwise it produces Nothing'.

Example:

                     xs:  1     0 5 2
                     ys:  1 2 3     2

zipWith (box plus) xs ys:  2 3 4 3 8 4
trigger (box plus) xy ys:  2 N N 3 8 4

where > plus x y = Just' (x+y)

triggerAwaitM :: Stable b => Box (a -> b -> Maybe' c) -> O (Sig a) -> Sig b -> O (Sig (Maybe' c)) Source #

This function is a variant of triggerAwait that only produces a value when the first signal ticks; otherwise it produces Nothing'.

Example:

                            xs:    1     0 5 2
                            ys:  5 1 2 3     2

triggerAwaitM (box plus) xy ys:    2 N N 3 8 4 where plus x y =

Just' (x+y)

buffer :: Stable a => a -> Sig a -> Sig a Source #

bufferAwait :: Stable a => a -> O (Sig a) -> O (Sig a) Source #

switchAwait :: O (Sig a) -> O (Sig a) -> O (Sig a) Source #

This function is similar to switch but works on delayed signals instead of signals.

interleave :: Box (a -> a -> a) -> O (Sig a) -> O (Sig a) -> O (Sig a) Source #

This function interleaves two signals producing a new value v whenever either input stream produces a new value v. In case the input signals produce a new value simultaneously, the function argument is used break ties, i.e. to compute the new output value based on the two new input values

Example:

                        xs: 1 3   5 3 1 3
                        ys:   0 2   4

interleave (box (+)) xs ys: 1 3 2 5 7 1 3

mapInterleave :: Box (a -> a) -> Box (a -> a -> a) -> O (Sig a) -> O (Sig a) -> O (Sig a) Source #

This is the composition of mapAwait and interleave. That is,

mapInterleave f g xs ys = mapAwait f (interleave xs ys)

interleaveAll :: Box (a -> a -> a) -> List (O (Sig a)) -> O (Sig a) Source #

mkSig :: Box (O a) -> O (Sig a) Source #

Turns a boxed delayed computation into a delayed signal.

mkSig' :: Box (O (C a)) -> O (Sig a) Source #

Turns a boxed delayed computation into a delayed signal.

current :: Sig a -> a Source #

Get the current value of a signal.

future :: Sig a -> O (Sig a) Source #

Get the future the signal.

const :: a -> Sig a Source #

Construct a constant signal that never updates.

jump :: Box (a -> Maybe' (Sig a)) -> Sig a -> Sig a Source #

jump (box f) xs first behaves like xs, but as soon as f x = Just xs' for a (current or future) value x of xs, it behaves like xs'.

jumping :: Box (a -> Maybe' (Sig a)) -> Sig a -> Sig a Source #

Similar to jump, but it can jump repeatedly. That is, jumping (box f) xs first behaves like xs, but every time f x = Just xs' for a (current or future) value x of jumping (box f) xs, it behaves like xs'.

stop :: Box (a -> Bool) -> Sig a -> Sig a Source #

Stops as soon as the the predicate becomes true for the current value. That is, stop (box p) xs first behaves as xs, but as soon as f x = True for some (current or future) value x of xs, then it behaves as const x.

scan :: Stable b => Box (b -> a -> b) -> b -> Sig a -> Sig b Source #

Similar to Haskell's scanl.

scan (box f) x (v1 ::: v2 ::: v3 ::: ... ) == (x `f` v1) ::: ((x `f` v1) `f` v2) ::: ...

Note: Unlike scanl, scan starts with x f v1, not x.

scanC :: Stable b => Box (b -> a -> C b) -> b -> Sig a -> C (Sig b) Source #

A variant of scan that works with the C monad.

scanAwait :: Stable b => Box (b -> a -> b) -> b -> O (Sig a) -> Sig b Source #

Like scan, but uses a delayed signal.

scanAwaitC :: Stable b => Box (b -> a -> C b) -> b -> O (Sig a) -> Sig b Source #

A variant of scanAwait that works with the C monad.

scanMap :: Stable b => Box (b -> a -> b) -> Box (b -> c) -> b -> Sig a -> Sig c Source #

scanMap is a composition of map and scan:

scanMap f g x === map g . scan f x

data Sig a Source #

Sig a is a stream of values of type a.

Constructors

!a ::: !(O (Sig a)) infixr 5 

Instances

Instances details
Continuous a => Continuous (Sig a) Source # 
Instance details

Defined in WidgetRattus.Signal

zipWith :: (Stable a, Stable b) => Box (a -> b -> c) -> Sig a -> Sig b -> Sig c Source #

This function is a variant of combines the values of two signals using the function argument. zipWith f xs ys produces a new value unbox f x y whenever xs or ys produce a new value, where x and y are the current values of xs and ys, respectively.

Example:

                     xs:  1 2 3     2
                     ys:  1     0 5 2

zipWith (box (+)) xs ys:  2 3 4 3 8 4

zipWith3 :: forall a b c d. (Stable a, Stable b, Stable c) => Box (a -> b -> c -> d) -> Sig a -> Sig b -> Sig c -> Sig d Source #

Variant of zipWith with three signals.

zip :: (Stable a, Stable b) => Sig a -> Sig b -> Sig (a :* b) Source #

This is a special case of zipWith using the tupling function. That is,

zip = zipWith (box (:*))

cond :: Stable a => Sig Bool -> Sig a -> Sig a -> Sig a Source #

If-then-else lifted to signals. cond bs xs ys produces a stream whose value is taken from xs whenever bs is true and from ys otherwise.

update :: Stable a => Sig a -> O (Sig (a -> a)) -> Sig a Source #

Takes two signals and updates the first signal using the functions produced by the second signal:

Law:

(xs `update` fs) `update` gs = (xs `update` (interleave (box (.)) gs fs))

integral :: forall a v. (VectorSpace v a, Eq v, Fractional a, Stable v, Stable a) => v -> Sig v -> Sig v Source #

integral x xs computes the integral of the signal xs with the constant x. For example, if xs is the velocity of an object, the signal integral 0 xs describes the distance travelled by that object.

derivative :: forall a v. (VectorSpace v a, Eq v, Fractional a, Stable v, Stable a) => Sig v -> Sig v Source #

Compute the derivative of a signal. For example, if xs is the velocity of an object, the signal derivative xs describes the acceleration travelled by that object.