Copyright | (c) Daniel Winograd-Cort 2014 |
---|---|
License | see the LICENSE file in the distribution |
Maintainer | dwc@cs.yale.edu |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell98 |
Auxiliary functions for use with UISF or other arrows.
- type SEvent = Maybe
- type Time = Double
- type DeltaT = Double
- getDeltaT :: ArrowReader DeltaT a => a b DeltaT
- accumTime :: (ArrowCircuit a, ArrowReader DeltaT a) => a b Time
- constA :: Arrow a => c -> a b c
- constSF :: Arrow a => b -> a b d -> a c d
- edge :: ArrowCircuit a => a Bool (SEvent ())
- accum :: ArrowCircuit a => b -> a (SEvent (b -> b)) b
- unique :: Eq e => ArrowCircuit a => a e (SEvent e)
- hold :: ArrowCircuit a => b -> a (SEvent b) b
- now :: ArrowCircuit a => a () (SEvent ())
- mergeE :: (a -> a -> a) -> SEvent a -> SEvent a -> SEvent a
- (~++) :: SEvent [a] -> SEvent [a] -> SEvent [a]
- concatA :: Arrow a => [a b c] -> a [b] [c]
- runDynamic :: ArrowChoice a => a b c -> a [b] [c]
- foldA :: ArrowChoice a => (c -> d -> d) -> d -> a b c -> a [b] d
- foldSF :: Arrow a => (b -> c -> c) -> c -> [a () b] -> a () c
- maybeA :: ArrowChoice a => a () c -> a b c -> a (Maybe b) c
- evMap :: ArrowChoice a => a b c -> a (SEvent b) (SEvent c)
- class ArrowLoop a => ArrowCircuit a where
- delay :: b -> a b b
- vdelay :: (ArrowReader DeltaT a, ArrowCircuit a) => a (DeltaT, SEvent b) (SEvent b)
- fdelay :: (ArrowReader DeltaT a, ArrowCircuit a) => DeltaT -> a (SEvent b) (SEvent b)
- vcdelay :: (ArrowReader DeltaT a, ArrowCircuit a) => DeltaT -> b -> a (DeltaT, b) b
- fcdelay :: (ArrowReader DeltaT a, ArrowCircuit a) => b -> DeltaT -> a b b
- timer :: (ArrowReader DeltaT a, ArrowCircuit a) => a DeltaT (SEvent ())
- genEvents :: (ArrowReader DeltaT a, ArrowCircuit a) => [b] -> a DeltaT (SEvent b)
- type Tempo = Double
- data BufferOperation b
- = NoBOp
- | ClearBuffer
- | SkipAheadInBuffer DeltaT
- | MergeInBuffer [(DeltaT, b)]
- | AppendToBuffer [(DeltaT, b)]
- | SetBufferPlayStatus Bool (BufferOperation b)
- | SetBufferTempo Tempo (BufferOperation b)
- eventBuffer :: (ArrowReader DeltaT a, ArrowCircuit a) => a (BufferOperation b) (SEvent [b], Bool)
- eventBuffer' :: ArrowCircuit a => a (BufferOperation b, DeltaT) (SEvent [b], Bool)
Types
getDeltaT :: ArrowReader DeltaT a => a b DeltaT Source
This is a convenience function for any DeltaT ArrowReader
accumTime :: (ArrowCircuit a, ArrowReader DeltaT a) => a b Time Source
This function returns the accumulated delta times created by getDeltaT. Thus, it is the "accumulated" time.
Useful SF Utilities (Mediators)
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
Deprecated: As of UISF-0.4.0.0, mergeE is being removed as it's basically just mappend from Monoid.
mergeE merges two events with the given resolution function.
(~++) :: SEvent [a] -> SEvent [a] -> SEvent [a] Source
Deprecated: As of UISF-0.4.0.0, (~++) is being removed as it is equivalent to Monoid's mappend.
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
class ArrowLoop a => ArrowCircuit a where
An arrow type that can be used to interpret synchronous circuits.
:: b | the value to return initially. |
-> a b b | an arrow that propagates its input with a one-tick delay. |
A delay component.
ArrowCircuit UISF | |
ArrowLoop a => ArrowCircuit (Automaton a) |
vdelay :: (ArrowReader DeltaT 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 :: (ArrowReader DeltaT 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 :: (ArrowReader DeltaT 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 :: (ArrowReader DeltaT 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 :: (ArrowReader DeltaT 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 :: (ArrowReader DeltaT 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 BufferOperation b Source
The BufferOperation data type wraps up the data and operational commands
to control an eventbuffer
.
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 :: (ArrowReader DeltaT 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, DeltaT) (SEvent [b], Bool) Source
eventBuffer' is a version that takes Time explicitly rather than with ArrowTime.