{-# LANGUAGE TemplateHaskell #-} module Sound.SC3.Server.Process.Options where import Data.Accessor (Accessor) import Sound.SC3.Server.Process.Accessor (deriveAccessors) -- | Used with the 'verbosity' field in 'ServerOptions'. data Verbosity = Silent | Quiet | Normal | Verbose | VeryVerbose | ExtremelyVerbose deriving (Enum, Eq, Read, Show) -- ==================================================================== -- * Server options -- | Specify general server options used both in realtime and non-realtime -- mode. data ServerOptions = ServerOptions { serverProgram :: FilePath -- ^ Path to the @scsynth@ program , numberOfControlBusChannels :: Int -- ^ Number of allocated control bus channels , numberOfAudioBusChannels :: Int -- ^ Number of allocated audio bus channels , numberOfInputBusChannels :: Int -- ^ Number of physical input channels , numberOfOutputBusChannels :: Int -- ^ Number of physical output channels , blockSize :: Int -- ^ Synthesis block size , numberOfSampleBuffers :: Int -- ^ Number of allocated sample buffers , maxNumberOfNodes :: Int -- ^ Maximum number of synthesis nodes , maxNumberOfSynthDefs :: Int -- ^ Maximum number of synth definitions , realtimeMemorySize :: Int -- ^ Realtime memory size in bytes , numberOfWireBuffers :: Int -- ^ Number of unit generator connection buffers , numberOfRandomSeeds :: Int -- ^ Number of random number generator seeds , loadSynthDefs :: Bool -- ^ If 'True', load synth definitions from /synthdefs/ directory on startup , verbosity :: Verbosity -- ^ 'Verbosity' level , ugenPluginPath :: Maybe [FilePath] -- ^ List of UGen plugin search paths , restrictedPath :: Maybe FilePath -- ^ Sandbox path to restrict OSC command filesystem access } deriving (Eq, Show) -- | Default server options. defaultServerOptions :: ServerOptions defaultServerOptions = ServerOptions { serverProgram = "scsynth" , numberOfControlBusChannels = 4096 , numberOfAudioBusChannels = 128 , numberOfInputBusChannels = 8 , numberOfOutputBusChannels = 8 , blockSize = 64 , numberOfSampleBuffers = 1024 , maxNumberOfNodes = 1024 , maxNumberOfSynthDefs = 1024 , realtimeMemorySize = 8192 , numberOfWireBuffers = 64 , numberOfRandomSeeds = 64 , loadSynthDefs = True , verbosity = Normal , ugenPluginPath = Nothing , restrictedPath = Nothing } $(deriveAccessors ''ServerOptions) {-# DEPRECATED realTimeMemorySize "Use `realtimeMemorySize' instead" #-} realTimeMemorySize :: ServerOptions -> Int realTimeMemorySize = realtimeMemorySize {-# DEPRECATED _realTimeMemorySize "Use `_realtimeMemorySize' instead" #-} _realTimeMemorySize :: Accessor ServerOptions Int _realTimeMemorySize = _realtimeMemorySize -- ==================================================================== -- * Realtime options -- | Realtime server options, parameterized by the OpenSoundControl -- 'Transport' to be used. data RTOptions = RTOptions { -- Network control udpPortNumber :: Int, -- ^ UDP port number (one of 'udpPortNumber' and 'tcpPortNumber' must be non-zero) tcpPortNumber :: Int, -- ^ TCP port number (one of 'udpPortNumber' and 'tcpPortNumber' must be non-zero) useZeroconf :: Bool, -- ^ If 'True', publish scsynth service through Zeroconf maxNumberOfLogins :: Int, -- ^ Max number of supported logins if 'sessionPassword' is set sessionPassword :: Maybe String, -- ^ Session password -- Audio device control hardwareDeviceName :: Maybe String, -- ^ Hardware device name (JACK client:server name on Linux) hardwareBufferSize :: Int, -- ^ Hardware buffer size (no effect with JACK) hardwareSampleRate :: Int, -- ^ Hardware buffer size (no effect with JACK) inputStreamsEnabled :: Maybe Int, -- ^ Enabled input streams (CoreAudio only) outputStreamsEnabled :: Maybe Int -- ^ Enabled output streams (CoreAudio only) } deriving (Eq, Show) -- | Default realtime server options. defaultRTOptions :: RTOptions defaultRTOptions = RTOptions { -- Network control udpPortNumber = 0, tcpPortNumber = 0, useZeroconf = False, maxNumberOfLogins = 16, sessionPassword = Nothing, -- Audio device control hardwareDeviceName = Nothing, hardwareBufferSize = 0, hardwareSampleRate = 0, inputStreamsEnabled = Nothing, outputStreamsEnabled = Nothing } $(deriveAccessors ''RTOptions) -- | Default realtime server options (UDP transport). defaultRTOptionsUDP :: RTOptions defaultRTOptionsUDP = defaultRTOptions { udpPortNumber = 57110 } -- | Default realtime server options (TCP transport). defaultRTOptionsTCP :: RTOptions defaultRTOptionsTCP = defaultRTOptions { tcpPortNumber = 57110 } -- ==================================================================== -- * Non-Realtime options -- | Non-realtime server options. data NRTOptions = NRTOptions { commandFilePath :: Maybe FilePath, -- ^ Path to OSC command file ('Nothing' for stdin) inputFilePath :: Maybe FilePath, -- ^ Path to input sound file ('Nothing' for no audio input) outputFilePath :: FilePath, -- ^ Path to output sound file outputSampleRate :: Int, -- ^ Output sound file sample rate outputHeaderFormat :: String, -- ^ Output sound file header format outputSampleFormat :: String -- ^ Output sound file sample format } deriving (Eq, Show) -- | Default non-realtime server options. defaultNRTOptions :: NRTOptions defaultNRTOptions = NRTOptions { commandFilePath = Nothing, inputFilePath = Nothing, outputFilePath = "output.wav", outputSampleRate = 44100, outputHeaderFormat = "wav", outputSampleFormat = "int16" } $(deriveAccessors ''NRTOptions)