module Sound.SC3.Server.Process (
module Sound.SC3.Server.Process.Options,
commandLine,
EventHandler(..),
_onBoot,
_onPutString,
_onPutError,
defaultEventHandler,
withSynth,
withNRT
) where
import Sound.OpenSoundControl (Transport, TCP, UDP, openTCP, openUDP)
import Control.Concurrent (forkIO)
import Control.Monad (unless)
import Prelude hiding (catch)
import Data.List (isPrefixOf)
import Sound.SC3.Server.Process.Accessor (deriveAccessors)
import Sound.SC3.Server.Process.Options
import Sound.SC3.Server.Process.CommandLine
import System.Exit (ExitCode)
import System.IO (Handle, hGetLine, hIsEOF, hPutStrLn, stderr, stdout)
import System.Process (runInteractiveProcess, waitForProcess)
class OpenTransport t where
openTransport :: RTOptions -> String -> IO t
checkPort :: String -> Int -> Int
checkPort tag p | p <= 0 || p > 65535 = error ("Invalid " ++ tag ++ " port " ++ show p)
checkPort _ p = p
instance OpenTransport (UDP) where
openTransport options server = openUDP server (checkPort "UDP" $ udpPortNumber options)
instance OpenTransport (TCP) where
openTransport options server = openTCP server (checkPort "TCP" $ tcpPortNumber options)
data EventHandler t = EventHandler {
onPutString :: String -> IO (),
onPutError :: String -> IO (),
onBoot :: t -> IO ()
}
$(deriveAccessors ''EventHandler)
defaultEventHandler :: EventHandler t
defaultEventHandler = EventHandler {
onPutString = hPutStrLn stdout,
onPutError = hPutStrLn stderr,
onBoot = const (return ())
}
pipeOutput :: (String -> IO ()) -> Handle -> IO ()
pipeOutput f h = hIsEOF h >>= flip unless (hGetLine h >>= f >> pipeOutput f h)
withSynth :: (Transport t, OpenTransport t) =>
ServerOptions
-> RTOptions
-> EventHandler t
-> IO ExitCode
withSynth serverOptions rtOptions handler = do
print (exe, args)
(_, hOut, hErr, hProc) <- runInteractiveProcess exe args Nothing Nothing
forkIO $ putStdout0 hOut
forkIO $ putStderr hErr
waitForProcess hProc
where
(exe:args) = commandLine serverOptions rtOptions
putStdout0 h = do
eof <- hIsEOF h
unless eof $ do
l <- hGetLine h
if isPrefixOf "SuperCollider 3 server ready.." l
then do
onPutString handler l
fd <- openTransport rtOptions "127.0.0.1"
forkIO $ onBoot handler fd
forkIO $ putStdout h
return ()
else do
onPutString handler l
putStdout0 h
putStdout = pipeOutput (onPutString handler)
putStderr = pipeOutput (onPutError handler)
withNRT ::
ServerOptions
-> NRTOptions
-> EventHandler Handle
-> IO ExitCode
withNRT serverOptions nrtOptions handler = do
(hIn, hOut, hErr, hProc) <- runInteractiveProcess exe args Nothing Nothing
forkIO $ putStdout hOut
forkIO $ putStderr hErr
forkIO $ onBoot handler hIn
waitForProcess hProc
where
(exe:args) = commandLine serverOptions nrtOptions { commandFilePath = Nothing }
putStdout = pipeOutput (onPutString handler)
putStderr = pipeOutput (onPutString handler)