module Sound.SC3.Server.Process.Options where
import Data.Accessor (Accessor)
import Sound.SC3.Server.Process.Accessor (deriveAccessors)
data Verbosity =
Silent
| Quiet
| Normal
| Verbose
| VeryVerbose
| ExtremelyVerbose
deriving (Enum, Eq, Read, Show)
data ServerOptions = ServerOptions {
serverProgram :: FilePath
, numberOfControlBusChannels :: Int
, numberOfAudioBusChannels :: Int
, numberOfInputBusChannels :: Int
, numberOfOutputBusChannels :: Int
, blockSize :: Int
, numberOfSampleBuffers :: Int
, maxNumberOfNodes :: Int
, maxNumberOfSynthDefs :: Int
, realtimeMemorySize :: Int
, numberOfWireBuffers :: Int
, numberOfRandomSeeds :: Int
, loadSynthDefs :: Bool
, verbosity :: Verbosity
, ugenPluginPath :: Maybe [FilePath]
, restrictedPath :: Maybe FilePath
} deriving (Eq, Show)
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)
realTimeMemorySize :: ServerOptions -> Int
realTimeMemorySize = realtimeMemorySize
_realTimeMemorySize :: Accessor ServerOptions Int
_realTimeMemorySize = _realtimeMemorySize
data RTOptions = RTOptions {
udpPortNumber :: Int,
tcpPortNumber :: Int,
useZeroconf :: Bool,
maxNumberOfLogins :: Int,
sessionPassword :: Maybe String,
hardwareDeviceName :: Maybe String,
hardwareBufferSize :: Int,
hardwareSampleRate :: Int,
inputStreamsEnabled :: Maybe Int,
outputStreamsEnabled :: Maybe Int
} deriving (Eq, Show)
defaultRTOptions :: RTOptions
defaultRTOptions = RTOptions {
udpPortNumber = 0,
tcpPortNumber = 0,
useZeroconf = False,
maxNumberOfLogins = 16,
sessionPassword = Nothing,
hardwareDeviceName = Nothing,
hardwareBufferSize = 0,
hardwareSampleRate = 0,
inputStreamsEnabled = Nothing,
outputStreamsEnabled = Nothing
}
$(deriveAccessors ''RTOptions)
defaultRTOptionsUDP :: RTOptions
defaultRTOptionsUDP = defaultRTOptions { udpPortNumber = 57110 }
defaultRTOptionsTCP :: RTOptions
defaultRTOptionsTCP = defaultRTOptions { tcpPortNumber = 57110 }
data NRTOptions = NRTOptions {
commandFilePath :: Maybe FilePath,
inputFilePath :: Maybe FilePath,
outputFilePath :: FilePath,
outputSampleRate :: Int,
outputHeaderFormat :: String,
outputSampleFormat :: String
} deriving (Eq, Show)
defaultNRTOptions :: NRTOptions
defaultNRTOptions = NRTOptions {
commandFilePath = Nothing,
inputFilePath = Nothing,
outputFilePath = "output.wav",
outputSampleRate = 44100,
outputHeaderFormat = "wav",
outputSampleFormat = "int16"
}
$(deriveAccessors ''NRTOptions)