UISF-0.4.0.0: Library for Arrowized Graphical User Interfaces.

Copyright(c) Daniel Winograd-Cort 2015
Licensesee the LICENSE file in the distribution
Maintainerdwc@cs.yale.edu
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell98

FRP.UISF.Asynchrony

Contents

Description

This module provides functionality to allow UISF to perform asynchronous computations.

Synopsis

ArrowIO

Programming with UISF is not pure functional reactive programming. Indeed, the GUI nature demands a certain amount of effectful computation to really allow for an interface at all. That said, widgets allow only very specific effects, and they are handled in such a way that the programming feels functional and reactive.

To allow for more generic needs, we introduce the ArrowIO class below, which UISF instantiates. Note that using the ArrowIO functions should be done very carefully; if a lifted IO action blocks within the UISF, it will very likely block the entire GUI. Thus, when possible, one is advised to use initialAIO or terminalAIO, which are guaranteed to perform their IO action only once.

class Arrow a => ArrowIO a where Source

Instances of the ArrowIO class have an arrowized ability to perform IO actions.

Methods

liftAIO :: (b -> IO c) -> a b c Source

The liftAIO function lifts an IO action into an arrow.

initialAIO :: IO d -> (d -> a b c) -> a b c Source

The initialAIO function performs an IO action once when the arrow is first initialized and then uses the result of that action to generate the arrow itself.

terminalAIO :: IO () -> a b b Source

The terminalAIO function stores an IO action to be performed once when the arrow terminates. This will typically be some sort of clean up behavior.

Instances

Signal Function Asynchrony

The functions we want to perform asynchronously may be pure, but it is quite possible that they are somewhat more complex. Thus, in keeping with the general arrowized nature of UISF, we allow the asynchronized functions to be Automatons.

Use the Arrow arr function to convert a pure function to an Automaton of any type.

newtype Automaton a b c :: (* -> * -> *) -> * -> * -> *

An arrow type comprising Mealy-style automata, each step of which is is a computation in the original arrow type.

Constructors

Automaton (a b (c, Automaton a b c)) 

statefulFunctionToAutomaton :: ArrowLoop a => s -> ((b, s) -> (c, s)) -> Automaton a b c Source

A convenience function for converting stateful functions to Automatons.

actionToIOAuto :: (b -> IO c) -> IOAuto b c Source

A convenience function for converting IO actions to IOAutos.

statefulActionToIOAuto :: s -> ((b, s) -> IO (c, s)) -> IOAuto b c Source

A convenience function for converting stateful IO actions to IOAutos.

pureAutoToIOAuto :: PureAuto b c -> IOAuto b c Source

A convenience function for lifting a PureAuto into an IOAuto.

There are times when we want to perform some behavior during the course of running an arrow, but that behavior doesn't temporally align nicely with the main GUI. For example:

  • We have an FRP program that needs to be run at a fixed time rate, with each tick through time well specified.
  • We have a costly computation or potentially blocking action whose result is not immediately relevant, and we do not want to sacrifice the GUI's response time by making it part of the main loop. That is, we are okay with it taking multiple ticks to finish, but we don't want to slow down any current ticks.
  • We want to perform an action in a private, tight loop. For instance, we need to poll a device, and we do not want the GUI's framerate tied to the polling frequency in any way.

The following functions implement these different forms of asynchrony.

asyncV Source

Arguments

:: (ArrowIO a, NFData c) 
=> Double

Clockrate

-> DeltaT

Amount of time to buffer

-> PureAuto b c

The automaton to run virtually

-> a (b, Time) [(c, Time)] 

The asyncV functions is for "Virtual time" asynchrony. The embedded signal function is given along with an expected clockrate, and the output conforms to that clockrate as well as it can.

The clockrate is the simulated rate of the input signal function. The buffer is the amount of time the given signal function is allowed to get ahead of real time.

The output signal function takes and returns values in real time. The input must be paired with time, and the return values are the list of bs generated in the given time step, each time stamped. Note that the returned list may be long if the clockrate is much faster than real time and potentially empty if it's slower. Note also that the caller can check the time stamp on the element at the end of the list to see if the inner, "simulated" signal function is performing as fast as it should.

asyncVOn Source

Arguments

:: (ArrowIO a, NFData c) 
=> Int

Core to fork on

-> Double

Clockrate

-> DeltaT

Amount of time to buffer

-> PureAuto b c

The automaton to run virtually

-> a (b, Time) [(c, Time)] 

A variant of asyncV that uses forkOn internally and thus takes a core ID to fork on.

asyncVT Source

Arguments

:: (ArrowIO a, ArrowCircuit a, ArrowReader DeltaT a, NFData c) 
=> Double

Clockrate

-> DeltaT

Amount of time to buffer

-> PureAuto b c

The automaton to run virtually

-> a b [(c, Time)] 

A variant of asyncV that uses a built-in time step of the arrow to accumulate and use the current time.

asyncVTOn Source

Arguments

:: (ArrowIO a, ArrowCircuit a, ArrowReader DeltaT a, NFData c) 
=> Int

Core to fork on

-> Double

Clockrate

-> DeltaT

Amount of time to buffer

-> PureAuto b c

The automaton to run virtually

-> a b [(c, Time)] 

A variant of asyncVT that uses forkOn internally and thus takes a core ID to fork on.

asyncE Source

Arguments

:: (ArrowIO a, ArrowLoop a, ArrowCircuit a, ArrowChoice a, NFData c) 
=> PureAuto b c

The automaton to convert to asynchronize

-> a (SEvent b) (SEvent c) 

The asyncE (E for "Event") function takes a signal function (an Automaton) and converts it into an asynchronous event-based signal function usable in a ArrowIO signal function context. The output arrow takes events of type a, feeds them to the asynchronously running input signal function, and returns events with the output b whenever they are ready. The input signal function is expected to run slowly compared to the output one, but it is capable of running just as fast.

asyncEOn Source

Arguments

:: (ArrowIO a, ArrowLoop a, ArrowCircuit a, ArrowChoice a, NFData c) 
=> Int

Core to fork on

-> PureAuto b c

The automaton to asynchronize

-> a (SEvent b) (SEvent c) 

A variant of asyncE that uses forkOn internally and thus takes a core ID to fork on.

asyncEIO Source

Arguments

:: (ArrowIO a, ArrowLoop a, ArrowCircuit a, ArrowChoice a, NFData c) 
=> (IO d, d -> IO ())

Initialization and termination procedures

-> (d -> IOAuto b c)

The automaton to asynchronize

-> a (SEvent b) (SEvent c) 

A variant of asyncE that takes an IOAuto and can thus perform IO actions.

asyncEIOOn Source

Arguments

:: (ArrowIO a, ArrowLoop a, ArrowCircuit a, ArrowChoice a, NFData c) 
=> Int

Core to fork on

-> (IO d, d -> IO ())

Initialization and termination procedures

-> (d -> IOAuto b c)

The automaton to asynchronize

-> a (SEvent b) (SEvent c) 

A variant of asyncEIO that uses forkOn internally and thus takes a core ID to fork on.

asyncC Source

Arguments

:: (ArrowIO a, ArrowLoop a, ArrowCircuit a, ArrowChoice a, NFData c) 
=> PureAuto b c

The automaton to convert to realtime

-> a b [c] 

The asyncC (C for "Continuous time") function allows a continuous signal function to run as fast as it can asynchronously. There are no guarantees that all input data make it to the asynchronous signal function; if this is required, asyncE should be used instead. Rather, the embedded signal function runs as fast as it can on whatever value it has most recently seen. Its results are bundled together in a list to be returned to the main signal function.

asyncCOn Source

Arguments

:: (ArrowIO a, ArrowLoop a, ArrowCircuit a, ArrowChoice a, NFData c) 
=> Int

Core to fork on

-> PureAuto b c

The automaton to convert to realtime

-> a b [c] 

A variant of asyncC that uses forkOn internally and thus takes a core ID to fork on.

asyncCIO Source

Arguments

:: (ArrowIO a, ArrowLoop a, ArrowCircuit a, ArrowChoice a, NFData c) 
=> (IO d, d -> IO ())

Initialization and termination procedures

-> (d -> IOAuto b c)

The automaton to convert to realtime

-> a b [c] 

A variant of asyncC that takes an IOAuto and can thus perform IO actions.

asyncCIOOn Source

Arguments

:: (ArrowIO a, ArrowLoop a, ArrowCircuit a, ArrowChoice a, NFData c) 
=> Int

Core to fork on

-> (IO d, d -> IO ())

Initialization and termination procedures

-> (d -> IOAuto b c)

The automaton to convert to realtime

-> a b [c] 

A variant of asyncCIO that uses forkOn internally and thus takes a core ID to fork on.