-- | Dynamic Spectrum Oscillators module CsoundExpr.Opcodes.Siggen.Dynamic (buzz, gbuzz, mpulse, vco, vco2, vco2init, vco2ft, vco2ift) where import CsoundExpr.Base.Types import CsoundExpr.Base.MultiOut import CsoundExpr.Base.SideEffect import CsoundExpr.Base.UserDefined -- | * opcode : buzz -- -- -- * syntax : -- -- > ares buzz xamp, xcps, knh, ifn [, iphs] -- -- -- * description : -- -- Output is a set of harmonically related sine partials. -- -- -- * url : buzz :: (X x0, X x1, K k0) => [Irate] -> x0 -> x1 -> k0 -> Irate -> Arate buzz i0init x1amp x2cps k3nh i4fn = opcode "buzz" args where args = [to x1amp, to x2cps, to k3nh, to i4fn] ++ map to i0init -- | * opcode : gbuzz -- -- -- * syntax : -- -- > ares gbuzz xamp, xcps, knh, klh, kmul, ifn [, iphs] -- -- -- * description : -- -- Output is a set of harmonically related cosine partials. -- -- -- * url : gbuzz :: (X x0, X x1, K k0, K k1, K k2) => [Irate] -> x0 -> x1 -> k0 -> k1 -> k2 -> Irate -> Arate gbuzz i0init x1amp x2cps k3nh k4lh k5mul i6fn = opcode "gbuzz" args where args = [to x1amp, to x2cps, to k3nh, to k4lh, to k5mul, to i6fn] ++ map to i0init -- | * opcode : mpulse -- -- -- * syntax : -- -- > ares mpulse kamp, kintvl [, ioffset] -- -- -- * description : -- -- Generates a set of impulses of amplitude kamp separated by -- kintvl seconds (or samples if kintvl is negative). The first -- impulse is generated after a delay of ioffset seconds. -- -- -- * url : mpulse :: (K k0, K k1) => [Irate] -> k0 -> k1 -> Arate mpulse i0init k1amp k2intvl = opcode "mpulse" args where args = [to k1amp, to k2intvl] ++ map to i0init -- | * opcode : vco -- -- -- * syntax : -- -- > ares vco xamp, xcps, iwave, kpw [, ifn] [, imaxd] [, ileak] [, inyx] -- > [, iphs] [, iskip] -- -- -- * description : -- -- Implementation of a band limited, analog modeled oscillator, -- based on integration of band limited impulses. vco can be used to -- simulate a variety of analog wave forms. -- -- -- * url : vco :: (X x0, X x1, K k0) => [Irate] -> x0 -> x1 -> Irate -> k0 -> Arate vco i0init x1amp x2cps i3wave k4pw = opcode "vco" args where args = [to x1amp, to x2cps, to i3wave, to k4pw] ++ map to i0init -- | * opcode : vco2 -- -- -- * syntax : -- -- > ares vco2 kamp, kcps [, imode] [, kpw] [, kphs] [, inyx] -- -- -- * description : -- -- vco2 is similar to vco. But the implementation uses -- pre-calculated tables of band-limited waveforms (see also GEN30) -- rather than integrating impulses. This opcode can be faster than -- vco (especially if a low control-rate is used) and also allows -- better sound quality. Additionally, there are more waveforms and -- oscillator phase can be modulated at k-rate. The disadvantage is -- increased memory usage. For more details about vco2 tables, see -- also vco2init and vco2ft. -- -- -- * url : vco2 :: (K k0, K k1, K k2) => [Irate] -> [k0] -> [Irate] -> k1 -> k2 -> Arate vco2 i0init k1init i2init k3amp k4cps = opcode "vco2" args where args = [to k3amp, to k4cps] ++ map to i0init ++ map to k1init ++ map to i2init -- | * opcode : vco2init -- -- -- * syntax : -- -- > ifn vco2init iwave [, ibasfn] [, ipmul] [, iminsiz] [, imaxsiz] [, isrcft] -- -- -- * description : -- -- vco2init calculates tables for use by vco2 opcode. Optionally, -- it is also possible to access these tables as standard Csound -- function tables. In this case, vco2ft can be used to find the -- correct table number for a given oscillator frequency. -- -- -- * url : vco2init :: [Irate] -> Irate -> Irate vco2init i0init i1wave = opcode "vco2init" args where args = [to i1wave] ++ map to i0init -- | * opcode : vco2ft -- -- -- * syntax : -- -- > kfn vco2ft kcps, iwave [, inyx] -- -- -- * description : -- -- vco2ft returns the function table number to be used for -- generating the specified waveform at a given frequency. This -- function table number can be used by any Csound opcode that -- generates a signal by reading function tables (like oscilikt). -- The tables must be calculated by vco2init before vco2ft is called -- and shared as Csound ftables (ibasfn). -- -- -- * url : vco2ft :: (K k0) => [Irate] -> k0 -> Irate -> Krate vco2ft i0init k1cps i2wave = opcode "vco2ft" args where args = [to k1cps, to i2wave] ++ map to i0init -- | * opcode : vco2ift -- -- -- * syntax : -- -- > ifn vco2ift icps, iwave [, inyx] -- -- -- * description : -- -- vco2ift is the same as vco2ft, but works at i-time. It is -- suitable for use with opcodes that expect an i-rate table number -- (for example, oscili). -- -- -- * url : vco2ift :: [Irate] -> Irate -> Irate -> Irate vco2ift i0init i1cps i2wave = opcode "vco2ift" args where args = [to i1cps, to i2wave] ++ map to i0init