Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- renderOut :: Sigs a => SE a -> IO String
- renderOutBy :: Sigs a => Options -> SE a -> IO String
- renderEff :: (Sigs a, Sigs b) => (a -> SE b) -> IO String
- renderEffBy :: (Sigs a, Sigs b) => Options -> (a -> SE b) -> IO String
- renderOut_ :: SE () -> IO String
- renderOutBy_ :: Options -> SE () -> IO String
- data Options = Options {}
- defGain :: Options -> Double
- defSampleRate :: Options -> Int
- defBlockSize :: Options -> Int
- defTabFi :: Options -> TabFi
- defScaleUI :: Options -> (Double, Double)
- data TabFi = TabFi {}
- fineFi :: Int -> [(Int, Int)] -> [(String, Int)] -> TabFi
- coarseFi :: Int -> TabFi
- idWavs :: Int
- idMp3s :: Int
- idDoubles :: Int
- idSines :: Int
- idSines3 :: Int
- idSines2 :: Int
- idPartials :: Int
- idSines4 :: Int
- idBuzzes :: Int
- idConsts :: Int
- idLins :: Int
- idCubes :: Int
- idExps :: Int
- idSplines :: Int
- idStartEnds :: Int
- idPolys :: Int
- idChebs1 :: Int
- idChebs2 :: Int
- idBessels :: Int
- idWins :: Int
- idTabHarmonics :: Int
- idMixOnTab :: Int
- idMixTabs :: Int
- idNormTab :: Int
- idPolynomFuns :: Int
- idLinTab :: Int
- idRandDists :: Int
- idReadNumFile :: Int
- idReadNumTab :: Int
- idExpsBreakPoints :: Int
- idLinsBreakPoints :: Int
- idReadTrajectoryFile :: Int
- idMixSines1 :: Int
- idMixSines2 :: Int
- idRandHist :: Int
- idRandPairs :: Int
- idRandRanges :: Int
- idPvocex :: Int
- idTuning :: Int
- idMultichannel :: Int
- idPadsynth :: String
- idTanh :: String
- idExp :: String
- idSone :: String
- idFarey :: String
- idWave :: String
- data Jacko = Jacko {}
- type JackoConnect = (String, String)
- renderJacko :: Jacko -> String
- csdNeedTrace :: Options -> Bool
- module Csound.Dynamic.Types.Flags
- saveUserOptions :: Options -> IO ()
- getUserOptions :: IO (Maybe Options)
Documentation
Options
Csound options. The default values are
flags = def -- the only flag set by default is "no-displays" -- to supress the display of the tables sampleRate = 44100 blockSize = 64 gain = 0.5 tabFi = fineFi 13 [(idLins, 11), (idExps, 11), (idConsts, 9), (idSplines, 11), (idStartEnds, 12)] } scaleUI = (1, 1)
Options | |
|
defSampleRate :: Options -> Int Source #
defBlockSize :: Options -> Int Source #
Table fidelity
Table size fidelity (how many points in the table by default).
fineFi :: Int -> [(Int, Int)] -> [(String, Int)] -> TabFi Source #
Sets different table size for different GEN-routines.
fineFi n ps
where
n
is the default value for table size (size is an
power of 2) for all gen routines that are not listed in the next argumentps
.ps
is a list of pairs(genRoutineId, tableSizeDegreeOf2)
that sets the given table size for a given GEN-routine.
with this function we can set lower table sizes for tables that are usually used in the envelopes.
coarseFi :: Int -> TabFi Source #
Sets the same table size for all tables.
coarseFi n
where n
is a degree of 2. For example, n = 10
sets size to 1024 points for all tables by default.
Gen identifiers
Low level Csound integer identifiers for tables. These names can be used in the function fineFi
*** Integer identifiers
idPartials :: Int Source #
idStartEnds :: Int Source #
idTabHarmonics :: Int Source #
idMixOnTab :: Int Source #
idPolynomFuns :: Int Source #
idRandDists :: Int Source #
idReadNumFile :: Int Source #
idReadNumTab :: Int Source #
idMixSines1 :: Int Source #
idMixSines2 :: Int Source #
idRandHist :: Int Source #
idRandPairs :: Int Source #
idRandRanges :: Int Source #
idMultichannel :: Int Source #
String identifiers
idPadsynth :: String Source #
Jacko
Describes the Jacko header. All information that is going to be set in the global settings for Jacko opcodes. The jacko opcodes allows us to easily turn our app into Jack-client. We can also do it with command line flags. But the Jacko opcodes provide more options.
see the Csound docs for details: http://csound.github.io/docs/manual/JackoOpcodes.html
Jacko | |
|
type JackoConnect = (String, String) Source #
renderJacko :: Jacko -> String Source #
Debug trace
csdNeedTrace :: Options -> Bool Source #
module Csound.Dynamic.Types.Flags
saveUserOptions :: Options -> IO () Source #
Saves the user options in the current directory.
If it's saved in the User's home directory it becomes global options.