module Sound.Sc3.Server.Command.Completion where
import Sound.Osc.Core
import Sound.Sc3.Server.Enum
import Sound.Sc3.Server.Synthdef
encode_blob :: Packet -> Datum
encode_blob :: Packet -> Datum
encode_blob = Blob -> Datum
Blob forall b c a. (b -> c) -> (a -> b) -> a -> c
. Packet -> Blob
encodePacket
d_recv :: Packet -> Synthdef -> Message
d_recv :: Packet -> Synthdef -> Message
d_recv Packet
pkt Synthdef
d = Address_Pattern -> [Datum] -> Message
Message Address_Pattern
"/d_recv" [Blob -> Datum
Blob (Synthdef -> Blob
synthdefData Synthdef
d),Packet -> Datum
encode_blob Packet
pkt]
d_load :: Packet -> String -> Message
d_load :: Packet -> Address_Pattern -> Message
d_load Packet
pkt Address_Pattern
p = Address_Pattern -> [Datum] -> Message
Message Address_Pattern
"/d_load" [Address_Pattern -> Datum
string Address_Pattern
p,Packet -> Datum
encode_blob Packet
pkt]
d_loadDir :: Packet -> String -> Message
d_loadDir :: Packet -> Address_Pattern -> Message
d_loadDir Packet
pkt Address_Pattern
p = Address_Pattern -> [Datum] -> Message
Message Address_Pattern
"/d_loadDir" [Address_Pattern -> Datum
string Address_Pattern
p,Packet -> Datum
encode_blob Packet
pkt]
b_alloc :: Packet -> Int -> Int -> Int -> Message
b_alloc :: Packet -> Int -> Int -> Int -> Message
b_alloc Packet
pkt Int
nid Int
frames Int
channels = Address_Pattern -> [Datum] -> Message
Message Address_Pattern
"/b_alloc" [forall n. Integral n => n -> Datum
int32 Int
nid,forall n. Integral n => n -> Datum
int32 Int
frames,forall n. Integral n => n -> Datum
int32 Int
channels,Packet -> Datum
encode_blob Packet
pkt]
b_allocRead :: Packet -> Int -> String -> Int -> Int -> Message
b_allocRead :: Packet -> Int -> Address_Pattern -> Int -> Int -> Message
b_allocRead Packet
pkt Int
nid Address_Pattern
p Int
f Int
n = Address_Pattern -> [Datum] -> Message
Message Address_Pattern
"/b_allocRead" [forall n. Integral n => n -> Datum
int32 Int
nid,Address_Pattern -> Datum
string Address_Pattern
p,forall n. Integral n => n -> Datum
int32 Int
f,forall n. Integral n => n -> Datum
int32 Int
n,Packet -> Datum
encode_blob Packet
pkt]
b_allocReadChannel :: Packet -> Int -> String -> Int -> Int -> [Int] -> Message
b_allocReadChannel :: Packet -> Int -> Address_Pattern -> Int -> Int -> [Int] -> Message
b_allocReadChannel Packet
pkt Int
nid Address_Pattern
p Int
f Int
n [Int]
cs = Address_Pattern -> [Datum] -> Message
Message Address_Pattern
"/b_allocReadChannel" ([forall n. Integral n => n -> Datum
int32 Int
nid,Address_Pattern -> Datum
string Address_Pattern
p,forall n. Integral n => n -> Datum
int32 Int
f,forall n. Integral n => n -> Datum
int32 Int
n] forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall n. Integral n => n -> Datum
int32 [Int]
cs forall a. [a] -> [a] -> [a]
++ [Packet -> Datum
encode_blob Packet
pkt])
b_free :: Packet -> Int -> Message
b_free :: Packet -> Int -> Message
b_free Packet
pkt Int
nid = Address_Pattern -> [Datum] -> Message
Message Address_Pattern
"/b_free" [forall n. Integral n => n -> Datum
int32 Int
nid,Packet -> Datum
encode_blob Packet
pkt]
b_close :: Packet -> Int -> Message
b_close :: Packet -> Int -> Message
b_close Packet
pkt Int
nid = Address_Pattern -> [Datum] -> Message
Message Address_Pattern
"/b_close" [forall n. Integral n => n -> Datum
int32 Int
nid,Packet -> Datum
encode_blob Packet
pkt]
b_read :: Packet -> Int -> String -> Int -> Int -> Int -> Bool -> Message
b_read :: Packet
-> Int -> Address_Pattern -> Int -> Int -> Int -> Bool -> Message
b_read Packet
pkt Int
nid Address_Pattern
p Int
f Int
n Int
f' Bool
z = Address_Pattern -> [Datum] -> Message
Message Address_Pattern
"/b_read" [forall n. Integral n => n -> Datum
int32 Int
nid,Address_Pattern -> Datum
string Address_Pattern
p,forall n. Integral n => n -> Datum
int32 Int
f,forall n. Integral n => n -> Datum
int32 Int
n,forall n. Integral n => n -> Datum
int32 Int
f',forall n. Integral n => n -> Datum
int32 (forall a. Enum a => a -> Int
fromEnum Bool
z),Packet -> Datum
encode_blob Packet
pkt]
b_readChannel :: Packet -> Int -> String -> Int -> Int -> Int -> Bool -> [Int] -> Message
b_readChannel :: Packet
-> Int
-> Address_Pattern
-> Int
-> Int
-> Int
-> Bool
-> [Int]
-> Message
b_readChannel Packet
pkt Int
nid Address_Pattern
p Int
f Int
n Int
f' Bool
z [Int]
cs = Address_Pattern -> [Datum] -> Message
Message Address_Pattern
"/b_readChannel" ([forall n. Integral n => n -> Datum
int32 Int
nid,Address_Pattern -> Datum
string Address_Pattern
p,forall n. Integral n => n -> Datum
int32 Int
f,forall n. Integral n => n -> Datum
int32 Int
n,forall n. Integral n => n -> Datum
int32 Int
f',forall n. Integral n => n -> Datum
int32 (forall a. Enum a => a -> Int
fromEnum Bool
z)] forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map forall n. Integral n => n -> Datum
int32 [Int]
cs forall a. [a] -> [a] -> [a]
++ [Packet -> Datum
encode_blob Packet
pkt])
b_write :: Packet -> Int -> String -> SoundFileFormat -> SampleFormat -> Int -> Int -> Bool -> Message
b_write :: Packet
-> Int
-> Address_Pattern
-> SoundFileFormat
-> SampleFormat
-> Int
-> Int
-> Bool
-> Message
b_write Packet
pkt Int
nid Address_Pattern
p SoundFileFormat
h SampleFormat
t Int
f Int
s Bool
z = Address_Pattern -> [Datum] -> Message
Message Address_Pattern
"/b_write" [forall n. Integral n => n -> Datum
int32 Int
nid,Address_Pattern -> Datum
string Address_Pattern
p,Address_Pattern -> Datum
string (SoundFileFormat -> Address_Pattern
soundFileFormatString SoundFileFormat
h),Address_Pattern -> Datum
string (SampleFormat -> Address_Pattern
sampleFormatString SampleFormat
t),forall n. Integral n => n -> Datum
int32 Int
f,forall n. Integral n => n -> Datum
int32 Int
s,forall n. Integral n => n -> Datum
int32 (forall a. Enum a => a -> Int
fromEnum Bool
z),Packet -> Datum
encode_blob Packet
pkt]
b_zero :: Packet -> Int -> Message
b_zero :: Packet -> Int -> Message
b_zero Packet
pkt Int
nid = Address_Pattern -> [Datum] -> Message
Message Address_Pattern
"/b_zero" [forall n. Integral n => n -> Datum
int32 Int
nid,Packet -> Datum
encode_blob Packet
pkt]