netwire-1.2.6: Arrowized FRP implementation

MaintainerErtugrul Soeylemez <es@ertes.de>

FRP.NetWire.Request

Contents

Description

Object managers, unique identifiers and context-sensitive wires.

Synopsis

Containers

data MgrMsg k m a b Source

Messages to wire managers (see the manager wire).

Constructors

MgrNop

Do nothing. Send this, if the wire shouldn't be changed in an instant.

MgrMulti (MgrMsg k m a b) (MgrMsg k m a b)

Perform two operations in an instant.

MgrAdd k (Wire m a b)

Add the given wire with the given key. If the manager already has a wire with this key, it is overwritten.

MgrDel k

Delete the wire with the given key, if it exists.

Instances

Eq k => Monoid (MgrMsg k m a b)

The monoid instance can be used to combine multiple manager operations. They are performed from left to right. This instance tries hard to optimize operations away without sacrificing performance.

manager :: forall a b k m. (Monad m, Ord k) => Wire m (a, MgrMsg k m a b) (Map k b)Source

Wire manager, which can be manipulated during the session. This is a convenient alternative to parallel switches.

This wire manages a set of subwires, each indexed by a key. Through messages new subwires can be added and existing ones can be deleted.

Inhibits, whenever one of the managed wires inhibits. Inherits feedback behaviour from the worst managed wire.

Context-sensitive mutation

context :: forall a b ctx m. (Ord ctx, Monad m) => Wire m (ctx, a) b -> Wire m (ctx, a) bSource

Make the given wire context-sensitive. The left input signal is a context and the argument wire will mutate individually for each such context.

Inherits inhibition and feedback behaviour from the current context's wire.

contextInt :: forall a b m. Monad m => Wire m (Int, a) b -> Wire m (Int, a) bSource

Specialized version of context. Use this one, if your contexts are Ints and you have a lot of them.

Inherits inhibition and feedback behaviour from the current context's wire.

contextLimited :: forall a b ctx m. (Ord ctx, Monad m) => Wire m (ctx, a) b -> Wire m (Int, Time, ctx, a) bSource

Same as context, but with a time limit. The first signal specifies a threshold and the second signal specifies a maximum age. If the current number of contexts exceeds the threshold, then all contexts exceeding the maximum age are deleted.

Inherits inhibition and feedback behaviour from the current context's wire.

contextLimitedInt :: forall a b m. Monad m => Wire m (Int, a) b -> Wire m (Int, Time, Int, a) bSource

Specialized version of contextLimited. Use this one, if your contexts are Ints and you have a lot of them.

Inherits inhibition and feedback behaviour from the current context's wire.

Simple variants

context_ :: (Ord ctx, Monad m) => Wire m ctx b -> Wire m ctx bSource

Simplified variant of context. Takes a context signal only.

contextInt_ :: Monad m => Wire m Int b -> Wire m Int bSource

Simplified variant of contextInt. Takes a context signal only.

contextLimited_ :: (Ord ctx, Monad m) => Wire m ctx b -> Wire m (Int, Time, ctx) bSource

Simplified variant of contextLimited. Takes a context signal only.

contextLimitedInt_ :: Monad m => Wire m Int b -> Wire m (Int, Time, Int) bSource

Simplified variant of contextLimitedInt. Takes a context signal only.

Identifiers.

identifier :: MonadIO m => Wire m a IntSource

Choose a new unique identifier at every instant.

Never inhibits. Feedback by delay.