| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Reactive.Threepenny
Synopsis
- data Event a
- data Behavior a
- type Handler a = a -> IO ()
- newEvent :: IO (Event a, Handler a)
- register :: Event a -> Handler a -> IO (IO ())
- currentValue :: MonadIO m => Behavior a -> m a
- module Control.Applicative
- never :: Event a
- filterJust :: Event (Maybe a) -> Event a
- unionWith :: (a -> a -> a) -> Event a -> Event a -> Event a
- accumE :: MonadIO m => a -> Event (a -> a) -> m (Event a)
- apply :: Behavior (a -> b) -> Event a -> Event b
- stepper :: MonadIO m => a -> Event a -> m (Behavior a)
- (<@>) :: Behavior (a -> b) -> Event a -> Event b
- (<@) :: Behavior a -> Event b -> Event a
- filterE :: (a -> Bool) -> Event a -> Event a
- filterApply :: Behavior (a -> Bool) -> Event a -> Event a
- whenE :: Behavior Bool -> Event a -> Event a
- split :: Event (Either a b) -> (Event a, Event b)
- unions :: [Event a] -> Event [a]
- concatenate :: [a -> a] -> a -> a
- accumB :: MonadIO m => a -> Event (a -> a) -> m (Behavior a)
- mapAccum :: MonadIO m => acc -> Event (acc -> (x, acc)) -> m (Event x, Behavior acc)
- data Tidings a
- tidings :: Behavior a -> Event a -> Tidings a
- facts :: Tidings a -> Behavior a
- rumors :: Tidings a -> Event a
- onChange :: Behavior a -> Handler a -> IO ()
- unsafeMapIO :: (a -> IO b) -> Event a -> Event b
- newEventsNamed :: Ord name => Handler (name, Event a, Handler a) -> IO (name -> Event a)
- test :: IO (Int -> IO ())
- test_recursion1 :: IO (IO ())
Synopsis
Functional reactive programming.
Types
At its core, Functional Reactive Programming (FRP) is about two
data types Event and Behavior and the various ways to combine them.
Event a represents a stream of events as they occur in time.
Semantically, you can think of Event a as an infinite list of values
that are tagged with their corresponding time of occurence,
type Event a = [(Time,a)]
Behavior a represents a value that varies in time. Think of it as
type Behavior a = Time -> a
IO
Functions to connect events to the outside world.
type Handler a = a -> IO () Source #
An event handler is a function that takes an event value and performs some computation.
newEvent :: IO (Event a, Handler a) Source #
Create a new event. Also returns a function that triggers an event occurrence.
register :: Event a -> Handler a -> IO (IO ()) Source #
Register an event Handler for an Event.
 All registered handlers will be called whenever the event occurs.
When registering an event handler, you will also be given an action that unregisters this handler again.
do unregisterMyHandler <- register event myHandler
FIXME: Unregistering event handlers does not work yet.
Core Combinators
module Control.Applicative
filterJust :: Event (Maybe a) -> Event a Source #
Return all event occurrences that are Just values, discard the rest.
 Think of it as
filterJust es = [(time,a) | (time,Just a) <- es]
unionWith :: (a -> a -> a) -> Event a -> Event a -> Event a Source #
Merge two event streams of the same type. In case of simultaneous occurrences, the event values are combined with the binary function. Think of it as
unionWith f ((timex,x):xs) ((timey,y):ys) | timex == timey = (timex,f x y) : unionWith f xs ys | timex < timey = (timex,x) : unionWith f xs ((timey,y):ys) | timex > timey = (timey,y) : unionWith f ((timex,x):xs) ys
apply :: Behavior (a -> b) -> Event a -> Event b Source #
Apply a time-varying function to a stream of events. Think of it as
apply bf ex = [(time, bf time x) | (time, x) <- ex]
stepper :: MonadIO m => a -> Event a -> m (Behavior a) Source #
Construct a time-varying function from an initial value and a stream of new values. Think of it as
stepper x0 ex = return $ \time ->
    last (x0 : [x | (timex,x) <- ex, timex < time])Note that the smaller-than-sign in the comparison timex < time means
 that the value of the behavior changes "slightly after"
 the event occurrences. This allows for recursive definitions.
Further combinators that Haddock can't document properly.
instance Applicative Behavior
Behavior is an applicative functor. In particular, we have the following functions.
pure :: a -> Behavior a
The constant time-varying value. Think of it as pure x = \time -> x.
(<*>) :: Behavior (a -> b) -> Behavior a -> Behavior b
Combine behaviors in applicative style.
Think of it as bf <*> bx = \time -> bf time $ bx time.
Derived Combinators
Filtering
filterE :: (a -> Bool) -> Event a -> Event a Source #
Return all event occurrences that fulfill the predicate, discard the rest.
filterApply :: Behavior (a -> Bool) -> Event a -> Event a Source #
Return all event occurrences that fulfill the time-varying predicate,
 discard the rest. Generalization of filterE.
whenE :: Behavior Bool -> Event a -> Event a Source #
Return event occurrences only when the behavior is True.
 Variant of filterApply.
Union
concatenate :: [a -> a] -> a -> a Source #
Apply a list of functions in succession.
 Useful in conjunction with unions.
concatenate [f,g,h] = f . g . h
Accumulation
Note: All accumulation functions are strict in the accumulated value!
acc -> (x,acc) is the order used by unfoldr and State.
accumB :: MonadIO m => a -> Event (a -> a) -> m (Behavior a) Source #
The accumB function is similar to a strict left fold, foldl'.
 It starts with an initial value and combines it with incoming events.
 For example, think
accumB "x" [(time1,(++"y")),(time2,(++"z"))] = stepper "x" [(time1,"xy"),(time2,"xyz")]
Note that the value of the behavior changes "slightly after" the events occur. This allows for recursive definitions.
Additional Notes
Recursion in the IO monad is possible, but somewhat limited.
The main rule is that the sequence of IO actions must be known
in advance, only the values may be recursive.
Good:
mdo
    let e2 = apply (const <$> b) e1   -- applying a behavior is not an IO action
    b <- accumB $ (+1) <$ e2Bad:
mdo
    b <- accumB $ (+1) <$ e2          -- actions executed here could depend ...
    let e2 = apply (const <$> b) e1   -- ... on this valueTidings
tidings :: Behavior a -> Event a -> Tidings a Source #
Smart constructor. Combine facts and rumors into Tidings.
Internal
Functions reserved for special circumstances. Do not use unless you know what you're doing.
Arguments
| :: Ord name | |
| => Handler (name, Event a, Handler a) | Initialization procedure. | 
| -> IO (name -> Event a) | Series of events. | 
Create a series of events with delayed initialization.
For each name, the initialization handler will be called exactly once when the event is first "brought to life", e.g. when an event handler is registered to it.
Testing
test_recursion1 :: IO (IO ()) Source #