netwire-1.2.7: Arrowized FRP implementation

MaintainerErtugrul Soeylemez <es@ertes.de>

FRP.NetWire.Wire

Contents

Description

The module contains the main Wire type and its type class instances. It also provides convenience functions for wire developers.

Synopsis

Wires

data Wire whereSource

A wire is a network of signal transformers.

Constructors

WArr :: (a -> b) -> Wire m a b 
WGen :: (WireState m -> a -> m (Output b, Wire m a b)) -> Wire m a b 

Instances

Monad m => Arrow (Wire m)

Arrow interface to signal networks.

Monad m => ArrowZero (Wire m)

The zero arrow always inhibits.

Monad m => ArrowPlus (Wire m)

Left-biased signal network combination. If the left arrow inhibits, the right arrow is tried. If both inhibit, their combination inhibits. Ignored wire networks still run in real time, i.e. passed time deltas are accumulated.

Monad m => ArrowChoice (Wire m)

Signal routing. Unused routes are ignored. Note that they still run in real time, i.e. the time deltas passed are accumulated.

Monad m => ArrowApply (Wire m)

The app combinator has the behaviour of appFrozen. Note that this effectively keeps a wire bound by the -<< syntax from evolving. For alternative embedding combinators see also appEvent and appFirst.

MonadFix m => ArrowLoop (Wire m)

Value recursion. Warning: Recursive signal networks must never inhibit. Make use of FRP.NetWire.Tools.exhibit or FRP.NetWire.Event.event for wires that may inhibit.

Monad m => Category (Wire m)

Identity signal network and signal network sequencing.

Monad m => Functor (Wire m a)

Map over the output of a signal network.

Monad m => Applicative (Wire m a)

Applicative interface to signal networks.

Monad m => Alternative (Wire m a)

This instance corresponds to the ArrowPlus and ArrowZero instances.

data WireState whereSource

The state of the wire.

Constructors

ImpureState :: MonadIO m => Double -> MTGen -> TVar Int -> WireState m 

Fields

wsDTime :: Double

Time difference for current instant.

wsRndGen :: MTGen

Random number generator.

wsReqVar :: TVar Int

Request counter.

PureState :: Double -> WireState m 

Fields

wsDTime :: Double

Time difference for current instant.

Auxilliary types

data InhibitException Source

Inhibition exception with an informative message. This exception is the result of signal inhibition, where no further exception information is available.

Constructors

InhibitException String 

type Output = Either SomeExceptionSource

Functor for output signals.

type SF = Wire IdentitySource

Signal functions are wires over the identity monad.

type Time = DoubleSource

Time.

Utilities

cleanupWireState :: WireState m -> IO ()Source

Clean up wire state.

initWireState :: MonadIO m => IO (WireState m)Source

Initialize wire state.

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

Create a fixed wire from the given function. This is a smart constructor. It creates a stateless wire.

mkGen :: (WireState m -> a -> m (Output b, Wire m a b)) -> Wire m a bSource

Create a generic (i.e. possibly stateful) wire from the given function. This is a smart constructor. Please use it instead of the WGen constructor for creating generic wires.

noEvent :: SomeExceptionSource

Construct an InhibitException wrapped in a SomeException with a message indicating that a certain event did not happen.

toGen :: Monad m => Wire m a b -> WireState m -> a -> m (Output b, Wire m a b)Source

Extract the transition function of a wire. Unless there is reason (like optimization) to pattern-match against the Wire constructors, this function is the recommended way to evolve a wire.

Wire transformers

appEvent :: forall a b m. Monad m => Wire m a b -> Wire m (Maybe (Wire m a b), a) bSource

Embeds the input wire (left signal) into the network with the given input signal (right signal). Each time the input wire is a Just, the current state of the last wire is discarded and the new wire is evolved instead. New wires can be generated by an event wire and catched via FRP.NetWire.Event.event. The initial wire is given by the argument.

Inhibits whenever the embedded wire inhibits. Same feedback behaviour as the embedded wire.

appFirst :: forall a b m. Monad m => Wire m (Wire m a b, a) bSource

Embeds the first received input wire (left signal) into the network, feeding it the right signal. This wire respects its left signal only in the first instant, after which it wraps that wire's evolution.

Inhibits whenever the embedded wire inhibits. Same feedback behaviour as the embedded wire.

appFrozen :: Monad m => Wire m (Wire m a b, a) bSource

Embeds the first instant of the input wire (left signal) into the network, feeding it the right signal. This wire respects its left signal in all instances, such that the embedded wire cannot evolve.

Inhibits whenever the embedded wire inhibits. Same feedback behaviour as the embedded wire.