threepenny-gui-0.8.3.0: GUI framework that uses the web browser as a display.

Safe HaskellNone
LanguageHaskell98

Reactive.Threepenny

Contents

Synopsis

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.

data Event a Source #

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)]
Instances
Functor Event Source # 
Instance details

Defined in Reactive.Threepenny

Methods

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

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

data Behavior a Source #

Behavior a represents a value that varies in time. Think of it as

type Behavior a = Time -> a
Instances
Functor Behavior Source # 
Instance details

Defined in Reactive.Threepenny

Methods

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

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

Applicative Behavior Source # 
Instance details

Defined in Reactive.Threepenny

Methods

pure :: a -> Behavior a #

(<*>) :: Behavior (a -> b) -> Behavior a -> Behavior b #

liftA2 :: (a -> b -> c) -> Behavior a -> Behavior b -> Behavior c #

(*>) :: Behavior a -> Behavior b -> Behavior b #

(<*) :: Behavior a -> Behavior b -> Behavior 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.

currentValue :: MonadIO m => Behavior a -> m a Source #

Read the current value of a Behavior.

Core Combinators

Minimal set of combinators for programming with Event and Behavior.

never :: Event a Source #

Event that never occurs. Think of it as never = [].

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

accumE :: MonadIO m => a -> Event (a -> a) -> m (Event a) Source #

The accumE function accumulates a stream of events. Example:

accumE "x" [(time1,(++"y")),(time2,(++"z"))]
   = return [(time1,"xy"),(time2,"xyz")]

Note that the output events are simultaneous with the input events, there is no "delay" like in the case of accumB.

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

Additional combinators that make programming with Event and Behavior convenient. ** Application

(<@>) :: Behavior (a -> b) -> Event a -> Event b infixl 4 Source #

Infix synonym for apply, similar to <*>.

(<@) :: Behavior a -> Event b -> Event a infixl 4 Source #

Variant of apply similar to <*

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.

split :: Event (Either a b) -> (Event a, Event b) Source #

Split event occurrences according to a tag. The Left values go into the left component while the Right values go into the right component of the result.

Union

unions :: [Event a] -> Event [a] Source #

Collect simultaneous event occurrences in a list.

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.

mapAccum :: MonadIO m => acc -> Event (acc -> (x, acc)) -> m (Event x, Behavior acc) Source #

Efficient combination of accumE and accumB.

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) <$ e2

Bad:

mdo
    b <- accumB $ (+1) <$ e2          -- actions executed here could depend ...
    let e2 = apply (const <$> b) e1   -- ... on this value

Tidings

data Tidings a Source #

Data type representing a behavior (facts) and suggestions to change it (rumors).

Instances
Functor Tidings Source # 
Instance details

Defined in Reactive.Threepenny

Methods

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

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

Applicative Tidings Source #

The applicative instance combines rumors and uses facts when some of the rumors are not available.

Instance details

Defined in Reactive.Threepenny

Methods

pure :: a -> Tidings a #

(<*>) :: Tidings (a -> b) -> Tidings a -> Tidings b #

liftA2 :: (a -> b -> c) -> Tidings a -> Tidings b -> Tidings c #

(*>) :: Tidings a -> Tidings b -> Tidings b #

(<*) :: Tidings a -> Tidings b -> Tidings a #

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.

onChange :: Behavior a -> Handler a -> IO () Source #

Register an event Handler for a Behavior. All registered handlers will be called whenever the behavior changes.

However, note that this is only an approximation, as behaviors may change continuously. Consequently, handlers should be idempotent.

unsafeMapIO :: (a -> IO b) -> Event a -> Event b Source #

newEventsNamed Source #

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.