module Sound.SC3.Server.NRT where
import qualified Data.ByteString.Lazy as B 
import System.FilePath 
import System.IO 
import System.Process 
import Sound.OSC.Core 
import qualified Sound.OSC.Coding.Byte as Byte 
import Sound.SC3.Common.Base
import Sound.SC3.Server.Enum
oscWithSize :: Bundle -> B.ByteString
oscWithSize o =
    let b = encodeBundle o
        l = Byte.encode_i32 (fromIntegral (B.length b))
    in B.append l b
data NRT = NRT {nrt_bundles :: [Bundle]} deriving (Show)
type NRT_STAT =
    ((String, Time)
    ,(String, Int)
    ,(String, Int)
    ,(String, [(String,Int)]))
nrt_stat_param :: (String, String, String, String)
nrt_stat_param = ("duration","# bundles","# messages","command set")
nrt_stat :: NRT -> NRT_STAT
nrt_stat (NRT b_seq) =
    let b_msg = map bundleMessages b_seq
    in p4_zip
       nrt_stat_param
       (bundleTime (last b_seq)
       ,length b_seq
       ,sum (map length b_msg)
       ,histogram (concatMap (map messageAddress) b_msg))
nrt_span :: (Time -> Bool) -> NRT -> ([Bundle],[Bundle])
nrt_span f = span (f . bundleTime) . nrt_bundles
encodeNRT :: NRT -> B.ByteString
encodeNRT = B.concat . map oscWithSize . nrt_bundles
writeNRT :: FilePath -> NRT -> IO ()
writeNRT fn = B.writeFile fn . encodeNRT
putNRT :: Handle -> NRT -> IO ()
putNRT h = B.hPut h . encodeNRT
decode_nrt_bundles :: B.ByteString -> [Bundle]
decode_nrt_bundles s =
    let (p,q) = B.splitAt 4 s
        n = fromIntegral (Byte.decode_i32 p)
        (r,s') = B.splitAt n q
        r' = decodeBundle r
    in if B.null s'
       then [r']
       else r' : decode_nrt_bundles s'
decodeNRT :: B.ByteString -> NRT
decodeNRT = NRT . decode_nrt_bundles
readNRT :: FilePath -> IO NRT
readNRT = fmap decodeNRT . B.readFile
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 (osc_nm,(in_sf,in_nc),(out_sf,out_nc),sr,sf,param) =
  let sf_ty = case takeExtension out_sf of
                '.':ext -> soundFileFormat_from_extension_err ext
                _ -> error "nrt_exec_plain: invalid sf extension"
  in concat [["-i",show in_nc
             ,"-o",show out_nc]
            ,param
            ,["-N"
             ,osc_nm,in_sf,out_sf
             ,show sr,soundFileFormatString sf_ty,sampleFormatString sf]]
nrt_exec_plain :: NRT_Param_Plain -> IO ()
nrt_exec_plain opt = callProcess "scsynth" (nrt_param_plain_to_arg opt)
nrt_proc_plain :: NRT_Param_Plain -> NRT -> IO ()
nrt_proc_plain opt sc = do
  let (osc_nm,_,_,_,_,_) = opt
  writeNRT osc_nm sc
  nrt_exec_plain opt
type NRT_Render_Plain = (FilePath,FilePath,Int,Int,SampleFormat,[String])
nrt_render_plain :: NRT_Render_Plain -> NRT -> IO ()
nrt_render_plain (osc_nm,sf_nm,nc,sr,sf,param) sc =
  let opt = (osc_nm,("_",0),(sf_nm,nc),sr,sf,param)
  in nrt_proc_plain opt sc