netwire-4.0.1: Flexible wire arrows for FRP

Copyright(c) 2012 Ertugrul Soeylemez
LicenseBSD3
MaintainerErtugrul Soeylemez <es@ertes.de>
Safe HaskellNone
LanguageHaskell2010

Control.Wire.Wire

Contents

Description

This is the core module implementing the Wire type.

Synopsis

Wires

data Wire e m a b Source

A wire is a signal function from an input value of type a that either produces an output value of type b or inhibits with a value of type e. The underlying monad is m.

Constructors

WGen (Time -> a -> m (Either e b, Wire e m a b)) 
WPure (Time -> a -> (Either e b, Wire e m a b)) 

Instances

Monad m => Category * (Wire e m) 
Monad m => Arrow (Wire e m) 
(Monad m, Monoid e) => ArrowZero (Wire e m) 
(Monad m, Monoid e) => ArrowPlus (Wire e m) 
Monad m => ArrowChoice (Wire e m) 
MonadFix m => ArrowLoop (Wire e m) 
Monad m => Profunctor (Wire e m) 
(Monad m, Monoid e) => Alternative (Wire e m a) 
Monad m => Functor (Wire e m a) 
Monad m => Applicative (Wire e m a) 
(Floating b, Monad m) => Floating (Wire e m a b) 
(Fractional b, Monad m) => Fractional (Wire e m a b) 
(Monad m, Num b) => Num (Wire e m a b) 
(Monad m, Read b) => Read (Wire e m a b) 
(IsString b, Monad m) => IsString (Wire e m a b) 
(Monad m, Monoid b) => Monoid (Wire e m a b) 
(HasNormal b, Monad m) => HasNormal (Wire e m a b) 
(HasCross2 b, Monad m) => HasCross2 (Wire e m a b) 
(HasCross3 b, Monad m) => HasCross3 (Wire e m a b) 
(AdditiveGroup (Diff b), AffineSpace b, Monad m) => AffineSpace (Wire e m a b) 
(Monad m, VectorSpace b) => VectorSpace (Wire e m a b) 
(InnerSpace b, Monad m) => InnerSpace (Wire e m a b) 
(AdditiveGroup b, Monad m) => AdditiveGroup (Wire e m a b) 
type Diff (Wire e m a b) = Wire e m a (Diff b) 
type Scalar (Wire e m a b) = Wire e m a (Scalar b) 

type Time = Double Source

Time.

Constructing wires

mkFix :: (Time -> a -> Either e b) -> Wire e m a b Source

Construct a pure stateless wire from the given function.

mkFixM :: Monad m => (Time -> a -> m (Either e b)) -> Wire e m a b Source

Construct a stateless effectful wire from the given function.

mkGen :: (Time -> a -> m (Either e b, Wire e m a b)) -> Wire e m a b Source

Construct an effectful wire from the given function.

mkPure :: (Time -> a -> (Either e b, Wire e m a b)) -> Wire e m a b Source

Construct a pure wire from the given function.

mkState :: s -> (Time -> (a, s) -> (Either e b, s)) -> Wire e m a b Source

Construct a pure wire from the given local state transision function.

mkStateM :: Monad m => s -> (Time -> (a, s) -> m (Either e b, s)) -> Wire e m a b Source

Construct a monadic wire from the given local state transision function.

Simple predefined wires

constant :: b -> Wire e m a b Source

Variant of pure without the Monad constraint. Using pure is preferable.

identity :: Wire e m a a Source

Variant of id without the Monad constraint. Using id is preferable.

never :: Monoid e => Wire e m a b Source

Variant of empty without the Monad constraint. Using empty is preferable.

Helper functions

mapOutput :: Monad m => (Either e b' -> Either e b) -> Wire e m a b' -> Wire e m a b Source

Map the given function over the raw wire output.

Stepping

stepWire :: Monad m => Wire e m a b -> Time -> a -> m (Either e b, Wire e m a b) Source

Perform an instant of the given wire.

stepWireP :: Wire e Identity a b -> Time -> a -> (Either e b, Wire e Identity a b) Source

Perform an instant of the given pure wire.