hsc3-0.13: Haskell SuperCollider

Safe HaskellNone

Sound.SC3.Server.Command

Contents

Description

Constructors for the command set implemented by the SuperCollider synthesis server.

Synopsis

Instrument definition commands

d_recv :: Synthdef -> MessageSource

Install a bytecode instrument definition. (Asynchronous)

d_load :: String -> MessageSource

Load an instrument definition from a named file. (Asynchronous)

d_loadDir :: String -> MessageSource

Load a directory of instrument definitions files. (Asynchronous)

d_free :: [String] -> MessageSource

Remove definition once all nodes using it have ended.

Node commands

n_after :: [(Int, Int)] -> MessageSource

Place a node after another.

n_before :: [(Int, Int)] -> MessageSource

Place a node before another.

n_fill :: Int -> [(String, Int, Double)] -> MessageSource

Fill ranges of a node's control values.

n_free :: [Int] -> MessageSource

Delete a node.

n_map :: Int -> [(String, Int)] -> MessageSource

Map a node's controls to read from a bus.

n_mapn :: Int -> [(String, Int, Int)] -> MessageSource

Map a node's controls to read from buses.

n_mapa :: Int -> [(String, Int)] -> MessageSource

Map a node's controls to read from an audio bus.

n_mapan :: Int -> [(String, Int, Int)] -> MessageSource

Map a node's controls to read from audio buses.

n_query :: [Int] -> MessageSource

Get info about a node.

n_run :: [(Int, Bool)] -> MessageSource

Turn node on or off.

n_set :: Int -> [(String, Double)] -> MessageSource

Set a node's control values.

n_setn :: Int -> [(String, [Double])] -> MessageSource

Set ranges of a node's control values.

n_trace :: [Int] -> MessageSource

Trace a node.

n_order :: AddAction -> Int -> [Int] -> MessageSource

Move an ordered sequence of nodes.

Synthesis node commands

s_get :: Int -> [String] -> MessageSource

Get control values.

s_getn :: Int -> [(String, Int)] -> MessageSource

Get ranges of control values.

data AddAction Source

Enumeration of possible locations to add new nodes (s_new and g_new).

s_new :: String -> Int -> AddAction -> Int -> [(String, Double)] -> MessageSource

Create a new synth.

s_noid :: [Int] -> MessageSource

Auto-reassign synth's ID to a reserved value.

Group node commands

g_deepFree :: [Int] -> MessageSource

Free all synths in this group and all its sub-groups.

g_freeAll :: [Int] -> MessageSource

Delete all nodes in a group.

g_head :: [(Int, Int)] -> MessageSource

Add node to head of group.

g_new :: [(Int, AddAction, Int)] -> MessageSource

Create a new group.

g_tail :: [(Int, Int)] -> MessageSource

Add node to tail of group.

g_dumpTree :: [(Int, Bool)] -> MessageSource

Post a representation of a group's node subtree, optionally including the current control values for synths.

g_queryTree :: [(Int, Bool)] -> MessageSource

Request a representation of a group's node subtree, optionally including the current control values for synths.

Replies to the sender with a /g_queryTree.reply message listing all of the nodes contained within the group in the following format:

 int - if synth control values are included 1, else 0
 int - node ID of the requested group
 int - number of child nodes contained within the requested group

 For each node in the subtree:
 [
   int - node ID
   int - number of child nodes contained within this node. If -1 this is a synth, if >= 0 it's a group.

   If this node is a synth:
     symbol - the SynthDef name for this node.

   If flag (see above) is true:
     int - numControls for this synth (M)
     [
       symbol or int: control name or index
       float or symbol: value or control bus mapping symbol (e.g. 'c1')
     ] * M
 ] * the number of nodes in the subtree

N.B. The order of nodes corresponds to their execution order on the server. Thus child nodes (those contained within a group) are listed immediately following their parent.

p_new :: [(Int, AddAction, Int)] -> MessageSource

Create a new parallel group (supernova specific).

Plugin commands

cmd :: String -> [Datum] -> MessageSource

Send a plugin command.

Unit Generator commands

u_cmd :: Int -> Int -> String -> [Datum] -> MessageSource

Send a command to a unit generator.

Buffer commands

b_alloc :: Int -> Int -> Int -> MessageSource

Allocates zero filled buffer to number of channels and samples. (Asynchronous)

b_allocRead :: Int -> String -> Int -> Int -> MessageSource

Allocate buffer space and read a sound file. (Asynchronous)

b_allocReadChannel :: Int -> String -> Int -> Int -> [Int] -> MessageSource

Allocate buffer space and read a sound file, picking specific channels. (Asynchronous)

b_close :: Int -> MessageSource

Close attached soundfile and write header information. (Asynchronous)

b_fill :: Int -> [(Int, Int, Double)] -> MessageSource

Fill ranges of sample values.

b_free :: Int -> MessageSource

Free buffer data. (Asynchronous)

b_gen :: Int -> String -> [Datum] -> MessageSource

Call a command to fill a buffer. (Asynchronous)

b_gen_sine1 :: Int -> [B_Gen] -> [Double] -> MessageSource

Call sine1 b_gen command.

b_gen_sine2 :: Int -> [B_Gen] -> [(Double, Double)] -> MessageSource

Call sine2 b_gen command.

b_gen_sine3 :: Int -> [B_Gen] -> [(Double, Double, Double)] -> MessageSource

Call sine3 b_gen command.

b_gen_cheby :: Int -> [B_Gen] -> [Double] -> MessageSource

Call cheby b_gen command.

b_gen_copy :: Int -> Int -> Int -> Int -> Maybe Int -> MessageSource

Call copy b_gen command.

b_get :: Int -> [Int] -> MessageSource

Get sample values.

b_getn :: Int -> [(Int, Int)] -> MessageSource

Get ranges of sample values.

b_query :: [Int] -> MessageSource

Request /b_info messages.

b_read :: Int -> String -> Int -> Int -> Int -> Bool -> MessageSource

Read sound file data into an existing buffer. (Asynchronous)

b_readChannel :: Int -> String -> Int -> Int -> Int -> Bool -> [Int] -> MessageSource

Read sound file data into an existing buffer, picking specific channels. (Asynchronous)

b_set :: Int -> [(Int, Double)] -> MessageSource

Set sample values.

b_setn :: Int -> [(Int, [Double])] -> MessageSource

Set ranges of sample values.

b_write :: Int -> String -> SoundFileFormat -> SampleFormat -> Int -> Int -> Bool -> MessageSource

Write sound file data. (Asynchronous)

b_zero :: Int -> MessageSource

Zero sample data. (Asynchronous)

Control bus commands

c_fill :: [(Int, Int, Double)] -> MessageSource

Fill ranges of bus values.

c_get :: [Int] -> MessageSource

Get bus values.

c_getn :: [(Int, Int)] -> MessageSource

Get ranges of bus values.

c_set :: [(Int, Double)] -> MessageSource

Set bus values.

c_setn :: [(Int, [Double])] -> MessageSource

Set ranges of bus values.

Server operation commands

clearSched :: MessageSource

Remove all bundles from the scheduling queue.

data PrintLevel Source

Enumeration of Message printer types.

dumpOSC :: PrintLevel -> MessageSource

Select printing of incoming Open Sound Control messages.

notify :: Bool -> MessageSource

Select reception of notification messages. (Asynchronous)

quit :: MessageSource

Stop synthesis server.

status :: MessageSource

Request /status.reply message.

sync :: Int -> MessageSource

Request /synced message when all current asynchronous commands complete.

data ErrorScope Source

Error posting scope.

Constructors

Globally

Global scope

Locally

Bundle scope

data ErrorMode Source

Error posting mode.

Constructors

ErrorsOff

Turn error posting off

ErrorsOn

Turn error posting on

errorMode :: ErrorScope -> ErrorMode -> MessageSource

Set error posting scope and mode.

Variants to simplify common cases

b_alloc_setn1 :: Int -> Int -> [Double] -> MessageSource

Pre-allocate for b_setn1, values preceding offset are zeroed.

b_getn1 :: Int -> (Int, Int) -> MessageSource

Get ranges of sample values.

b_set1 :: Int -> Int -> Double -> MessageSource

Set single sample value.

b_setn1 :: Int -> Int -> [Double] -> MessageSource

Set a range of sample values.

b_query1 :: Int -> MessageSource

Variant on b_query.

c_set1 :: Int -> Double -> MessageSource

Set single bus values.

n_set1 :: Int -> String -> Double -> MessageSource

Set a signle node control value.

Modify existing message to include completion message

async_cmds :: [String]Source

List of asynchronous server commands.

isAsync :: Message -> BoolSource

True if Message is an asynchronous Message.

 map isAsync [b_close 0,n_set1 0 "0" 0] == [True,False]

withCM :: OSC o => Message -> o -> MessageSource

Add a completion message (or bundle, the name is misleading) to an existing asynchronous command.

 let {m = n_set1 0 "0" 0
     ;m' = encodeMessage m}
 in withCM (b_close 0) m == Message "/b_close" [Int 0,Blob m']

Buffer segmentation and indices

b_segment :: Int -> Int -> [Int]Source

Segment a request for m places into sets of at most n.

 b_segment 1024 2056 == [8,1024,1024]
 b_segment 1 5 == replicate 5 1

b_indices :: Int -> Int -> Int -> [(Int, Int)]Source

Variant of b_segment that takes a starting index and returns (index,size) duples.

 b_indices 1 5 0 == zip [0..4] (replicate 5 1)
 b_indices 1024 2056 16 == [(16,8),(24,1024),(1048,1024)]