netwire-1.2.6: Arrowized FRP implementation

MaintainerErtugrul Soeylemez <es@ertes.de>

FRP.NetWire.Wire

Contents

Description

The module contains the main Wire type.

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.

Monad m => ArrowChoice (Wire m)

Signal routing. Unused routes are frozen, until they are put back into use.

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.

Monad m => Category (Wire m)

Identity signal network and signal network sequencing.

Monad m => Functor (Wire m a)

Map over the result 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.

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

Create a generic wire from the given function. This is a smart constructor. Please use it instead of the WGen constructor.

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.