| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Sound.Sc3.Server.Command.Plain
Contents
- Types
 - Buffer commands (b_)
 - Control bus commands
 - Instrument definition commands (d_)
 - Group node commands (g_)
 - Node commands (n_)
 - Par commands (p_)
 - Synthesis node commands (s_)
 - Unit Generator commands (u_)
 - Server operation commands
 - Variants to simplify common cases
 - Buffer segmentation and indices
 - Ugen commands.
 - Unpack
 
Description
Functions from Sound.Sc3.Server.Command.Generic specialised to Int and Double.
Synopsis
- type Buffer_Id = Int
 - type Buffer_Ix = Int
 - type Buffer_Leave_File_Open = Bool
 - type Bus_Id = Int
 - type Node_Id = Int
 - type Group_Id = Int
 - type Synth_Id = Int
 - b_alloc :: Buffer_Id -> Int -> Int -> Message
 - b_allocRead :: Buffer_Id -> String -> Int -> Int -> Message
 - b_allocReadChannel :: Buffer_Id -> String -> Int -> Int -> [Int] -> Message
 - b_close :: Buffer_Id -> Message
 - b_fill :: Buffer_Id -> [(Buffer_Ix, Int, Double)] -> Message
 - b_free :: Buffer_Id -> Message
 - b_gen :: Buffer_Id -> String -> [Datum] -> Message
 - b_get :: Buffer_Id -> [Buffer_Ix] -> Message
 - b_getn :: Buffer_Id -> [(Buffer_Ix, Int)] -> Message
 - b_query :: [Buffer_Id] -> Message
 - b_read :: Buffer_Id -> String -> Int -> Int -> Buffer_Ix -> Buffer_Leave_File_Open -> Message
 - b_readChannel :: Buffer_Id -> String -> Int -> Int -> Buffer_Ix -> Buffer_Leave_File_Open -> [Int] -> Message
 - b_set :: Buffer_Id -> [(Buffer_Ix, Double)] -> Message
 - b_setn :: Buffer_Id -> [(Buffer_Ix, [Double])] -> Message
 - b_write :: Buffer_Id -> String -> SoundFileFormat -> SampleFormat -> Int -> Buffer_Ix -> Buffer_Leave_File_Open -> Message
 - b_zero :: Buffer_Id -> Message
 - c_fill :: [(Bus_Id, Int, Double)] -> Message
 - c_get :: [Bus_Id] -> Message
 - c_getn :: [(Bus_Id, Int)] -> Message
 - c_set :: [(Bus_Id, Double)] -> Message
 - c_setn :: [(Bus_Id, [Double])] -> 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 :: [Group_Id] -> Message
 - g_freeAll :: [Group_Id] -> Message
 - g_head :: [(Group_Id, Node_Id)] -> Message
 - g_new :: [(Group_Id, AddAction, Node_Id)] -> Message
 - g_tail :: [(Group_Id, Node_Id)] -> Message
 - g_dumpTree :: [(Group_Id, Bool)] -> Message
 - g_queryTree :: [(Group_Id, Bool)] -> Message
 - n_after :: [(Node_Id, Node_Id)] -> Message
 - n_before :: [(Node_Id, Node_Id)] -> Message
 - n_fill :: Node_Id -> [(String, Int, Double)] -> Message
 - n_free :: [Node_Id] -> Message
 - n_map :: Node_Id -> [(String, Bus_Id)] -> Message
 - n_mapn :: Node_Id -> [(Int, Bus_Id, Int)] -> Message
 - n_mapa :: Node_Id -> [(String, Bus_Id)] -> Message
 - n_mapan :: Node_Id -> [(String, Bus_Id, Int)] -> Message
 - n_query :: [Node_Id] -> Message
 - n_run :: [(Node_Id, Bool)] -> Message
 - n_set :: Node_Id -> [(String, Double)] -> Message
 - n_setn :: Node_Id -> [(Int, [Double])] -> Message
 - n_trace :: [Node_Id] -> Message
 - n_order :: AddAction -> Node_Id -> [Node_Id] -> Message
 - p_new :: [(Group_Id, AddAction, Node_Id)] -> Message
 - s_get :: Synth_Id -> [String] -> Message
 - s_getn :: Synth_Id -> [(String, Int)] -> Message
 - s_new :: String -> Synth_Id -> AddAction -> Node_Id -> [(String, Double)] -> Message
 - s_noid :: [Synth_Id] -> Message
 - u_cmd :: Int -> Int -> 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 :: Int -> Message
 - b_getn1 :: Buffer_Id -> (Buffer_Ix, Int) -> Message
 - b_query1 :: Buffer_Id -> Message
 - c_getn1 :: (Bus_Id, Int) -> Message
 - c_set1 :: Bus_Id -> Double -> Message
 - c_setn1 :: (Bus_Id, [Double]) -> Message
 - n_run1 :: Node_Id -> Bool -> Message
 - n_set1 :: Node_Id -> String -> Double -> Message
 - s_new0 :: String -> Synth_Id -> AddAction -> Node_Id -> Message
 - b_segment :: Int -> Int -> [Int]
 - b_indices :: Int -> Int -> Int -> [(Int, Int)]
 - b_gen_copy :: Buffer_Id -> Int -> Buffer_Id -> Int -> Maybe Int -> Message
 - b_gen_sine1 :: Buffer_Id -> [B_Gen] -> [Double] -> Message
 - b_gen_sine2 :: Buffer_Id -> [B_Gen] -> [(Double, Double)] -> Message
 - b_gen_sine3 :: Buffer_Id -> [B_Gen] -> [(Double, Double, Double)] -> Message
 - b_gen_cheby :: Buffer_Id -> [B_Gen] -> [Double] -> Message
 - b_alloc_setn1 :: Buffer_Id -> Buffer_Ix -> [Double] -> Message
 - b_set1 :: Buffer_Id -> Buffer_Ix -> Double -> Message
 - b_setn1 :: Buffer_Id -> Buffer_Ix -> [Double] -> Message
 - b_setn1_segmented :: Int -> Buffer_Id -> Buffer_Ix -> [Double] -> [Message]
 - partConv_preparePartConv :: Int -> Int -> Int -> Message
 - unpack_n_info_plain :: Message -> [Int]
 - unpack_n_info :: Message -> Maybe (Int, Int, Int, Int, Int, Maybe (Int, Int))
 - unpack_n_info_err :: Message -> (Int, Int, Int, Int, Int, Maybe (Int, Int))
 - unpack_tr :: Message -> Maybe (Int, Int, Double)
 - unpack_tr_err :: Message -> (Int, Int, Double)
 - unpack_b_setn :: Message -> Maybe (Int, Int, Int, [Double])
 - unpack_b_setn_err :: Message -> (Int, Int, Int, [Double])
 - unpack_b_info :: Message -> Maybe (Int, Int, Int, Double)
 - unpack_b_info_err :: Message -> (Int, Int, Int, Double)
 
Types
type Buffer_Leave_File_Open = Bool Source #
File connection flag.
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_gen :: Buffer_Id -> String -> [Datum] -> Message Source #
Call a command to fill a buffer. (Asynchronous)
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_write :: Buffer_Id -> String -> SoundFileFormat -> SampleFormat -> Int -> Buffer_Ix -> Buffer_Leave_File_Open -> Message Source #
Write sound file data. (Asynchronous)
Control bus commands
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 :: [Group_Id] -> Message Source #
Free all synths in this group and all its sub-groups.
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_fill :: Node_Id -> [(String, Int, Double)] -> Message Source #
Fill ranges of a node's control values.
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.
Par commands (p_)
p_new :: [(Group_Id, AddAction, Node_Id)] -> Message Source #
Create a new parallel group (supernova specific).
Synthesis node commands (s_)
s_new :: String -> Synth_Id -> AddAction -> Node_Id -> [(String, Double)] -> Message Source #
Create a new synth.
Unit Generator commands (u_)
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 :: Int -> Message Source #
Request /synced message when all current asynchronous commands complete.
Variants to simplify common cases
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 1True
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)True
>>>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_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_alloc_setn1 :: Buffer_Id -> Buffer_Ix -> [Double] -> Message Source #
Pre-allocate for b_setn1, values preceding offset are zeroed.
b_setn1_segmented :: Int -> Buffer_Id -> Buffer_Ix -> [Double] -> [Message] Source #
Segmented variant of b_setn1.
Ugen commands.
partConv_preparePartConv :: Int -> Int -> Int -> Message Source #
Generate accumulation buffer given time-domain IR buffer and FFT size.
Unpack
unpack_n_info_plain :: Message -> [Int] Source #