module Sound.Sc3.Server.Command.Enum where
import Data.List
import Data.Maybe
import qualified Sound.Osc.Packet as Osc
type SC3_Command = String
sc3_cmd_enumeration :: [(SC3_Command,Int)]
sc3_cmd_enumeration :: [(Address_Pattern, Int)]
sc3_cmd_enumeration =
[(Address_Pattern
"/notify",Int
1)
,(Address_Pattern
"/status",Int
2)
,(Address_Pattern
"/quit",Int
3)
,(Address_Pattern
"/cmd",Int
4)
,(Address_Pattern
"/d_recv",Int
5)
,(Address_Pattern
"/d_load",Int
6)
,(Address_Pattern
"/d_loadDir",Int
7)
,(Address_Pattern
"/d_freeAll",Int
8)
,(Address_Pattern
"/s_new",Int
9)
,(Address_Pattern
"/n_trace",Int
10)
,(Address_Pattern
"/n_free",Int
11)
,(Address_Pattern
"/n_run",Int
12)
,(Address_Pattern
"/n_cmd",Int
13)
,(Address_Pattern
"/n_map",Int
14)
,(Address_Pattern
"/n_set",Int
15)
,(Address_Pattern
"/n_setn",Int
16)
,(Address_Pattern
"/n_fill",Int
17)
,(Address_Pattern
"/n_before",Int
18)
,(Address_Pattern
"/n_after",Int
19)
,(Address_Pattern
"/u_cmd",Int
20)
,(Address_Pattern
"/g_new",Int
21)
,(Address_Pattern
"/g_head",Int
22)
,(Address_Pattern
"/g_tail",Int
23)
,(Address_Pattern
"/g_freeAll",Int
24)
,(Address_Pattern
"/c_set",Int
25)
,(Address_Pattern
"/c_setn",Int
26)
,(Address_Pattern
"/c_fill",Int
27)
,(Address_Pattern
"/b_alloc",Int
28)
,(Address_Pattern
"/b_allocRead",Int
29)
,(Address_Pattern
"/b_read",Int
30)
,(Address_Pattern
"/b_write",Int
31)
,(Address_Pattern
"/b_free",Int
32)
,(Address_Pattern
"/b_close",Int
33)
,(Address_Pattern
"/b_zero",Int
34)
,(Address_Pattern
"/b_set",Int
35)
,(Address_Pattern
"/b_setn",Int
36)
,(Address_Pattern
"/b_fill",Int
37)
,(Address_Pattern
"/b_gen",Int
38)
,(Address_Pattern
"/dumpOSC",Int
39)
,(Address_Pattern
"/c_get",Int
40)
,(Address_Pattern
"/c_getn",Int
41)
,(Address_Pattern
"/b_get",Int
42)
,(Address_Pattern
"/b_getn",Int
43)
,(Address_Pattern
"/s_get",Int
44)
,(Address_Pattern
"/s_getn",Int
45)
,(Address_Pattern
"/n_query",Int
46)
,(Address_Pattern
"/b_query",Int
47)
,(Address_Pattern
"/n_mapn",Int
48)
,(Address_Pattern
"/s_noid",Int
49)
,(Address_Pattern
"/g_deepFree",Int
50)
,(Address_Pattern
"/clearSched",Int
51)
,(Address_Pattern
"/sync",Int
52)
,(Address_Pattern
"/d_free",Int
53)
,(Address_Pattern
"/b_allocReadChannel",Int
54)
,(Address_Pattern
"/b_readChannel",Int
55)
,(Address_Pattern
"/g_dumpTree",Int
56)
,(Address_Pattern
"/g_queryTree",Int
57)
,(Address_Pattern
"/error",Int
58)
,(Address_Pattern
"/s_newargs",Int
59)
,(Address_Pattern
"/n_mapa",Int
60)
,(Address_Pattern
"/n_mapan",Int
61)
,(Address_Pattern
"/n_order",Int
62)
]
sc3_cmd_number :: SC3_Command -> Maybe Int
sc3_cmd_number :: Address_Pattern -> Maybe Int
sc3_cmd_number = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup [(Address_Pattern, Int)]
sc3_cmd_enumeration
known_sc3_cmd :: SC3_Command -> Bool
known_sc3_cmd :: Address_Pattern -> Bool
known_sc3_cmd = forall a. Maybe a -> Bool
isJust forall b c a. (b -> c) -> (a -> b) -> a -> c
. Address_Pattern -> Maybe Int
sc3_cmd_number
async_cmds :: [SC3_Command]
async_cmds :: [Address_Pattern]
async_cmds =
[Address_Pattern
"/b_alloc"
,Address_Pattern
"/b_allocRead"
,Address_Pattern
"/b_allocReadChannel"
,Address_Pattern
"/b_close"
,Address_Pattern
"/b_free"
,Address_Pattern
"/b_read"
,Address_Pattern
"/b_readChannel"
,Address_Pattern
"/b_write"
,Address_Pattern
"/b_zero"
,Address_Pattern
"/d_load"
,Address_Pattern
"/d_loadDir"
,Address_Pattern
"/d_recv"
,Address_Pattern
"/notify"
,Address_Pattern
"/quit"
,Address_Pattern
"/sync"]
isAsync :: Osc.Message -> Bool
isAsync :: Message -> Bool
isAsync (Osc.Message Address_Pattern
a [Datum]
_) = Address_Pattern
a forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Address_Pattern]
async_cmds
partition_async :: [Osc.Message] -> ([Osc.Message],[Osc.Message])
partition_async :: [Message] -> ([Message], [Message])
partition_async = forall a. (a -> Bool) -> [a] -> ([a], [a])
partition Message -> Bool
isAsync
b_info_fields :: [(String,String)]
b_info_fields :: [(Address_Pattern, Address_Pattern)]
b_info_fields =
[(Address_Pattern
"int",Address_Pattern
"buffer-id")
,(Address_Pattern
"int",Address_Pattern
"frame-count")
,(Address_Pattern
"int",Address_Pattern
"channels-count")
,(Address_Pattern
"float",Address_Pattern
"sample-rate")]
n_info_fields :: [(String,String,String)]
n_info_fields :: [(Address_Pattern, Address_Pattern, Address_Pattern)]
n_info_fields =
[(Address_Pattern
"int",Address_Pattern
"node-id",Address_Pattern
"")
,(Address_Pattern
"int",Address_Pattern
"parent group-id",Address_Pattern
"-1 = nil")
,(Address_Pattern
"int",Address_Pattern
"previous node-id",Address_Pattern
"-1 = nil")
,(Address_Pattern
"int",Address_Pattern
"next node-id",Address_Pattern
"-1 = nil")
,(Address_Pattern
"int",Address_Pattern
"node-type",Address_Pattern
"0 = synth,1 = group")
,(Address_Pattern
"int",Address_Pattern
"head node-id",Address_Pattern
"-1 = nil")
,(Address_Pattern
"int",Address_Pattern
"tail node-id",Address_Pattern
"-1 = nil")]