hsc3-0.17: Haskell SuperCollider

Safe HaskellNone
LanguageHaskell98

Sound.SC3.Server.Command.Plain

Contents

Description

Functions from Sound.SC3.Server.Command.Generic specialised to Int and Double.

Synopsis

Types

type Buffer_Id = Int Source #

Buffer identifier (buffer number).

type Buffer_Ix = Int Source #

Buffer index (frame index).

type Buffer_Leave_File_Open = Bool Source #

File connection flag.

type Bus_Id = Int Source #

Audio/control bus identifier (number).

type Node_Id = Int Source #

Node identifier (number).

type Group_Id = Int Source #

Group-node identifier (number).

type Synth_Id = Int Source #

Synth-node identifier (number).

Buffer commands (b_)

b_alloc :: Buffer_Id -> Int -> Int -> Message Source #

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

b_allocRead :: Buffer_Id -> String -> Int -> Int -> Message Source #

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

b_allocReadChannel :: Buffer_Id -> String -> Int -> Int -> [Int] -> Message Source #

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

b_close :: Buffer_Id -> Message Source #

Close attached soundfile and write header information. (Asynchronous)

b_fill :: Buffer_Id -> [(Buffer_Ix, Int, Double)] -> Message Source #

Fill ranges of sample values.

b_free :: Buffer_Id -> Message Source #

Free buffer data. (Asynchronous)

b_gen :: Buffer_Id -> String -> [Datum] -> Message Source #

Call a command to fill a buffer. (Asynchronous)

b_get :: Buffer_Id -> [Buffer_Ix] -> Message Source #

Get sample values.

b_getn :: Buffer_Id -> [(Buffer_Ix, Int)] -> Message Source #

Get ranges of sample values.

b_query :: [Buffer_Id] -> Message Source #

Request /b_info messages.

b_read :: Buffer_Id -> String -> Int -> Int -> Buffer_Ix -> Buffer_Leave_File_Open -> Message Source #

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

b_readChannel :: Buffer_Id -> String -> Int -> Int -> Buffer_Ix -> Buffer_Leave_File_Open -> [Int] -> Message Source #

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

b_set :: Buffer_Id -> [(Buffer_Ix, Double)] -> Message Source #

Set sample values.

b_setn :: Buffer_Id -> [(Buffer_Ix, [Double])] -> Message Source #

Set ranges of sample values.

b_write :: Buffer_Id -> String -> SoundFileFormat -> SampleFormat -> Int -> Buffer_Ix -> Buffer_Leave_File_Open -> Message Source #

Write sound file data. (Asynchronous)

b_zero :: Buffer_Id -> Message Source #

Zero sample data. (Asynchronous)

Control bus commands

c_fill :: [(Bus_Id, Int, Double)] -> Message Source #

Fill ranges of bus values.

c_get :: [Bus_Id] -> Message Source #

Get bus values.

c_getn :: [(Bus_Id, Int)] -> Message Source #

Get ranges of bus values.

c_set :: [(Bus_Id, Double)] -> Message Source #

Set bus values.

c_setn :: [(Bus_Id, [Double])] -> Message Source #

Set ranges of bus values.

Instrument definition commands (d_)

d_recv' :: Graphdef -> Message Source #

Install a bytecode instrument definition. (Asynchronous)

d_recv :: Synthdef -> Message Source #

Install a bytecode instrument definition. (Asynchronous)

d_load :: String -> Message Source #

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

d_loadDir :: String -> Message Source #

Load a directory of instrument definitions files. (Asynchronous)

d_free :: [String] -> Message Source #

Remove definition once all nodes using it have ended.

Group node commands (g_)

g_deepFree :: [Group_Id] -> Message Source #

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

g_freeAll :: [Group_Id] -> Message Source #

Delete all nodes in a set of groups.

g_head :: [(Group_Id, Node_Id)] -> Message Source #

Add node to head of group.

g_new :: [(Group_Id, AddAction, Node_Id)] -> Message Source #

Create a new group.

g_tail :: [(Group_Id, Node_Id)] -> Message Source #

Add node to tail of group.

g_dumpTree :: [(Group_Id, Bool)] -> Message Source #

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

g_queryTree :: [(Group_Id, Bool)] -> Message Source #

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

Node commands (n_)

n_after :: [(Node_Id, Node_Id)] -> Message Source #

Place a node after another.

n_before :: [(Node_Id, Node_Id)] -> Message Source #

Place a node before another.

n_fill :: Node_Id -> [(String, Int, Double)] -> Message Source #

Fill ranges of a node's control values.

n_free :: [Node_Id] -> Message Source #

Delete a node.

n_mapn :: Node_Id -> [(Int, Bus_Id, Int)] -> 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 :: Node_Id -> [(String, Bus_Id)] -> Message Source #

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

n_mapan :: Node_Id -> [(String, Bus_Id, Int)] -> Message Source #

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

n_query :: [Node_Id] -> Message Source #

Get info about a node.

n_run :: [(Node_Id, Bool)] -> Message Source #

Turn node on or off.

n_set :: Node_Id -> [(String, Double)] -> Message Source #

Set a node's control values.

n_setn :: Node_Id -> [(Int, [Double])] -> Message Source #

Set ranges of a node's control values.

n_trace :: [Node_Id] -> Message Source #

Trace a node.

n_order :: AddAction -> Node_Id -> [Node_Id] -> Message Source #

Move and order a sequence of nodes.

Par commands (p_)

p_new :: [(Group_Id, AddAction, Node_Id)] -> Message Source #

Create a new parallel group (supernova specific).

Synthesis node commands (s_)

s_get :: Synth_Id -> [String] -> Message Source #

Get control values.

s_getn :: Synth_Id -> [(String, Int)] -> Message Source #

Get ranges of control values.

s_new :: String -> Synth_Id -> AddAction -> Node_Id -> [(String, Double)] -> Message Source #

Create a new synth.

s_noid :: [Synth_Id] -> Message Source #

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

Unit Generator commands (u_)

u_cmd :: Int -> Int -> String -> [Datum] -> Message Source #

Send a command to a unit generator.

Server operation commands

cmd :: String -> [Datum] -> Message Source #

Send a plugin command.

clearSched :: Message Source #

Remove all bundles from the scheduling queue.

dumpOSC :: PrintLevel -> Message Source #

Select printing of incoming Open Sound Control messages.

errorMode :: ErrorScope -> ErrorMode -> Message Source #

Set error posting scope and mode.

notify :: Bool -> Message Source #

Select reception of notification messages. (Asynchronous)

nrt_end :: Message Source #

End real time mode, close file (un-implemented).

quit :: Message Source #

Stop synthesis server.

status :: Message Source #

Request /status.reply message.

sync :: Int -> Message Source #

Request /synced message when all current asynchronous commands complete.

Variants to simplify common cases

b_getn1 :: Buffer_Id -> (Buffer_Ix, Int) -> Message Source #

Get ranges of sample values.

c_getn1 :: (Bus_Id, Int) -> Message Source #

Get ranges of sample values.

c_set1 :: Bus_Id -> Double -> Message Source #

Set single bus values.

c_setn1 :: (Bus_Id, [Double]) -> Message Source #

Set single range of bus values.

n_run1 :: Node_Id -> Bool -> Message Source #

Turn a single node on or off.

n_set1 :: Node_Id -> String -> Double -> Message Source #

Set a single node control value.

s_new0 :: String -> Synth_Id -> AddAction -> Node_Id -> Message Source #

s_new with no parameters.

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

b_gen_copy :: Buffer_Id -> Int -> Buffer_Id -> Int -> Maybe Int -> Message Source #

Call copy b_gen command.

b_gen_sine1 :: Buffer_Id -> [B_Gen] -> [Double] -> Message Source #

Call sine1 b_gen command.

b_gen_sine2 :: Buffer_Id -> [B_Gen] -> [(Double, Double)] -> Message Source #

Call sine2 b_gen command.

b_gen_sine3 :: Buffer_Id -> [B_Gen] -> [(Double, Double, Double)] -> Message Source #

Call sine3 b_gen command.

b_gen_cheby :: Buffer_Id -> [B_Gen] -> [Double] -> Message Source #

Call cheby b_gen command.

b_alloc_setn1 :: Buffer_Id -> Buffer_Ix -> [Double] -> Message Source #

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

b_set1 :: Buffer_Id -> Buffer_Ix -> Double -> Message Source #

Set single sample value.

b_setn1 :: Buffer_Id -> Buffer_Ix -> [Double] -> Message Source #

Set a range of sample values.

b_setn1_segmented :: Int -> Buffer_Id -> Buffer_Ix -> [Double] -> [Message] Source #

Segmented variant of b_setn1.

UGen commands.

pc_preparePartConv :: Int -> Int -> Int -> Message Source #

Generate accumulation buffer given time-domain IR buffer and FFT size.

Unpack