-- | Interaction with @jack-dl@, @scsynth@ and @text-dl@. module Sound.DF.Uniform.LL.Audition where import Sound.OSC {- hosc -} import qualified Sound.SC3 as S {- hsc3 -} import Sound.SC3.UGen.External.RDU {- sc3-rdu -} import System.Directory {- directory -} import System.FilePath {- filepath -} import System.Process {- process -} import Sound.DF.Uniform.LL.CGen import Sound.DF.Uniform.LL.Command import Sound.DF.Uniform.LL.UId -- * jack-dl -- | Run action with @UDP@ link to @jack-dl@. with_jack_dl :: Connection UDP a -> IO a with_jack_dl = withTransport (openUDP "127.0.0.1" 57190) -- | Audition graph after sending initialisation messages. audition :: [Message] -> Instructions -> IO () audition is ins = do t <- getTemporaryDirectory k <- generateId let fn = t ("audition" ++ show k) dl_gen fn (JACK,"/home/rohan/opt") ins with_jack_dl (mapM sendMessage is >> sendMessage (g_load (fn <.> "so"))) -- * scsynth -- | Load graph. u_cmd_g_load :: Int -> Int -> String -> Message u_cmd_g_load nid uid s = S.u_cmd nid uid "/g_load" [string s] -- | Audition graph after sending initialisation messages. audition_sc3 :: [Message] -> Instructions -> IO () audition_sc3 is ins = do t <- getTemporaryDirectory k <- generateId let fn = t ("audition" ++ show k) dl_gen fn (SC3,"/home/rohan/opt") ins S.withSC3 (mapM sendMessage is >> S.play (S.out 0 (rdl 2 0)) >> sendMessage (u_cmd_g_load (-1) 0 (fn <.> "so"))) -- * text-dl -- | Audition at @text-dl@. audition_text :: Int -> Instructions -> IO () audition_text nf ins = do t <- getTemporaryDirectory k <- generateId let fn = t ("audition" ++ show k) dl_gen fn (Text,"/home/rohan/opt") ins _ <- rawSystem "text-dl" ["-f",show nf,fn <.> "so"] return ()