UISF-0.3.0.2: Library for Arrowized Graphical User Interfaces.

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

FRP.UISF.AuxFunctions

Contents

Description

Auxiliary functions for use with UISF or other arrows.

Synopsis

Types

type SEvent = Maybe Source

SEvent is short for "Stream Event" and is a type synonym for Maybe.

type Time = Double Source

Time is simply represented as a Double.

type DeltaT = Double Source

DeltaT is a type synonym referring to a change in Time.

class ArrowTime a where Source

Instances of this class have arrowized access to time. This is convenient in many cases where time is necessary but we would prefer not to make it an explicit argument.

Methods

time :: a () Time Source

Instances

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 upon the initialization of the arrow and then uses the result of that action to generate the arrow itself.

Instances

Useful SF Utilities (Mediators)

constA :: Arrow a => c -> a b c Source

constA is an arrowized version of const.

constSF :: Arrow a => b -> a b d -> a c d Source

constSF is a convenience composing constA with the given SF.

edge :: ArrowCircuit a => a Bool (SEvent ()) Source

edge generates an event whenever the Boolean input signal changes from False to True -- in signal processing this is called an ``edge detector,'' and thus the name chosen here.

accum :: ArrowCircuit a => b -> a (SEvent (b -> b)) b Source

The signal function (accum v) starts with the value v, but then applies the function attached to the first event to that value to get the next value, and so on.

unique :: Eq e => ArrowCircuit a => a e (SEvent e) Source

The signal function unique will produce an event each time its input signal changes.

hold :: ArrowCircuit a => b -> a (SEvent b) b Source

hold is a signal function whose output starts as the value of the static argument. This value is held until the first input event happens, at which point it changes to the value attached to that event, which it then holds until the next event, and so on.

now :: ArrowCircuit a => a () (SEvent ()) Source

Now is a signal function that produces one event and then forever after produces nothing. It is essentially an impulse function.

mergeE :: (a -> a -> a) -> SEvent a -> SEvent a -> SEvent a Source

mergeE merges two events with the given resolution function.

(~++) :: SEvent [a] -> SEvent [a] -> SEvent [a] Source

This is an infix specialization of mergeE to lists.

concatA :: Arrow a => [a b c] -> a [b] [c] Source

Combines the input list of arrows into one arrow that takes a list of inputs and returns a list of outputs.

runDynamic :: ArrowChoice a => a b c -> a [b] [c] Source

This is a special case of foldA for lists.

foldA :: ArrowChoice a => (c -> d -> d) -> d -> a b c -> a [b] d Source

This essentially allows an arrow that processes b to c to take [b] and recursively generate cs, combining them all into a final output d.

foldSF :: Arrow a => (b -> c -> c) -> c -> [a () b] -> a () c Source

For folding results of a list of signal functions.

maybeA :: ArrowChoice a => a () c -> a b c -> a (Maybe b) c Source

This behaves much like the maybe function except lifted to the ArrowChoice level. The arrow behaves like its first argument when the input stream is Nothing and like its second when it is a Just value.

evMap :: ArrowChoice a => a b c -> a (SEvent b) (SEvent c) Source

This lifts the arrow to an event-based arrow that behaves as a constant stream of Nothing when there is no event.

Delays and Timers

delay

Arguments

:: forall (a :: * -> * -> *). ArrowCircuit a 
=> b

the value to return initially.

-> a b b

an arrow that propagates its input with a one-tick delay.

A delay component.

delay is a unit delay. It is exactly the delay from ArrowCircuit.

vdelay :: (ArrowTime a, ArrowCircuit a) => a (DeltaT, SEvent b) (SEvent b) Source

vdelay is a delay function that delays for a variable amount of time. It takes the current time, an amount of time to delay, and an event stream and delays the event stream by the delay amount. vdelay, like fdelay, guarantees that the order of events in is the same as the order of events out and that no event will be skipped. If the events are too dense or the delay argument drops too quickly, some events may be over delayed.

fdelay :: (ArrowTime a, ArrowCircuit a) => DeltaT -> a (SEvent b) (SEvent b) Source

fdelay is a delay function that delays for a fixed amount of time, given as the static argument. It returns a signal function that takes the current time and an event stream and delays the event stream by the delay amount. fdelay guarantees that the order of events in is the same as the order of events out and that no event will be skipped. However, if events are too densely packed in the signal (compared to the clock rate of the underlying arrow), then some events may be over delayed.

vcdelay :: (ArrowTime a, ArrowCircuit a) => DeltaT -> b -> a (DeltaT, b) b Source

vcdelay is a continuous version of vdelay. It will always emit the value that was produced dt seconds earlier (erring on the side of an older value if necessary). Be warned that this version of delay can both omit some data entirely and emit the same data multiple times. As such, it is usually inappropriate for events (use vdelay). vcdelay takes a maxDT argument that stands for the maximum delay time that it can handle. This is to prevent a space leak.

Implementation note: Rather than keep a single buffer, we keep two sequences that act to produce a sort of lens for a buffer. qlow has all the values that are older than what we currently need, and qhigh has all of the newer ones. Obviously, as time moves forward and the delay amount variably changes, values are moved back and forth between these two sequences as necessary. This should provide a slight performance boost.

fcdelay :: (ArrowTime a, ArrowCircuit a) => b -> DeltaT -> a b b Source

fcdelay is a continuous version of fdelay. It takes an initial value to emit for the first dt seconds. After that, the delay will always be accurate, but some data may be ommitted entirely. As such, it is not advisable to use fcdelay for event streams where every event must be processed (that's what fdelay is for).

timer :: (ArrowTime a, ArrowCircuit a) => a DeltaT (SEvent ()) Source

timer is a variable duration timer. This timer takes the current time as well as the (variable) time between events and returns an SEvent steam. When the second argument is non-positive, the output will be a steady stream of events. As long as the clock speed is fast enough compared to the timer frequency, this should give accurate and predictable output and stay synchronized with any other timer and with time itself.

genEvents :: (ArrowTime a, ArrowCircuit a) => [b] -> a DeltaT (SEvent b) Source

genEvents is a timer that instead of returning unit events returns the next element of the input list. When the input list is empty, the output stream becomes all Nothing.

Event buffer

type Tempo = Double Source

Tempo is just a Double.

data BufferOperation b Source

The BufferOperation data type wraps up the data and operational commands to control an eventbuffer.

Constructors

NoBOp

No Buffer Operation

ClearBuffer

Erase the buffer

SkipAheadInBuffer DeltaT

Skip ahead a certain amount of time in the buffer

MergeInBuffer [(DeltaT, b)]

Merge data into the buffer

AppendToBuffer [(DeltaT, b)]

Append data to the end of the buffer

SetBufferPlayStatus Bool (BufferOperation b)

Set a new play status (True = Playing, False = Paused)

SetBufferTempo Tempo (BufferOperation b)

Set the buffer's tempo

eventBuffer :: (ArrowTime a, ArrowCircuit a) => a (BufferOperation b) (SEvent [b], Bool) Source

eventBuffer allows for a timed series of events to be prepared and emitted. The streaming input is a BufferOperation, described above. Note that the default play status is playing and the default tempo is 1. Just as MIDI files have events timed based on ticks since the last event, the events here are timed based on seconds since the last event. If an event is to occur 0.0 seconds after the last event, then it is assumed to be played at the same time as the last event, and all simultaneous events are emitted at the same timestep. In addition to any events emitted, a streaming Bool is emitted that is True if the buffer is empty and False if the buffer is full (meaning that events will still come).

eventBuffer' :: ArrowCircuit a => a (BufferOperation b, Time) (SEvent [b], Bool) Source

eventBuffer' is a version that takes Time explicitly rather than with ArrowTime.

Signal Function Asynchrony

Due to the ability for ArrowIO arrows to perform IO actions, they are obviously not guaranteed to be pure, and thus when we run them, we say that they run "in real time". This means that the time between two samples can vary and is inherently unpredictable.

However, there are cases when we would like more control over the timing of certain arrowized computations. For instance, sometimes we have a pure computation that we would like to run on a simulated clock. This computation will expect to produce values at specific intervals, and because it's pure, that expectation can sort of be satisfied.

To achieve this, we allow these sub-computations to be performed asynchronously. The following functions behave subtly differently to exhibit different forms of asynchrony for different use cases.

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

asyncV Source

Arguments

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

Clockrate

-> DeltaT

Amount of time to buffer

-> (ThreadId -> a () ())

The thread handler

-> Automaton (->) b c

The automaton to convert to realtime

-> 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 threadHandler is where the ThreadId of the forked thread is sent.

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.

asyncE Source

Arguments

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

The thread handler

-> Automaton (->) 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.

asyncC Source

Arguments

:: (ArrowIO a, NFData c) 
=> (ThreadId -> a () ())

The thread handler

-> Automaton (->) 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.

asyncC' Source

Arguments

:: (ArrowIO a, ArrowLoop a, ArrowCircuit a, ArrowChoice a, NFData b) 
=> (ThreadId -> a () ())

The thread handler

-> (b -> IO d, e -> IO ())

Effectful input and output channels for the automaton

-> Automaton (->) (b, d) (c, e)

The automaton to convert to asynchronize

-> a b [c] 

This is a version of asyncC that does IO actions on either end of the embedded signal function.