netwire-1.2.7: Arrowized FRP implementation

MaintainerErtugrul Soeylemez <es@ertes.de>

FRP.NetWire

Contents

Description

Arrowized FRP implementation for networking applications. The aim of this library is to provide a convenient FRP implementation, which should enable you to write entirely pure network sessions.

Synopsis

Wires

data Wire Source

A wire is a network of signal transformers.

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.

type Output = Either SomeExceptionSource

Functor for output signals.

type Time = DoubleSource

Time.

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.

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.

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.

Reactive sessions

data Session m a b Source

Reactive sessions with the given input and output types over the given monad. The monad must have a MonadControlIO instance to be usable with the stepping functions.

stepWireSource

Arguments

:: MonadControlIO m 
=> a

Input value.

-> Session m a b

Session to step.

-> m (Output b)

System's output.

Feed the given input value into the reactive system performing the next instant using real time.

stepWireDeltaSource

Arguments

:: MonadControlIO m 
=> NominalDiffTime

Time delta.

-> a

Input value.

-> Session m a b

Session to step.

-> m (Output b)

System's output.

Feed the given input value into the reactive system performing the next instant using the given time delta.

stepWireTimeSource

Arguments

:: MonadControlIO m 
=> UTCTime

Absolute time of the instant to perform.

-> a

Input value.

-> Session m a b

Session to step.

-> m (Output b)

System's output.

Feed the given input value into the reactive system performing the next instant, which is at the given time. This function is thread-safe.

withWireSource

Arguments

:: (MonadControlIO m, MonadIO sm) 
=> Wire sm a b

Initial wire of the session.

-> (Session sm a b -> m c)

Continuation, which receives the session data.

-> m c

Continuation's result.

Initialize a reactive session and pass it to the given continuation.

Testing wires

testWireSource

Arguments

:: forall a b m . (MonadControlIO m, Show b) 
=> Int

Show output once each this number of frames.

-> m a

Input generator.

-> Wire m a b

Your wire.

-> m () 

Interface to testWireStr accepting all Show instances as the output type.

testWireStrSource

Arguments

:: forall a m . MonadControlIO m 
=> Int

Show output once each this number of frames.

-> m a

Input generator.

-> Wire m a String

Wire to evolve.

-> m () 

This function provides a convenient way to test wires. It wraps a default loop around your wire, which just displays the output on your stdout in a single line (it uses an ANSI escape sequence to clear the line). It uses real time.

Pure wires

type SF = Wire IdentitySource

Signal functions are wires over the identity monad.

stepSF :: Time -> a -> SF a b -> (Output b, SF a b)Source

Perform the next instant of a pure wire over the identity monad.

stepWirePure :: Monad m => Time -> a -> Wire m a b -> m (Output b, Wire m a b)Source

Perform the next instant of a pure wire.

Inhibition

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 

noEvent :: SomeExceptionSource

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

Netwire Reexports

Other convenience reexports