hsc3-lang-0.13: Haskell SuperCollider Language

Safe HaskellNone

Sound.SC3.Lang.Control.Event

Description

An Event is a (Key,Value) map.

Synopsis

Documentation

type Key = StringSource

The type of the key at an Event.

type Value = DoubleSource

The type of the value at an Event.

data Type Source

The type of an Event.

Constructors

E_s_new 
E_n_set 
E_rest 

Instances

data Event Source

An Event has a Type, possibly an integer identifier, possibly an Instrument and a map of (Key,Value) pairs.

Constructors

Event 

defaultEvent :: EventSource

The default empty event.

lookup_m :: Key -> Event -> Maybe ValueSource

Lookup k in e.

 lookup_m "k" defaultEvent == Nothing

lookup_v :: Value -> Key -> Event -> ValueSource

Variant of lookup_m with a default value v.

 lookup_v 1 "k" defaultEvent == 1

lookup_t :: t -> (Value -> t) -> Key -> Event -> tSource

Variant of lookup_v with a transformation function.

 lookup_t 1 negate "k" defaultEvent == 1
 lookup_t 1 negate "k" (insert "k" 1 defaultEvent) == -1

pitch :: Event -> Pitch DoubleSource

Lookup Pitch model parameters at e and construct a Pitch value.

duration :: Event -> Duration DoubleSource

Lookup Duration model parameters at an Event and construct a Duration value.

insert :: Key -> Value -> Event -> EventSource

Insert (k,v) into e.

 lookup_m "k" (insert "k" 1 defaultEvent) == Just 1

db :: Event -> ValueSource

Lookup db field of Event, the default value is -20db.

dbAmp' :: Floating a => a -> aSource

Function to convert from decibels to linear amplitude.

amp :: Event -> ValueSource

The linear amplitude of the amplitude model at e.

 amp (event [("db",-20)]) == 0.1

fwd :: Event -> DoubleSource

The fwd value of the duration model at e.

 fwd (event [("dur",1),("stretch",2)]) == 2

latency :: Event -> DoubleSource

The latency to compensate for when sending messages based on the event. Defaults to 0.1.

model_keys :: [Key]Source

List of Keys used in pitch, duration and amplitude models.

 ("degree" `elem` model_keys) == True

reserved :: [Key]Source

List of reserved Keys used in pitch, duration and amplitude models. These are keys that may be provided explicitly, but if not will be calculated implicitly.

 ("freq" `elem` reserved) == True

parameters' :: (Key, Value) -> Maybe (Key, Value)Source

If Key is reserved then Nothing, else id.

parameters :: Event -> [(Key, Value)]Source

Extract non-reserved Keys from Event.

edit_v :: Key -> Value -> (Value -> Value) -> Event -> EventSource

Value editor for Key at Event, with default value in case Key is not present.

edit :: Key -> (Value -> Value) -> Event -> EventSource

Variant of edit_v with no default value.

from_list :: Type -> Maybe Int -> Maybe Instrument -> [(Key, Value)] -> EventSource

Basic Event constructor function with e_map given as a list.

event :: [(Key, Value)] -> EventSource

Construct an Event from a list of (key,value) pairs.

 lookup_m "k" (event [("k",1)]) == Just 1

instrument_name :: Event -> StringSource

Extract Instrument name from Event, or default.

instrument_def :: Event -> Maybe SynthdefSource

Extract Instrument definition from Event if present.

f_merge :: Ord a => [(a, t)] -> [(a, t)] -> [(a, t)]Source

Merge two sorted sequence of (location,value) pairs.

 let m = f_merge (zip [0,2..6] ['a'..]) (zip [0,3,6] ['A'..])
 in m == [(0,'a'),(0,'A'),(2,'b'),(3,'B'),(4,'c'),(6,'d'),(6,'C')]

type Time = TimeSource

Times are hosc (NTP) times.

merge' :: (Time, [Event]) -> (Time, [Event]) -> [(Time, Event)]Source

Merge two time-stamped Event sequences. Note that this uses fwd to calculate start times.

add_fwd :: [(Time, Event)] -> [Event]Source

Insert fwd Keys into a time-stamped Event sequence.

merge :: (Time, [Event]) -> (Time, [Event]) -> [Event]Source

Composition of add_fwd and merge'.

is_rest :: Event -> BoolSource

Does Event have a non-zero rest key.

to_sc3_bundle :: Time -> Int -> Event -> Maybe (Bundle, Bundle)Source

Generate SC3 Bundle messages describing Event. Consults the instrument_send_release in relation to gate command.