Copyright | (c) Atze van der Ploeg 2015 |
---|---|
License | BSD-style |
Maintainer | atzeus@gmail.org |
Stability | provisional |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
The core FRPNow interface, based on the paper "Principled Practical FRP: Forget the past, Change the future, FRPNow!", ICFP 2015, by Atze van der Ploeg and Koenem Claessem.
This module contains the core FRPNow interface, which consists of:
- The pure interface, which has denotational semantics
- The IO interface
- The entry points, i.e. the functions that are used to start the FRP system.
- data Event a
- data Behavior a
- never :: Event a
- switch :: Behavior a -> Event (Behavior a) -> Behavior a
- whenJust :: Behavior (Maybe a) -> Behavior (Event a)
- futuristic :: Behavior (Event a) -> Behavior (Event a)
- data Now a
- async :: IO a -> Now (Event a)
- asyncOS :: IO a -> Now (Event a)
- callback :: Now (Event a, a -> IO ())
- sampleNow :: Behavior a -> Now a
- planNow :: Event (Now a) -> Now (Event a)
- sync :: IO a -> Now a
- runNowMaster :: Now (Event a) -> IO a
- initNow :: (IO (Maybe a) -> IO ()) -> Now (Event a) -> IO ()
Pure interface
The FRPNow interface is centered around behaviors, values that change over time, and events, value that are known from some point in time on.
What the pure part of the FRPNow interface does is made precise by denotation semantics, i.e. mathematical meaning. The denotational semantics of the pure interface are
type Event a = (Time+,a) never :: Event a never = (∞, undefined) instance Monad Event where return x = (-∞,x) (ta,a) >>= f = let (tb,b) = f a in (max ta tb, b) type Behavior a = Time -> a instance Monad Behavior where return x = λt -> x m >>= f = λt -> f (m t) t instance MonadFix Behavior where mfix f = λt -> let x = f x t in x switch :: Behavior a -> Event (Behavior a) -> Behavior a switch b (ts,s) = λn -> if n < ts then b n else s n whenJust :: Behavior (Maybe a) -> Behavior (Event a) whenJust b = λt -> let w = minSet { t' | t' >= t && isJust (b t') } in if w == ∞ then never else (w, fromJust (b w))
Where Time
is a set that is totally ordered set and has a least element, -∞.
For events, we also use Time+ = Time ∪ ∞
.
The notation minSet x
indicates the minimum element of the set x
, which is not valid Haskell, but is a valid denotation. Note that if there is no time at which the input behavior is Just
in the present or future, then minSet
will give the minimum element of the empty set, which is ∞
.
The monad instance of events is denotationally a writer monad in time, whereas the monad instance of behaviors is denotationally a reader monad in time.
An event is a value that is known from some point in time on.
An behavior is a value that changes over time.
switch :: Behavior a -> Event (Behavior a) -> Behavior a Source
Introduce a change over time.
b `switch` e
Gives a behavior that acts as b
initially, and switches to the behavior inside e
as soon as e
occurs.
whenJust :: Behavior (Maybe a) -> Behavior (Event a) Source
Observe a change over time.
The behavior whenJust b
gives at any point in time the event that
the behavior b
is Just
at that time or afterwards.
As an example,
let getPos x | x > 0 = Just x | otherwise = Nothing in whenJust (getPos <$> b)
Gives gives the event that
the behavior b
is positive. If b
is currently positive
then the event will occur now, otherwise it
will be the first time that b
becomes positive in the future.
If b
never again is positive then the result is never
.
futuristic :: Behavior (Event a) -> Behavior (Event a) Source
Not typically needed, used for event streams.
If we have a behavior giving events, such that each time the behavior is sampled the obtained event is in the future, then this function ensures that we can use the event without inspecting it (i.e. before binding it).
If the implementation samples such an event and it turns out the event does actually occur at the time the behavior is sampled, an error is thrown.
IO interface
A monad that alows you to:
- Sample the current value of a behavior via
sampleNow
- Interact with the outside world via
async
,callback
andsync
. - Plan to do Now actions later, via
planNow
All actions in the Now
monad are conceptually instantaneous, which entails it is guaranteed that for any behavior b
and Now action m
:
do x <- sample b; m ; y <- sample b; return (x,y) == do x <- sample b; m ; return (x,x)
async :: IO a -> Now (Event a) Source
Asynchronously execte an IO action, and obtain the event that it is done.
Starts a seperate thread for the IO action, and then immediatly returns the
event that the IO action is done. Since all actions in the Now
monad are instantaneous,
the resulting event is guaranteed to occur in the future (not now).
Use this for IO actions which might take a long time, such as waiting for a network message, reading a large file, or expensive computations.
Note:Use this only when using FRPNow with Gloss or something else that does not block haskell threads.
For use with GTK or other GUI libraries that do block Haskell threads, use asyncOS
instead.
asyncOS :: IO a -> Now (Event a) Source
Like async
, but uses an OS thread instead of a regular lightweight thread.
Useful when interacting with GUI systems that claim the main loop, such as GTK.
callback :: Now (Event a, a -> IO ()) Source
Create an event that occurs when the callback is called.
The callback can be safely called from any thread. An error occurs if the callback is called more than once.
See callbackStream
for a callback that can be called repeatidly.
The event occurs strictly later than the time that the callback was created, even if the callback is called immediately.
Synchronously execte an IO action.
Use this is for IO actions which do not take a long time, such as opening a file or creating a widget.
Entry point
runNowMaster :: Now (Event a) -> IO a Source
Run the FRP system in master mode.
Typically, you don't need this function, but instead use a function for whatever library you want to use FRPNow with such as runNowGTK
, runNowGloss
. This function can be used in case you are not interacting with any GUI library, only using FRPNow.
Runs the given Now
computation and the plans it makes until the ending event (given by the inital Now
computation) occurs. Returns the value of the ending event.
:: (IO (Maybe a) -> IO ()) | An IO action that schedules some FRP actions to be run. The callee should ensure that all actions that are scheduled are ran on the same thread. If a scheduled action returns |
-> Now (Event a) | The |
-> IO () |
General interface to interact with the FRP system.
Typically, you don't need this function, but instead use a specialized function for whatever library you want to use FRPNow with such as runNowGTK
or runNowGloss
, which themselves are implemented using this function.