hsc3-0.21: Haskell SuperCollider
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.Sc3.Server.Options

Description

scsynth server command-line options.

Synopsis

Documentation

type Sc3_Opt i = (Char, String, i) Source #

(short-option, long-option, default-value)

sc3_opt_value :: Sc3_Opt i -> i Source #

Get value from option.

sc3_host_name_def :: String Source #

Default host name string.

sc3_port_def :: Num i => i Source #

Default port number, either a u or a t option is required.

data Sc3_Protocol Source #

Protocol is either Udp or Tcp.

Constructors

Sc3_Udp 
Sc3_Tcp 

sc3_opt_port_def :: Num i => Sc3_Protocol -> Sc3_Opt i Source #

Default port option.

sc3_opt_def :: Num i => Sc3_Protocol -> [Sc3_Opt i] Source #

Sc3 default options.

sc3_opt_def_udp :: Num i => [Sc3_Opt i] Source #

SC3 default options for Udp.

sc3_opt_bool :: Sc3_Opt i -> Bool Source #

Is option boolean, ie. 0=False and 1=True.

>>> filter sc3_opt_bool sc3_opt_def_udp
[('D',"load-synthdefs?",1),('R',"publish-to-rendezvous?",1)]

sc3_opt_get :: [Sc3_Opt i] -> Either Char String -> Maybe i Source #

Lookup option given either short or long name.

sc3_opt_set :: [Sc3_Opt i] -> (Either Char String, i) -> [Sc3_Opt i] Source #

Set option given either short or long name.

>>> sc3_opt_get (sc3_opt_set sc3_opt_def_udp (Left 'w',256)) (Right "number-of-wire-buffers")
Just 256

sc3_opt_edit :: [Sc3_Opt i] -> [(Either Char String, i)] -> [Sc3_Opt i] Source #

Apply set of edits to options.

>>> unwords (sc3_opt_arg (sc3_opt_edit sc3_opt_def_udp [(Left 'w',256),(Left 'm',2 ^ 16)]))
"-u 57110 -a 1024 -b 1024 -c 16384 -D 1 -d 1024 -i 8 -l 64 -m 65536 -n 1024 -o 8 -r 64 -R 1 -S 0 -V 0 -w 256 -z 64 -Z 0"

sc3_opt_arg :: Show i => [Sc3_Opt i] -> [String] Source #

Generate scsynth argument list.

>>> unwords (sc3_opt_arg sc3_opt_def_udp)
"-u 57110 -a 1024 -b 1024 -c 16384 -D 1 -d 1024 -i 8 -l 64 -m 8192 -n 1024 -o 8 -r 64 -R 1 -S 0 -V 0 -w 64 -z 64 -Z 0"

sc3_opt_cmd :: Show i => [Sc3_Opt i] -> (FilePath, [String]) Source #

Generate arguments for callProcess or related functions.

>>> let o = sc3_opt_def_udp in sc3_opt_cmd o == ("scsynth", sc3_opt_arg o)
True