module Sound.SC3.Server.PlayEasy ( play, stop, reset, audition, withSC3, withSC3UDP, withSC3TCP, withSC3File, NodeId, noId, autoId, lastId, rootId, homeId, set, setMulti, setId, playIdCustomOut, playId, stopId, sync, d_recv', simpleSync, mceDegree, ) where import Sound.SC3.UGen.IO (out) import Sound.SC3.UGen.UGen (UGen(..)) import Sound.SC3.UGen.Graph (graph) import Sound.SC3.Server.Graphdef (graphdef) import Sound.SC3.Server.Command (AddAction(AddToTail), s_new, d_recv, g_new, g_freeAll, n_set, n_free) import Sound.OpenSoundControl (OSC) import Sound.OpenSoundControl.Transport.TCP (TCP) import Sound.OpenSoundControl.Transport.UDP (UDP) import Sound.OpenSoundControl.Transport.File (File) import Sound.OpenSoundControl.Transport.Monad (Transport, send, wait, withTransport) import qualified Sound.OpenSoundControl.Transport.TCP as TCP import qualified Sound.OpenSoundControl.Transport.UDP as UDP import qualified Sound.OpenSoundControl.Transport.File as File import qualified Sound.OpenSoundControl.Transport.Monad as Trans type NodeId = Int -- | Construct an instrument definition, send /d_recv and /s_new messages to scsynth. play :: Transport t => UGen -> Trans.IO t OSC play u = do send (d_recv' "Anonymous" (addOut u)) r <- wait "/done" send (s_new "Anonymous" autoId AddToTail homeId []) return r -- | Free all nodes at the group with node id 'homeId'. stop :: Transport t => Trans.IO t () stop = send (g_freeAll [homeId]) -- | Free all nodes and re-create group node with id 'homeId'. reset :: Transport t => Trans.IO t () reset = send (g_freeAll [rootId]) >> init_ -- | Bracket SC3 communication. withSC3 :: Trans.IO UDP a -> IO a withSC3 = withSC3UDP -- | Bracket SC3 communication via UDP. withSC3UDP :: Trans.IO UDP a -> IO a withSC3UDP = withTransport (UDP.openUDP "127.0.0.1" 57110) -- | Bracket SC3 communication via TCP. withSC3TCP :: Trans.IO TCP a -> IO a withSC3TCP = withTransport (TCP.openTCP "127.0.0.1" 57110) -- | Write SC3 communication to a command file. withSC3File :: FilePath -> Trans.IO File a -> IO a withSC3File fn = withTransport (File.open fn) -- | withSC3 . play audition :: UGen -> IO OSC audition = withSC3 . play d_recv' :: String -> UGen -> OSC d_recv' n = d_recv . graphdef n . graph {- * Lemming's extensions -} {- ** Special identifiers -} {-# DEPRECATED noId "use autoId instead" #-} noId :: NodeId noId = -1 -- for new: choose an arbitrary id autoId :: NodeId autoId = -1 -- for set: the last created node lastId :: NodeId lastId = -1 rootId :: NodeId rootId = 0 homeId :: NodeId homeId = 1 {- ** Functions for custom node identifiers -} sync :: Transport t => OSC -> Trans.IO t OSC sync o = send o >> wait "/done" -- sync o = send o >> recv simpleSync :: Transport t => OSC -> Trans.IO t () simpleSync o = sync o >> return () init_ :: Transport t => Trans.IO t () init_ = send (g_new [(homeId, AddToTail, rootId)]) playIdCustomOut :: Transport t => NodeId -> UGen -> Trans.IO t OSC playIdCustomOut sid u = do r <- sync (d_recv' "Anonymous" u) send (s_new "Anonymous" sid AddToTail homeId []) return r set :: Transport t => String -> Double -> Trans.IO t () set = setId lastId setMulti :: Transport t => [(String, Double)] -> Trans.IO t () setMulti = setMultiId lastId playId :: Transport t => NodeId -> UGen -> Trans.IO t OSC playId sid u = playIdCustomOut sid (addOut u) stopId :: Transport t => NodeId -> Trans.IO t () stopId sid = send (n_free [sid]) setId :: Transport t => NodeId -> String -> Double -> Trans.IO t () setId sid name value = send (n_set sid [(name, value)]) setMultiId :: Transport t => NodeId -> [(String, Double)] -> Trans.IO t () setMultiId sid attrs = send (n_set sid attrs) -- | If the UGen has output ports connect it to an 'out' UGen. addOut :: UGen -> UGen addOut u = if hasOutputs u then out (Constant 0) u else u -- | True if the 'UGen' has output ports (ie. is not a sink UGen). hasOutputs :: UGen -> Bool hasOutputs (UGen _ _ _ o _ _) = not (null o) hasOutputs (MCE l) = any hasOutputs l hasOutputs (MRG l) = any hasOutputs l hasOutputs (Proxy _ _) = True hasOutputs _ = False -- | Returns 1 for mono signals. mceDegree :: UGen -> Int mceDegree (UGen _ _ _ _ _ _) = 1 mceDegree (MCE l) = length l mceDegree _ = error "mceDegree: illegal ugen"