Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Server input enumerations.
Synopsis
- data AddAction
- data B_Gen
- b_gen_bit :: B_Gen -> Int
- b_gen_flag :: [B_Gen] -> Int
- data ErrorScope
- data ErrorMode
- data PrintLevel
- data SoundFileFormat
- data SampleFormat
- soundFileFormatString :: SoundFileFormat -> String
- soundFileFormat_from_extension :: String -> Maybe SoundFileFormat
- soundFileFormat_from_extension_err :: String -> SoundFileFormat
- sampleFormatString :: SampleFormat -> String
Documentation
Enumeration of possible locations to add new nodes (s_new and g_new).
fromEnum AddToTail == 1
Instances
Enum AddAction Source # | |
Defined in Sound.Sc3.Server.Enum succ :: AddAction -> AddAction # pred :: AddAction -> AddAction # fromEnum :: AddAction -> Int # enumFrom :: AddAction -> [AddAction] # enumFromThen :: AddAction -> AddAction -> [AddAction] # enumFromTo :: AddAction -> AddAction -> [AddAction] # enumFromThenTo :: AddAction -> AddAction -> AddAction -> [AddAction] # | |
Show AddAction Source # | |
Eq AddAction Source # | |
Enumeration of flags for '/b_gen' command.
b_gen_bit :: B_Gen -> Int Source #
B_Gen
to bit number.
map b_gen_bit [minBound .. maxBound] == [0, 1, 2]
data ErrorScope Source #
Error posting scope.
Instances
Enum ErrorScope Source # | |
Defined in Sound.Sc3.Server.Enum succ :: ErrorScope -> ErrorScope # pred :: ErrorScope -> ErrorScope # toEnum :: Int -> ErrorScope # fromEnum :: ErrorScope -> Int # enumFrom :: ErrorScope -> [ErrorScope] # enumFromThen :: ErrorScope -> ErrorScope -> [ErrorScope] # enumFromTo :: ErrorScope -> ErrorScope -> [ErrorScope] # enumFromThenTo :: ErrorScope -> ErrorScope -> ErrorScope -> [ErrorScope] # | |
Show ErrorScope Source # | |
Defined in Sound.Sc3.Server.Enum showsPrec :: Int -> ErrorScope -> ShowS # show :: ErrorScope -> String # showList :: [ErrorScope] -> ShowS # | |
Eq ErrorScope Source # | |
Defined in Sound.Sc3.Server.Enum (==) :: ErrorScope -> ErrorScope -> Bool # (/=) :: ErrorScope -> ErrorScope -> Bool # |
Error posting mode.
Instances
Enum ErrorMode Source # | |
Defined in Sound.Sc3.Server.Enum succ :: ErrorMode -> ErrorMode # pred :: ErrorMode -> ErrorMode # fromEnum :: ErrorMode -> Int # enumFrom :: ErrorMode -> [ErrorMode] # enumFromThen :: ErrorMode -> ErrorMode -> [ErrorMode] # enumFromTo :: ErrorMode -> ErrorMode -> [ErrorMode] # enumFromThenTo :: ErrorMode -> ErrorMode -> ErrorMode -> [ErrorMode] # | |
Show ErrorMode Source # | |
Eq ErrorMode Source # | |
data PrintLevel Source #
Enumeration of Message printer types.
Instances
Enum PrintLevel Source # | |
Defined in Sound.Sc3.Server.Enum succ :: PrintLevel -> PrintLevel # pred :: PrintLevel -> PrintLevel # toEnum :: Int -> PrintLevel # fromEnum :: PrintLevel -> Int # enumFrom :: PrintLevel -> [PrintLevel] # enumFromThen :: PrintLevel -> PrintLevel -> [PrintLevel] # enumFromTo :: PrintLevel -> PrintLevel -> [PrintLevel] # enumFromThenTo :: PrintLevel -> PrintLevel -> PrintLevel -> [PrintLevel] # | |
Show PrintLevel Source # | |
Defined in Sound.Sc3.Server.Enum showsPrec :: Int -> PrintLevel -> ShowS # show :: PrintLevel -> String # showList :: [PrintLevel] -> ShowS # | |
Eq PrintLevel Source # | |
Defined in Sound.Sc3.Server.Enum (==) :: PrintLevel -> PrintLevel -> Bool # (/=) :: PrintLevel -> PrintLevel -> Bool # |
data SoundFileFormat Source #
Sound file format.
Instances
Enum SoundFileFormat Source # | |
Defined in Sound.Sc3.Server.Enum succ :: SoundFileFormat -> SoundFileFormat # pred :: SoundFileFormat -> SoundFileFormat # toEnum :: Int -> SoundFileFormat # fromEnum :: SoundFileFormat -> Int # enumFrom :: SoundFileFormat -> [SoundFileFormat] # enumFromThen :: SoundFileFormat -> SoundFileFormat -> [SoundFileFormat] # enumFromTo :: SoundFileFormat -> SoundFileFormat -> [SoundFileFormat] # enumFromThenTo :: SoundFileFormat -> SoundFileFormat -> SoundFileFormat -> [SoundFileFormat] # | |
Read SoundFileFormat Source # | |
Defined in Sound.Sc3.Server.Enum | |
Show SoundFileFormat Source # | |
Defined in Sound.Sc3.Server.Enum showsPrec :: Int -> SoundFileFormat -> ShowS # show :: SoundFileFormat -> String # showList :: [SoundFileFormat] -> ShowS # | |
Eq SoundFileFormat Source # | |
Defined in Sound.Sc3.Server.Enum (==) :: SoundFileFormat -> SoundFileFormat -> Bool # (/=) :: SoundFileFormat -> SoundFileFormat -> Bool # |
data SampleFormat Source #
Sample format.
Instances
Enum SampleFormat Source # | |
Defined in Sound.Sc3.Server.Enum succ :: SampleFormat -> SampleFormat # pred :: SampleFormat -> SampleFormat # toEnum :: Int -> SampleFormat # fromEnum :: SampleFormat -> Int # enumFrom :: SampleFormat -> [SampleFormat] # enumFromThen :: SampleFormat -> SampleFormat -> [SampleFormat] # enumFromTo :: SampleFormat -> SampleFormat -> [SampleFormat] # enumFromThenTo :: SampleFormat -> SampleFormat -> SampleFormat -> [SampleFormat] # | |
Read SampleFormat Source # | |
Defined in Sound.Sc3.Server.Enum readsPrec :: Int -> ReadS SampleFormat # readList :: ReadS [SampleFormat] # | |
Show SampleFormat Source # | |
Defined in Sound.Sc3.Server.Enum showsPrec :: Int -> SampleFormat -> ShowS # show :: SampleFormat -> String # showList :: [SampleFormat] -> ShowS # | |
Eq SampleFormat Source # | |
Defined in Sound.Sc3.Server.Enum (==) :: SampleFormat -> SampleFormat -> Bool # (/=) :: SampleFormat -> SampleFormat -> Bool # |
soundFileFormatString :: SoundFileFormat -> String Source #
Sample format to standard file extension name.
soundFileFormat_from_extension :: String -> Maybe SoundFileFormat Source #
Infer sample format from file extension name.
soundFileFormat_from_extension_err :: String -> SoundFileFormat Source #
Erroring variant.
sampleFormatString :: SampleFormat -> String Source #
SampleFormat
string as recognised by scsynth NRT mode.