module Sound.Sc3.Server.Transport.Monad where
import Control.Monad
import Data.List
import Data.Maybe
import System.Directory
import System.FilePath
import qualified Data.ByteString.Lazy as L
import qualified Data.List.Split as Split
import qualified Data.Tree as Tree
import qualified Safe
import Sound.Osc
import qualified Sound.Osc.Time.Timeout
import qualified Sound.Sc3.Server.Command as Command
import qualified Sound.Sc3.Server.Command.Generic as Generic
import qualified Sound.Sc3.Server.Enum as Enum
import qualified Sound.Sc3.Server.Graphdef as Graphdef
import qualified Sound.Sc3.Server.Graphdef.Binary as Graphdef
import qualified Sound.Sc3.Server.Nrt as Nrt
import qualified Sound.Sc3.Server.Options as Options
import qualified Sound.Sc3.Server.Status as Status
import qualified Sound.Sc3.Server.Synthdef as Synthdef
import qualified Sound.Sc3.Ugen.Bindings.Composite as Composite
import qualified Sound.Sc3.Ugen.Ugen as Ugen
async :: DuplexOsc m => Message -> m Message
async :: forall (m :: * -> *). DuplexOsc m => Message -> m Message
async Message
m = forall (m :: * -> *). SendOsc m => Message -> m ()
sendMessage Message
m forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *). RecvOsc m => Address_Pattern -> m Message
waitReply Address_Pattern
"/done"
async_ :: DuplexOsc m => Message -> m ()
async_ :: forall (m :: * -> *). DuplexOsc m => Message -> m ()
async_ = forall (f :: * -> *) a. Functor f => f a -> f ()
void forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). DuplexOsc m => Message -> m Message
async
maybe_async :: DuplexOsc m => Message -> m ()
maybe_async :: forall (m :: * -> *). DuplexOsc m => Message -> m ()
maybe_async Message
m = if Message -> Bool
Command.isAsync Message
m then forall (m :: * -> *). DuplexOsc m => Message -> m ()
async_ Message
m else forall (m :: * -> *). SendOsc m => Message -> m ()
sendMessage Message
m
maybe_async_at :: DuplexOsc m => Time -> Message -> m ()
maybe_async_at :: forall (m :: * -> *). DuplexOsc m => Time -> Message -> m ()
maybe_async_at Time
t Message
m =
if Message -> Bool
Command.isAsync Message
m
then forall (m :: * -> *). DuplexOsc m => Message -> m ()
async_ Message
m
else forall (m :: * -> *). SendOsc m => Bundle -> m ()
sendBundle (Time -> [Message] -> Bundle
bundle Time
t [Message
m])
type Sc3_Address = (String, Int)
sc3_default_udp :: Sc3_Address
sc3_default_udp :: Sc3_Address
sc3_default_udp = (Address_Pattern
Options.sc3_addr_def,forall i. Num i => i
Options.sc3_port_def)
sc3_udp_limit :: Num n => n
sc3_udp_limit :: forall i. Num i => i
sc3_udp_limit = n
65507
withSc3At :: Sc3_Address -> Connection Udp a -> IO a
withSc3At :: forall a. Sc3_Address -> Connection Udp a -> IO a
withSc3At (Address_Pattern
h,Node_Id
p) = forall t r. Transport t => IO t -> Connection t r -> IO r
withTransport (Address_Pattern -> Node_Id -> IO Udp
openUdp Address_Pattern
h Node_Id
p)
withSc3 :: Connection Udp a -> IO a
withSc3 :: forall a. Connection Udp a -> IO a
withSc3 = forall a. Sc3_Address -> Connection Udp a -> IO a
withSc3At Sc3_Address
sc3_default_udp
withSc3_ :: Connection Udp a -> IO ()
withSc3_ :: forall a. Connection Udp a -> IO ()
withSc3_ = forall (f :: * -> *) a. Functor f => f a -> f ()
void forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Connection Udp a -> IO a
withSc3
withSc3_tm :: Double -> Connection Udp a -> IO (Maybe a)
withSc3_tm :: forall a. Time -> Connection Udp a -> IO (Maybe a)
withSc3_tm Time
tm = forall a. Time -> IO a -> IO (Maybe a)
Sound.Osc.Time.Timeout.timeout_r Time
tm forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Connection Udp a -> IO a
withSc3
withSc3AtSeq :: Sc3_Address -> Int -> Connection Udp a -> IO [a]
withSc3AtSeq :: forall a. Sc3_Address -> Node_Id -> Connection Udp a -> IO [a]
withSc3AtSeq (Address_Pattern
h,Node_Id
p) Node_Id
k Connection Udp a
f = do
let mk_udp :: Node_Id -> IO Udp
mk_udp Node_Id
i = Address_Pattern -> Node_Id -> IO Udp
openUdp Address_Pattern
h (Node_Id
p forall a. Num a => a -> a -> a
+ Node_Id
i)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (\Node_Id
i -> forall t r. Transport t => IO t -> Connection t r -> IO r
withTransport (Node_Id -> IO Udp
mk_udp Node_Id
i) Connection Udp a
f) [Node_Id
0 .. Node_Id
k forall a. Num a => a -> a -> a
- Node_Id
1]
withSc3AtSeq_ :: Sc3_Address -> Int -> Connection Udp a -> IO ()
withSc3AtSeq_ :: forall a. Sc3_Address -> Node_Id -> Connection Udp a -> IO ()
withSc3AtSeq_ Sc3_Address
loc Node_Id
k = forall (f :: * -> *) a. Functor f => f a -> f ()
void forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Sc3_Address -> Node_Id -> Connection Udp a -> IO [a]
withSc3AtSeq Sc3_Address
loc Node_Id
k
stop :: SendOsc m => m ()
stop :: forall (m :: * -> *). SendOsc m => m ()
stop = forall (m :: * -> *). SendOsc m => Message -> m ()
sendMessage ([Node_Id] -> Message
Command.g_freeAll [Node_Id
1])
reset :: SendOsc m => m ()
reset :: forall (m :: * -> *). SendOsc m => m ()
reset =
let m :: [Message]
m = [Message
Command.clearSched
,[Node_Id] -> Message
Command.n_free [Node_Id
1,Node_Id
2]
,[(Node_Id, AddAction, Node_Id)] -> Message
Command.g_new [(Node_Id
1,AddAction
Enum.AddToHead,Node_Id
0),(Node_Id
2,AddAction
Enum.AddToTail,Node_Id
0)]]
in forall (m :: * -> *). SendOsc m => Bundle -> m ()
sendBundle (Time -> [Message] -> Bundle
bundle Time
immediately [Message]
m)
type Play_Opt = (Command.Node_Id,Enum.AddAction,Command.Group_Id,[(String,Double)])
play_graphdef_msg :: Play_Opt -> Graphdef.Graphdef -> Message
play_graphdef_msg :: Play_Opt -> Graphdef -> Message
play_graphdef_msg (Node_Id
nid,AddAction
act,Node_Id
gid,[(Address_Pattern, Time)]
param) Graphdef
g =
let nm :: Address_Pattern
nm = Ascii -> Address_Pattern
ascii_to_string (Graphdef -> Ascii
Graphdef.graphdef_name Graphdef
g)
in Address_Pattern
-> Node_Id
-> AddAction
-> Node_Id
-> [(Address_Pattern, Time)]
-> Message
Command.s_new Address_Pattern
nm Node_Id
nid AddAction
act Node_Id
gid [(Address_Pattern, Time)]
param
recv_or_load_graphdef :: Transport m => Graphdef.Graphdef -> m Message
recv_or_load_graphdef :: forall (m :: * -> *). Transport m => Graphdef -> m Message
recv_or_load_graphdef Graphdef
g = do
Address_Pattern
tmp <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO Address_Pattern
getTemporaryDirectory
let nm :: Address_Pattern
nm = Ascii -> Address_Pattern
ascii_to_string (Graphdef -> Ascii
Graphdef.graphdef_name Graphdef
g)
fn :: Address_Pattern
fn = Address_Pattern
tmp Address_Pattern -> Address_Pattern -> Address_Pattern
</> Address_Pattern
nm Address_Pattern -> Address_Pattern -> Address_Pattern
<.> Address_Pattern
"scsyndef"
by :: ByteString
by = Graphdef -> ByteString
Graphdef.encode_graphdef Graphdef
g
sz :: Int64
sz = ByteString -> Int64
L.length ByteString
by
if Int64
sz forall a. Ord a => a -> a -> Bool
< forall i. Num i => i
sc3_udp_limit
then forall (m :: * -> *). DuplexOsc m => Message -> m Message
async (ByteString -> Message
Command.d_recv_bytes ByteString
by)
else forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Address_Pattern -> Graphdef -> IO ()
Graphdef.graphdefWrite Address_Pattern
fn Graphdef
g) forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *). DuplexOsc m => Message -> m Message
async (Address_Pattern -> Message
Command.d_load Address_Pattern
fn)
playGraphdef :: Transport m => Play_Opt -> Graphdef.Graphdef -> m ()
playGraphdef :: forall (m :: * -> *). Transport m => Play_Opt -> Graphdef -> m ()
playGraphdef Play_Opt
opt Graphdef
g = forall (m :: * -> *). Transport m => Graphdef -> m Message
recv_or_load_graphdef Graphdef
g forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *). SendOsc m => Message -> m ()
sendMessage (Play_Opt -> Graphdef -> Message
play_graphdef_msg Play_Opt
opt Graphdef
g)
playSynthdef :: Transport m => Play_Opt -> Synthdef.Synthdef -> m ()
playSynthdef :: forall (m :: * -> *). Transport m => Play_Opt -> Synthdef -> m ()
playSynthdef Play_Opt
opt = forall (m :: * -> *). Transport m => Play_Opt -> Graphdef -> m ()
playGraphdef Play_Opt
opt forall b c a. (b -> c) -> (a -> b) -> a -> c
. Synthdef -> Graphdef
Synthdef.synthdef_to_graphdef
playUgen :: Transport m => Play_Opt -> Ugen.Ugen -> m ()
playUgen :: forall (m :: * -> *). Transport m => Play_Opt -> Ugen -> m ()
playUgen Play_Opt
loc =
forall (m :: * -> *). Transport m => Play_Opt -> Synthdef -> m ()
playSynthdef Play_Opt
loc forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Address_Pattern -> Ugen -> Synthdef
Synthdef.synthdef Address_Pattern
"Anonymous" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Maybe Time -> Ugen -> Ugen
Composite.wrapOut forall a. Maybe a
Nothing
run_bundle :: Transport m => Time -> Bundle -> m ()
run_bundle :: forall (m :: * -> *). Transport m => Time -> Bundle -> m ()
run_bundle Time
t0 Bundle
b = do
let t :: Time
t = Time
t0 forall a. Num a => a -> a -> a
+ Bundle -> Time
bundleTime Bundle
b
latency :: Time
latency = Time
0.1
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (forall (m :: * -> *) n. (MonadIO m, RealFrac n) => n -> m ()
pauseThreadUntil (Time
t forall a. Num a => a -> a -> a
- Time
latency))
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (forall (m :: * -> *). DuplexOsc m => Time -> Message -> m ()
maybe_async_at Time
t) (Bundle -> [Message]
bundleMessages Bundle
b)
nrt_play :: Transport m => Nrt.Nrt -> m ()
nrt_play :: forall (m :: * -> *). Transport m => Nrt -> m ()
nrt_play Nrt
sc = do
Time
t0 <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall (m :: * -> *). MonadIO m => m Time
time
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (forall (m :: * -> *). Transport m => Time -> Bundle -> m ()
run_bundle Time
t0) (Nrt -> [Bundle]
Nrt.nrt_bundles Nrt
sc)
nrt_play_reorder :: Transport m => Nrt.Nrt -> m ()
nrt_play_reorder :: forall (m :: * -> *). Transport m => Nrt -> m ()
nrt_play_reorder Nrt
s = do
let ([Bundle]
i,[Bundle]
r) = (Time -> Bool) -> Nrt -> ([Bundle], [Bundle])
Nrt.nrt_span (forall a. Ord a => a -> a -> Bool
<= Time
0) Nrt
s
i' :: [Message]
i' = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Bundle -> [Message]
bundleMessages [Bundle]
i
([Message]
a,[Message]
b) = [Message] -> ([Message], [Message])
Command.partition_async [Message]
i'
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ forall (m :: * -> *). DuplexOsc m => Message -> m Message
async [Message]
a
Time
t <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall (m :: * -> *). MonadIO m => m Time
time
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (forall (m :: * -> *). Transport m => Time -> Bundle -> m ()
run_bundle Time
t) (Time -> [Message] -> Bundle
Bundle Time
0 [Message]
b forall a. a -> [a] -> [a]
: [Bundle]
r)
nrt_audition :: Nrt.Nrt -> IO ()
nrt_audition :: Nrt -> IO ()
nrt_audition = forall a. Connection Udp a -> IO a
withSc3 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). Transport m => Nrt -> m ()
nrt_play
class Audible e where
playAt :: Transport m => Play_Opt -> e -> m ()
play :: Transport m => e -> m ()
play = forall e (m :: * -> *).
(Audible e, Transport m) =>
Play_Opt -> e -> m ()
playAt (-Node_Id
1,AddAction
Enum.AddToHead,Node_Id
1,[])
instance Audible Graphdef.Graphdef where
playAt :: forall (m :: * -> *). Transport m => Play_Opt -> Graphdef -> m ()
playAt = forall (m :: * -> *). Transport m => Play_Opt -> Graphdef -> m ()
playGraphdef
instance Audible Synthdef.Synthdef where
playAt :: forall (m :: * -> *). Transport m => Play_Opt -> Synthdef -> m ()
playAt = forall (m :: * -> *). Transport m => Play_Opt -> Synthdef -> m ()
playSynthdef
instance Audible Ugen.Ugen where
playAt :: forall (m :: * -> *). Transport m => Play_Opt -> Ugen -> m ()
playAt = forall (m :: * -> *). Transport m => Play_Opt -> Ugen -> m ()
playUgen
auditionAt :: Audible e => Sc3_Address -> Play_Opt -> e -> IO ()
auditionAt :: forall e. Audible e => Sc3_Address -> Play_Opt -> e -> IO ()
auditionAt Sc3_Address
loc Play_Opt
opt = forall a. Sc3_Address -> Connection Udp a -> IO a
withSc3At Sc3_Address
loc forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *).
(Audible e, Transport m) =>
Play_Opt -> e -> m ()
playAt Play_Opt
opt
auditionAtSeq :: Audible e => Sc3_Address -> Play_Opt -> Int -> e -> IO ()
auditionAtSeq :: forall e.
Audible e =>
Sc3_Address -> Play_Opt -> Node_Id -> e -> IO ()
auditionAtSeq Sc3_Address
loc Play_Opt
opt Node_Id
k = forall a. Sc3_Address -> Node_Id -> Connection Udp a -> IO ()
withSc3AtSeq_ Sc3_Address
loc Node_Id
k forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e (m :: * -> *).
(Audible e, Transport m) =>
Play_Opt -> e -> m ()
playAt Play_Opt
opt
def_play_opt :: Play_Opt
def_play_opt :: Play_Opt
def_play_opt = (-Node_Id
1,AddAction
Enum.AddToHead,Node_Id
1,[])
audition :: Audible e => e -> IO ()
audition :: forall e. Audible e => e -> IO ()
audition = forall e. Audible e => Sc3_Address -> Play_Opt -> e -> IO ()
auditionAt Sc3_Address
sc3_default_udp Play_Opt
def_play_opt
auditionSeq :: Audible e => Int -> e -> IO ()
auditionSeq :: forall e. Audible e => Node_Id -> e -> IO ()
auditionSeq = forall e.
Audible e =>
Sc3_Address -> Play_Opt -> Node_Id -> e -> IO ()
auditionAtSeq Sc3_Address
sc3_default_udp Play_Opt
def_play_opt
withNotifications :: DuplexOsc m => m a -> m a
withNotifications :: forall (m :: * -> *) a. DuplexOsc m => m a -> m a
withNotifications m a
f = do
forall (m :: * -> *). DuplexOsc m => Message -> m ()
async_ (Bool -> Message
Command.notify Bool
True)
a
r <- m a
f
forall (m :: * -> *). DuplexOsc m => Message -> m ()
async_ (Bool -> Message
Command.notify Bool
False)
forall (m :: * -> *) a. Monad m => a -> m a
return a
r
b_getn1_data :: DuplexOsc m => Int -> (Int,Int) -> m [Double]
b_getn1_data :: forall (m :: * -> *).
DuplexOsc m =>
Node_Id -> (Node_Id, Node_Id) -> m [Time]
b_getn1_data Node_Id
b (Node_Id, Node_Id)
s = do
let f :: Message -> [Time]
f Message
m = let (Node_Id
_,Node_Id
_,Node_Id
_,[Time]
r) = Message -> (Node_Id, Node_Id, Node_Id, [Time])
Command.unpack_b_setn_err Message
m in [Time]
r
forall (m :: * -> *). SendOsc m => Message -> m ()
sendMessage (Node_Id -> (Node_Id, Node_Id) -> Message
Command.b_getn1 Node_Id
b (Node_Id, Node_Id)
s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Message -> [Time]
f (forall (m :: * -> *). RecvOsc m => Address_Pattern -> m Message
waitReply Address_Pattern
"/b_setn")
b_getn1_data_segment :: DuplexOsc m =>
Int -> Int -> (Int,Int) -> m [Double]
b_getn1_data_segment :: forall (m :: * -> *).
DuplexOsc m =>
Node_Id -> Node_Id -> (Node_Id, Node_Id) -> m [Time]
b_getn1_data_segment Node_Id
n Node_Id
b (Node_Id
i,Node_Id
j) = do
let ix :: [(Node_Id, Node_Id)]
ix = Node_Id -> Node_Id -> Node_Id -> [(Node_Id, Node_Id)]
Command.b_indices Node_Id
n Node_Id
j Node_Id
i
[[Time]]
d <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (m :: * -> *).
DuplexOsc m =>
Node_Id -> (Node_Id, Node_Id) -> m [Time]
b_getn1_data Node_Id
b) [(Node_Id, Node_Id)]
ix
forall (m :: * -> *) a. Monad m => a -> m a
return (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Time]]
d)
b_fetch :: DuplexOsc m => Int -> Int -> m [[Double]]
b_fetch :: forall (m :: * -> *).
DuplexOsc m =>
Node_Id -> Node_Id -> m [[Time]]
b_fetch Node_Id
n Node_Id
b = do
let f :: Message -> f [[Time]]
f Message
m = let (Node_Id
_,Node_Id
nf,Node_Id
nc,Time
_) = Message -> (Node_Id, Node_Id, Node_Id, Time)
Command.unpack_b_info_err Message
m
ix :: (Node_Id, Node_Id)
ix = (Node_Id
0,Node_Id
nf forall a. Num a => a -> a -> a
* Node_Id
nc)
deinterleave :: [a] -> [[a]]
deinterleave = forall a. [[a]] -> [[a]]
transpose forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall e. Node_Id -> [e] -> [[e]]
Split.chunksOf Node_Id
nc
in forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall {a}. [a] -> [[a]]
deinterleave (forall (m :: * -> *).
DuplexOsc m =>
Node_Id -> Node_Id -> (Node_Id, Node_Id) -> m [Time]
b_getn1_data_segment Node_Id
n Node_Id
b (Node_Id, Node_Id)
ix)
forall (m :: * -> *). SendOsc m => Message -> m ()
sendMessage (Node_Id -> Message
Command.b_query1 Node_Id
b)
forall (m :: * -> *). RecvOsc m => Address_Pattern -> m Message
waitReply Address_Pattern
"/b_info" forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall {f :: * -> *}. DuplexOsc f => Message -> f [[Time]]
f
b_fetch1 :: DuplexOsc m => Int -> Int -> m [Double]
b_fetch1 :: forall (m :: * -> *). DuplexOsc m => Node_Id -> Node_Id -> m [Time]
b_fetch1 Node_Id
n Node_Id
b = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Partial => Address_Pattern -> [a] -> a
Safe.headNote Address_Pattern
"b_fetch1: no data") (forall (m :: * -> *).
DuplexOsc m =>
Node_Id -> Node_Id -> m [[Time]]
b_fetch Node_Id
n Node_Id
b)
b_fetch_hdr :: Transport m => Int -> Int -> m ((Int,Int,Int,Double),[[Double]])
b_fetch_hdr :: forall (m :: * -> *).
Transport m =>
Node_Id
-> Node_Id -> m ((Node_Id, Node_Id, Node_Id, Time), [[Time]])
b_fetch_hdr Node_Id
k Node_Id
b = do
(Node_Id, Node_Id, Node_Id, Time)
q <- forall (m :: * -> *).
DuplexOsc m =>
Node_Id -> m (Node_Id, Node_Id, Node_Id, Time)
b_query1_unpack Node_Id
b
[[Time]]
d <- forall (m :: * -> *).
DuplexOsc m =>
Node_Id -> Node_Id -> m [[Time]]
b_fetch Node_Id
k Node_Id
b
forall (m :: * -> *) a. Monad m => a -> m a
return ((Node_Id, Node_Id, Node_Id, Time)
q,[[Time]]
d)
b_query1_unpack_generic :: (DuplexOsc m,Num n,Fractional r) => Int -> m (n,n,n,r)
b_query1_unpack_generic :: forall (m :: * -> *) n r.
(DuplexOsc m, Num n, Fractional r) =>
Node_Id -> m (n, n, n, r)
b_query1_unpack_generic Node_Id
n = do
forall (m :: * -> *). SendOsc m => Message -> m ()
sendMessage (Node_Id -> Message
Command.b_query1 Node_Id
n)
Message
q <- forall (m :: * -> *). RecvOsc m => Address_Pattern -> m Message
waitReply Address_Pattern
"/b_info"
forall (m :: * -> *) a. Monad m => a -> m a
return (forall i f. (Num i, Fractional f) => Message -> (i, i, i, f)
Generic.unpack_b_info_err Message
q)
b_query1_unpack :: DuplexOsc m => Command.Buffer_Id -> m (Int,Int,Int,Double)
b_query1_unpack :: forall (m :: * -> *).
DuplexOsc m =>
Node_Id -> m (Node_Id, Node_Id, Node_Id, Time)
b_query1_unpack = forall (m :: * -> *) n r.
(DuplexOsc m, Num n, Fractional r) =>
Node_Id -> m (n, n, n, r)
b_query1_unpack_generic
c_getn1_data :: (DuplexOsc m,Floating t) => (Int,Int) -> m [t]
c_getn1_data :: forall (m :: * -> *) t.
(DuplexOsc m, Floating t) =>
(Node_Id, Node_Id) -> m [t]
c_getn1_data (Node_Id, Node_Id)
s = do
let f :: [Datum] -> [b]
f [Datum]
d = case [Datum]
d of
Int32 Int32
_:Int32 Int32
_:[Datum]
x -> forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe forall n. Floating n => Datum -> Maybe n
datum_floating [Datum]
x
[Datum]
_ -> forall a. Partial => Address_Pattern -> a
error Address_Pattern
"c_getn1_data"
forall (m :: * -> *). SendOsc m => Message -> m ()
sendMessage ((Node_Id, Node_Id) -> Message
Command.c_getn1 (Node_Id, Node_Id)
s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall {b}. Floating b => [Datum] -> [b]
f (forall (m :: * -> *). RecvOsc m => Address_Pattern -> m [Datum]
waitDatum Address_Pattern
"/c_setn")
n_query1_unpack_f :: DuplexOsc m => (Message -> t) -> Command.Node_Id -> m t
n_query1_unpack_f :: forall (m :: * -> *) t.
DuplexOsc m =>
(Message -> t) -> Node_Id -> m t
n_query1_unpack_f Message -> t
f Node_Id
n = do
forall (m :: * -> *). SendOsc m => Message -> m ()
sendMessage ([Node_Id] -> Message
Command.n_query [Node_Id
n])
Message
r <- forall (m :: * -> *). RecvOsc m => Address_Pattern -> m Message
waitReply Address_Pattern
"/n_info"
forall (m :: * -> *) a. Monad m => a -> m a
return (Message -> t
f Message
r)
n_query1_unpack :: DuplexOsc m => Command.Node_Id -> m (Maybe (Int,Int,Int,Int,Int,Maybe (Int,Int)))
n_query1_unpack :: forall (m :: * -> *).
DuplexOsc m =>
Node_Id
-> m (Maybe
(Node_Id, Node_Id, Node_Id, Node_Id, Node_Id,
Maybe (Node_Id, Node_Id)))
n_query1_unpack = forall (m :: * -> *) t.
DuplexOsc m =>
(Message -> t) -> Node_Id -> m t
n_query1_unpack_f Message
-> Maybe
(Node_Id, Node_Id, Node_Id, Node_Id, Node_Id,
Maybe (Node_Id, Node_Id))
Command.unpack_n_info
n_query1_unpack_plain :: DuplexOsc m => Command.Node_Id -> m [Int]
n_query1_unpack_plain :: forall (m :: * -> *). DuplexOsc m => Node_Id -> m [Node_Id]
n_query1_unpack_plain = forall (m :: * -> *) t.
DuplexOsc m =>
(Message -> t) -> Node_Id -> m t
n_query1_unpack_f Message -> [Node_Id]
Command.unpack_n_info_plain
g_queryTree1_unpack :: DuplexOsc m => Command.Group_Id -> m Status.Query_Node
g_queryTree1_unpack :: forall (m :: * -> *). DuplexOsc m => Node_Id -> m Query_Node
g_queryTree1_unpack Node_Id
n = do
forall (m :: * -> *). SendOsc m => Message -> m ()
sendMessage ([(Node_Id, Bool)] -> Message
Command.g_queryTree [(Node_Id
n,Bool
True)])
Message
r <- forall (m :: * -> *). RecvOsc m => Address_Pattern -> m Message
waitReply Address_Pattern
"/g_queryTree.reply"
forall (m :: * -> *) a. Monad m => a -> m a
return ([Datum] -> Query_Node
Status.queryTree (Message -> [Datum]
messageDatum Message
r))
serverStatus :: DuplexOsc m => m [String]
serverStatus :: forall (m :: * -> *). DuplexOsc m => m [Address_Pattern]
serverStatus = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Datum] -> [Address_Pattern]
Status.statusFormat forall (m :: * -> *). DuplexOsc m => m [Datum]
serverStatusData
server_status_concise :: DuplexOsc m => m String
server_status_concise :: forall (m :: * -> *). DuplexOsc m => m Address_Pattern
server_status_concise = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [Datum] -> Address_Pattern
Status.status_format_concise forall (m :: * -> *). DuplexOsc m => m [Datum]
serverStatusData
serverSampleRateNominal :: DuplexOsc m => m Double
serverSampleRateNominal :: forall (m :: * -> *). DuplexOsc m => m Time
serverSampleRateNominal = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall n. Floating n => Node_Id -> [Datum] -> n
Status.extractStatusField Node_Id
7) forall (m :: * -> *). DuplexOsc m => m [Datum]
serverStatusData
serverSampleRateActual :: DuplexOsc m => m Double
serverSampleRateActual :: forall (m :: * -> *). DuplexOsc m => m Time
serverSampleRateActual = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall n. Floating n => Node_Id -> [Datum] -> n
Status.extractStatusField Node_Id
8) forall (m :: * -> *). DuplexOsc m => m [Datum]
serverStatusData
serverStatusData :: DuplexOsc m => m [Datum]
serverStatusData :: forall (m :: * -> *). DuplexOsc m => m [Datum]
serverStatusData = do
forall (m :: * -> *). SendOsc m => Message -> m ()
sendMessage Message
Command.status
forall (m :: * -> *). RecvOsc m => Address_Pattern -> m [Datum]
waitDatum Address_Pattern
"/status.reply"
serverTree :: DuplexOsc m => m [String]
serverTree :: forall (m :: * -> *). DuplexOsc m => m [Address_Pattern]
serverTree = do
Query_Node
qt <- forall (m :: * -> *). DuplexOsc m => Node_Id -> m Query_Node
g_queryTree1_unpack Node_Id
0
let tr :: Tree Query_Node
tr = Query_Node -> Tree Query_Node
Status.queryTree_rt Query_Node
qt
forall (m :: * -> *) a. Monad m => a -> m a
return [Address_Pattern
"***** SuperCollider Server Tree *****",Tree Address_Pattern -> Address_Pattern
Tree.drawTree (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Query_Node -> Address_Pattern
Status.query_node_pp Tree Query_Node
tr)]