Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
- Buffer commands (b_)
- Control bus commands (c_)
- Instrument definition commands (d_)
- Group node commands (g_)
- Node commands (n_)
- Par commands (p_)
- Synthesis node commands (s_)
- Ugen commands (u_)
- Server operation commands
- Modify existing message to include completion message
- Variants to simplify common cases
- Buffer segmentation and indices
- Ugen commands.
- Unpack
Generic constructors for the command set implemented by the SuperCollider synthesis server.
Synopsis
- cmd_check_arg :: String -> (t -> Bool) -> t -> t
- b_bufnum :: Integral t => t -> Datum
- b_ix :: Integral t => t -> Datum
- b_ch :: Integral t => t -> Datum
- b_size :: Integral t => t -> Datum
- b_alloc :: Integral i => i -> i -> i -> Message
- b_allocRead :: Integral i => i -> String -> i -> i -> Message
- b_allocReadChannel :: Integral i => i -> String -> i -> i -> [i] -> Message
- b_close :: Integral i => i -> Message
- b_fill :: (Integral i, Real n) => i -> [(i, i, n)] -> Message
- b_free :: Integral i => i -> Message
- b_gen :: Integral i => i -> String -> [Datum] -> Message
- b_gen_sine1 :: (Integral i, Real n) => i -> [B_Gen] -> [n] -> Message
- b_gen_sine2 :: (Integral i, Real n) => i -> [B_Gen] -> [(n, n)] -> Message
- b_gen_sine3 :: (Integral i, Real n) => i -> [B_Gen] -> [(n, n, n)] -> Message
- b_gen_cheby :: (Integral i, Real n) => i -> [B_Gen] -> [n] -> Message
- b_gen_copy :: Integral i => i -> i -> i -> i -> Maybe i -> Message
- b_get :: Integral i => i -> [i] -> Message
- b_getn :: Integral i => i -> [(i, i)] -> Message
- b_query :: Integral i => [i] -> Message
- b_read :: Integral i => i -> String -> i -> i -> i -> Bool -> Message
- b_readChannel :: Integral i => i -> String -> i -> i -> i -> Bool -> [i] -> Message
- b_set :: (Integral i, Real n) => i -> [(i, n)] -> Message
- b_setn :: (Integral i, Real n) => i -> [(i, [n])] -> Message
- b_write :: Integral i => i -> String -> SoundFileFormat -> SampleFormat -> i -> i -> Bool -> Message
- b_zero :: Integral i => i -> Message
- c_fill :: (Integral i, Real n) => [(i, i, n)] -> Message
- c_get :: Integral i => [i] -> Message
- c_getn :: Integral i => [(i, i)] -> Message
- c_set :: (Integral i, Real n) => [(i, n)] -> Message
- c_setn :: (Integral i, Real n) => [(i, [n])] -> Message
- d_recv_bytes :: Blob -> Message
- d_recv_gr :: Graphdef -> Message
- d_recv :: Synthdef -> Message
- d_load :: String -> Message
- d_loadDir :: String -> Message
- d_free :: [String] -> Message
- g_deepFree :: Integral i => [i] -> Message
- g_freeAll :: Integral i => [i] -> Message
- g_head :: Integral i => [(i, i)] -> Message
- g_new :: Integral i => [(i, AddAction, i)] -> Message
- g_tail :: Integral i => [(i, i)] -> Message
- g_dumpTree :: Integral i => [(i, Bool)] -> Message
- g_queryTree :: Integral i => [(i, Bool)] -> Message
- n_id :: Integral t => t -> Datum
- n_after :: Integral i => [(i, i)] -> Message
- n_before :: Integral i => [(i, i)] -> Message
- n_fill :: (Integral i, Real f) => i -> [(String, i, f)] -> Message
- n_free :: Integral i => [i] -> Message
- n_map :: Integral i => i -> [(String, i)] -> Message
- n_mapn :: Integral i => i -> [(i, i, i)] -> Message
- n_mapa :: Integral i => i -> [(String, i)] -> Message
- n_mapan :: Integral i => i -> [(String, i, i)] -> Message
- n_query :: Integral i => [i] -> Message
- n_run :: Integral i => [(i, Bool)] -> Message
- n_set :: (Integral i, Real n) => i -> [(String, n)] -> Message
- n_setn :: (Integral i, Real n) => i -> [(i, [n])] -> Message
- n_trace :: Integral i => [i] -> Message
- n_order :: Integral i => AddAction -> i -> [i] -> Message
- p_new :: Integral i => [(i, AddAction, i)] -> Message
- s_get :: Integral i => i -> [String] -> Message
- s_getn :: Integral i => i -> [(String, i)] -> Message
- s_new :: (Integral i, Real n) => String -> i -> AddAction -> i -> [(String, n)] -> Message
- s_noid :: Integral i => [i] -> Message
- u_cmd :: Integral i => i -> i -> String -> [Datum] -> Message
- cmd :: String -> [Datum] -> Message
- clearSched :: Message
- dumpOsc :: PrintLevel -> Message
- errorMode :: ErrorScope -> ErrorMode -> Message
- notify :: Bool -> Message
- nrt_end :: Message
- quit :: Message
- status :: Message
- sync :: Integral i => i -> Message
- with_completion_packet :: Message -> Packet -> Message
- withCM :: Message -> Message -> Message
- b_alloc_setn1 :: (Integral i, Real n) => i -> i -> [n] -> Message
- b_getn1 :: Integral i => i -> (i, i) -> Message
- b_query1 :: Integral i => i -> Message
- b_set1 :: (Integral i, Real n) => i -> i -> n -> Message
- b_setn1 :: (Integral i, Real n) => i -> i -> [n] -> Message
- b_setn1_segmented :: (Integral i, Real n) => i -> i -> i -> [n] -> [Message]
- c_getn1 :: Integral i => (i, i) -> Message
- c_set1 :: (Integral i, Real n) => i -> n -> Message
- c_setn1 :: (Integral i, Real n) => (i, [n]) -> Message
- n_run1 :: Integral i => i -> Bool -> Message
- n_set1 :: (Integral i, Real n) => i -> String -> n -> Message
- s_new0 :: Integral i => String -> i -> AddAction -> i -> Message
- b_segment :: Integral i => i -> i -> [i]
- b_indices :: Integral i => i -> i -> i -> [(i, i)]
- partConv_preparePartConv :: Integral i => i -> i -> i -> Message
- unpack_n_info_datum_plain :: Num i => [Datum] -> [i]
- unpack_n_info_plain :: Num i => Message -> [i]
- unpack_n_info :: Num i => Message -> Maybe (i, i, i, i, i, Maybe (i, i))
- unpack_n_info_err :: Num i => Message -> (i, i, i, i, i, Maybe (i, i))
- unpack_tr :: (Num i, Fractional f) => Message -> Maybe (i, i, f)
- unpack_tr_err :: (Num i, Fractional f) => Message -> (i, i, f)
- unpack_b_setn :: (Num i, Fractional f) => Message -> Maybe (i, i, i, [f])
- unpack_b_setn_err :: (Num i, Fractional f) => Message -> (i, i, i, [f])
- unpack_b_info :: (Num i, Fractional f) => Message -> Maybe (i, i, i, f)
- unpack_b_info_err :: (Num i, Fractional f) => Message -> (i, i, i, f)
Documentation
cmd_check_arg :: String -> (t -> Bool) -> t -> t Source #
Buffer commands (b_)
b_alloc :: Integral i => i -> i -> i -> Message Source #
Allocates zero filled buffer to number of channels and samples. (Asynchronous)
b_allocRead :: Integral i => i -> String -> i -> i -> Message Source #
Allocate buffer space and read a sound file. (Asynchronous)
b_allocReadChannel :: Integral i => i -> String -> i -> i -> [i] -> Message Source #
Allocate buffer space and read a sound file, picking specific channels. (Asynchronous)
b_close :: Integral i => i -> Message Source #
Close attached soundfile and write header information. (Asynchronous)
b_gen :: Integral i => i -> String -> [Datum] -> Message Source #
Call a command to fill a buffer. (Asynchronous)
b_gen_sine1 :: (Integral i, Real n) => i -> [B_Gen] -> [n] -> Message Source #
Call sine1
b_gen
command.
b_gen_sine2 :: (Integral i, Real n) => i -> [B_Gen] -> [(n, n)] -> Message Source #
Call sine2
b_gen
command.
b_gen_sine3 :: (Integral i, Real n) => i -> [B_Gen] -> [(n, n, n)] -> Message Source #
Call sine3
b_gen
command.
b_gen_cheby :: (Integral i, Real n) => i -> [B_Gen] -> [n] -> Message Source #
Call cheby
b_gen
command.
b_read :: Integral i => i -> String -> i -> i -> i -> Bool -> Message Source #
Read sound file data into an existing buffer. (Asynchronous) Param: bufId pathName startFrame numFrames bufFrame leaveOpen
b_readChannel :: Integral i => i -> String -> i -> i -> i -> Bool -> [i] -> Message Source #
Read sound file data into an existing buffer, picking specific channels. (Asynchronous)
b_write :: Integral i => i -> String -> SoundFileFormat -> SampleFormat -> i -> i -> Bool -> Message Source #
Write sound file data. (Asynchronous)
Control bus commands (c_)
Instrument definition commands (d_)
d_recv_bytes :: Blob -> Message Source #
Install a bytecode instrument definition. (Asynchronous)
d_loadDir :: String -> Message Source #
Load a directory of instrument definitions files. (Asynchronous)
Group node commands (g_)
g_deepFree :: Integral i => [i] -> Message Source #
Free all synths in this group and all its sub-groups.
g_dumpTree :: Integral i => [(i, Bool)] -> Message Source #
Post a representation of a group's node subtree, optionally including the current control values for synths.
g_queryTree :: Integral i => [(i, Bool)] -> Message Source #
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:
int32 - if synth control values are included 1, else 0 int32 - node ID of the requested group int32 - number of child nodes contained within the requested group For each node in the subtree: [ int32 - node ID int32 - 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: int32 - 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.Common.Base. 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.
Node commands (n_)
n_fill :: (Integral i, Real f) => i -> [(String, i, f)] -> Message Source #
Fill ranges of a node's control values.
n_mapn :: Integral i => i -> [(i, i, i)] -> Message Source #
Map a node's controls to read from buses. n_mapn only works if the control is given as an index and not as a name (3.8.0).
n_mapa :: Integral i => i -> [(String, i)] -> Message Source #
Map a node's controls to read from an audio bus.
n_mapan :: Integral i => i -> [(String, i, i)] -> Message Source #
Map a node's controls to read from audio buses.
n_setn :: (Integral i, Real n) => i -> [(i, [n])] -> Message Source #
Set ranges of a node's control values. n_mapn and n_setn only work if the control is given as an index and not as a name.
n_order :: Integral i => AddAction -> i -> [i] -> Message Source #
Move an ordered sequence of nodes.
Par commands (p_)
p_new :: Integral i => [(i, AddAction, i)] -> Message Source #
Create a new parallel group (supernova specific).
Synthesis node commands (s_)
s_new :: (Integral i, Real n) => String -> i -> AddAction -> i -> [(String, n)] -> Message Source #
Create a new synth.
Ugen commands (u_)
u_cmd :: Integral i => i -> i -> String -> [Datum] -> Message Source #
Send a command to a unit generator.
Server operation commands
clearSched :: Message Source #
Remove all bundles from the scheduling queue.
dumpOsc :: PrintLevel -> Message Source #
Select printing of incoming Open Sound Control messages.
sync :: Integral i => i -> Message Source #
Request /synced message when all current asynchronous commands complete.
Modify existing message to include completion message
with_completion_packet :: Message -> Packet -> Message Source #
Add a completion packet to an existing asynchronous command.
withCM :: Message -> Message -> Message Source #
Add a completion message to an existing asynchronous command.
let m = n_set1 0 "0" 0 let e = encodeMessage m withCM (b_close 0) m == Message "/b_close" [Int32 0,Blob e]
Variants to simplify common cases
b_alloc_setn1 :: (Integral i, Real n) => i -> i -> [n] -> Message Source #
Pre-allocate for b_setn1, values preceding offset are zeroed.
b_setn1_segmented :: (Integral i, Real n) => i -> i -> i -> [n] -> [Message] Source #
Segmented variant of b_setn1
.
n_set1 :: (Integral i, Real n) => i -> String -> n -> Message Source #
Set a single node control value.
Buffer segmentation and indices
b_segment :: Integral i => i -> i -> [i] 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 :: Integral i => i -> i -> i -> [(i, i)] 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)]
Ugen commands.
partConv_preparePartConv :: Integral i => i -> i -> i -> Message Source #
Generate accumulation buffer given time-domain IR buffer and FFT size.
Unpack
unpack_n_info_datum_plain :: Num i => [Datum] -> [i] Source #
Result is null for non-conforming data, or has five or seven elements.
unpack_n_info_plain :: Num i => Message -> [i] Source #
unpack_n_info :: Num i => Message -> Maybe (i, i, i, i, i, Maybe (i, i)) Source #
Unpack n_info
message.
unpack_tr :: (Num i, Fractional f) => Message -> Maybe (i, i, f) Source #
Unpack the '/tr' messages sent by sendTrig
.
unpack_tr_err :: (Num i, Fractional f) => Message -> (i, i, f) Source #
unpack_b_setn :: (Num i, Fractional f) => Message -> Maybe (i, i, i, [f]) Source #
unpack_b_setn_err :: (Num i, Fractional f) => Message -> (i, i, i, [f]) Source #
unpack_b_info :: (Num i, Fractional f) => Message -> Maybe (i, i, i, f) Source #
Unpack b_info message, fields are (id,frames,channels,sample-rate).
unpack_b_info_err :: (Num i, Fractional f) => Message -> (i, i, i, f) Source #
Variant generating error
.