-- | Header section module CsoundExpr.Base.Header ( -- * Types Header, SignalInit, -- * Setup variables gSr, gKr, gKsmps, gNchnls, g0dbfs, -- * midi instruments massign, pgmassign, -- * Setting instrument order instrOrder, -- * Header opcodes instr0, initA, initK, initI, seed, ctrlinit, ftgen, -- * Constants -- | (gSr = 44100, gKr = 4410, gKsmps = 10) headerMono, headerStereo ) where import CsoundExpr.Translator.Cs.CsTree (int, double, argIn, Rate(..)) import CsoundExpr.Translator.Types import CsoundExpr.Base.UserDefined import CsoundExpr.Base.Imperative((<=>)) import CsoundExpr.Base.Arithmetic gSr, gKr, gKsmps, gNchnls, g0dbfs :: Irate gSr = argIn SetupRate "sr" gKr = argIn SetupRate "kr" gKsmps = argIn SetupRate "ksmps" gNchnls = argIn SetupRate "nchnls" g0dbfs = argIn SetupRate "0dbfs" massign :: [Int] -- ^ ireset -> Int -- ^ ichnl -> SignalOut -- ^ midi instrument -> SignalInit massign = Massign pgmassign :: [Int] -- ^ ichn -> Int -- ^ ipgm -> SignalOut -- ^ midi instrument -> SignalInit pgmassign = Pgmassign -- | 'instrOrder' defines relative order of instruments in orchestra -- -- Instrument is a mapping from note-interface to 'SignalOut'. If two SignalOut's -- have equal expression-tree structure they are rendered to the same instrument. -- Value in list refers to expresion-tree structure of instrument. -- -- Example : -- -- > header = [ -- > instr0 [ -- > gSr <=> 44100, -- > gKr <=> 4410, -- > gKsmps <=> 10, -- > gNchnls <=> 1], -- > instrOrder [instr1 (0, 0), instr2 ""] -- > ] -- -- > instr1 :: (Irate, Irate) -> SignalOut -- > instr1 (amp, cps) = out $ oscilA [] amp cps -- -- > instr2 :: String -> SignalOut -- > instr2 file = out $ moA1 $ diskin2 [] file (num 1) -- instrOrder :: [SignalOut] -> SignalInit instrOrder = InstrOrder -- | header's initialization statements, like global variables initialization, seed, ctrlinit, fltk, etc. -- -- Example : -- -- > instr0 [ -- > gar "sig0" <=> initA 0, -- > gar "sig1" <=> initA 0, -- > gir "fn" <=> ftgen 0 16384 10 [1], -- > seed 0 -- > ] instr0 :: [SignalOut] -> SignalInit instr0 = Instr0 . outList init' :: X a => Irate -> a init' x = opcode "init" [to x] -- | Puts the value of the i-time expression into a a-rate variable. initA :: Irate -> Arate initA = init' -- | Puts the value of the i-time expression into a k-rate variable. initK :: Irate -> Krate initK = init' -- | Puts the value of the i-time expression into a i-rate variable. initI :: Irate -> Irate initI = init' -- | Sets the global seed value for all x-class noise generators, as well as other opcodes that use a random call, such as grain. -- -- > seed ival seed :: Irate -> SignalOut seed = outOpcode "seed" . return . to -- | Sets the initial values for a set of MIDI controllers. -- -- > ctrlinit ichnl, ictlno1, ival1 [, ictlno2] [, ival2] [, ictlno3] \ -- > [, ival3] [,...ival32] ctrlinit :: Irate -> [Irate] -> SignalOut ctrlinit ichnl ivals = outOpcode "ctrlinit" args where args = to ichnl : map to ivals -- | Generate a score function table from within the orchestra. -- -- > gir ftgen ifn, itime, isize, igen, iarga [, iargb ] [...] -- -- @ifn@ - is set to zero -- -- > ftgen itime isize igen [iargs] ftgen :: Irate -> Irate -> Irate -> [Irate] -> Irate ftgen itime isize igen inits = opcode "ftgen" args where args = [int 0, to itime, to isize, to igen] ++ map to inits headerMono :: Header headerMono = return $ instr0 [ gSr <=> 44100, gKr <=> 4410, gKsmps <=> 10, gNchnls <=> 1] headerStereo :: Header headerStereo = return $ instr0 [ gSr <=> 44100, gKr <=> 4410, gKsmps <=> 10, gNchnls <=> 1]