UISF-0.1.0.0: Library for Arrowized Graphical User Interfaces.

Stabilityexperimental
Maintainerdwc@cs.yale.edu
Safe HaskellNone

FRP.UISF.AuxFunctions

Contents

Description

Auxiliary functions for use with UISF or other arrows.

Synopsis

Types

type SEvent = MaybeSource

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

type Time = DoubleSource

Time is simply represented as a Double.

type DeltaT = DoubleSource

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

class ArrowTime a whereSource

Instances of this class have arrowized access to the time

Methods

time :: a () TimeSource

Instances

Useful SF Utilities (Mediators)

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

constA is an arrowized version of const

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

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

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

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 aSource

mergeE merges two events with the given resolution function.

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

A nice infix operator for merging event lists

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

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

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

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.

Delays and Timers

delay :: ArrowCircuit a => forall b. b -> a b b

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

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

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.

vdelayC :: (ArrowTime a, ArrowCircuit a) => DeltaT -> b -> a (DeltaT, b) bSource

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

fdelayC :: (ArrowTime a, ArrowCircuit a) => b -> DeltaT -> a b bSource

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

data BufferEvent b Source

The BufferEvent data type is used in tandem with BufferControl to provide the right control information to eventBuffer.

Constructors

Clear

Erase the buffer

SkipAhead DeltaT

Skip ahead a certain amount of time in the buffer

AddData [(DeltaT, b)]

Merge data into the buffer

AddDataToEnd [(DeltaT, b)]

Add data to the end of the buffer

type Tempo = DoubleSource

Tempo is just a Double.

type BufferControl b = (SEvent (BufferEvent b), Bool, Tempo)Source

BufferControl has a Buffer event, a bool saying whether to Play (true) or Pause (false), and a tempo multiplier.

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

eventBuffer allows for a timed series of events to be prepared and emitted. The streaming input is a BufferControl, described above. 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).

Signal Function Conversions

Due to the internal monad (specifically, because it could be IO), MSFs are not necessarily pure. 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, 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.

The three functions in this section are three different ways to handle this case. toMSF simply lifts the pure computation and "hopes" that the timing works the way you want. As expected, this is not recommended. async lets the pure computation compute in its own thread, but it puts no restrictions on speed. toRealTimeMSF takes a signal rate argument and attempts to mediate between real and virtual time.

Rather than use MSF Identity as our default pure function, we present the Automaton type:

newtype Automaton a b Source

Constructors

Automaton (a -> (b, Automaton a b)) 

toAutomaton :: (a -> b) -> Automaton a bSource

toAutomaton lifts a pure function to an Automaton.

msfiToAutomaton :: MSF Identity a b -> Automaton a bSource

msfiToAutomaton lifts a pure MSF (i.e. one in the Identity monad) to an Automaton.

Conversions

The following two functions are for lifting SFs to MSFs. The first one is a quick and dirty solution, and the second one appropriately converts a simulated time SF into a real time one.

toMSF :: Monad m => Automaton a b -> MSF m a bSource

This function should be avoided, as it directly converts the automaton with no real regard for time.

toRealTimeMSFSource

Arguments

:: forall m a b . (Monad m, MonadIO m, MonadFix m, NFData b) 
=> Double

Clockrate

-> DeltaT

Amount of time to buffer

-> (ThreadId -> m ())

The thread handler

-> Automaton a b

The automaton to convert to realtime

-> MSF m (a, Double) [(b, Double)] 

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.

asyncSource

Arguments

:: forall m a b . (Monad m, MonadIO m, MonadFix m, NFData b) 
=> (ThreadId -> m ())

The thread handler

-> Automaton a b

The automaton to convert to asynchronize

-> MSF m (SEvent a) (SEvent b) 

The async function takes a pure (non-monadic) signal function and converts it into an asynchronous signal function usable in a MonadIO signal function context. The output MSF takes events of type a, feeds them to the asynchronously running input SF, and returns events with the output b whenever they are ready. The input SF is expected to run slowly compared to the output MSF, but it is capable of running just as fast.

Might we practically want a way to "clear the buffer" if we accidentally queue up too many async inputs? Perhaps the output should be something like: data AsyncOutput b = None | Calculating Int | Value b where the Int is the size of the buffer. Similarly, we could have data AsyncInput a = None | ClearBuffer | Value a