netwire-1.2.6: Arrowized FRP implementation

MaintainerErtugrul Soeylemez <es@ertes.de>

FRP.NetWire.Tools

Contents

Description

The usual FRP tools you'll want to work with.

Synopsis

Basic utilities

constant :: Monad m => b -> Wire m a bSource

The constant wire. Please use this function instead of arr (const c).

Never inhibits.

identity :: Monad m => Wire m a aSource

Identity signal transformer. Outputs its input.

Never inhibits. Feedback by delay.

Time

time :: Monad m => Wire m a TimeSource

Get the local time.

Never inhibits.

timeFrom :: Monad m => Time -> Wire m a TimeSource

Get the local time, assuming it starts from the given value.

Never inhibits.

Signal transformers

accum :: Monad m => a -> Wire m (a -> a) aSource

This function corresponds to the iterate function for lists. Begins with an initial output value. Each time an input function is received, it is applied to the current accumulator and the new value is emitted.

Never inhibits. Direct feedback.

delay :: Monad m => a -> Wire m a aSource

One-instant delay. Delay the signal for an instant returning the argument value at the first instant. This wire is mainly useful to add feedback support to wires, which wouldn't support it by themselves. For example, the FRP.NetWire.Analyze.avg wire does not support feedback by itself, but the following works:

 do rec x <- delay 1 <<< avg 1000 -< x

Never inhibits. Direct feedback.

discrete :: forall a m. Monad m => Wire m (Time, a) aSource

Turn a continuous signal into a discrete one. This transformer picks values from the right signal at intervals of the left signal.

The interval length is followed in real time. If it's zero, then this wire acts like second id.

Never inhibits. Feedback by delay.

hold :: forall a b m. Monad m => Wire m a b -> Wire m a bSource

Keep the latest output.

Inhibits until first signal from argument wire. Same feedback properties as argument wire.

inject :: forall a e m. (Exception e, Monad m) => Wire m (Either e a) aSource

Inject the input Either signal.

Inhibits on Left signals.

injectMaybe :: Monad m => Wire m (Maybe a) aSource

Inject the input Maybe signal.

Inhibits on Nothing signals.

keep :: Monad m => Wire m a aSource

Keep the value in the first instant forever.

Never inhibits. Feedback by delay.

Inhibitors

forbid :: Monad m => Wire m (Bool, a) aSource

Inhibit, when the left signal is true.

Inhibits on true left signal. No feedback.

forbid_ :: Monad m => Wire m Bool ()Source

Inhibit, when the signal is true.

Inhibits on true signal. No feedback.

inhibit :: (Exception e, Monad m) => Wire m e bSource

Unconditional inhibition with the given inhibition exception.

Always inhibits.

inhibit_ :: Monad m => Wire m a bSource

Unconditional inhibition with default inhibition exception.

Always inhibits.

require :: Monad m => Wire m (Bool, a) aSource

Inhibit, when the left signal is false.

Inhibits on false left signal. No feedback.

require_ :: Monad m => Wire m Bool ()Source

Inhibit, when the signal is false.

Inhibits on false signal. No feedback.

Wire transformers

exhibit :: Monad m => Wire m a b -> Wire m a (Output b)Source

This function corresponds to try for exceptions, allowing you to observe inhibited signals. See also FRP.NetWire.Event.event.

Never inhibits. Same feedback properties as argument wire.

freeze :: Monad m => Wire m a b -> Wire m a bSource

Effectively prevent a wire from rewiring itself. This function will turn any stateful wire into a stateless wire, rendering most wires useless.

Note: This function should not be used normally. Use it only, if you know exactly what you're doing.

Same inhibition properties as first instant of argument wire. Same feedback properties as first instant of argument wire.

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

Sample the given wire at specific intervals. Use this instead of discrete, if you want to prevent the signal from passing through the wire all the time. Returns the most recent result.

The left signal interval is allowed to become zero, at which point the signal is passed through the wire at every instant.

Inhibits until the first result from the argument wire. Same feedback properties as argument wire.

swallow :: Monad m => Wire m a b -> Wire m a bSource

Wait for the first signal from the given wire and keep it forever.

Inhibits until signal from argument wire. Direct feedback, if argument wire never inhibits, otherwise no feedback.

(-->) :: Monad m => b -> Wire m a b -> Wire m a bSource

Override the output value at the first non-inhibited instant.

Same inhibition properties as argument wire. Same feedback properties as argument wire.

(>--) :: Monad m => a -> Wire m a b -> Wire m a bSource

Override the input value, until the wire starts producing.

Same inhibition properties as argument wire. Same feedback properties as argument wire.

(-=>) :: Monad m => (b -> b) -> Wire m a b -> Wire m a bSource

Apply a function to the wire's output at the first non-inhibited instant.

Same inhibition properties as argument wire. Same feedback properties as argument wire.

(>=-) :: Monad m => (a -> a) -> Wire m a b -> Wire m a bSource

Apply a function to the wire's input, until the wire starts producing.

Same inhibition properties as argument wire. Same feedback properties as argument wire.

Arrow tools

mapA :: ArrowChoice a => a b c -> a [b] [c]Source

Apply an arrow to a list of inputs.

Convenience functions

dup :: a -> (a, a)Source

Duplicate a value to a tuple.

fmod :: Double -> Double -> DoubleSource

Floating point modulo operation. Note that fmod n 0 = 0.

swap :: (a, b) -> (b, a)Source

Swap the values in a tuple.