csound-expression-typed-0.0.5.2: typed core for the library csound-expression

Safe HaskellNone

Csound.Typed.Types.Evt

Synopsis

Documentation

data Evt a Source

A stream of events. We can convert a stream of events to the procedure with the function runEvt. It waits for events and invokes the given procedure when the event happens.

Constructors

Evt 

Fields

runEvt :: Bam a -> SE ()
 

Instances

type Bam a = a -> SE ()Source

A procedure. Something that takes a value and suddenly bams with it.

sync :: (Default a, Tuple a) => D -> Evt a -> Evt aSource

Executes actions synchronized with global tempo (in Hz).

 runEvtSync tempoCps evt proc

boolToEvt :: BoolSig -> Evt UnitSource

Converts booleans to events.

evtToBool :: Evt a -> SE BoolSigSource

Converts an event to boolean signal. It forgets everything about the event values. Signal equals to one when an event happens and zero otherwise.

sigToEvt :: Sig -> Evt UnitSource

Triggers an event when signal equals to 1.

stepper :: Tuple a => a -> Evt a -> SE aSource

Converts events to signals.

filterE :: (a -> BoolD) -> Evt a -> Evt aSource

Filters events with predicate.

filterSE :: (a -> SE BoolD) -> Evt a -> Evt aSource

Filters events with effectful predicate.

accumSE :: Tuple s => s -> (a -> s -> SE (b, s)) -> Evt a -> Evt bSource

Accumulator for events with side effects.

accumE :: Tuple s => s -> (a -> s -> (b, s)) -> Evt a -> Evt bSource

Accumulator for events.

filterAccumE :: Tuple s => s -> (a -> s -> (BoolD, b, s)) -> Evt a -> Evt bSource

Accumulator with filtering. It can skip the events from the event stream. If the third element of the triple equals to 1 then we should include the event in the resulting stream. If the element equals to 0 we skip the event.

filterAccumSE :: Tuple s => s -> (a -> s -> SE (BoolD, b, s)) -> Evt a -> Evt bSource

Accumulator for events with side effects and filtering. Event triggers only if the first element in the tripplet is true.

type family Snap a :: *Source

A snapshot of the signal. It converts a type of the signal to the type of the value in the given moment. Instances:

 type instance Snap D   = D
 type instance Snap Str = Str
 type instance Snap Tab = Tab

 type instance Snap Sig = D
 
 type instance Snap (a, b) = (Snap a, Snap b)
 type instance Snap (a, b, c) = (Snap a, Snap b, Snap c)
 type instance Snap (a, b, c, d) = (Snap a, Snap b, Snap c, Snap d)
 type instance Snap (a, b, c, d, e) = (Snap a, Snap b, Snap c, Snap d, Snap e)
 type instance Snap (a, b, c, d, e, f) = (Snap a, Snap b, Snap c, Snap d, Snap e, Snap f)

snapshot :: (Tuple a, Tuple (Snap a)) => (Snap a -> b -> c) -> a -> Evt b -> Evt cSource

Get values of some signal at the given events.

snaps :: Sig -> Evt DSource

Constructs an event stream that contains values from the given signal. Events happens only when the signal changes.

readSnap :: (Tuple (Snap a), Tuple a) => a -> Snap aSource