AsyncRattus-0.2.0.1: An asynchronous modal FRP language
Safe HaskellSafe-Inferred
LanguageHaskell2010

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

mkInputSig :: Producer p a => p -> IO (Box (O (Sig a))) Source #

Turn a producer into a signal. This is a variant of mkInput that returns a signal instead of a boxed delayed computation.

getInputSig :: IO (Box (O (Sig a)) :* (a -> IO ())) Source #

Variant of getInput that returns a signal instead of a boxed delayed computation.

filterMap :: Box (a -> Maybe' b) -> Sig a -> IO (Box (O (Sig b))) Source #

This function is essentially the composition of filter with map. The signal produced by filterMap f s has the value v whenever s has the value u such that unbox f u = Just' v.

filterMapAwait :: Box (a -> Maybe' b) -> O (Sig a) -> IO (Box (O (Sig b))) Source #

This function is similar to filterMap but takes a delayed signal (type O (Sig a)) as an argument instead of a signal (Sig a).

filter :: Box (a -> Bool) -> Sig a -> IO (Box (O (Sig a))) Source #

Filter the given signal using a predicate. The signal produced by filter p s contains only values from s that satisfy the predicate p.

filterAwait :: Box (a -> Bool) -> O (Sig a) -> IO (Box (O (Sig a))) Source #

This function is similar to filter but takes a delayed signal (type O (Sig a)) as an argument instead of a signal (Sig a).

trigger :: (Stable a, Stable b) => Box (a -> b -> c) -> Sig a -> Sig b -> IO (Box (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.

Example:

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

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

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

This function is similar to trigger but takes a delayed signal (type O (Sig a)) as an argument instead of a signal (Sig a).

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.

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

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

Turns a boxed delayed computation into a delayed signal.

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

Variant of mkSig that returns a boxed 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.

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.

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

Like scan, but uses a delayed signal.

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
Producer (Sig a) a Source # 
Instance details

Defined in AsyncRattus.Signal

Methods

getCurrent :: Sig a -> Maybe' a Source #

getNext :: Sig a -> (forall q. Producer q a => O q -> b) -> b Source #

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.

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.