module Sound.Sc3.Server.Nrt.Render where
import System.FilePath
import System.Process
import Sound.Sc3.Server.Enum
import Sound.Sc3.Server.Nrt
type Nrt_Param_Plain = (FilePath,(FilePath,Int),(FilePath,Int),Int,SampleFormat,[String])
nrt_param_plain_to_arg :: Nrt_Param_Plain -> [String]
nrt_param_plain_to_arg :: Nrt_Param_Plain -> [String]
nrt_param_plain_to_arg (String
osc_nm,(String
in_sf,Int
in_nc),(String
out_sf,Int
out_nc),Int
sr,SampleFormat
sf,[String]
param) =
let sf_ty :: SoundFileFormat
sf_ty = case String -> String
takeExtension String
out_sf of
Char
'.':String
ext -> String -> SoundFileFormat
soundFileFormat_from_extension_err String
ext
String
_ -> forall a. HasCallStack => String -> a
error String
"nrt_exec_plain: invalid sf extension"
in forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[String
"-i",forall a. Show a => a -> String
show Int
in_nc
,String
"-o",forall a. Show a => a -> String
show Int
out_nc]
,[String]
param
,[String
"-N"
,String
osc_nm,String
in_sf,String
out_sf
,forall a. Show a => a -> String
show Int
sr,SoundFileFormat -> String
soundFileFormatString SoundFileFormat
sf_ty,SampleFormat -> String
sampleFormatString SampleFormat
sf]]
nrt_exec_plain :: Nrt_Param_Plain -> IO ()
nrt_exec_plain :: Nrt_Param_Plain -> IO ()
nrt_exec_plain Nrt_Param_Plain
opt = String -> [String] -> IO ()
callProcess String
"scsynth" (Nrt_Param_Plain -> [String]
nrt_param_plain_to_arg Nrt_Param_Plain
opt)
nrt_proc_plain :: Nrt_Param_Plain -> Nrt -> IO ()
nrt_proc_plain :: Nrt_Param_Plain -> Nrt -> IO ()
nrt_proc_plain Nrt_Param_Plain
opt Nrt
sc = do
let (String
osc_nm,(String, Int)
_,(String, Int)
_,Int
_,SampleFormat
_,[String]
_) = Nrt_Param_Plain
opt
String -> Nrt -> IO ()
writeNrt String
osc_nm Nrt
sc
Nrt_Param_Plain -> IO ()
nrt_exec_plain Nrt_Param_Plain
opt
type Nrt_Render_Plain = (FilePath,FilePath,Int,Int,SampleFormat,[String])
nrt_render_plain :: Nrt_Render_Plain -> Nrt -> IO ()
nrt_render_plain :: Nrt_Render_Plain -> Nrt -> IO ()
nrt_render_plain (String
osc_nm,String
sf_nm,Int
nc,Int
sr,SampleFormat
sf,[String]
param) Nrt
sc =
let opt :: Nrt_Param_Plain
opt = (String
osc_nm,(String
"_",Int
0),(String
sf_nm,Int
nc),Int
sr,SampleFormat
sf,[String]
param)
in Nrt_Param_Plain -> Nrt -> IO ()
nrt_proc_plain Nrt_Param_Plain
opt Nrt
sc