csound-expression-3.3.2: library to make electronic music

Safe HaskellNone

Csound.Control.Evt

Contents

Synopsis

Documentation

data Evt a

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

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

Core functions

boolToEvt :: BoolSig -> Evt Unit

Converts booleans to events.

evtToBool :: Evt a -> SE BoolSig

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 Unit

Triggers an event when signal equals to 1.

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

Converts events to signals.

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

Filters events with predicate.

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

Filters events with effectful predicate.

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

Accumulator for events with side effects.

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

Accumulator for events.

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

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 b

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

type family Snap a :: *

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 c

Get values of some signal at the given events.

snaps :: Sig -> Evt D

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

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

Executes actions synchronized with global tempo (in Hz).

 runEvtSync tempoCps evt proc

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

the sync function but time is measured in beats per minute.

Opcodes

metroE :: Sig -> Evt UnitSource

Behaves like metro, but returns an event stream.

impulseE :: D -> Evt UnitSource

Fires a single event in the given time ahead.

changedE :: [Sig] -> Evt UnitSource

Behaves like changed, but returns an event stream.

triggerE :: Sig -> Sig -> Sig -> Evt UnitSource

Behaves like trigger, but returns an event stream.

loadbang :: Evt UnitSource

Fires a single event right now.

 loadbang = pulseE 0

impulse :: D -> SigSource

Fires a single true value in the given time ahead.

Higher-level event functions

eventList :: [(D, D, a)] -> Evt [(D, D, a)]Source

Makes an event stream from list of events.

cycleE :: (Tuple a, Arg a) => [a] -> Evt b -> Evt aSource

Constructs an event stream that contains an infinite repetition values from the given list. When an event happens this function takes the next value from the list, if there is no values left it starts from the beggining of the list.

iterateE :: Tuple a => a -> (a -> a) -> Evt b -> Evt aSource

When something happens on the given event stream resulting event stream contains an application of some unary function to the given initial value. So the event stream contains the values:

 [s0, f s0, f (f s0), f (f (f s0)), ...]

repeatE :: Tuple a => a -> Evt b -> Evt aSource

Substitutes all values in the input stream with the given constant value.

appendE :: Tuple a => a -> (a -> a -> a) -> Evt a -> Evt aSource

Accumulates a values from the given event stream with binary function. It's a variant of the fold for event streams.

 appendE z f evt

When value a happens with evt, the resulting event stream contains a value (z f a) and in the next time z equals to this value.

mappendE :: (Monoid a, Tuple a) => Evt a -> Evt aSource

A special variant of the function appendE for the monoids. Initial value is mempty and binary function is mappend which belong to the instance of the class Monoid.

partitionE :: (a -> BoolD) -> Evt a -> (Evt a, Evt a)Source

Splits event stream on two streams with predicate.

splitToggle :: Evt D -> (Evt D, Evt D)Source

Splits a toggle event stream on on-events and off-events.

oneOf :: (Tuple a, Arg a) => [a] -> Evt b -> Evt aSource

Constructs an event stream that contains values from the given list which are taken in the random order.

freqOf :: (Tuple a, Arg a) => Rnds a -> Evt b -> Evt aSource

Constructs an event stream that contains values from the given list which are taken in the random order. In the list we specify not only values but the frequencies of occurrence. Sum of the frequencies should be equal to one.

freqAccum :: (Tuple s, Tuple (b, s), Arg (b, s)) => s -> (a -> s -> Rnds (b, s)) -> Evt a -> Evt bSource

This function combines the functions accumE and freqOf. We transform the values of the event stream with stateful function that produce not just values but the list of values with frequencies of occurrence. We apply this function to the current state and the value and then at random pick one of the values.

randDs :: Evt b -> Evt DSource

An event stream of the random values in the interval (0, 1).

randInts :: (D, D) -> Evt b -> Evt DSource

An event stream of the integers taken from the given diapason.

randSkip :: D -> Evt a -> Evt aSource

Skips elements at random.

 randSkip prob

where prob is probability of includinng the element in the output stream.

randSkipBy :: (a -> D) -> Evt a -> Evt aSource

Skips elements at random.

 randSkip probFun

It behaves just like randSkip, but probability depends on the value.

range :: (D, D) -> Evt b -> Evt DSource

 range (xMin, xMax) === cycleE [xMin .. pred xMax]

listAt :: (Tuple a, Arg a) => [a] -> Evt D -> Evt aSource

Turns an event of indices to the event of the values from the list. A value is taken with index.

every :: (Tuple a, Arg a) => Int -> [Int] -> Evt a -> Evt aSource

Specialization of the function masked.

 every n [a, b, c, ..] evt

constructs a mask that skips first n elements and then produces an event and skips next (a - 1) events, then produces an event and skips next (b - 1) events and so on. It's useful for construction of the percussive beats. For example

 every 0 [2] (metroE 2)

triggers an event on the odd beats. With this function we can create a complex patterns of cyclic events.

masked :: (Tuple a, Arg a) => [D] -> Evt a -> Evt aSource

Filters events with the mask. A mask is a list of ones and zeroes. n'th element from the given list should be included in the resulting stream if the n'th element from the list equals to one or skipped if the element equals to zero.