netwire-5.0.0: Functional reactive programming library

MaintainerErtugrul Soeylemez <es@ertes.de>
Safe HaskellNone

Control.Wire.Core

Contents

Description

 

Synopsis

Wires

data Wire s e m a b whereSource

A wire is a signal function. It maps a reactive value to another reactive value.

Constructors

WArr :: (Either e a -> Either e b) -> Wire s e m a b 
WConst :: Either e b -> Wire s e m a b 
WGen :: (s -> Either e a -> m (Either e b, Wire s e m a b)) -> Wire s e m a b 
WId :: Wire s e m a a 
WPure :: (s -> Either e a -> (Either e b, Wire s e m a b)) -> Wire s e m a b 

Instances

Monad m => Arrow (Wire s e m) 
(Monad m, Monoid e) => ArrowZero (Wire s e m) 
(Monad m, Monoid e) => ArrowPlus (Wire s e m) 
(Monad m, Monoid e) => ArrowChoice (Wire s e m) 
MonadFix m => ArrowLoop (Wire s e m) 
Monad m => Category (Wire s e m) 
Monad m => Functor (Wire s e m a) 
Monad m => Applicative (Wire s e m a) 
(Monad m, Monoid e) => Alternative (Wire s e m a) 
(Monad m, Floating b) => Floating (Wire s e m a b) 
(Monad m, Fractional b) => Fractional (Wire s e m a b) 
(Monad m, Num b) => Num (Wire s e m a b) 
(Monad m, IsString b) => IsString (Wire s e m a b) 
(Monad m, Monoid b) => Monoid (Wire s e m a b) 
(Monad m, Semigroup b) => Semigroup (Wire s e m a b) 

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

Perform one step of the given wire.

Constructing wires

mkConst :: Either e b -> Wire s e m a bSource

Construct a stateless wire from the given signal mapping function.

mkEmpty :: Monoid e => Wire s e m a bSource

Construct the empty wire, which inhibits forever.

mkGen :: (Monad m, Monoid s) => (s -> a -> m (Either e b, Wire s e m a b)) -> Wire s e m a bSource

Construct a stateful wire from the given transition function.

mkGen_ :: Monad m => (a -> m (Either e b)) -> Wire s e m a bSource

Construct a stateless wire from the given transition function.

mkGenN :: Monad m => (a -> m (Either e b, Wire s e m a b)) -> Wire s e m a bSource

Construct a stateful wire from the given transition function.

mkId :: Wire s e m a aSource

Construct the identity wire.

mkPure :: Monoid s => (s -> a -> (Either e b, Wire s e m a b)) -> Wire s e m a bSource

Construct a pure stateful wire from the given transition function.

mkPure_ :: (a -> Either e b) -> Wire s e m a bSource

Construct a pure stateless wire from the given transition function.

mkPureN :: (a -> (Either e b, Wire s e m a b)) -> Wire s e m a bSource

Construct a pure stateful wire from the given transition function.

mkSF :: Monoid s => (s -> a -> (b, Wire s e m a b)) -> Wire s e m a bSource

Construct a pure stateful wire from the given signal function.

mkSF_ :: (a -> b) -> Wire s e m a bSource

Construct a pure stateless wire from the given function.

mkSFN :: (a -> (b, Wire s e m a b)) -> Wire s e m a bSource

Construct a pure stateful wire from the given signal function.

Data flow and dependencies

delay :: a -> Wire s e m a aSource

This wire delays its input signal by the smallest possible (semantically infinitesimal) amount of time. You can use it when you want to use feedback (ArrowLoop): If the user of the feedback depends on now, delay the value before feeding it back. The argument value is the replacement signal at the beginning.

  • Depends: before now.

evalWith :: Strategy a -> Wire s e m a aSource

Evaluate the input signal using the given Strategy here. This wire evaluates only produced values.

  • Depends: now.

force :: Wire s e m a aSource

Force the input signal to WHNF here. This wire forces both produced values and inhibition values.

  • Depends: now.

forceNF :: NFData a => Wire s e m a aSource

Force the input signal to NF here. This wire forces only produced values.

  • Depends: now.

Utilities

(&&&!) :: (a -> b) -> (a -> c) -> a -> (b, c)Source

Left-strict version of &&& for functions.

(***!) :: (a -> c) -> (b -> d) -> (a, b) -> (c, d)Source

Left-strict version of *** for functions.

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

Left-strict tuple.

mapWire :: (Monad m', Monad m) => (forall a. m' a -> m a) -> Wire s e m' a b -> Wire s e m a bSource

Apply the given monad morphism to the wire's underlying monad.