wires-0.2.1: Functional reactive programming library

Copyright(c) 2017 Ertugrul Söylemez
LicenseBSD3
MaintainerErtugrul Söylemez <esz@posteo.de>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Control.Wire.Core

Contents

Description

 

Synopsis

Wires

data Wire m a b Source #

Wire is a language for defining reactive systems. It is similar to the underlying monad m, but runs continuously.

Instances

Monad m => Arrow (Wire m) Source # 

Methods

arr :: (b -> c) -> Wire m b c #

first :: Wire m b c -> Wire m (b, d) (c, d) #

second :: Wire m b c -> Wire m (d, b) (d, c) #

(***) :: Wire m b c -> Wire m b' c' -> Wire m (b, b') (c, c') #

(&&&) :: Wire m b c -> Wire m b c' -> Wire m b (c, c') #

Monad m => ArrowChoice (Wire m) Source # 

Methods

left :: Wire m b c -> Wire m (Either b d) (Either c d) #

right :: Wire m b c -> Wire m (Either d b) (Either d c) #

(+++) :: Wire m b c -> Wire m b' c' -> Wire m (Either b b') (Either c c') #

(|||) :: Wire m b d -> Wire m c d -> Wire m (Either b c) d #

MonadFix m => ArrowLoop (Wire m) Source # 

Methods

loop :: Wire m (b, d) (c, d) -> Wire m b c #

Applicative m => Choice (Wire m) Source # 

Methods

left' :: Wire m a b -> Wire m (Either a c) (Either b c) #

right' :: Wire m a b -> Wire m (Either c a) (Either c b) #

Functor m => Strong (Wire m) Source # 

Methods

first' :: Wire m a b -> Wire m (a, c) (b, c) #

second' :: Wire m a b -> Wire m (c, a) (c, b) #

MonadFix m => Costrong (Wire m) Source # 

Methods

unfirst :: Wire m (a, d) (b, d) -> Wire m a b #

unsecond :: Wire m (d, a) (d, b) -> Wire m a b #

Functor m => Profunctor (Wire m) Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> Wire m b c -> Wire m a d #

lmap :: (a -> b) -> Wire m b c -> Wire m a c #

rmap :: (b -> c) -> Wire m a b -> Wire m a c #

(#.) :: Coercible * c b => (b -> c) -> Wire m a b -> Wire m a c #

(.#) :: Coercible * b a => Wire m b c -> (a -> b) -> Wire m a c #

Monad m => Category * (Wire m) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

Functor m => Functor (Wire m a) Source # 

Methods

fmap :: (a -> b) -> Wire m a a -> Wire m a b #

(<$) :: a -> Wire m a b -> Wire m a a #

Applicative m => Applicative (Wire m a) Source # 

Methods

pure :: a -> Wire m a a #

(<*>) :: Wire m a (a -> b) -> Wire m a a -> Wire m a b #

liftA2 :: (a -> b -> c) -> Wire m a a -> Wire m a b -> Wire m a c #

(*>) :: Wire m a a -> Wire m a b -> Wire m a b #

(<*) :: Wire m a a -> Wire m a b -> Wire m a a #

evalWith :: Applicative m => (forall b. a -> b -> b) -> Wire m a a Source #

Evaluate the input using the given strategy in every frame. Valid arguments include functions like seq.

initial :: Applicative m => Wire m (m a) a Source #

Run the given action once at the beginning.

withM :: Monad m => (s -> Wire m a b) -> (a -> m s) -> Wire m a b Source #

Run the given action to initialise the given wire. Example:

withM (scan f) actionFromInitialInput

Events

data Event a Source #

An event is a timestamped stream of occurrences with payloads of the given type.

Instances

Functor Event Source # 

Methods

fmap :: (a -> b) -> Event a -> Event b #

(<$) :: a -> Event b -> Event a #

Plus Event Source # 

Methods

zero :: Event a #

Alt Event Source # 

Methods

(<!>) :: Event a -> Event a -> Event a #

some :: Applicative Event => Event a -> Event [a] #

many :: Applicative Event => Event a -> Event [a] #

Apply Event Source # 

Methods

(<.>) :: Event (a -> b) -> Event a -> Event b #

(.>) :: Event a -> Event b -> Event b #

(<.) :: Event a -> Event b -> Event a #

Bind Event Source # 

Methods

(>>-) :: Event a -> (a -> Event b) -> Event b #

join :: Event (Event a) -> Event a #

Extend Event Source # 

Methods

duplicated :: Event a -> Event (Event a) #

extended :: (Event a -> b) -> Event a -> Event b #

Align Event Source # 

Methods

nil :: Event a #

align :: Event a -> Event b -> Event (These a b) #

alignWith :: (These a b -> c) -> Event a -> Event b -> Event c #

Semigroup a => Semigroup (Event a) Source # 

Methods

(<>) :: Event a -> Event a -> Event a #

sconcat :: NonEmpty (Event a) -> Event a #

stimes :: Integral b => b -> Event a -> Event a #

Semigroup a => Monoid (Event a) Source # 

Methods

mempty :: Event a #

mappend :: Event a -> Event a -> Event a #

mconcat :: [Event a] -> Event a #

NFData a => NFData (Event a) Source # 

Methods

rnf :: Event a -> () #

catMapE :: (a -> Maybe b) -> Event a -> Event b Source #

Map and filter event occurrences using the given function.

hold :: Applicative m => a -> Wire m (Event a) a Source #

Hold the latest occurrence of the given event starting with the given initial value. The value switch occurs in the next frame.

hold' :: Applicative m => a -> Wire m (Event a) a Source #

Hold the latest occurrence of the given event starting with the given initial value. The value switch occurs instantly.

never :: Event a Source #

The event that never occurs.

unfoldE :: Applicative m => s -> Wire m (Event (s -> (a, s))) (Event a) Source #

Unfold the given event using the state transition functions it carries.

Switching

newtype Switch f m a b Source #

Functions to be applied to the current set of wires managed by manage.

Constructors

Switch 

Fields

manage :: (Traversable f, Applicative m) => f (Wire m a b) -> Wire m (a, Event (Switch f m a b)) (f b) Source #

Sequence each of the given wires and collect their results. Whenever the given event occurs its function is applied to the current set of wires. Changes are applied in the next frame.

manage' :: (Traversable f, Applicative m) => f (Wire m a b) -> Wire m (a, Event (Switch f m a b)) (f b) Source #

Sequence each of the given wires and collect their results. Whenever the given event occurs its function is applied to the current set of wires. Changes are applied immediately.

sequenceW :: (Traversable f, Applicative m) => f (Wire m a b) -> Wire m a (f b) Source #

Sequence each of the given wires and collect their results.

switch :: Functor m => Wire m a (b, Event (Wire m a b)) -> Wire m a b Source #

Acts like the given wire until its event occurs, then switches to the wire the occurrence contained. The switch occurs in the next frame.

switch' :: Monad m => Wire m a (b, Event (Wire m a b)) -> Wire m a b Source #

Acts like the given wire until its event occurs, then switches to the wire the occurrence contained. The switch occurs immediately.

Monad transformers

hoistW :: Functor m => (a -> a') -> (forall x. a -> m' x -> m x) -> Wire m' a' b -> Wire m a b Source #

Map the underlying monad using the given function.