Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Basic types and functions.
This module re-exports everything.
WARNING (for Csound users): the maximum amplitude is 1.0. There is no way to alter it. Don't define your amplitudes with 9000 or 11000. But the good news are: all signals are clipped by 1 so that you can not damage your ears and your speakers by a little typo.
Synopsis
- module Csound.Types
- module Csound.Control
- module Csound.IO
- module Csound.Air
- module Csound.Tab
- module Csound.Tuning
- module Csound.Options
- module Csound.SigSpace
- module Data.Boolean
- module Data.Default
- module Data.Monoid
- class Functor f => Applicative (f :: Type -> Type) where
- class Applicative f => Alternative (f :: Type -> Type) where
- newtype Const a (b :: k) = Const {
- getConst :: a
- newtype ZipList a = ZipList {
- getZipList :: [a]
- newtype WrappedArrow (a :: Type -> Type -> Type) b c = WrapArrow {
- unwrapArrow :: a b c
- newtype WrappedMonad (m :: Type -> Type) a = WrapMonad {
- unwrapMonad :: m a
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- (<$) :: Functor f => a -> f b -> f a
- (<**>) :: Applicative f => f a -> f (a -> b) -> f b
- liftA :: Applicative f => (a -> b) -> f a -> f b
- liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
- optional :: Alternative f => f a -> f (Maybe a)
- asum :: (Foldable t, Alternative f) => t (f a) -> f a
- module Temporal.Media
- module Temporal.Class
- directory :: Str -> Str
- fold :: Sig -> Sig -> Sig
- puts :: Str -> Sig -> SE ()
- release :: Sig
- printf :: Str -> Sig -> [Sig] -> SE ()
- diff :: Sig -> Sig
- clear :: [Sig] -> SE ()
- times :: SE Sig
- linen :: Sig -> D -> D -> D -> Sig
- scale :: Sig -> Sig -> Sig -> Sig
- balance :: Sig -> Sig -> Sig
- link_beat_force :: D -> Sig -> SE ()
- link_beat_get :: D -> (Sig, Sig, Sig)
- link_beat_request :: D -> Sig -> SE ()
- link_create :: D
- ableton_link_enable :: D -> SE ()
- link_is_enabled :: D -> Sig
- link_metro :: D -> (Sig, Sig, Sig, Sig)
- link_peers :: D -> Sig
- link_tempo_get :: D -> Sig
- link_tempo_set :: D -> Sig -> SE ()
- flGroup :: Str -> D -> D -> D -> D -> SE ()
- flGroupEnd :: SE ()
- flPack :: D -> D -> D -> D -> D -> D -> D -> SE ()
- flPackEnd :: SE ()
- flPanel :: Str -> D -> D -> SE ()
- flPanelEnd :: SE ()
- flScroll :: D -> D -> SE ()
- flScrollEnd :: SE ()
- flTabs :: D -> D -> D -> D -> SE ()
- flTabsEnd :: SE ()
- flCount :: Str -> D -> D -> D -> D -> D -> D -> D -> D -> D -> D -> SE (Sig, D)
- flJoy :: Str -> D -> D -> D -> D -> D -> D -> D -> D -> D -> D -> D -> D -> SE (Sig, Sig, D, D)
- flKnob :: Str -> D -> D -> D -> D -> D -> D -> D -> D -> SE (Sig, D)
- flRoller :: Str -> D -> D -> D -> D -> D -> D -> D -> D -> D -> D -> SE (Sig, D)
- flSlider :: Str -> D -> D -> D -> D -> D -> D -> D -> D -> D -> SE (Sig, D)
- flText :: Str -> D -> D -> D -> D -> D -> D -> D -> D -> SE (Sig, D)
- flBox :: Str -> D -> D -> D -> D -> D -> D -> D -> SE D
- flButBank :: D -> D -> D -> D -> D -> D -> D -> D -> SE (Sig, D)
- flButton :: Str -> D -> D -> D -> D -> D -> D -> D -> D -> SE (Sig, D)
- flCloseButton :: Str -> D -> D -> D -> D -> SE D
- flExecButton :: Str -> D -> D -> D -> D -> SE D
- flGetsnap :: D -> SE D
- flHvsBox :: D -> D -> D -> D -> D -> D -> SE D
- flHvsBoxSetValue :: Sig -> Sig -> D -> SE ()
- flKeyIn :: SE Sig
- flLoadsnap :: Str -> SE ()
- flMouse :: Tuple a => SE a
- flPrintk :: D -> Sig -> D -> SE ()
- flPrintk2 :: Sig -> D -> SE ()
- flRun :: SE ()
- flSavesnap :: Str -> SE ()
- flSetsnap :: D -> SE (D, D)
- flSetSnapGroup :: D -> SE ()
- flSetVal :: Sig -> Sig -> D -> SE ()
- flSetVal_i :: D -> D -> SE ()
- flSlidBnk :: Str -> D -> SE ()
- flSlidBnk2 :: Str -> D -> D -> D -> SE ()
- flSlidBnk2Set :: D -> Tab -> SE ()
- flSlidBnk2Setk :: Sig -> D -> Tab -> SE ()
- flSlidBnkGetHandle :: SE D
- flSlidBnkSet :: D -> Tab -> SE ()
- flSlidBnkSetk :: Sig -> D -> Tab -> SE ()
- flUpdate :: SE ()
- flValue :: Str -> D -> D -> D -> D -> SE D
- flVkeybd :: Str -> D -> D -> D -> D -> SE ()
- flVslidBnk :: Str -> D -> SE ()
- flVslidBnk2 :: Str -> D -> D -> D -> SE ()
- flXyin :: D -> D -> D -> D -> D -> D -> D -> D -> SE (Sig, Sig, Sig)
- vphaseseg :: Sig -> D -> D -> [D] -> SE ()
- flColor :: D -> D -> D -> SE ()
- flColor2 :: D -> D -> D -> SE ()
- flHide :: D -> SE ()
- flLabel :: D -> D -> D -> D -> D -> D -> SE ()
- flSetAlign :: D -> D -> SE ()
- flSetBox :: D -> D -> SE ()
- flSetColor :: D -> D -> D -> D -> SE ()
- flSetColor2 :: D -> D -> D -> D -> SE ()
- flSetFont :: D -> D -> SE ()
- flSetPosition :: D -> D -> D -> SE ()
- flSetSize :: D -> D -> D -> SE ()
- flSetText :: Str -> D -> SE ()
- flSetTextColor :: D -> D -> D -> D -> SE ()
- flSetTextSize :: D -> D -> SE ()
- flSetTextType :: D -> D -> SE ()
- flShow :: D -> SE ()
- faustctl :: D -> Str -> Sig -> SE ()
- imagecreate :: D -> D -> SE D
- imagefree :: D -> SE ()
- imagegetpixel :: D -> Sig -> Sig -> (Sig, Sig, Sig)
- imageload :: Spec -> SE D
- imagesave :: D -> Spec -> SE ()
- imagesetpixel :: D -> Sig -> Sig -> Sig -> Sig -> Sig -> SE ()
- imagesize :: D -> (D, D)
- clockoff :: D -> SE ()
- clockon :: D -> SE ()
- compilecsd :: Str -> D
- compileorc :: Str -> D
- compilestr :: Str -> D
- evalstr :: Str -> Sig
- ihold :: SE ()
- turnoff :: SE ()
- turnon :: D -> SE ()
- event :: Str -> Sig -> Sig -> Sig -> [Sig] -> SE ()
- event_i :: Str -> D -> D -> D -> [D] -> SE ()
- mute :: D -> SE ()
- nstance :: D -> D -> D -> D
- readscore :: Str -> SE ()
- remove :: D -> SE ()
- schedkwhen :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE ()
- schedkwhennamed :: Sig -> Sig -> Sig -> Str -> Sig -> Sig -> SE ()
- schedule :: D -> D -> D -> SE ()
- schedwhen :: Sig -> Sig -> Sig -> Sig -> SE ()
- scoreline :: Str -> Sig -> SE ()
- scoreline_i :: Str -> SE ()
- active :: D -> Sig
- cpumeter :: Tuple a => D -> a
- cpuprc :: D -> D -> SE ()
- exitnow :: SE ()
- jacktransport :: D -> SE ()
- maxalloc :: D -> D -> SE ()
- prealloc :: D -> D -> SE ()
- changed :: [Sig] -> Sig
- changed2 :: Sig -> Sig
- checkbox :: Sig -> Sig
- control :: Sig -> Sig
- follow :: Sig -> D -> Sig
- follow2 :: Sig -> Sig -> Sig -> Sig
- getcfg :: D -> Str
- joystick :: Sig -> Tab -> Sig
- midifilestatus :: Sig
- miditempo :: Sig
- p5gconnect :: SE ()
- p5gdata :: Sig -> Sig
- pcount :: D
- peak :: Sig -> Sig
- pindex :: D -> D
- pitch :: Sig -> D -> D -> D -> D -> (Sig, Sig)
- pitchamdf :: Sig -> D -> D -> (Sig, Sig)
- plltrack :: Sig -> Sig -> (Sig, Sig)
- ptrack :: Sig -> D -> (Sig, Sig)
- readscratch :: D
- rewindscore :: SE ()
- rms :: Sig -> Sig
- sensekey :: Tuple a => a
- seqtime :: Sig -> Sig -> Sig -> Sig -> Tab -> Sig
- seqtime2 :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig
- setctrl :: D -> D -> D -> SE ()
- setscorepos :: D -> SE ()
- splitrig :: Sig -> Sig -> D -> Tab -> [Sig] -> SE ()
- tempest :: Sig -> D -> D -> D -> D -> D -> D -> D -> D -> Tab -> Sig
- tempo :: Sig -> D -> SE ()
- tempoval :: Sig
- timedseq :: Sig -> Tab -> [Sig] -> Sig
- trigger :: Sig -> Sig -> Sig -> Sig
- trigseq :: Sig -> Sig -> Sig -> Sig -> Tab -> [Sig] -> SE ()
- vactrol :: Sig -> Sig
- wiiconnect :: D
- wiidata :: Sig -> Sig
- wiirange :: D -> D -> D -> SE ()
- wiisend :: Sig -> Sig -> Sig
- writescratch :: D -> SE ()
- xyin :: D -> D -> D -> D -> D -> (Sig, Sig)
- pop :: Tuple a => a
- pop_f :: Spec
- push :: [Sig] -> SE ()
- push_f :: Spec -> SE ()
- stack :: D -> SE ()
- subinstr :: Tuple a => D -> [D] -> a
- subinstrinit :: D -> [D] -> SE ()
- date :: Tuple a => a
- dates :: Str
- readclock :: D -> D
- rtclock :: Sig
- timeinstk :: Sig
- timeinsts :: Sig
- timek :: SE Sig
- jackoAudioIn :: Str -> SE Sig
- jackoAudioInConnect :: Str -> Str -> SE ()
- jackoAudioOut :: Str -> Sig -> SE ()
- jackoAudioOutConnect :: Str -> Str -> SE ()
- jackoInit :: Str -> Str -> SE ()
- jackoMidiInConnect :: Str -> Str -> SE ()
- jackoMidiOut :: Str -> Sig -> Sig -> Sig -> SE ()
- jackoMidiOutConnect :: Str -> Str -> SE ()
- jackoNoteOut :: Str -> Sig -> Sig -> Sig -> SE ()
- jackoOn :: SE ()
- jackoTransport :: Sig -> SE ()
- vincr :: Sig -> Sig -> SE ()
- ampdb :: SigOrD a => a -> a
- ampdbfs :: SigOrD a => a -> a
- dbamp :: SigOrD a => a -> a
- dbfsamp :: SigOrD a => a -> a
- birnd :: SigOrD a => a -> SE a
- rnd :: SigOrD a => a -> SE a
- divz :: SigOrD a => a -> a -> a
- mac :: [Sig] -> Sig
- maca :: [Sig] -> Sig
- polynomial :: Sig -> [Sig] -> Sig
- pow :: Sig -> Sig -> Sig
- product' :: [Sig] -> Sig
- sum' :: [Sig] -> Sig
- taninv2 :: SigOrD a => a -> a -> a
- fareylen :: Tab -> Sig
- fareyleni :: Tab -> D
- modmatrix :: Tab -> Tab -> Tab -> D -> D -> D -> Sig -> SE ()
- pwd :: Str
- select :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- system_i :: D -> Str -> D
- system :: Sig -> Str -> Sig
- tableshuffle :: Sig -> SE ()
- tableshufflei :: D -> SE ()
- mixerClear :: SE ()
- mixerGetLevel :: D -> D -> SE Sig
- mixerReceive :: D -> D -> SE Sig
- mixerSend :: Sig -> D -> D -> D -> SE ()
- mixerSetLevel :: D -> D -> Sig -> SE ()
- mixerSetLevel_i :: D -> D -> D -> SE ()
- remoteport :: D -> SE ()
- sockrecv :: D -> D -> Sig
- sockrecvs :: D -> D -> (Sig, Sig)
- strecv :: Str -> D -> Sig
- socksend :: Sig -> Str -> D -> D -> SE ()
- socksends :: Sig -> Sig -> Str -> D -> D -> SE ()
- stsend :: Sig -> Str -> D -> SE ()
- oscRaw :: Tuple a => D -> a
- cent :: SigOrD a => a -> a
- cpsmidinn :: SigOrD a => a -> a
- cpsoct :: SigOrD a => a -> a
- cpspch :: SigOrD a => a -> a
- ftom :: D -> Sig
- mtof :: D -> Sig
- mton :: Sig -> Str
- ntom :: Str -> D
- octave :: SigOrD a => a -> a
- octcps :: SigOrD a => a -> a
- octmidinn :: SigOrD a => a -> a
- octpch :: SigOrD a => a -> a
- pchmidinn :: SigOrD a => a -> a
- pchoct :: SigOrD a => a -> a
- pchtom :: D -> Sig
- semitone :: SigOrD a => a -> a
- cps2pch :: D -> D -> D
- cpstun :: Sig -> Sig -> Tab -> Sig
- cpstuni :: D -> Tab -> D
- cpsxpch :: D -> D -> D -> D -> D
- dssiactivate :: D -> Sig -> SE ()
- dssiaudio :: Tuple a => D -> [Sig] -> a
- dssictls :: D -> D -> Sig -> Sig -> SE ()
- dssiinit :: D -> D -> SE D
- dssilist :: SE ()
- vstaudio :: D -> (Sig, Sig)
- vstaudiog :: D -> (Sig, Sig)
- vstbankload :: D -> D -> SE ()
- vstedit :: D -> SE ()
- vstinfo :: D -> SE ()
- vstinit :: D -> SE D
- vstmidiout :: D -> Sig -> Sig -> Sig -> Sig -> SE ()
- vstnote :: D -> Sig -> Sig -> Sig -> Sig -> SE ()
- vstparamset :: D -> Sig -> Sig -> SE ()
- vstparamget :: D -> Sig -> Sig
- vstprogset :: D -> Sig -> SE ()
- aftouch :: Sig
- chanctrl :: D -> D -> Sig
- ctrl14 :: D -> D -> D -> D -> D -> Sig
- ctrl21 :: D -> D -> D -> D -> D -> D -> Sig
- ctrlinit :: [D] -> SE ()
- initc14 :: D -> D -> D -> D -> SE ()
- initc21 :: D -> D -> D -> D -> D -> SE ()
- massign :: D -> D -> SE ()
- midic14 :: D -> D -> D -> D -> Sig
- midic21 :: D -> D -> D -> D -> D -> Sig
- midic7 :: D -> D -> D -> Sig
- midictrl :: D -> Sig
- notnum :: Msg -> D
- pchbend :: Msg -> Sig
- pgmassign :: D -> D -> SE ()
- polyaft :: D -> Sig
- veloc :: Msg -> D
- nrpn :: Sig -> Sig -> Sig -> SE ()
- outiat :: D -> D -> D -> D -> SE ()
- outic :: D -> D -> D -> D -> D -> SE ()
- outic14 :: D -> D -> D -> D -> D -> D -> SE ()
- outipat :: D -> D -> D -> D -> D -> SE ()
- outipb :: D -> D -> D -> D -> SE ()
- outipc :: D -> D -> D -> D -> SE ()
- outkat :: Sig -> Sig -> Sig -> Sig -> SE ()
- outkc :: Sig -> Sig -> Sig -> Sig -> Sig -> SE ()
- outkc14 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE ()
- outkpat :: Sig -> Sig -> Sig -> Sig -> Sig -> SE ()
- outkpb :: Sig -> Sig -> Sig -> Sig -> SE ()
- outkpc :: Sig -> Sig -> Sig -> Sig -> SE ()
- ampmidi :: Msg -> D -> D
- ampmidid :: D -> D -> Sig
- cpsmidi :: Msg -> D
- cpsmidib :: Msg -> Sig
- cpstmid :: Msg -> Tab -> D
- octmidi :: Msg -> D
- octmidib :: Msg -> Sig
- pchmidi :: Msg -> D
- pchmidib :: Msg -> Sig
- midiin :: (Sig, Sig, Sig, Sig)
- midiout :: Sig -> Sig -> Sig -> Sig -> SE ()
- midiout_i :: D -> D -> D -> D -> SE ()
- xtratim :: D -> SE ()
- midion :: Sig -> Sig -> Sig -> SE ()
- midion2 :: Sig -> Sig -> Sig -> Sig -> SE ()
- moscil :: Sig -> Sig -> Sig -> Sig -> Sig -> SE ()
- noteoff :: D -> D -> D -> SE ()
- noteon :: D -> D -> D -> SE ()
- noteondur :: D -> D -> D -> D -> SE ()
- noteondur2 :: D -> D -> D -> D -> SE ()
- midichannelaftertouch :: Sig -> SE ()
- midichn :: D
- midicontrolchange :: Sig -> Sig -> SE ()
- mididefault :: Sig -> Sig -> SE ()
- midinoteoff :: Sig -> Sig -> SE ()
- midinoteoncps :: Sig -> Sig -> SE ()
- midinoteonkey :: Sig -> Sig -> SE ()
- midinoteonoct :: Sig -> Sig -> SE ()
- midinoteonpch :: Sig -> Sig -> SE ()
- midipitchbend :: Sig -> SE ()
- midipolyaftertouch :: Sig -> Sig -> SE ()
- midiprogramchange :: Sig -> SE ()
- mclock :: D -> SE ()
- mrtmsg :: D -> SE ()
- insglobal :: D -> D -> SE ()
- insremot :: D -> D -> D -> SE ()
- midglobal :: D -> D -> SE ()
- midremot :: D -> D -> D -> SE ()
- serialBegin :: Str -> SE D
- serialEnd :: D -> SE ()
- serialFlush :: D -> SE ()
- serialPrint :: D -> SE ()
- serialRead :: D -> Sig
- serialWrite :: D -> D -> SE ()
- serialWrite_i :: D -> D -> SE ()
- ftgenonce :: D -> D -> D -> D -> D -> [D] -> SE Tab
- inleta :: Str -> Sig
- inletf :: Str -> Spec
- inletk :: Str -> Sig
- inletkid :: Str -> Str -> Sig
- inletv :: Str -> Sig
- outleta :: Str -> Sig -> SE ()
- outletf :: Str -> Spec -> SE ()
- outletk :: Str -> Sig -> SE ()
- outletkid :: Str -> Str -> Sig -> SE ()
- outletv :: Str -> Sig -> SE ()
- adsyn :: Sig -> Sig -> Sig -> Str -> Sig
- adsynt :: Sig -> Sig -> Tab -> Tab -> Tab -> D -> Sig
- adsynt2 :: Sig -> Sig -> Tab -> Tab -> Tab -> D -> Sig
- hsboscil :: Sig -> Sig -> Sig -> D -> Tab -> Tab -> Sig
- oscbnk :: Sig -> Sig -> Sig -> Sig -> D -> D -> Sig -> Sig -> Sig -> Sig -> D -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Tab -> Sig
- oscil :: Sig -> Sig -> Tab -> Sig
- oscil3 :: Sig -> Sig -> Tab -> Sig
- oscili :: Sig -> Sig -> Tab -> Sig
- oscilikt :: Sig -> Sig -> Tab -> Sig
- osciliktp :: Sig -> Tab -> Sig -> Sig
- oscilikts :: Sig -> Sig -> Tab -> Sig -> Sig -> Sig
- osciln :: Sig -> D -> Tab -> D -> Sig
- oscils :: D -> D -> D -> Sig
- poscil :: Sig -> Sig -> Tab -> Sig
- poscil3 :: Sig -> Sig -> Tab -> Sig
- vibr :: Sig -> Sig -> Tab -> Sig
- vibrato :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig
- buzz :: Sig -> Sig -> Sig -> Tab -> Sig
- gbuzz :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig
- mpulse :: Sig -> Sig -> Sig
- squinewave :: Tuple a => Sig -> Sig -> Sig -> a
- vco :: Sig -> Sig -> D -> Sig -> Sig
- vco2 :: Sig -> Sig -> Sig
- vco2ft :: Sig -> D -> Tab
- vco2ift :: D -> D -> Tab
- vco2init :: D -> SE Tab
- crossfm :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> (Sig, Sig)
- crossfmi :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> (Sig, Sig)
- crosspm :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> (Sig, Sig)
- crosspmi :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> (Sig, Sig)
- crossfmpm :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> (Sig, Sig)
- crossfmpmi :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> (Sig, Sig)
- fmb3 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- fmbell :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- fmmetal :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Tab -> Tab -> Sig
- fmpercfl :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- fmrhode :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Tab -> Tab -> Sig
- fmvoice :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- fmwurlie :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Tab -> Tab -> Sig
- foscil :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig
- foscili :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig
- diskgrain :: Str -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> Sig
- fof :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Tab -> Tab -> D -> Sig
- fog :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Tab -> Tab -> D -> Sig
- grain :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> D -> Sig
- grain2 :: Sig -> Sig -> Sig -> D -> Tab -> Tab -> Sig
- grain3 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Tab -> Tab -> Sig -> Sig -> Sig
- partikkelget :: Sig -> D -> Sig
- partikkelset :: Sig -> Sig -> D -> SE ()
- partikkelsync :: Tuple a => D -> a
- syncloop :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> D -> Sig
- vosim :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig
- hvs1 :: Sig -> D -> D -> D -> D -> D -> SE ()
- hvs2 :: Sig -> Sig -> D -> D -> D -> D -> D -> D -> SE ()
- hvs3 :: Sig -> Sig -> Sig -> D -> D -> D -> D -> D -> D -> D -> SE ()
- bpf :: Sig -> Sig -> Sig -> [Sig] -> Sig
- cosseg :: [D] -> Sig
- cossegb :: [D] -> Sig
- cossegr :: [D] -> D -> D -> Sig
- expcurve :: Sig -> Sig -> Sig
- expon :: D -> D -> D -> Sig
- expseg :: [D] -> Sig
- expsega :: [D] -> Sig
- expsegb :: [D] -> Sig
- expsegba :: D -> D -> D -> Sig
- expsegr :: [D] -> D -> D -> Sig
- gainslider :: Sig -> Sig
- linlin :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- linseg :: [D] -> Sig
- linsegb :: [D] -> Sig
- linsegr :: [D] -> D -> D -> Sig
- logcurve :: Sig -> Sig -> Sig
- loopsegp :: Sig -> [Sig] -> Sig
- looptseg :: Sig -> Sig -> [Sig] -> Sig
- lpsholdp :: Sig -> Sig -> [Sig] -> Sig
- transeg :: [D] -> Sig
- transegb :: [D] -> Sig
- transegr :: [D] -> D -> D -> D -> Sig
- xyscale :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- adsr :: D -> D -> D -> D -> Sig
- envlpx :: Sig -> D -> D -> D -> Tab -> D -> D -> Sig
- envlpxr :: Sig -> D -> D -> Tab -> D -> D -> Sig
- linenr :: Sig -> D -> D -> D -> Sig
- madsr :: D -> D -> D -> D -> Sig
- mxadsr :: D -> D -> D -> D -> Sig
- xadsr :: D -> D -> D -> D -> Sig
- bamboo :: Sig -> D -> Sig
- barmodel :: Sig -> Sig -> D -> D -> Sig -> D -> D -> D -> D -> Sig
- cabasa :: D -> D -> Sig
- chuap :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> D -> Sig -> (Sig, Sig, Sig)
- crunch :: D -> D -> Sig
- dripwater :: Sig -> D -> Sig
- gendy :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- gendyc :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- gendyx :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- gogobel :: Sig -> Sig -> D -> D -> D -> Sig -> Sig -> Tab -> Sig
- guiro :: Sig -> D -> Sig
- lorenz :: Sig -> Sig -> Sig -> Sig -> D -> D -> D -> D -> (Sig, Sig, Sig)
- mandel :: Sig -> Sig -> Sig -> Sig -> (Sig, Sig)
- mandol :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- marimba :: Sig -> Sig -> D -> D -> D -> Sig -> Sig -> Tab -> D -> Sig
- moog :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Sig
- planet :: Sig -> Sig -> Sig -> D -> D -> D -> D -> D -> D -> D -> (Sig, Sig, Sig)
- prepiano :: D -> D -> D -> D -> D -> D -> Sig -> Sig -> D -> D -> D -> D -> D -> D -> D -> (Sig, Sig)
- sandpaper :: D -> D -> Sig
- sekere :: D -> D -> Sig
- shaker :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- sleighbells :: Sig -> D -> Sig
- stix :: D -> D -> Sig
- tambourine :: Sig -> D -> Sig
- vibes :: Sig -> Sig -> D -> D -> D -> Sig -> Sig -> Tab -> D -> Sig
- voice :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Sig
- phasor :: Sig -> Sig
- phasorbnk :: Sig -> Sig -> D -> Sig
- sc_phasor :: Sig -> Sig -> Sig -> Sig -> Sig
- syncphasor :: Sig -> Sig -> (Sig, Sig)
- betarand :: SigOrD a => a -> a -> a -> SE a
- bexprnd :: SigOrD a => a -> SE a
- cauchy :: SigOrD a => a -> SE a
- cauchyi :: SigOrD a => a -> a -> a -> SE a
- dust2 :: Sig -> Sig -> SE Sig
- exprand :: SigOrD a => a -> SE a
- exprandi :: SigOrD a => a -> a -> a -> SE a
- fractalnoise :: Sig -> Sig -> SE Sig
- gauss :: Sig -> SE Sig
- gaussi :: SigOrD a => a -> a -> a -> SE a
- gausstrig :: Sig -> Sig -> Sig -> SE Sig
- getseed :: SE Sig
- jitter :: Sig -> Sig -> Sig -> SE Sig
- jitter2 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE Sig
- jspline :: Sig -> Sig -> Sig -> SE Sig
- linrand :: SigOrD a => a -> SE a
- noise :: Sig -> Sig -> SE Sig
- pcauchy :: SigOrD a => a -> SE a
- pinker :: SE Sig
- pinkish :: Sig -> SE Sig
- poisson :: SigOrD a => a -> SE a
- rand :: Sig -> SE Sig
- randh :: Sig -> Sig -> SE Sig
- randi :: Sig -> Sig -> SE Sig
- random :: SigOrD a => a -> a -> SE a
- randomh :: Sig -> Sig -> Sig -> SE Sig
- randomi :: Sig -> Sig -> Sig -> SE Sig
- rnd31 :: SigOrD a => a -> a -> SE a
- rspline :: Sig -> Sig -> Sig -> Sig -> SE Sig
- seed :: D -> SE ()
- trandom :: Sig -> Sig -> Sig -> SE Sig
- trirand :: SigOrD a => a -> SE a
- unirand :: SigOrD a => a -> SE a
- urandom :: SigOrD a => SE a
- weibull :: SigOrD a => a -> a -> SE a
- bbcutm :: Sig -> D -> D -> D -> D -> D -> Sig
- bbcuts :: Sig -> Sig -> D -> D -> D -> D -> D -> (Sig, Sig)
- flooper :: Tuple a => Sig -> Sig -> D -> D -> D -> Tab -> a
- flooper2 :: Tuple a => Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> a
- fluidAllOut :: (Sig, Sig)
- fluidCCi :: D -> D -> D -> D -> SE ()
- fluidCCk :: D -> D -> D -> Sig -> SE ()
- fluidControl :: D -> Sig -> Sig -> Sig -> Sig -> SE ()
- fluidEngine :: D
- fluidLoad :: D -> D -> Tab
- fluidNote :: D -> D -> D -> D -> SE ()
- fluidOut :: D -> (Sig, Sig)
- fluidProgramSelect :: D -> D -> Tab -> D -> D -> SE ()
- fluidSetInterpMethod :: D -> D -> D -> SE ()
- loscil :: Tuple a => Sig -> Sig -> Tab -> a
- loscil3 :: Tuple a => Sig -> Sig -> Tab -> a
- loscilx :: Tuple a => Sig -> Sig -> Tab -> a
- lphasor :: Sig -> Sig
- lposcil :: Sig -> Sig -> Sig -> Sig -> Tab -> Sig
- lposcil3 :: Sig -> Sig -> Sig -> Sig -> Tab -> Sig
- lposcila :: Sig -> Sig -> Sig -> Sig -> D -> Sig
- lposcilsa :: Sig -> Sig -> Sig -> Sig -> D -> (Sig, Sig)
- lposcilsa2 :: Sig -> Sig -> Sig -> Sig -> D -> (Sig, Sig)
- sfilist :: Sf -> SE ()
- sfinstr :: D -> D -> Sig -> Sig -> D -> Sf -> (Sig, Sig)
- sfinstr3 :: D -> D -> Sig -> Sig -> D -> Sf -> (Sig, Sig)
- sfinstr3m :: D -> D -> Sig -> Sig -> D -> Sf -> Sig
- sfinstrm :: D -> D -> Sig -> Sig -> D -> Sf -> Sig
- sfload :: Str -> D
- sflooper :: D -> D -> Sig -> Sig -> Sf -> Sig -> Sig -> Sig -> (Sig, Sig)
- sfpassign :: D -> Sf -> SE ()
- sfplay :: D -> D -> Sig -> Sig -> Sf -> (Sig, Sig)
- sfplay3 :: D -> D -> Sig -> Sig -> Sf -> (Sig, Sig)
- sfplay3m :: D -> D -> Sig -> Sig -> Sf -> Sig
- sfplaym :: D -> D -> Sig -> Sig -> Sf -> Sig
- sfplist :: Sf -> SE ()
- sfpreset :: D -> D -> Sf -> Sf -> D
- sndloop :: Sig -> Sig -> Sig -> D -> D -> (Sig, Sig)
- waveset :: Sig -> Sig -> Sig
- scanhammer :: D -> D -> D -> D -> SE ()
- scans :: Sig -> Sig -> Tab -> D -> Sig
- scantable :: Sig -> Sig -> D -> D -> D -> D -> D -> Sig
- scanu :: D -> D -> Tab -> Tab -> Tab -> Tab -> Tab -> Sig -> Sig -> Sig -> Sig -> D -> D -> Sig -> Sig -> Sig -> D -> D -> SE ()
- xscanmap :: D -> Sig -> Sig -> (Sig, Sig)
- xscans :: Sig -> Sig -> Tab -> D -> Sig
- xscansmap :: Sig -> Sig -> D -> Sig -> Sig -> SE ()
- xscanu :: D -> D -> Tab -> Tab -> Tab -> Tab -> Tab -> Sig -> Sig -> Sig -> Sig -> D -> D -> Sig -> Sig -> Sig -> D -> D -> SE ()
- stkBandedWG :: D -> D -> Sig
- stkBeeThree :: D -> D -> Sig
- stkBlowBotl :: D -> D -> Sig
- stkBlowHole :: D -> D -> Sig
- stkBowed :: D -> D -> Sig
- stkBrass :: D -> D -> Sig
- stkClarinet :: D -> D -> Sig
- stkDrummer :: D -> D -> Sig
- stkFMVoices :: D -> D -> Sig
- stkFlute :: D -> D -> Sig
- stkHevyMetl :: D -> D -> Sig
- stkMandolin :: D -> D -> Sig
- stkModalBar :: D -> D -> Sig
- stkMoog :: D -> D -> Sig
- stkPercFlut :: D -> D -> Sig
- stkPlucked :: D -> D -> Sig
- stkResonate :: D -> D -> Sig
- stkRhodey :: D -> D -> Sig
- stkSaxofony :: D -> D -> Sig
- stkShakers :: D -> D -> Sig
- stkSimple :: D -> D -> Sig
- stkSitar :: D -> D -> Sig
- stkStifKarp :: D -> D -> Sig
- stkTubeBell :: D -> D -> Sig
- stkVoicForm :: D -> D -> Sig
- stkWhistle :: D -> D -> Sig
- stkWurley :: D -> D -> Sig
- oscil1 :: D -> Sig -> D -> Sig
- oscil1i :: D -> Sig -> D -> Sig
- ptable :: Sig -> Tab -> Sig
- ptable3 :: Sig -> Tab -> Sig
- ptablei :: Sig -> Tab -> Sig
- tab_i :: D -> Tab -> D
- tab :: Sig -> Tab -> Sig
- tabw_i :: D -> D -> Tab -> SE ()
- tabw :: Sig -> Sig -> Tab -> SE ()
- table :: SigOrD a => a -> Tab -> a
- table3 :: SigOrD a => a -> Tab -> a
- tablei :: SigOrD a => a -> Tab -> a
- wterrain :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> Sig
- pluck :: Sig -> Sig -> D -> Tab -> D -> Sig
- repluck :: D -> Sig -> D -> Sig -> Sig -> Sig -> Sig
- streson :: Sig -> Sig -> Sig -> Sig
- wgbow :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- wgbowedbar :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- wgbrass :: Sig -> Sig -> Sig -> D -> Sig -> Sig -> Sig
- wgclar :: Sig -> Sig -> Sig -> D -> D -> Sig -> Sig -> Sig -> Sig
- wgflute :: Sig -> Sig -> Sig -> D -> D -> Sig -> Sig -> Sig -> Sig
- wgpluck :: D -> D -> Sig -> D -> D -> D -> Sig -> Sig
- wgpluck2 :: D -> Sig -> D -> Sig -> Sig -> Sig
- dumpk :: Sig -> Str -> D -> D -> SE ()
- dumpk2 :: Sig -> Sig -> Str -> D -> D -> SE ()
- dumpk3 :: Sig -> Sig -> Sig -> Str -> D -> D -> SE ()
- dumpk4 :: Sig -> Sig -> Sig -> Sig -> Str -> D -> D -> SE ()
- ficlose :: D -> SE ()
- fin :: Str -> D -> D -> [Sig] -> SE ()
- fini :: Str -> D -> D -> [D] -> SE ()
- fink :: Str -> D -> D -> [Sig] -> SE ()
- fiopen :: Str -> D -> SE D
- fout :: Str -> D -> [Sig] -> SE ()
- fouti :: Str -> D -> D -> [D] -> SE ()
- foutir :: Str -> D -> D -> [D] -> SE ()
- foutk :: Str -> D -> [Sig] -> SE ()
- fprintks :: Str -> Str -> [Sig] -> SE ()
- fprints :: Str -> Str -> [D] -> SE ()
- hdf5read :: Tuple a => Str -> D -> a
- hdf5write :: Str -> Sig -> SE ()
- readf :: Str -> (Str, Sig)
- readfi :: Str -> (Str, D)
- readk :: Str -> D -> D -> Sig
- readk2 :: Str -> D -> D -> (Sig, Sig)
- readk3 :: Str -> D -> D -> (Sig, Sig, Sig)
- readk4 :: Str -> D -> D -> (Sig, Sig, Sig, Sig)
- diskin :: Tuple a => Str -> a
- diskin2 :: Tuple a => Str -> a
- in' :: Sig
- in32 :: Tuple a => a
- inch :: Tuple a => [Sig] -> a
- inh :: Tuple a => a
- ino :: Tuple a => a
- inq :: (Sig, Sig, Sig, Sig)
- inrg :: Sig -> [Sig] -> SE ()
- ins :: (Sig, Sig)
- invalue :: Str -> Str
- inx :: Tuple a => a
- inz :: Sig -> SE ()
- mp3in :: Str -> (Sig, Sig)
- soundin :: Tuple a => Str -> a
- mdelay :: Sig -> Sig -> Sig -> Sig -> Sig -> SE ()
- monitor :: Tuple a => a
- out :: Sig -> SE ()
- out32 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE ()
- outc :: [Sig] -> SE ()
- outch :: Sig -> [Sig] -> SE ()
- outh :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE ()
- outo :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE ()
- outq :: Sig -> Sig -> Sig -> Sig -> SE ()
- outq1 :: Sig -> SE ()
- outq2 :: Sig -> SE ()
- outq3 :: Sig -> SE ()
- outq4 :: Sig -> SE ()
- outrg :: Sig -> [Sig] -> SE ()
- outs :: Sig -> Sig -> SE ()
- outs1 :: Sig -> SE ()
- outs2 :: Sig -> SE ()
- outvalue :: Str -> D -> SE ()
- outx :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE ()
- outz :: Sig -> SE ()
- soundout :: Sig -> Str -> SE ()
- soundouts :: Sig -> Sig -> Str -> SE ()
- chani :: Sig -> SE Sig
- chano :: Sig -> Sig -> SE ()
- chn_k :: Str -> D -> SE ()
- chn_a :: Str -> D -> SE ()
- chn_S :: Str -> D -> SE ()
- chnclear :: Str -> SE ()
- chnexport :: Str -> D -> Str
- chnget :: Str -> SE Str
- chngetks :: Str -> Str
- chnmix :: Sig -> Str -> SE ()
- chnparams :: Tuple a => Str -> a
- chnset :: D -> Str -> SE ()
- chnsetks :: Str -> Str -> SE ()
- setksmps :: D -> SE ()
- xin :: Tuple a => a
- xout :: [Sig] -> SE ()
- dispfft :: Sig -> D -> D -> SE ()
- flashtxt :: D -> Str -> SE ()
- print' :: [D] -> SE ()
- printf_i :: Str -> D -> [D] -> SE ()
- printk :: D -> Sig -> SE ()
- printk2 :: Sig -> SE ()
- printks :: Str -> D -> [Sig] -> SE ()
- printks2 :: Str -> Sig -> SE ()
- prints :: Str -> [Sig] -> SE ()
- filebit :: Str -> D
- filelen :: Str -> D
- filenchnls :: Str -> D
- filepeak :: Str -> D
- filesr :: Str -> D
- filevalid :: Str -> D
- mp3len :: Str -> D
- clip :: Sig -> D -> D -> Sig
- compress :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Sig
- compress2 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Sig
- dam :: Sig -> Sig -> D -> D -> D -> D -> Sig
- gain :: Sig -> Sig -> Sig
- convolve :: Tuple a => Sig -> Str -> a
- cross2 :: Sig -> Sig -> D -> D -> D -> Sig -> Sig
- dconv :: Sig -> D -> Tab -> Sig
- ftconv :: Tuple a => Sig -> D -> D -> a
- ftmorf :: Sig -> Tab -> Tab -> SE ()
- liveconv :: Sig -> D -> D -> Sig -> Sig -> Sig
- pconvolve :: Tuple a => Sig -> Str -> a
- tvconv :: Sig -> Sig -> Sig -> Sig -> D -> D -> Sig
- delay1 :: Sig -> Sig
- delayk :: Sig -> D -> Sig
- vdel_k :: Sig -> Sig -> D -> Sig
- delayr :: D -> SE Sig
- delayw :: Sig -> SE ()
- deltap :: Sig -> SE Sig
- deltap3 :: Sig -> SE Sig
- deltapi :: Sig -> SE Sig
- deltapn :: Sig -> Sig
- deltapx :: Sig -> D -> SE Sig
- deltapxw :: Sig -> Sig -> D -> SE ()
- multitap :: Sig -> [D] -> Sig
- vdelay :: Sig -> Sig -> D -> Sig
- vdelay3 :: Sig -> Sig -> D -> Sig
- vdelayx :: Sig -> Sig -> D -> D -> Sig
- vdelayxq :: Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> (Sig, Sig, Sig, Sig)
- vdelayxs :: Sig -> Sig -> Sig -> D -> D -> (Sig, Sig)
- vdelayxw :: Sig -> Sig -> D -> D -> Sig
- vdelayxwq :: Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> (Sig, Sig, Sig, Sig)
- vdelayxws :: Sig -> Sig -> Sig -> D -> D -> (Sig, Sig)
- bformdec :: Tuple a => D -> Sig -> Sig -> Sig -> Sig -> a
- bformdec1 :: Tuple a => D -> Sig -> Sig -> Sig -> Sig -> a
- bformenc :: Tuple a => Sig -> Sig -> Sig -> Sig -> Sig -> a
- bformenc1 :: Tuple a => Sig -> Sig -> Sig -> a
- hrtfearly :: Tuple a => Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> D -> a
- hrtfmove :: Sig -> Sig -> Sig -> D -> D -> (Sig, Sig)
- hrtfmove2 :: Sig -> Sig -> Sig -> D -> D -> (Sig, Sig)
- hrtfreverb :: Sig -> D -> D -> D -> D -> (Sig, Sig, D)
- hrtfstat :: Sig -> D -> D -> D -> D -> (Sig, Sig)
- locsend :: (Sig, Sig, Sig, Sig)
- locsig :: Sig -> Sig -> Sig -> Sig -> (Sig, Sig, Sig, Sig)
- pan :: Sig -> Sig -> Sig -> Tab -> (Sig, Sig, Sig, Sig)
- pan2 :: Sig -> Sig -> (Sig, Sig)
- spat3d :: Sig -> Sig -> Sig -> Sig -> D -> D -> D -> D -> D -> (Sig, Sig, Sig, Sig)
- spat3di :: Sig -> D -> D -> D -> D -> D -> D -> (Sig, Sig, Sig, Sig)
- spat3dt :: D -> D -> D -> D -> D -> D -> D -> D -> SE ()
- spdist :: Tab -> Sig -> Sig -> Sig -> Sig
- spsend :: (Sig, Sig, Sig, Sig)
- vbap :: Tuple a => Sig -> Sig -> a
- vbap16 :: Tuple a => Sig -> Sig -> a
- vbap16move :: Tuple a => Sig -> D -> D -> D -> [D] -> a
- vbap4 :: Sig -> Sig -> (Sig, Sig, Sig, Sig)
- vbap4move :: Tuple a => Sig -> D -> D -> D -> [D] -> a
- vbap8 :: Tuple a => Sig -> Sig -> a
- vbap8move :: Tuple a => Sig -> D -> D -> D -> [D] -> a
- vbapg :: Tuple a => Sig -> a
- vbapgmove :: Tuple a => D -> D -> D -> D -> a
- vbaplsinit :: D -> D -> SE ()
- vbapmove :: Tuple a => Sig -> D -> D -> D -> [D] -> a
- vbapz :: D -> D -> Sig -> Sig -> SE ()
- vbapzmove :: Sig -> D -> D -> D -> [D] -> SE ()
- alpass :: Sig -> Sig -> D -> Sig
- babo :: Sig -> Sig -> Sig -> Sig -> D -> D -> D -> (Sig, Sig)
- comb :: Sig -> Sig -> D -> Sig
- combinv :: Sig -> Sig -> D -> Sig
- freeverb :: Sig -> Sig -> Sig -> Sig -> (Sig, Sig)
- nestedap :: Sig -> D -> D -> D -> D -> Sig
- nreverb :: Sig -> Sig -> Sig -> Sig
- platerev :: Tuple a => D -> D -> Sig -> D -> D -> D -> D -> [Sig] -> a
- reverb :: Sig -> Sig -> Sig
- reverb2 :: Sig -> Sig -> Sig -> Sig
- reverbsc :: Sig -> Sig -> Sig -> Sig -> (Sig, Sig)
- valpass :: Sig -> Sig -> Sig -> D -> Sig
- vcomb :: Sig -> Sig -> Sig -> D -> Sig
- denorm :: [Sig] -> SE ()
- downsamp :: Sig -> Sig
- integ :: Sig -> Sig
- interp :: Sig -> Sig
- ntrpol :: Sig -> Sig -> Sig -> Sig
- samphold :: Sig -> Sig -> Sig
- upsamp :: Sig -> Sig
- vaget :: Sig -> Sig -> Sig
- vaset :: Sig -> Sig -> Sig -> SE ()
- limit :: Sig -> Sig -> Sig -> Sig
- mirror :: Sig -> Sig -> Sig -> Sig
- wrap :: Sig -> Sig -> Sig -> Sig
- distort :: Sig -> Sig -> Tab -> Sig
- distort1 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- flanger :: Sig -> Sig -> Sig -> Sig
- harmon :: Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> D -> Sig
- harmon2 :: Sig -> Sig -> Sig -> Sig -> D -> D -> Sig
- harmon3 :: Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> Sig
- harmon4 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> Sig
- phaser1 :: Sig -> Sig -> Sig -> Sig -> Sig
- phaser2 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- atone :: Sig -> Sig -> Sig
- atonex :: Sig -> Sig -> Sig
- biquad :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- biquada :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- butbp :: Sig -> Sig -> Sig -> Sig
- butbr :: Sig -> Sig -> Sig -> Sig
- buthp :: Sig -> Sig -> Sig
- butlp :: Sig -> Sig -> Sig
- butterbp :: Sig -> Sig -> Sig -> Sig
- butterbr :: Sig -> Sig -> Sig -> Sig
- butterhp :: Sig -> Sig -> Sig
- butterlp :: Sig -> Sig -> Sig
- clfilt :: Sig -> Sig -> D -> D -> Sig
- diode_ladder :: Sig -> Sig -> Sig -> Sig
- doppler :: Sig -> Sig -> Sig -> Sig
- k35_hpf :: Sig -> Sig -> Sig -> Sig
- k35_lpf :: Sig -> Sig -> Sig -> Sig
- median :: Sig -> Sig -> D -> Sig
- mediank :: Sig -> Sig -> D -> Sig
- mode :: Sig -> Sig -> Sig -> Sig
- tone :: Sig -> Sig -> Sig
- tonex :: Sig -> Sig -> Sig
- zdf_1pole :: Sig -> Sig -> Sig
- zdf_1pole_mode :: Sig -> Sig -> (Sig, Sig)
- zdf_2pole :: Sig -> Sig -> Sig -> Sig
- zdf_2pole_mode :: Sig -> Sig -> Sig -> (Sig, Sig, Sig)
- zdf_ladder :: Sig -> Sig -> Sig -> Sig
- areson :: Sig -> Sig -> Sig -> Sig
- bqrez :: Sig -> Sig -> Sig -> Sig
- lowpass2 :: Sig -> Sig -> Sig -> Sig
- lowres :: Sig -> Sig -> Sig -> Sig
- lowresx :: Sig -> Sig -> Sig -> Sig
- lpf18 :: Sig -> Sig -> Sig -> Sig -> Sig
- moogladder :: Sig -> Sig -> Sig -> Sig
- moogladder2 :: Sig -> Sig -> Sig -> Sig
- moogvcf :: Sig -> Sig -> Sig -> Sig
- moogvcf2 :: Sig -> Sig -> Sig -> Sig
- mvchpf :: Sig -> Sig -> Sig
- mvclpf1 :: Sig -> Sig -> Sig -> Sig
- mvclpf2 :: Sig -> Sig -> Sig -> Sig
- mvclpf3 :: Sig -> Sig -> Sig -> Sig
- mvclpf4 :: Sig -> Sig -> Sig -> (Sig, Sig, Sig, Sig)
- reson :: Sig -> Sig -> Sig -> Sig
- resonr :: Sig -> Sig -> Sig -> Sig
- resonx :: Sig -> Sig -> Sig -> Sig
- resony :: Sig -> Sig -> Sig -> D -> Sig -> Sig
- resonz :: Sig -> Sig -> Sig -> Sig
- rezzy :: Sig -> Sig -> Sig -> Sig
- statevar :: Sig -> Sig -> Sig -> (Sig, Sig, Sig, Sig)
- svfilter :: Sig -> Sig -> Sig -> (Sig, Sig, Sig)
- tbvcf :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- vlowres :: Sig -> Sig -> Sig -> D -> Sig -> Sig
- aresonk :: Sig -> Sig -> Sig -> Sig
- atonek :: Sig -> Sig -> Sig
- lineto :: Sig -> Sig -> Sig
- port :: Sig -> D -> Sig
- portk :: Sig -> Sig -> Sig
- resonk :: Sig -> Sig -> Sig -> Sig
- resonxk :: Sig -> Sig -> Sig -> Sig
- sc_lag :: Sig -> Sig -> Sig
- sc_lagud :: Sig -> Sig -> Sig -> Sig
- sc_trig :: Sig -> Sig -> Sig
- tlineto :: Sig -> Sig -> Sig -> Sig
- tonek :: Sig -> Sig -> Sig
- dcblock :: Sig -> Sig
- dcblock2 :: Sig -> Sig
- eqfil :: Sig -> Sig -> Sig -> Sig -> Sig
- filter2 :: Sig -> D -> D -> [D] -> Sig
- fmanal :: Sig -> Sig -> (Sig, Sig)
- fofilter :: Sig -> Sig -> Sig -> Sig -> Sig
- hilbert :: Sig -> (Sig, Sig)
- hilbert2 :: Sig -> D -> D -> (Sig, Sig)
- nlfilt :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- nlfilt2 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- pareq :: Sig -> Sig -> Sig -> Sig -> Sig
- rbjeq :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- zfilter2 :: Sig -> Sig -> Sig -> D -> D -> [D] -> Sig
- wguide1 :: Sig -> Sig -> Sig -> Sig -> Sig
- wguide2 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- chebyshevpoly :: Sig -> [Sig] -> Sig
- pdclip :: Sig -> Sig -> Sig -> Sig
- pdhalf :: Sig -> Sig -> Sig
- pdhalfy :: Sig -> Sig -> Sig
- powershape :: Sig -> Sig -> Sig
- cmp :: Sig -> Str -> Sig -> Sig
- max' :: [Sig] -> Sig
- max_k :: Sig -> Sig -> D -> Sig
- maxabs :: [Sig] -> Sig
- maxabsaccum :: Sig -> Sig -> SE ()
- maxaccum :: Sig -> Sig -> SE ()
- min' :: [Sig] -> Sig
- minabs :: [Sig] -> Sig
- minabsaccum :: Sig -> Sig -> SE ()
- minaccum :: Sig -> Sig -> SE ()
- ktableseg :: Tab -> D -> Tab -> SE ()
- pvadd :: Sig -> Sig -> Str -> Tab -> D -> Sig
- pvbufread :: Sig -> Str -> SE ()
- pvcross :: Sig -> Sig -> Str -> Sig -> Sig -> Sig
- pvinterp :: Sig -> Sig -> Str -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig
- pvoc :: Sig -> Sig -> Str -> Sig
- pvread :: Sig -> Str -> D -> (Sig, Sig)
- tableseg :: Tab -> D -> Tab -> SE ()
- tablexseg :: Tab -> D -> Tab -> SE ()
- vpvoc :: Sig -> Sig -> Str -> Sig
- lpfreson :: Sig -> Sig -> Sig
- lpinterp :: D -> D -> Sig -> SE ()
- lpread :: Sig -> Str -> (Sig, Sig, Sig, Sig)
- lpreson :: Sig -> Sig
- lpslot :: D -> SE ()
- specaddm :: Wspec -> Wspec -> Wspec
- specdiff :: Wspec -> Wspec
- specdisp :: Wspec -> D -> SE ()
- specfilt :: Wspec -> D -> Wspec
- spechist :: Wspec -> Wspec
- specptrk :: Wspec -> Sig -> D -> D -> D -> D -> D -> D -> (Sig, Sig)
- specscal :: Wspec -> D -> D -> Wspec
- specsum :: Wspec -> Sig
- spectrum :: Sig -> D -> D -> D -> Wspec
- binit :: Spec -> D -> Spec
- cudanal :: Sig -> D -> D -> D -> D -> Spec
- cudasliding :: Sig -> Sig -> D -> Sig
- cudasynth :: Sig -> Sig -> Tab -> D -> D -> Sig
- partials :: Spec -> Spec -> Sig -> Sig -> Sig -> D -> Spec
- pvsadsyn :: Spec -> D -> Sig -> Sig
- pvsanal :: Sig -> D -> D -> D -> D -> Spec
- pvsarp :: Spec -> Sig -> Sig -> Sig -> Spec
- pvsbandp :: Spec -> Sig -> Sig -> Sig -> Sig -> Spec
- pvsbandr :: Spec -> Sig -> Sig -> Sig -> Sig -> Spec
- pvsbin :: Spec -> Sig -> (Sig, Sig)
- pvsblur :: Spec -> Sig -> D -> Spec
- pvsbuffer :: Spec -> D -> (D, Sig)
- pvsbufread :: Sig -> Sig -> Spec
- pvsbufread2 :: Sig -> Sig -> D -> D -> Spec
- pvscale :: Spec -> Sig -> Spec
- pvscent :: Spec -> Sig
- pvsceps :: Spec -> Sig
- pvscross :: Spec -> Spec -> Sig -> Sig -> Spec
- pvsdemix :: Spec -> Spec -> Sig -> Sig -> D -> Spec
- pvsdiskin :: Str -> Sig -> Sig -> Spec
- pvsdisp :: Spec -> SE ()
- pvsfilter :: Spec -> Spec -> Sig -> Spec
- pvsfread :: Sig -> Tab -> Spec
- pvsfreeze :: Spec -> Sig -> Sig -> Spec
- pvsftr :: Spec -> Tab -> SE ()
- pvsftw :: Spec -> Tab -> Sig
- pvsfwrite :: Spec -> Str -> SE ()
- pvsgain :: Spec -> Sig -> Spec
- pvshift :: Spec -> Sig -> Sig -> Spec
- pvsifd :: Sig -> D -> D -> D -> (Spec, Spec)
- pvsin :: Sig -> Spec
- pvsinfo :: Spec -> (D, D, D, D)
- pvsinit :: D -> Spec
- pvslock :: Spec -> Sig -> Spec
- pvsmaska :: Spec -> Tab -> Sig -> Spec
- pvsmix :: Spec -> Spec -> Spec
- pvsmooth :: Spec -> Sig -> Sig -> Spec
- pvsmorph :: Spec -> Spec -> Sig -> Sig -> Spec
- pvsosc :: Sig -> Sig -> Sig -> D -> Spec
- pvsout :: Spec -> Sig -> SE ()
- pvspitch :: Spec -> Sig -> (Sig, Sig)
- pvstanal :: Sig -> Sig -> Sig -> Tab -> Spec
- pvstencil :: Spec -> Sig -> Sig -> D -> Spec
- pvstrace :: Spec -> Sig -> Spec
- pvsvoc :: Spec -> Spec -> Sig -> Sig -> Spec
- pvswarp :: Spec -> Sig -> Sig -> Spec
- pvsynth :: Spec -> Sig
- resyn :: Spec -> Sig -> Sig -> Sig -> Tab -> Sig
- sinsyn :: Spec -> Sig -> Sig -> Tab -> Sig
- tabifd :: Sig -> Sig -> Sig -> D -> D -> D -> Tab -> (Spec, Spec)
- tradsyn :: Spec -> Sig -> Sig -> Sig -> Tab -> Sig
- trcross :: Spec -> Spec -> Sig -> Sig -> Spec
- trfilter :: Spec -> Sig -> Tab -> Spec
- trhighest :: Spec -> Sig -> (Spec, Sig, Sig)
- trlowest :: Spec -> Sig -> (Spec, Sig, Sig)
- trmix :: Spec -> Spec -> Spec
- trscale :: Spec -> Sig -> Spec
- trshift :: Spec -> Sig -> Spec
- trsplit :: Spec -> Sig -> (Spec, Spec)
- atsAdd :: Sig -> Sig -> D -> Tab -> D -> Sig
- atsAddnz :: Sig -> D -> D -> Sig
- atsBufread :: Sig -> Sig -> D -> D -> SE ()
- atsCross :: Sig -> Sig -> D -> Tab -> Sig -> Sig -> D -> Sig
- atsInfo :: D -> D -> D
- atsInterpread :: Sig -> Sig
- atsPartialtap :: D -> (Sig, Sig)
- atsRead :: Sig -> D -> D -> (Sig, Sig)
- atsReadnz :: Sig -> D -> D -> Sig
- atsSinnoi :: Sig -> Sig -> Sig -> Sig -> D -> D -> Sig
- lorismorph :: D -> D -> D -> Sig -> Sig -> Sig -> SE ()
- lorisplay :: D -> Sig -> Sig -> Sig -> Sig
- lorisread :: Sig -> Str -> D -> Sig -> Sig -> Sig -> SE ()
- centroid :: Sig -> Sig -> D -> Sig
- filescal :: Tuple a => Sig -> Sig -> Sig -> Str -> Sig -> a
- mincer :: Sig -> Sig -> Sig -> Tab -> Sig -> Sig
- mp3scal :: Str -> Sig -> Sig -> Sig -> (Sig, Sig, Sig)
- paulstretch :: D -> D -> D -> Sig
- temposcal :: Sig -> Sig -> Sig -> Tab -> Sig -> Sig
- strfromurl :: Str -> Str
- strget :: D -> Str
- strset :: D -> D -> SE ()
- sprintf :: Str -> Sig -> Str
- sprintfk :: Str -> Sig -> Str
- strcat :: Str -> Str -> Str
- strcatk :: Str -> Str -> Str
- strcmp :: Str -> Str -> D
- strcmpk :: Str -> Str -> Sig
- strcpy :: Str -> Str
- strcpyk :: Str -> Str
- strindex :: Str -> Str -> D
- strindexk :: Str -> Str -> Sig
- strlen :: Str -> D
- strlenk :: Str -> Sig
- strrindex :: Str -> Str -> D
- strrindexk :: Str -> Str -> Sig
- strsub :: Str -> Str
- strsubk :: Str -> Sig -> Sig -> Str
- strchar :: Str -> D
- strchark :: Str -> Sig
- strlower :: Str -> Str
- strlowerk :: Str -> Str
- strtod :: Str -> D
- strtodk :: Str -> Sig
- strtol :: Str -> D
- strtolk :: Str -> Sig
- strupper :: Str -> Str
- strupperk :: Str -> Str
- ftfree :: Tab -> D -> SE ()
- ftgen :: Tab -> D -> D -> D -> D -> SE D
- ftgentmp :: D -> D -> D -> D -> D -> [D] -> SE Tab
- getftargs :: D -> Sig -> Str
- sndload :: Str -> SE ()
- vtaba :: Sig -> Tab -> Sig -> SE ()
- vtabi :: D -> Tab -> D -> SE ()
- vtabk :: Sig -> Tab -> Sig -> SE ()
- vtable1k :: Tab -> Sig -> SE ()
- vtablea :: Sig -> Tab -> Sig -> D -> Sig -> SE ()
- vtablei :: D -> Tab -> D -> D -> D -> SE ()
- vtablek :: Sig -> Tab -> Sig -> D -> Sig -> SE ()
- vtablewa :: Sig -> Tab -> D -> Sig -> SE ()
- vtablewi :: D -> Tab -> D -> D -> SE ()
- vtablewk :: Sig -> Tab -> D -> Sig -> SE ()
- vtabwa :: Sig -> Tab -> Sig -> SE ()
- vtabwi :: D -> Tab -> D -> SE ()
- vtabwk :: Sig -> Tab -> Sig -> SE ()
- vadd :: Tab -> Sig -> Sig -> SE ()
- vadd_i :: Tab -> D -> D -> SE ()
- vexp :: Tab -> Sig -> Sig -> SE ()
- vexp_i :: Tab -> D -> D -> SE ()
- vmult :: Tab -> Sig -> Sig -> SE ()
- vmult_i :: Tab -> D -> D -> SE ()
- vpow :: Tab -> Sig -> Sig -> SE ()
- vpow_i :: Tab -> D -> D -> SE ()
- vaddv :: Tab -> Tab -> Sig -> SE ()
- vaddv_i :: Tab -> Tab -> D -> SE ()
- vcopy :: Tab -> Tab -> Sig -> SE ()
- vcopy_i :: Tab -> Tab -> D -> SE ()
- vdivv :: Tab -> Tab -> Sig -> SE ()
- vdivv_i :: Tab -> Tab -> D -> SE ()
- vexpv :: Tab -> Tab -> Sig -> SE ()
- vexpv_i :: Tab -> Tab -> D -> SE ()
- vmap :: Tab -> Tab -> D -> SE ()
- vmultv :: Tab -> Tab -> Sig -> SE ()
- vmultv_i :: Tab -> Tab -> D -> SE ()
- vpowv :: Tab -> Tab -> Sig -> SE ()
- vpowv_i :: Tab -> Tab -> D -> SE ()
- vsubv :: Tab -> Tab -> Sig -> SE ()
- vsubv_i :: Tab -> Tab -> D -> SE ()
- vexpseg :: Tab -> D -> Tab -> D -> Tab -> SE ()
- vlinseg :: Tab -> D -> Tab -> D -> Tab -> SE ()
- vlimit :: Tab -> Sig -> Sig -> D -> SE ()
- vmirror :: Tab -> Sig -> Sig -> D -> SE ()
- vwrap :: Tab -> Sig -> Sig -> D -> SE ()
- vdelayk :: Sig -> Sig -> D -> Sig
- vecdelay :: Tab -> Tab -> Tab -> D -> D -> SE ()
- vport :: Tab -> Sig -> D -> SE ()
- vrandh :: Tab -> Sig -> Sig -> D -> SE ()
- vrandi :: Tab -> Sig -> Sig -> D -> SE ()
- cell :: Sig -> Sig -> D -> D -> D -> D -> SE ()
- vcella :: Sig -> Sig -> D -> D -> D -> D -> D -> SE ()
- zacl :: Sig -> Sig -> SE ()
- zakinit :: D -> D -> SE ()
- zamod :: Sig -> Sig -> Sig
- zar :: Sig -> Sig
- zarg :: Sig -> Sig -> Sig
- zaw :: Sig -> Sig -> SE ()
- zawm :: Sig -> Sig -> SE ()
- zir :: D -> D
- ziw :: D -> D -> SE ()
- ziwm :: D -> D -> SE ()
- zkcl :: Sig -> Sig -> SE ()
- zkmod :: Sig -> Sig -> Sig
- zkr :: Sig -> Sig
- zkw :: Sig -> Sig -> SE ()
- zkwm :: Sig -> Sig -> SE ()
Documentation
module Csound.Types
module Csound.Control
module Csound.IO
module Csound.Air
module Csound.Tab
module Csound.Tuning
module Csound.Options
module Csound.SigSpace
Standard classes
module Data.Boolean
module Data.Default
module Data.Monoid
class Functor f => Applicative (f :: Type -> Type) where #
A functor with application, providing operations to
A minimal complete definition must include implementations of pure
and of either <*>
or liftA2
. If it defines both, then they must behave
the same as their default definitions:
(<*>
) =liftA2
id
liftA2
f x y = f<$>
x<*>
y
Further, any definition must satisfy the following:
- Identity
pure
id
<*>
v = v- Composition
pure
(.)<*>
u<*>
v<*>
w = u<*>
(v<*>
w)- Homomorphism
pure
f<*>
pure
x =pure
(f x)- Interchange
u
<*>
pure
y =pure
($
y)<*>
u
The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:
As a consequence of these laws, the Functor
instance for f
will satisfy
It may be useful to note that supposing
forall x y. p (q x y) = f x . g y
it follows from the above that
liftA2
p (liftA2
q u v) =liftA2
f u .liftA2
g v
If f
is also a Monad
, it should satisfy
(which implies that pure
and <*>
satisfy the applicative functor laws).
Lift a value.
(<*>) :: f (a -> b) -> f a -> f b infixl 4 #
Sequential application.
A few functors support an implementation of <*>
that is more
efficient than the default one.
Example
Used in combination with (
, <$>
)(
can be used to build a record.<*>
)
>>>
data MyState = MyState {arg1 :: Foo, arg2 :: Bar, arg3 :: Baz}
>>>
produceFoo :: Applicative f => f Foo
>>>
produceBar :: Applicative f => f Bar
>>>
produceBaz :: Applicative f => f Baz
>>>
mkState :: Applicative f => f MyState
>>>
mkState = MyState <$> produceFoo <*> produceBar <*> produceBaz
liftA2 :: (a -> b -> c) -> f a -> f b -> f c #
Lift a binary function to actions.
Some functors support an implementation of liftA2
that is more
efficient than the default one. In particular, if fmap
is an
expensive operation, it is likely better to use liftA2
than to
fmap
over the structure and then use <*>
.
This became a typeclass method in 4.10.0.0. Prior to that, it was
a function defined in terms of <*>
and fmap
.
Example
>>>
liftA2 (,) (Just 3) (Just 5)
Just (3,5)
(*>) :: f a -> f b -> f b infixl 4 #
Sequence actions, discarding the value of the first argument.
Examples
If used in conjunction with the Applicative instance for Maybe
,
you can chain Maybe computations, with a possible "early return"
in case of Nothing
.
>>>
Just 2 *> Just 3
Just 3
>>>
Nothing *> Just 3
Nothing
Of course a more interesting use case would be to have effectful computations instead of just returning pure values.
>>>
import Data.Char
>>>
import Text.ParserCombinators.ReadP
>>>
let p = string "my name is " *> munch1 isAlpha <* eof
>>>
readP_to_S p "my name is Simon"
[("Simon","")]
Instances
Applicative ZipList | f <$> ZipList xs1 <*> ... <*> ZipList xsN = ZipList (zipWithN f xs1 ... xsN) where (\a b c -> stimes c [a, b]) <$> ZipList "abcd" <*> ZipList "567" <*> ZipList [1..] = ZipList (zipWith3 (\a b c -> stimes c [a, b]) "abcd" "567" [1..]) = ZipList {getZipList = ["a5","b6b6","c7c7c7"]} Since: base-2.1 |
Applicative Complex | Since: base-4.9.0.0 |
Applicative Identity | Since: base-4.8.0.0 |
Applicative First | Since: base-4.8.0.0 |
Applicative Last | Since: base-4.8.0.0 |
Applicative First | Since: base-4.9.0.0 |
Applicative Last | Since: base-4.9.0.0 |
Applicative Max | Since: base-4.9.0.0 |
Applicative Min | Since: base-4.9.0.0 |
Applicative Dual | Since: base-4.8.0.0 |
Applicative Product | Since: base-4.8.0.0 |
Applicative Sum | Since: base-4.8.0.0 |
Applicative NonEmpty | Since: base-4.9.0.0 |
Applicative Par1 | Since: base-4.9.0.0 |
Applicative P | Since: base-4.5.0.0 |
Applicative ReadP | Since: base-4.6.0.0 |
Applicative Put | |
Applicative Seq | Since: containers-0.5.4 |
Applicative Tree | |
Applicative GE | |
Applicative SE | |
Applicative Cab' | |
Applicative CabProp' | |
Applicative DList | |
Applicative IO | Since: base-2.1 |
Applicative Array | |
Applicative SmallArray | |
Defined in Data.Primitive.SmallArray pure :: a -> SmallArray a # (<*>) :: SmallArray (a -> b) -> SmallArray a -> SmallArray b # liftA2 :: (a -> b -> c) -> SmallArray a -> SmallArray b -> SmallArray c # (*>) :: SmallArray a -> SmallArray b -> SmallArray b # (<*) :: SmallArray a -> SmallArray b -> SmallArray a # | |
Applicative Q | |
Applicative Maybe | Since: base-2.1 |
Applicative Solo | Since: base-4.15 |
Applicative List | Since: base-2.1 |
Monad m => Applicative (WrappedMonad m) | Since: base-2.1 |
Defined in Control.Applicative pure :: a -> WrappedMonad m a # (<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b # liftA2 :: (a -> b -> c) -> WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m c # (*>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b # (<*) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m a # | |
Arrow a => Applicative (ArrowMonad a) | Since: base-4.6.0.0 |
Defined in Control.Arrow pure :: a0 -> ArrowMonad a a0 # (<*>) :: ArrowMonad a (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b # liftA2 :: (a0 -> b -> c) -> ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a c # (*>) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a b # (<*) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a a0 # | |
Applicative (Either e) | Since: base-3.0 |
Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Applicative (U1 :: Type -> Type) | Since: base-4.9.0.0 |
Monad m => Applicative (DepT m) | |
Applicative (Scene ctx) | |
(Functor m, Monad m) => Applicative (MaybeT m) | |
Monoid a => Applicative ((,) a) | For tuples, the ("hello ", (+15)) <*> ("world!", 2002) ("hello world!",2017) Since: base-2.1 |
Arrow a => Applicative (WrappedArrow a b) | Since: base-2.1 |
Defined in Control.Applicative pure :: a0 -> WrappedArrow a b a0 # (<*>) :: WrappedArrow a b (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 # liftA2 :: (a0 -> b0 -> c) -> WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b c # (*>) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b b0 # (<*) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 # | |
Applicative m => Applicative (Kleisli m a) | Since: base-4.14.0.0 |
Defined in Control.Arrow | |
Monoid m => Applicative (Const m :: Type -> Type) | Since: base-2.0.1 |
Applicative f => Applicative (Ap f) | Since: base-4.12.0.0 |
Applicative f => Applicative (Alt f) | Since: base-4.8.0.0 |
(Generic1 f, Applicative (Rep1 f)) => Applicative (Generically1 f) | Since: base-4.17.0.0 |
Defined in GHC.Generics pure :: a -> Generically1 f a # (<*>) :: Generically1 f (a -> b) -> Generically1 f a -> Generically1 f b # liftA2 :: (a -> b -> c) -> Generically1 f a -> Generically1 f b -> Generically1 f c # (*>) :: Generically1 f a -> Generically1 f b -> Generically1 f b # (<*) :: Generically1 f a -> Generically1 f b -> Generically1 f a # | |
Applicative f => Applicative (Rec1 f) | Since: base-4.9.0.0 |
(Applicative f, Monad f) => Applicative (WhenMissing f x) | Equivalent to Since: containers-0.5.9 |
Defined in Data.IntMap.Internal pure :: a -> WhenMissing f x a # (<*>) :: WhenMissing f x (a -> b) -> WhenMissing f x a -> WhenMissing f x b # liftA2 :: (a -> b -> c) -> WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x c # (*>) :: WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x b # (<*) :: WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x a # | |
(Monoid w, Functor m, Monad m) => Applicative (AccumT w m) | |
Defined in Control.Monad.Trans.Accum | |
(Functor m, Monad m) => Applicative (ExceptT e m) | |
Defined in Control.Monad.Trans.Except | |
Applicative m => Applicative (IdentityT m) | |
Defined in Control.Monad.Trans.Identity | |
Applicative m => Applicative (ReaderT r m) | |
Defined in Control.Monad.Trans.Reader | |
(Functor m, Monad m) => Applicative (SelectT r m) | |
Defined in Control.Monad.Trans.Select | |
(Functor m, Monad m) => Applicative (StateT s m) | |
Defined in Control.Monad.Trans.State.Lazy | |
(Functor m, Monad m) => Applicative (StateT s m) | |
Defined in Control.Monad.Trans.State.Strict | |
(Functor m, Monad m) => Applicative (WriterT w m) | |
Defined in Control.Monad.Trans.Writer.CPS | |
(Monoid w, Applicative m) => Applicative (WriterT w m) | |
Defined in Control.Monad.Trans.Writer.Lazy | |
(Monoid w, Applicative m) => Applicative (WriterT w m) | |
Defined in Control.Monad.Trans.Writer.Strict | |
(Monoid a, Monoid b) => Applicative ((,,) a b) | Since: base-4.14.0.0 |
(Applicative f, Applicative g) => Applicative (Product f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Product | |
(Applicative f, Applicative g) => Applicative (f :*: g) | Since: base-4.9.0.0 |
Monoid c => Applicative (K1 i c :: Type -> Type) | Since: base-4.12.0.0 |
(Monad f, Applicative f) => Applicative (WhenMatched f x y) | Equivalent to Since: containers-0.5.9 |
Defined in Data.IntMap.Internal pure :: a -> WhenMatched f x y a # (<*>) :: WhenMatched f x y (a -> b) -> WhenMatched f x y a -> WhenMatched f x y b # liftA2 :: (a -> b -> c) -> WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y c # (*>) :: WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y b # (<*) :: WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y a # | |
(Applicative f, Monad f) => Applicative (WhenMissing f k x) | Equivalent to Since: containers-0.5.9 |
Defined in Data.Map.Internal pure :: a -> WhenMissing f k x a # (<*>) :: WhenMissing f k x (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b # liftA2 :: (a -> b -> c) -> WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x c # (*>) :: WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x b # (<*) :: WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x a # | |
Applicative (ContT r m) | |
(Monoid a, Monoid b, Monoid c) => Applicative ((,,,) a b c) | Since: base-4.14.0.0 |
Defined in GHC.Base | |
Applicative ((->) r) | Since: base-2.1 |
(Applicative f, Applicative g) => Applicative (Compose f g) | Since: base-4.9.0.0 |
Defined in Data.Functor.Compose | |
(Applicative f, Applicative g) => Applicative (f :.: g) | Since: base-4.9.0.0 |
Applicative f => Applicative (M1 i c f) | Since: base-4.9.0.0 |
(Monad f, Applicative f) => Applicative (WhenMatched f k x y) | Equivalent to Since: containers-0.5.9 |
Defined in Data.Map.Internal pure :: a -> WhenMatched f k x y a # (<*>) :: WhenMatched f k x y (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b # liftA2 :: (a -> b -> c) -> WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y c # (*>) :: WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y b # (<*) :: WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y a # | |
(Functor m, Monad m) => Applicative (RWST r w s m) | |
Defined in Control.Monad.Trans.RWS.CPS | |
(Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) | |
Defined in Control.Monad.Trans.RWS.Lazy | |
(Monoid w, Functor m, Monad m) => Applicative (RWST r w s m) | |
Defined in Control.Monad.Trans.RWS.Strict |
class Applicative f => Alternative (f :: Type -> Type) where #
A monoid on applicative functors.
If defined, some
and many
should be the least solutions
of the equations:
The identity of <|>
(<|>) :: f a -> f a -> f a infixl 3 #
An associative binary operation
One or more.
Zero or more.
Instances
The Const
functor.
Instances
Generic1 (Const a :: k -> Type) | |
Unbox a => Vector Vector (Const a b) | |
Defined in Data.Vector.Unboxed.Base basicUnsafeFreeze :: Mutable Vector s (Const a b) -> ST s (Vector (Const a b)) # basicUnsafeThaw :: Vector (Const a b) -> ST s (Mutable Vector s (Const a b)) # basicLength :: Vector (Const a b) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (Const a b) -> Vector (Const a b) # basicUnsafeIndexM :: Vector (Const a b) -> Int -> Box (Const a b) # basicUnsafeCopy :: Mutable Vector s (Const a b) -> Vector (Const a b) -> ST s () # | |
Unbox a => MVector MVector (Const a b) | |
Defined in Data.Vector.Unboxed.Base basicLength :: MVector s (Const a b) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (Const a b) -> MVector s (Const a b) # basicOverlaps :: MVector s (Const a b) -> MVector s (Const a b) -> Bool # basicUnsafeNew :: Int -> ST s (MVector s (Const a b)) # basicInitialize :: MVector s (Const a b) -> ST s () # basicUnsafeReplicate :: Int -> Const a b -> ST s (MVector s (Const a b)) # basicUnsafeRead :: MVector s (Const a b) -> Int -> ST s (Const a b) # basicUnsafeWrite :: MVector s (Const a b) -> Int -> Const a b -> ST s () # basicClear :: MVector s (Const a b) -> ST s () # basicSet :: MVector s (Const a b) -> Const a b -> ST s () # basicUnsafeCopy :: MVector s (Const a b) -> MVector s (Const a b) -> ST s () # basicUnsafeMove :: MVector s (Const a b) -> MVector s (Const a b) -> ST s () # basicUnsafeGrow :: MVector s (Const a b) -> Int -> ST s (MVector s (Const a b)) # | |
NFData2 (Const :: Type -> Type -> Type) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable2 (Const :: Type -> Type -> Type) | |
Defined in Data.Hashable.Class | |
Foldable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Functor.Const fold :: Monoid m0 => Const m m0 -> m0 # foldMap :: Monoid m0 => (a -> m0) -> Const m a -> m0 # foldMap' :: Monoid m0 => (a -> m0) -> Const m a -> m0 # foldr :: (a -> b -> b) -> b -> Const m a -> b # foldr' :: (a -> b -> b) -> b -> Const m a -> b # foldl :: (b -> a -> b) -> b -> Const m a -> b # foldl' :: (b -> a -> b) -> b -> Const m a -> b # foldr1 :: (a -> a -> a) -> Const m a -> a # foldl1 :: (a -> a -> a) -> Const m a -> a # elem :: Eq a => a -> Const m a -> Bool # maximum :: Ord a => Const m a -> a # minimum :: Ord a => Const m a -> a # | |
Traversable (Const m :: Type -> Type) | Since: base-4.7.0.0 |
Monoid m => Applicative (Const m :: Type -> Type) | Since: base-2.0.1 |
Functor (Const m :: Type -> Type) | Since: base-2.1 |
NFData a => NFData1 (Const a :: Type -> Type) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable a => Hashable1 (Const a :: Type -> Type) | |
Defined in Data.Hashable.Class | |
IsString a => IsString (Const a b) | Since: base-4.9.0.0 |
Defined in Data.String fromString :: String -> Const a b # | |
Storable a => Storable (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Monoid a => Monoid (Const a b) | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Const a b) | Since: base-4.9.0.0 |
Bits a => Bits (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const (.&.) :: Const a b -> Const a b -> Const a b # (.|.) :: Const a b -> Const a b -> Const a b # xor :: Const a b -> Const a b -> Const a b # complement :: Const a b -> Const a b # shift :: Const a b -> Int -> Const a b # rotate :: Const a b -> Int -> Const a b # setBit :: Const a b -> Int -> Const a b # clearBit :: Const a b -> Int -> Const a b # complementBit :: Const a b -> Int -> Const a b # testBit :: Const a b -> Int -> Bool # bitSizeMaybe :: Const a b -> Maybe Int # isSigned :: Const a b -> Bool # shiftL :: Const a b -> Int -> Const a b # unsafeShiftL :: Const a b -> Int -> Const a b # shiftR :: Const a b -> Int -> Const a b # unsafeShiftR :: Const a b -> Int -> Const a b # rotateL :: Const a b -> Int -> Const a b # | |
FiniteBits a => FiniteBits (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const finiteBitSize :: Const a b -> Int # countLeadingZeros :: Const a b -> Int # countTrailingZeros :: Const a b -> Int # | |
Bounded a => Bounded (Const a b) | Since: base-4.9.0.0 |
Enum a => Enum (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const succ :: Const a b -> Const a b # pred :: Const a b -> Const a b # fromEnum :: Const a b -> Int # enumFrom :: Const a b -> [Const a b] # enumFromThen :: Const a b -> Const a b -> [Const a b] # enumFromTo :: Const a b -> Const a b -> [Const a b] # enumFromThenTo :: Const a b -> Const a b -> Const a b -> [Const a b] # | |
Floating a => Floating (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const exp :: Const a b -> Const a b # log :: Const a b -> Const a b # sqrt :: Const a b -> Const a b # (**) :: Const a b -> Const a b -> Const a b # logBase :: Const a b -> Const a b -> Const a b # sin :: Const a b -> Const a b # cos :: Const a b -> Const a b # tan :: Const a b -> Const a b # asin :: Const a b -> Const a b # acos :: Const a b -> Const a b # atan :: Const a b -> Const a b # sinh :: Const a b -> Const a b # cosh :: Const a b -> Const a b # tanh :: Const a b -> Const a b # asinh :: Const a b -> Const a b # acosh :: Const a b -> Const a b # atanh :: Const a b -> Const a b # log1p :: Const a b -> Const a b # expm1 :: Const a b -> Const a b # | |
RealFloat a => RealFloat (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const floatRadix :: Const a b -> Integer # floatDigits :: Const a b -> Int # floatRange :: Const a b -> (Int, Int) # decodeFloat :: Const a b -> (Integer, Int) # encodeFloat :: Integer -> Int -> Const a b # exponent :: Const a b -> Int # significand :: Const a b -> Const a b # scaleFloat :: Int -> Const a b -> Const a b # isInfinite :: Const a b -> Bool # isDenormalized :: Const a b -> Bool # isNegativeZero :: Const a b -> Bool # | |
Generic (Const a b) | |
Ix a => Ix (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const range :: (Const a b, Const a b) -> [Const a b] # index :: (Const a b, Const a b) -> Const a b -> Int # unsafeIndex :: (Const a b, Const a b) -> Const a b -> Int # inRange :: (Const a b, Const a b) -> Const a b -> Bool # rangeSize :: (Const a b, Const a b) -> Int # unsafeRangeSize :: (Const a b, Const a b) -> Int # | |
Num a => Num (Const a b) | Since: base-4.9.0.0 |
Read a => Read (Const a b) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
Fractional a => Fractional (Const a b) | Since: base-4.9.0.0 |
Integral a => Integral (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Real a => Real (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const toRational :: Const a b -> Rational # | |
RealFrac a => RealFrac (Const a b) | Since: base-4.9.0.0 |
Show a => Show (Const a b) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 |
NFData a => NFData (Const a b) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Eq a => Eq (Const a b) | Since: base-4.9.0.0 |
Ord a => Ord (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
Hashable a => Hashable (Const a b) | |
Defined in Data.Hashable.Class | |
Unbox a => Unbox (Const a b) | |
Defined in Data.Vector.Unboxed.Base | |
type Rep1 (Const a :: k -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
newtype MVector s (Const a b) | |
Defined in Data.Vector.Unboxed.Base | |
type Rep (Const a b) | Since: base-4.9.0.0 |
Defined in Data.Functor.Const | |
newtype Vector (Const a b) | |
Defined in Data.Vector.Unboxed.Base |
Lists, but with an Applicative
functor based on zipping.
ZipList | |
|
Instances
Foldable ZipList | Since: base-4.9.0.0 |
Defined in Control.Applicative fold :: Monoid m => ZipList m -> m # foldMap :: Monoid m => (a -> m) -> ZipList a -> m # foldMap' :: Monoid m => (a -> m) -> ZipList a -> m # foldr :: (a -> b -> b) -> b -> ZipList a -> b # foldr' :: (a -> b -> b) -> b -> ZipList a -> b # foldl :: (b -> a -> b) -> b -> ZipList a -> b # foldl' :: (b -> a -> b) -> b -> ZipList a -> b # foldr1 :: (a -> a -> a) -> ZipList a -> a # foldl1 :: (a -> a -> a) -> ZipList a -> a # elem :: Eq a => a -> ZipList a -> Bool # maximum :: Ord a => ZipList a -> a # minimum :: Ord a => ZipList a -> a # | |
Traversable ZipList | Since: base-4.9.0.0 |
Alternative ZipList | Since: base-4.11.0.0 |
Applicative ZipList | f <$> ZipList xs1 <*> ... <*> ZipList xsN = ZipList (zipWithN f xs1 ... xsN) where (\a b c -> stimes c [a, b]) <$> ZipList "abcd" <*> ZipList "567" <*> ZipList [1..] = ZipList (zipWith3 (\a b c -> stimes c [a, b]) "abcd" "567" [1..]) = ZipList {getZipList = ["a5","b6b6","c7c7c7"]} Since: base-2.1 |
Functor ZipList | Since: base-2.1 |
NFData1 ZipList | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Generic1 ZipList | |
Generic (ZipList a) | |
IsList (ZipList a) | Since: base-4.15.0.0 |
Read a => Read (ZipList a) | Since: base-4.7.0.0 |
Show a => Show (ZipList a) | Since: base-4.7.0.0 |
NFData a => NFData (ZipList a) | Since: deepseq-1.4.0.0 |
Defined in Control.DeepSeq | |
Eq a => Eq (ZipList a) | Since: base-4.7.0.0 |
Ord a => Ord (ZipList a) | Since: base-4.7.0.0 |
Defined in Control.Applicative | |
type Rep1 ZipList | Since: base-4.7.0.0 |
Defined in Control.Applicative | |
type Rep (ZipList a) | Since: base-4.7.0.0 |
Defined in Control.Applicative | |
type Item (ZipList a) | |
Defined in GHC.IsList |
newtype WrappedArrow (a :: Type -> Type -> Type) b c #
WrapArrow | |
|
Instances
newtype WrappedMonad (m :: Type -> Type) a #
WrapMonad | |
|
Instances
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 #
An infix synonym for fmap
.
The name of this operator is an allusion to $
.
Note the similarities between their types:
($) :: (a -> b) -> a -> b (<$>) :: Functor f => (a -> b) -> f a -> f b
Whereas $
is function application, <$>
is function
application lifted over a Functor
.
Examples
Convert from a
to a Maybe
Int
using Maybe
String
show
:
>>>
show <$> Nothing
Nothing>>>
show <$> Just 3
Just "3"
Convert from an
to an
Either
Int
Int
Either
Int
String
using show
:
>>>
show <$> Left 17
Left 17>>>
show <$> Right 17
Right "17"
Double each element of a list:
>>>
(*2) <$> [1,2,3]
[2,4,6]
Apply even
to the second element of a pair:
>>>
even <$> (2,2)
(2,True)
(<**>) :: Applicative f => f a -> f (a -> b) -> f b infixl 4 #
A variant of <*>
with the arguments reversed.
liftA :: Applicative f => (a -> b) -> f a -> f b #
Lift a function to actions.
Equivalent to Functor's fmap
but implemented using only Applicative
's methods:
liftA
f a = pure
f <*>
a
As such this function may be used to implement a Functor
instance from an Applicative
one.
Examples
Using the Applicative instance for Lists:
>>>
liftA (+1) [1, 2]
[2,3]
Or the Applicative instance for Maybe
>>>
liftA (+1) (Just 3)
Just 4
liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d #
Lift a ternary function to actions.
optional :: Alternative f => f a -> f (Maybe a) #
One or none.
It is useful for modelling any computation that is allowed to fail.
Examples
Using the Alternative
instance of Control.Monad.Except, the following functions:
>>>
import Control.Monad.Except
>>>
canFail = throwError "it failed" :: Except String Int
>>>
final = return 42 :: Except String Int
Can be combined by allowing the first function to fail:
>>>
runExcept $ canFail *> final
Left "it failed">>>
runExcept $ optional canFail *> final
Right 42
asum :: (Foldable t, Alternative f) => t (f a) -> f a #
The sum of a collection of actions using (<|>)
, generalizing concat
.
asum
is just like msum
, but generalised to Alternative
.
Examples
Basic usage:
>>>
asum [Just "Hello", Nothing, Just "World"]
Just "Hello"
module Temporal.Media
module Temporal.Class
Opcodes
Reads a directory and outputs to a string array a list of file names.
Reads a directory for files and passes them to a string array. Users can set the file type by passing a file extension as a string.
SFiles[] directory SDirectory[, SExtention]
csound doc: http://csound.com/docs/manual/directory.html
Adds artificial foldover to an audio signal.
ares fold asig, kincr
csound doc: http://csound.com/docs/manual/fold.html
Print a string constant or variable
puts prints a string with an optional newline at the end whenever the trigger signal is positive and changes.
puts Sstr, ktrig[, inonl]
csound doc: http://csound.com/docs/manual/puts.html
Indicates whether a note is in its âreleaseâ stage.
Provides a way of knowing when a note off message for the current note is received. Only a noteoff message with the same MIDI note number as the one which triggered the note will be reported by release.
kflag release
csound doc: http://csound.com/docs/manual/release.html
printf :: Str -> Sig -> [Sig] -> SE () #
printf-style formatted output
printf and printf_i write formatted output, similarly to the C function printf(). printf_i runs at i-time only, while printf runs both at initialization and performance time.
printf Sfmt, ktrig, [xarg1[, xarg2[, ... ]]]
csound doc: http://csound.com/docs/manual/printf.html
Modify a signal by differentiation.
ares diff asig [, iskip] kres diff ksig [, iskip]
csound doc: http://csound.com/docs/manual/diff.html
Zeroes a list of audio signals.
clear zeroes a list of audio signals.
clear avar1 [, avar2] [, avar3] [...]
csound doc: http://csound.com/docs/manual/clear.html
Read absolute time in seconds.
Read absolute time, in seconds, since the start of the performance.
ires times kres times
csound doc: http://csound.com/docs/manual/times.html
linen :: Sig -> D -> D -> D -> Sig #
Applies a straight line rise and decay pattern to an input amp signal.
linen -- apply a straight line rise and decay pattern to an input amp signal.
ares linen xamp, irise, idur, idec kres linen kamp, irise, idur, idec
csound doc: http://csound.com/docs/manual/linen.html
scale :: Sig -> Sig -> Sig -> Sig #
Arbitrary signal scaling.
Scales incoming value to user-definable range. Similar to scale object found in popular dataflow languages.
kscl scale kinput, kmax, kmin
csound doc: http://csound.com/docs/manual/scale.html
balance :: Sig -> Sig -> Sig #
Adjust one audio signal according to the values of another.
The rms power of asig can be interrogated, set, or adjusted to match that of a comparator signal.
ares balance asig, acomp [, ihp] [, iskip]
csound doc: http://csound.com/docs/manual/balance.html
link_beat_force :: D -> Sig -> SE () #
Forces the global network Ableton Link session to adopt a specific beat number and time.
Forces the global network Ableton Link session to adopt a specific beat number and time, like a conductor stopping an orchestra and immediately starting it again.
link_beat_force i_peer, k_beat [, k_at_time_seconds [, k_quantum ]]
csound doc: http://csound.com/docs/manual/link_beat_force.html
link_beat_get :: D -> (Sig, Sig, Sig) #
Returns the beat, phase with respect to the local quantum, and current time for the session.
Returns the beat number, phase of the beat with respect to the local quantum of the beat, and current time for the global network Ableton Link session.
k_beat_number, k_phase, k_current_time_seconds link_beat_get i_peer [, k_quantum]
csound doc: http://csound.com/docs/manual/link_beat_get.html
link_beat_request :: D -> Sig -> SE () #
Requests the global network Ableton Link session to adopt a specific beat number and time.
link_beat_request i_peer, k_beat [, k_at_time_seconds [, k_quantum ]]
csound doc: http://csound.com/docs/manual/link_beat_request.html
link_create :: D #
Creates a peer in an Ableton Link network session.
Creates a peer in an Ableton Link network session. The first peer in a session determines the initial tempo of the session. The value returned must be passed as the first parameter to all subsequent Ableton Link opcode calls for this peer.
i_peer link_create [i_bpm]
csound doc: http://csound.com/docs/manual/link_create.html
ableton_link_enable :: D -> SE () #
Enable or disable synchronization with the Ableton Link session.
Enable or disable synchronization with the global network Ableton Link session tempo and beat.
ableton_link_enable i_peer [, k_enable]
csound doc: http://csound.com/docs/manual/link_enable.html
link_is_enabled :: D -> Sig #
Returns whether or not this peer is synchronized with the global network Ableton Link session.
Returns whether or not the beat and time of his peer are synchronized with the global network Ableton Link session.
k_is_enabled link_is_enabled i_peer
csound doc: http://csound.com/docs/manual/link_is_enabled.html
link_metro :: D -> (Sig, Sig, Sig, Sig) #
Returns a trigger that is 1 on the beat and 0 otherwise along with beat, phase, and time for this session of Ableton Link.
Returns a trigger that is 1 on the beat and 0 otherwise along with the beat, phase, and current time of Ableton Link for this session for a given quantum.
k_trigger, k_beat, k_phase, k_current_time_seconds link_metro i_peer [, k_quantum]
csound doc: http://csound.com/docs/manual/link_metro.html
link_peers :: D -> Sig #
Returns the number of peers in the session.
Returns the number of peers in the global network Ableton Link session.
k_count link_peers i_peer
csound doc: http://csound.com/docs/manual/link_peers.html
link_tempo_get :: D -> Sig #
Returns the current tempo of the global network Ableton Link session.
k_bpm link_tempo_get i_peer
csound doc: http://csound.com/docs/manual/link_tempo_get.html
link_tempo_set :: D -> Sig -> SE () #
Sets the tempo.
Sets the local tempo if this peer is not enabled; sets the tempo of the global network Ableton Link session if this peer is enabled.
link_tempo_set i_peer, k_bpm [, k_at_time_seconds]
csound doc: http://csound.com/docs/manual/link_tempo_set.html
flGroup :: Str -> D -> D -> D -> D -> SE () #
A FLTK container opcode that groups child widgets.
FLgroup "label", iwidth, iheight, ix, iy [, iborder] [, image]
csound doc: http://csound.com/docs/manual/FLgroup.html
flGroupEnd :: SE () #
Marks the end of a group of FLTK child widgets.
FLgroupEnd
csound doc: http://csound.com/docs/manual/FLgroupEnd.html
flPack :: D -> D -> D -> D -> D -> D -> D -> SE () #
Provides the functionality of compressing and aligning FLTK widgets.
FLpack provides the functionality of compressing and aligning widgets.
FLpack iwidth, iheight, ix, iy, itype, ispace, iborder
csound doc: http://csound.com/docs/manual/FLpack.html
Marks the end of a group of compressed or aligned FLTK widgets.
FLpackEnd
csound doc: http://csound.com/docs/manual/FLpackEnd.html
flPanel :: Str -> D -> D -> SE () #
Creates a window that contains FLTK widgets.
FLpanel "label", iwidth, iheight [, ix] [, iy] [, iborder] [, ikbdcapture] [, iclose]
csound doc: http://csound.com/docs/manual/FLpanel.html
flPanelEnd :: SE () #
Marks the end of a group of FLTK widgets contained inside of a window (panel).
FLpanelEnd
csound doc: http://csound.com/docs/manual/FLpanelEnd.html
A FLTK opcode that adds scroll bars to an area.
FLscroll adds scroll bars to an area.
FLscroll iwidth, iheight [, ix] [, iy]
csound doc: http://csound.com/docs/manual/FLscroll.html
flScrollEnd :: SE () #
A FLTK opcode that marks the end of an area with scrollbars.
FLscrollEnd
csound doc: http://csound.com/docs/manual/FLscrollEnd.html
flTabs :: D -> D -> D -> D -> SE () #
Creates a tabbed FLTK interface.
FLtabs is a âfile card tabsâ interface that is useful to display several areas containing widgets in the same windows, alternatively. It must be used together with FLgroup, another container that groups child widgets.
FLtabs iwidth, iheight, ix, iy
csound doc: http://csound.com/docs/manual/FLtabs.html
Marks the end of a tabbed FLTK interface.
FLtabsEnd
csound doc: http://csound.com/docs/manual/FLtabsEnd.html
flCount :: Str -> D -> D -> D -> D -> D -> D -> D -> D -> D -> D -> SE (Sig, D) #
A FLTK widget opcode that creates a counter.
Allows the user to increase/decrease a value with mouse clicks on a corresponding arrow button.
kout, ihandle FLcount "label", imin, imax, istep1, istep2, itype, \ iwidth, iheight, ix, iy, iopcode [, kp1] [, kp2] [, kp3] [...] [, kpN]
csound doc: http://csound.com/docs/manual/FLcount.html
flJoy :: Str -> D -> D -> D -> D -> D -> D -> D -> D -> D -> D -> D -> D -> SE (Sig, Sig, D, D) #
A FLTK opcode that acts like a joystick.
FLjoy is a squared area that allows the user to modify two output values at the same time. It acts like a joystick.
koutx, kouty, ihandlex, ihandley FLjoy "label", iminx, imaxx, iminy, \ imaxy, iexpx, iexpy, idispx, idispy, iwidth, iheight, ix, iy
csound doc: http://csound.com/docs/manual/FLjoy.html
flKnob :: Str -> D -> D -> D -> D -> D -> D -> D -> D -> SE (Sig, D) #
A FLTK widget opcode that creates a knob.
kout, ihandle FLknob "label", imin, imax, iexp, itype, idisp, iwidth, \ ix, iy [, icursorsize]
csound doc: http://csound.com/docs/manual/FLknob.html
flRoller :: Str -> D -> D -> D -> D -> D -> D -> D -> D -> D -> D -> SE (Sig, D) #
A FLTK widget that creates a transversal knob.
FLroller is a sort of knob, but put transversally.
kout, ihandle FLroller "label", imin, imax, istep, iexp, itype, idisp, \ iwidth, iheight, ix, iy
csound doc: http://csound.com/docs/manual/FLroller.html
flSlider :: Str -> D -> D -> D -> D -> D -> D -> D -> D -> D -> SE (Sig, D) #
Puts a slider into the corresponding FLTK container.
FLslider puts a slider into the corresponding container.
kout, ihandle FLslider "label", imin, imax, iexp, itype, idisp, iwidth, \ iheight, ix, iy
csound doc: http://csound.com/docs/manual/FLslider.html
flText :: Str -> D -> D -> D -> D -> D -> D -> D -> D -> SE (Sig, D) #
A FLTK widget opcode that creates a textbox.
FLtext allows the user to modify a parameter value by directly typing it into a text field.
kout, ihandle FLtext "label", imin, imax, istep, itype, iwidth, \ iheight, ix, iy
csound doc: http://csound.com/docs/manual/FLtext.html
flBox :: Str -> D -> D -> D -> D -> D -> D -> D -> SE D #
A FLTK widget that displays text inside of a box.
ihandle FLbox "label", itype, ifont, isize, iwidth, iheight, ix, iy [, image] ihandle FLbox istr, itype, ifont, isize, iwidth, iheight, ix, iy [, image]
csound doc: http://csound.com/docs/manual/FLbox.html
flButBank :: D -> D -> D -> D -> D -> D -> D -> D -> SE (Sig, D) #
A FLTK widget opcode that creates a bank of buttons.
kout, ihandle FLbutBank itype, inumx, inumy, iwidth, iheight, ix, iy, \ iopcode [, kp1] [, kp2] [, kp3] [, kp4] [, kp5] [....] [, kpN]
csound doc: http://csound.com/docs/manual/FLbutBank.html
flButton :: Str -> D -> D -> D -> D -> D -> D -> D -> D -> SE (Sig, D) #
A FLTK widget opcode that creates a button.
kout, ihandle FLbutton "label", ion, ioff, itype, iwidth, iheight, ix, \ iy, iopcode [, kp1] [, kp2] [, kp3] [, kp4] [, kp5] [....] [, kpN]
csound doc: http://csound.com/docs/manual/FLbutton.html
flCloseButton :: Str -> D -> D -> D -> D -> SE D #
A FLTK widget opcode that creates a button that will close the panel window it is a part of.
ihandle FLcloseButton "label", iwidth, iheight, ix, iy
csound doc: http://csound.com/docs/manual/FLcloseButton.html
flExecButton :: Str -> D -> D -> D -> D -> SE D #
A FLTK widget opcode that creates a button that executes a command.
A FLTK widget opcode that creates a button that executes a command. Useful for opening up HTML documentation as About text or to start a separate program from an FLTK widget interface.
ihandle FLexecButton "command", iwidth, iheight, ix, iy
csound doc: http://csound.com/docs/manual/FLexecButton.html
Retrieves a previously stored FLTK snapshot.
Retrieves a previously stored snapshot (in memory), i.e. sets all valuator to the corresponding values stored in that snaphot.
inumsnap FLgetsnap index [, igroup]
csound doc: http://csound.com/docs/manual/FLgetsnap.html
flHvsBox :: D -> D -> D -> D -> D -> D -> SE D #
Displays a box with a grid useful for visualizing two-dimensional Hyper Vectorial Synthesis.
FLhvsBox displays a box with a grid useful for visualizing two-dimensional Hyper Vectorial Synthesis.
ihandle FLhvsBox inumlinesX, inumlinesY, iwidth, iheight, ix, iy
csound doc: http://csound.com/docs/manual/FLhvsBox.html
flHvsBoxSetValue :: Sig -> Sig -> D -> SE () #
Sets the cursor position of a previously-declared FLhvsBox widget.
FLhvsBoxSetValue sets the cursor position of a previously-declared FLhvsBox widget.
FLhvsBoxSetValue kx, ky, ihandle
csound doc: http://csound.com/docs/manual/FLhvsBoxSetValue.html
Reports keys pressed (on alphanumeric keyboard) when an FLTK panel has focus.
FLkeyIn informs about the status of a key pressed by the user on the alphanumeric keyboard when an FLTK panel has got the focus.
kascii FLkeyIn [ifn]
csound doc: http://csound.com/docs/manual/FLkeyIn.html
flLoadsnap :: Str -> SE () #
Loads all snapshots into the memory bank of the current orchestra.
FLloadsnap loads all the snapshots contained in a file into the memory bank of the current orchestra.
FLloadsnap "filename" [, igroup]
csound doc: http://csound.com/docs/manual/FLloadsnap.html
Returns the mouse position and the state of the three mouse buttons.
FLmouse returns the coordinates of the mouse position within an FLTK panel and the state of the three mouse buttons.
kx, ky, kb1, kb2, kb3 FLmouse [imode]
csound doc: http://csound.com/docs/manual/FLmouse.html
flPrintk :: D -> Sig -> D -> SE () #
A FLTK opcode that prints a k-rate value at specified intervals.
FLprintk is similar to printk but shows values of a k-rate signal in a text field instead of on the console.
FLprintk itime, kval, idisp
csound doc: http://csound.com/docs/manual/FLprintk.html
flPrintk2 :: Sig -> D -> SE () #
A FLTK opcode that prints a new value every time a control-rate variable changes.
FLprintk2 is similar to FLprintk but shows a k-rate variable's value only when it changes.
FLprintk2 kval, idisp
csound doc: http://csound.com/docs/manual/FLprintk2.html
flSavesnap :: Str -> SE () #
Saves all snapshots currently created into a file.
FLsavesnap saves all snapshots currently created (i.e. the entire memory bank) into a file.
FLsavesnap "filename" [, igroup]
csound doc: http://csound.com/docs/manual/FLsavesnap.html
Stores the current status of all FLTK valuators into a snapshot location.
FLsetsnap stores the current status of all valuators present in the orchestra into a snapshot location (in memory).
inumsnap, inumval FLsetsnap index [, ifn, igroup]
csound doc: http://csound.com/docs/manual/FLsetsnap.html
flSetSnapGroup :: D -> SE () #
Determines the snapshot group for FL valuators.
FLsetSnapGroup determines the snapshot group of valuators declared after it.
FLsetSnapGroup igroup
csound doc: http://csound.com/docs/manual/FLsetSnapGroup.html
flSetVal :: Sig -> Sig -> D -> SE () #
Sets the value of a FLTK valuator at control-rate.
FLsetVal is almost identical to FLsetVal_i. Except it operates at k-rate and it affects the target valuator only when ktrig is set to a non-zero value.
FLsetVal ktrig, kvalue, ihandle
csound doc: http://csound.com/docs/manual/FLsetVal.html
flSetVal_i :: D -> D -> SE () #
Sets the value of a FLTK valuator to a number provided by the user.
FLsetVal_i forces the value of a valuator to a number provided by the user.
FLsetVal_i ivalue, ihandle
csound doc: http://csound.com/docs/manual/FLsetVal_i.html
flSlidBnk :: Str -> D -> SE () #
A FLTK widget containing a bank of horizontal sliders.
FLslidBnk is a widget containing a bank of horizontal sliders.
FLslidBnk "names", inumsliders [, ioutable] [, iwidth] [, iheight] [, ix] \ [, iy] [, itypetable] [, iexptable] [, istart_index] [, iminmaxtable]
csound doc: http://csound.com/docs/manual/FLslidBnk.html
flSlidBnk2 :: Str -> D -> D -> D -> SE () #
A FLTK widget containing a bank of horizontal sliders.
FLslidBnk2 is a widget containing a bank of horizontal sliders.
FLslidBnk2 "names", inumsliders, ioutable, iconfigtable [,iwidth, iheight, ix, iy, istart_index] FLslidBnk2 istring, inumsliders, ioutable, iconfigtable [,iwidth, iheight, ix, iy, istart_index]
csound doc: http://csound.com/docs/manual/FLslidBnk2.html
flSlidBnk2Set :: D -> Tab -> SE () #
modify the values of a slider bank.
FLslidBnk2Set modifies the values of a slider bank according to an array of values stored in a table.
FLslidBnk2Set ihandle, ifn [, istartIndex, istartSlid, inumSlid]
csound doc: http://csound.com/docs/manual/FLslidBnk2Set.html
flSlidBnk2Setk :: Sig -> D -> Tab -> SE () #
modify the values of a slider bank.
FLslidBnk2Setk modifies the values of a slider bank according to an array of values stored in a table.
FLslidBnk2Setk ktrig, ihandle, ifn [, istartIndex, istartSlid, inumSlid]
csound doc: http://csound.com/docs/manual/FLslidBnk2Setk.html
flSlidBnkGetHandle :: SE D #
gets the handle of last slider bank created.
FLslidBnkGetHandle gets the handle of last slider bank created.
ihandle FLslidBnkGetHandle
csound doc: http://csound.com/docs/manual/FLslidBnkGetHandle.html
flSlidBnkSet :: D -> Tab -> SE () #
modify the values of a slider bank.
FLslidBnkSet modifies the values of a slider bank according to an array of values stored in a table.
FLslidBnkSet ihandle, ifn [, istartIndex, istartSlid, inumSlid]
csound doc: http://csound.com/docs/manual/FLslidBnkSet.html
flSlidBnkSetk :: Sig -> D -> Tab -> SE () #
modify the values of a slider bank.
FLslidBnkSetk modifies the values of a slider bank according to an array of values stored in a table.
FLslidBnkSetk ktrig, ihandle, ifn [, istartIndex, istartSlid, inumSlid]
csound doc: http://csound.com/docs/manual/FLslidBnkSetk.html
flValue :: Str -> D -> D -> D -> D -> SE D #
Shows the current value of a FLTK valuator.
FLvalue shows current the value of a valuator in a text field.
ihandle FLvalue "label", iwidth, iheight, ix, iy
csound doc: http://csound.com/docs/manual/FLvalue.html
flVkeybd :: Str -> D -> D -> D -> D -> SE () #
An FLTK widget opcode that creates a virtual keyboard widget.
An FLTK widget opcode that creates a virtual keyboard widget. This must be used in conjunction with the virtual midi keyboard driver for this to operate correctly. The purpose of this opcode is for making demo versions of MIDI orchestras with the virtual keyboard embedded within the main window.
FLvkeybd "keyboard.map", iwidth, iheight, ix, iy
csound doc: http://csound.com/docs/manual/FLvkeybd.html
flVslidBnk :: Str -> D -> SE () #
A FLTK widget containing a bank of vertical sliders.
FLvslidBnk is a widget containing a bank of vertical sliders.
FLvslidBnk "names", inumsliders [, ioutable] [, iwidth] [, iheight] [, ix] \ [, iy] [, itypetable] [, iexptable] [, istart_index] [, iminmaxtable]
csound doc: http://csound.com/docs/manual/FLvslidBnk.html
flVslidBnk2 :: Str -> D -> D -> D -> SE () #
A FLTK widget containing a bank of vertical sliders.
FLvslidBnk2 is a widget containing a bank of vertical sliders.
FLvslidBnk2 "names", inumsliders, ioutable, iconfigtable [,iwidth, iheight, ix, iy, istart_index]
csound doc: http://csound.com/docs/manual/FLvslidBnk2.html
flXyin :: D -> D -> D -> D -> D -> D -> D -> D -> SE (Sig, Sig, Sig) #
Senses the mouse cursor position in a user-defined area inside an FLpanel.
Similar to xyin, sense the mouse cursor position in a user-defined area inside an FLpanel.
koutx, kouty, kinside FLxyin ioutx_min, ioutx_max, iouty_min, iouty_max, \ iwindx_min, iwindx_max, iwindy_min, iwindy_max [, iexpx, iexpy, ioutx, iouty]
csound doc: http://csound.com/docs/manual/FLxyin.html
vphaseseg :: Sig -> D -> D -> [D] -> SE () #
Allows one-dimensional HVS (Hyper-Vectorial Synthesis).
vphaseseg allows one-dimensional HVS (Hyper-Vectorial Synthesis).
vphaseseg kphase, ioutab, ielems, itab1,idist1,itab2 \ [,idist2,itab3, ... ,idistN-1,itabN]
csound doc: http://csound.com/docs/manual/vphaseseg.html
flColor :: D -> D -> D -> SE () #
A FLTK opcode that sets the primary colors.
Sets the primary colors to RGB values given by the user.
FLcolor ired, igreen, iblue [, ired2, igreen2, iblue2]
csound doc: http://csound.com/docs/manual/FLcolor.html
flColor2 :: D -> D -> D -> SE () #
A FLTK opcode that sets the secondary (selection) color.
FLcolor2 is the same of FLcolor except it affects the secondary (selection) color.
FLcolor2 ired, igreen, iblue
csound doc: http://csound.com/docs/manual/FLcolor2.html
Hides the target FLTK widget.
Hides the target FLTK widget, making it invisible.
FLhide ihandle
csound doc: http://csound.com/docs/manual/FLhide.html
flLabel :: D -> D -> D -> D -> D -> D -> SE () #
A FLTK opcode that modifies the appearance of a text label.
Modifies a set of parameters related to the text label appearence of a widget (i.e. size, font, alignment and color of corresponding text).
FLlabel isize, ifont, ialign, ired, igreen, iblue
csound doc: http://csound.com/docs/manual/FLlabel.html
flSetAlign :: D -> D -> SE () #
Sets the text alignment of a label of a FLTK widget.
FLsetAlign sets the text alignment of the label of the target widget.
FLsetAlign ialign, ihandle
csound doc: http://csound.com/docs/manual/FLsetAlign.html
Sets the appearance of a box surrounding a FLTK widget.
FLsetBox sets the appearance of a box surrounding the target widget.
FLsetBox itype, ihandle
csound doc: http://csound.com/docs/manual/FLsetBox.html
flSetColor :: D -> D -> D -> D -> SE () #
Sets the primary color of a FLTK widget.
FLsetColor sets the primary color of the target widget.
FLsetColor ired, igreen, iblue, ihandle
csound doc: http://csound.com/docs/manual/FLsetColor.html
flSetColor2 :: D -> D -> D -> D -> SE () #
Sets the secondary (or selection) color of a FLTK widget.
FLsetColor2 sets the secondary (or selection) color of the target widget.
FLsetColor2 ired, igreen, iblue, ihandle
csound doc: http://csound.com/docs/manual/FLsetColor2.html
flSetFont :: D -> D -> SE () #
Sets the font type of a FLTK widget.
FLsetFont sets the font type of the target widget.
FLsetFont ifont, ihandle
csound doc: http://csound.com/docs/manual/FLsetFont.html
flSetPosition :: D -> D -> D -> SE () #
Sets the position of a FLTK widget.
FLsetPosition sets the position of the target widget according to the ix and iy arguments.
FLsetPosition ix, iy, ihandle
csound doc: http://csound.com/docs/manual/FLsetPosition.html
flSetSize :: D -> D -> D -> SE () #
Resizes a FLTK widget.
FLsetSize resizes the target widget (not the size of its text) according to the iwidth and iheight arguments.
FLsetSize iwidth, iheight, ihandle
csound doc: http://csound.com/docs/manual/FLsetSize.html
flSetText :: Str -> D -> SE () #
Sets the label of a FLTK widget.
FLsetText sets the label of the target widget to the double-quoted text string provided with the itext argument.
FLsetText "itext", ihandle FLsetText istr, ihandle
csound doc: http://csound.com/docs/manual/FLsetText.html
flSetTextColor :: D -> D -> D -> D -> SE () #
Sets the color of the text label of a FLTK widget.
FLsetTextColor sets the color of the text label of the target widget.
FLsetTextColor ired, iblue, igreen, ihandle
csound doc: http://csound.com/docs/manual/FLsetTextColor.html
flSetTextSize :: D -> D -> SE () #
Sets the size of the text label of a FLTK widget.
FLsetTextSize sets the size of the text label of the target widget.
FLsetTextSize isize, ihandle
csound doc: http://csound.com/docs/manual/FLsetTextSize.html
flSetTextType :: D -> D -> SE () #
Sets some font attributes of the text label of a FLTK widget.
FLsetTextType sets some attributes related to the fonts of the text label of the target widget.
FLsetTextType itype, ihandle
csound doc: http://csound.com/docs/manual/FLsetTextType.html
Restores the visibility of a previously hidden FLTK widget.
FLshow restores the visibility of a previously hidden widget.
FLshow ihandle
csound doc: http://csound.com/docs/manual/FLshow.html
faustctl :: D -> Str -> Sig -> SE () #
Adjusts a given control in a Faust DSP instance.
Faustctl will set a given control in a running faust program
faustctl idsp,Scontrol,kval
csound doc: http://csound.com/docs/manual/faustctl.html
imagecreate :: D -> D -> SE D #
Create an empty image of a given size.
Create an empty image of a given size. Individual pixel values can then be set with. imagegetpixel.
iimagenum imagecreate iwidth, iheight
csound doc: http://csound.com/docs/manual/imagecreate.html
Frees memory allocated for a previously loaded or created image.
imagefree iimagenum
csound doc: http://csound.com/docs/manual/imagefree.html
imagegetpixel :: D -> Sig -> Sig -> (Sig, Sig, Sig) #
Return the RGB pixel values of a previously opened or created image.
Return the RGB pixel values of a previously opened or created image. An image can be loaded with imageload. An empty image can be created with imagecreate.
ared, agreen, ablue imagegetpixel iimagenum, ax, ay kred, kgreen, kblue imagegetpixel iimagenum, kx, ky
csound doc: http://csound.com/docs/manual/imagegetpixel.html
Load an image.
Load an image and return a reference to it. Individual pixel values can then be accessed with imagegetpixel.
iimagenum imageload filename
csound doc: http://csound.com/docs/manual/imageload.html
imagesave :: D -> Spec -> SE () #
Save a previously created image.
Save a previously created image. An empty image can be created with imagecreate and its pixel RGB values can be set with imagesetpixel. The image will be saved in PNG format.
imagesave iimagenum, filename
csound doc: http://csound.com/docs/manual/imagesave.html
imagesetpixel :: D -> Sig -> Sig -> Sig -> Sig -> Sig -> SE () #
Set the RGB value of a pixel inside a previously opened or created image.
Set the RGB value of a pixel inside a previously opened or created image. An image can be loaded with imageload. An empty image can be created with imagecreate and saved with imagesave.
imagesetpixel iimagenum, ax, ay, ared, agreen, ablue imagesetpixel iimagenum, kx, ky, kred, kgreen, kblue
csound doc: http://csound.com/docs/manual/imagesetpixel.html
Return the width and height of a previously opened or created image.
Return the width and height of a previously opened or created image. An image can be loaded with imageload. An empty image can be created with imagecreate.
iwidth, iheight imagesize iimagenum
csound doc: http://csound.com/docs/manual/imagesize.html
Stops one of a number of internal clocks.
clockoff inum
csound doc: http://csound.com/docs/manual/clockoff.html
Starts one of a number of internal clocks.
clockon inum
csound doc: http://csound.com/docs/manual/clockon.html
compilecsd :: Str -> D #
compiles a new orchestra from an ASCII file
Compilecsd will read a CSD file and compile one or more instruments at init time, which will be added to the running engine. In case of existing instrument numbers or names, these will be replaced, but any instance still running of the old instrument definition will still perform until it terminates. In addition, it will read the score (if it exists) contained in the CSD file and add it to the list of events to be performed by Csound. The opcode ignores any section in the CSD file that is not the orchestra or the score.
ires compilecsd Sfilename
csound doc: http://csound.com/docs/manual/compilecsd.html
compileorc :: Str -> D #
compiles a new orchestra from an ASCII file
Compileorc will compile one or more instruments at init time, which will be added to the running engine. In case of existing instrument numbers or names, these will be replaced, but any instance still running of the old instrument definition will still perform until it terminates.
ires compileorc Sfilename
csound doc: http://csound.com/docs/manual/compileorc.html
compilestr :: Str -> D #
compiles a new orchestra passed in as an ASCII string
Compilestr will compile one or more instruments at init time, which will be added to the running engine. In case of existing instrument numbers or names, these will be replaced, but any instance still running of the old instrument definition will still perform until it terminates. Only new instances will use the new definition. Multi-line strings are accepted, using {{ }} to enclose the string.
ires compilestr Sorch
csound doc: http://csound.com/docs/manual/compilestr.html
Evalstrs evaluates a string containing Csound code, returning a value.
Evalstr compiles and runs Csound code and returns a value from the global space (instr 0). This opcode can be also used to compile new instruments (as compilestr).
ires evalstr Scode kres evalstr Scode, ktrig
csound doc: http://csound.com/docs/manual/evalstr.html
Creates a held note.
Causes a finite-duration note to become a âheldâ note
ihold
csound doc: http://csound.com/docs/manual/ihold.html
Enables an instrument to turn itself off or to turn an instance of another instrument off.
turnoff turnoff inst turnoff knst
csound doc: http://csound.com/docs/manual/turnoff.html
Activate an instrument for an indefinite time.
turnon insnum [, itime]
csound doc: http://csound.com/docs/manual/turnon.html
event :: Str -> Sig -> Sig -> Sig -> [Sig] -> SE () #
Generates a score event from an instrument.
event "scorechar", kinsnum, kdelay, kdur, [, kp4] [, kp5] [, ...] event "scorechar", "insname", kdelay, kdur, [, kp4] [, kp5] [, ...]
csound doc: http://csound.com/docs/manual/event.html
event_i :: Str -> D -> D -> D -> [D] -> SE () #
Generates a score event from an instrument.
event_i "scorechar", iinsnum, idelay, idur, [, ip4] [, ip5] [, ...] event_i "scorechar", "insname", idelay, idur, [, ip4] [, ip5] [, ...]
csound doc: http://csound.com/docs/manual/event_i.html
Mutes/unmutes new instances of a given instrument.
mute insnum [, iswitch] mute "insname" [, iswitch]
csound doc: http://csound.com/docs/manual/mute.html
Schedules a new instrument instance, storing the instance handle in a variable.
Schedules a new instrument nstance, returning a handle that can be used later to refer directly to the running nstance. This opcode is similar to schedule, but has the added facility of retrieving the nstance handle.
iHandle nstance insnum, iwhen, idur [, ip4] [, ip5] [...] iHandle nstance "insname", iwhen, idur [, ip4] [, ip5] [...]
csound doc: http://csound.com/docs/manual/nstance.html
Read, preprocess and schedule a score from an input string.
Readscore will issue one or more score events. It can handle strings in the same conditions as the standard score, including preprocessing (carry, sort, ramp, etc). Multi-line strings are accepted, using {{ }} to enclose the string.
readscore Sin
csound doc: http://csound.com/docs/manual/readscore.html
Removes the definition of an instrument.
Removes the definition of an instrument as long as it is not in use.
remove insnum
csound doc: http://csound.com/docs/manual/remove.html
schedkwhen :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE () #
Adds a new score event generated by a k-rate trigger.
schedkwhen ktrigger, kmintim, kmaxnum, kinsnum, kwhen, kdur \ [, ip4] [, ip5] [...] schedkwhen ktrigger, kmintim, kmaxnum, "insname", kwhen, kdur \ [, ip4] [, ip5] [...]
csound doc: http://csound.com/docs/manual/schedkwhen.html
schedkwhennamed :: Sig -> Sig -> Sig -> Str -> Sig -> Sig -> SE () #
Similar to schedkwhen but uses a named instrument at init-time.
schedkwhennamed ktrigger, kmintim, kmaxnum, "name", kwhen, kdur \ [, ip4] [, ip5] [...]
csound doc: http://csound.com/docs/manual/schedkwhennamed.html
schedule :: D -> D -> D -> SE () #
Adds a new score event.
schedule insnum, iwhen, idur [, ip4] [, ip5] [...] schedule "insname", iwhen, idur [, ip4] [, ip5] [...]
csound doc: http://csound.com/docs/manual/schedule.html
schedwhen :: Sig -> Sig -> Sig -> Sig -> SE () #
Adds a new score event.
schedwhen ktrigger, kinsnum, kwhen, kdur [, ip4] [, ip5] [...] schedwhen ktrigger, "insname", kwhen, kdur [, ip4] [, ip5] [...]
csound doc: http://csound.com/docs/manual/schedwhen.html
scoreline :: Str -> Sig -> SE () #
Issues one or more score line events from an instrument.
Scoreline will issue one or more score events, if ktrig is 1 every k-period. It can handle strings in the same conditions as the standard score. Multi-line strings are accepted, using {{ }} to enclose the string.
scoreline Sin, ktrig
csound doc: http://csound.com/docs/manual/scoreline.html
scoreline_i :: Str -> SE () #
Issues one or more score line events from an instrument at i-time.
scoreline_i will issue score events at i-time. It can handle strings in the same conditions as the standard score. Multi-line strings are accepted, using {{ }} to enclose the string.
scoreline_i Sin
csound doc: http://csound.com/docs/manual/scoreline_i.html
Returns the number of active instances of an instrument.
Returns the number of active instances of an instrument with options to ignore releasing instances.
ir active insnum [,iopt [,inorel]] ir active Sinsname [,iopt [,inorel]] kres active kinsnum [,iopt [,inorel]]
csound doc: http://csound.com/docs/manual/active.html
cpumeter :: Tuple a => D -> a #
Reports the usage of cpu either total or per core.
Reports the usage of cpu either total or per core to monitor how close to max-out the processing is.
ktot[,kcpu1, kcpu2,...] cpumeter ifreq
csound doc: http://csound.com/docs/manual/cpumeter.html
Control allocation of cpu resources on a per-instrument basis, to optimize realtime output.
cpuprc insnum, ipercent cpuprc Sinsname, ipercent
csound doc: http://csound.com/docs/manual/cpuprc.html
Exit Csound as fast as possible, with no cleaning up.
In Csound4 calls an exit function to leave Csound as fast as possible. On Csound5 exits back to the driving code.
exitnow [ivalue]
csound doc: http://csound.com/docs/manual/exitnow.html
jacktransport :: D -> SE () #
Start/stop jack_transport and can optionally relocate the playback head.
jacktransport icommand [, ilocation]
csound doc: http://csound.com/docs/manual/jacktransport.html
Limits the number of allocations of an instrument.
maxalloc insnum, icount maxalloc Sinsname, icount
csound doc: http://csound.com/docs/manual/maxalloc.html
Creates space for instruments but does not run them.
prealloc insnum, icount prealloc "insname", icount
csound doc: http://csound.com/docs/manual/prealloc.html
k-rate signal change detector.
This opcode outputs a trigger signal that informs when any one of its k-rate arguments has changed. Useful with valuator widgets or MIDI controllers.
ktrig changed kvar1 [, kvar2,..., kvarN]
csound doc: http://csound.com/docs/manual/changed.html
k-rate signal change detector.
This opcode outputs a trigger signal that informs when any one of its k-rate arguments has changed, or a value in an array. Useful with valuator widgets or MIDI controllers.
ktrig changed2 kvar1 [, kvar2,..., kvarN] ktrig changed2 karr[] ktrig changed2 aarr[]
csound doc: http://csound.com/docs/manual/changed2.html
Sense on-screen controls.
Sense on-screen controls. Requires Winsound or TCL/TK.
kres checkbox knum
csound doc: http://csound.com/docs/manual/checkbox.html
Configurable slider controls for realtime user input.
Configurable slider controls for realtime user input. Requires Winsound or TCL/TK. control reads a slider's value.
kres control knum
csound doc: http://csound.com/docs/manual/control.html
Envelope follower unit generator.
ares follow asig, idt
csound doc: http://csound.com/docs/manual/follow.html
follow2 :: Sig -> Sig -> Sig -> Sig #
Another controllable envelope extractor.
A controllable envelope extractor using the algorithm attributed to Jean-Marc Jot.
ares follow2 asig, katt, krel
csound doc: http://csound.com/docs/manual/follow2.html
Return Csound settings.
Return various configuration settings in Svalue as a string at init time.
Svalue getcfg iopt
csound doc: http://csound.com/docs/manual/getcfg.html
joystick :: Sig -> Tab -> Sig #
Reads data from a joystick controller.
Reads data from a Linux joystick controller
kres joystick kdevice ktab
csound doc: http://csound.com/docs/manual/joystick.html
midifilestatus :: Sig #
Returns the playback status of MIDI file input.
Returns the current playback status at k-rate, of the input MIDI file, 1 if file is playing, 0 if the end-of-the file has been reached.
ksig midifilestatus
csound doc: http://csound.com/docs/manual/midifilestatus.html
Returns the current tempo at k-rate, of either the MIDI file (if available) or the score
ksig miditempo
csound doc: http://csound.com/docs/manual/miditempo.html
p5gconnect :: SE () #
Reads data from a P5 Glove controller.
Opens and at control-rate polls a P5 Glove controller.
p5gconnect
csound doc: http://csound.com/docs/manual/p5gconnect.html
Reads data fields from an external P5 Glove.
Reads data fields from a P5 Glove controller.
kres p5gdata kcontrol
csound doc: http://csound.com/docs/manual/p5gdata.html
Returns the number of pfields belonging to a note event.
pcount returns the number of pfields belonging to a note event.
icount pcount
csound doc: http://csound.com/docs/manual/pcount.html
Maintains the output equal to the highest absolute value received.
These opcodes maintain the output k-rate variable as the peak absolute level so far received.
kres peak asig kres peak ksig
csound doc: http://csound.com/docs/manual/peak.html
Returns the value of a specified pfield.
pindex returns the value of a specified pfield.
ivalue pindex ipfieldIndex
csound doc: http://csound.com/docs/manual/pindex.html
pitch :: Sig -> D -> D -> D -> D -> (Sig, Sig) #
Tracks the pitch of a signal.
Using the same techniques as spectrum and specptrk, pitch tracks the pitch of the signal in octave point decimal form, and amplitude in dB.
koct, kamp pitch asig, iupdte, ilo, ihi, idbthresh [, ifrqs] [, iconf] \ [, istrt] [, iocts] [, iq] [, inptls] [, irolloff] [, iskip]
csound doc: http://csound.com/docs/manual/pitch.html
pitchamdf :: Sig -> D -> D -> (Sig, Sig) #
Follows the pitch of a signal based on the AMDF method.
Follows the pitch of a signal based on the AMDF method (Average Magnitude Difference Function). Outputs pitch and amplitude tracking signals. The method is quite fast and should run in realtime. This technique usually works best for monophonic signals.
kcps, krms pitchamdf asig, imincps, imaxcps [, icps] [, imedi] \ [, idowns] [, iexcps] [, irmsmedi]
csound doc: http://csound.com/docs/manual/pitchamdf.html
plltrack :: Sig -> Sig -> (Sig, Sig) #
Tracks the pitch of a signal.
plltrack, a pitch tracker based on a phase-locked loop algorithm, described in Zolzer, U, Sankarababu, S.V. and Moller, S, "PLL-based Pitch Detection and Tracking for Audio Signals. Proc. of IIH-MSP 2012".
acps, alock plltrack asig, kd [, kloopf, kloopq, klf, khf, kthresh]
csound doc: http://csound.com/docs/manual/plltrack.html
ptrack :: Sig -> D -> (Sig, Sig) #
Tracks the pitch of a signal.
ptrack takes an input signal, splits it into ihopsize blocks and using a STFT method, extracts an estimated pitch for its fundamental frequency as well as estimating the total amplitude of the signal in dB, relative to full-scale (0dB). The method implies an analysis window size of 2*ihopsize samples (overlaping by 1/2 window), which has to be a power-of-two, between 128 and 8192 (hopsizes between 64 and 4096). Smaller windows will give better time precision, but worse frequency accuracy (esp. in low fundamentals).This opcode is based on an original algorithm by M. Puckette.
kcps, kamp ptrack asig, ihopsize[,ipeaks]
csound doc: http://csound.com/docs/manual/ptrack.html
readscratch :: D #
returns a value stored in the instance of an instrument.
The readscratch opcode returns one of four scalar values stored in the instance of an instrument.
ival readscratch [index]
csound doc: http://csound.com/docs/manual/readscratch.html
rewindscore :: SE () #
Rewinds the playback position of the current score performance.
Rewinds the playback position of the current score performance..
rewindscore
csound doc: http://csound.com/docs/manual/rewindscore.html
Determines the root-mean-square amplitude of an audio signal.
Determines the root-mean-square amplitude of an audio signal. It low-pass filters the actual value, to average in the manner of a VU meter.
kres rms asig [, ihp] [, iskip]
csound doc: http://csound.com/docs/manual/rms.html
Returns the ASCII code of a key that has been pressed.
Returns the ASCII code of a key that has been pressed, or -1 if no key has been pressed.
kres[, kkeydown] sensekey
csound doc: http://csound.com/docs/manual/sensekey.html
seqtime :: Sig -> Sig -> Sig -> Sig -> Tab -> Sig #
Generates a trigger signal according to the values stored in a table.
ktrig_out seqtime ktime_unit, kstart, kloop, kinitndx, kfn_times
csound doc: http://csound.com/docs/manual/seqtime.html
seqtime2 :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig #
Generates a trigger signal according to the values stored in a table.
ktrig_out seqtime2 ktrig_in, ktime_unit, kstart, kloop, kinitndx, kfn_times
csound doc: http://csound.com/docs/manual/seqtime2.html
setctrl :: D -> D -> D -> SE () #
Configurable slider controls for realtime user input.
Configurable slider controls for realtime user input. Requires Winsound or TCL/TK. setctrl sets a slider to a specific value, or sets a minimum or maximum range.
setctrl inum, ival, itype
csound doc: http://csound.com/docs/manual/setctrl.html
setscorepos :: D -> SE () #
Sets the playback position of the current score performance to a given position.
setscorepos ipos
csound doc: http://csound.com/docs/manual/setscorepos.html
splitrig :: Sig -> Sig -> D -> Tab -> [Sig] -> SE () #
Split a trigger signal
splitrig splits a trigger signal (i.e. a timed sequence of control-rate impulses) into several channels following a structure designed by the user.
splitrig ktrig, kndx, imaxtics, ifn, kout1 [,kout2,...,koutN]
csound doc: http://csound.com/docs/manual/splitrig.html
tempest :: Sig -> D -> D -> D -> D -> D -> D -> D -> D -> Tab -> Sig #
Estimate the tempo of beat patterns in a control signal.
ktemp tempest kin, iprd, imindur, imemdur, ihp, ithresh, ihtim, ixfdbak, \ istartempo, ifn [, idisprd] [, itweek]
csound doc: http://csound.com/docs/manual/tempest.html
Apply tempo control to an uninterpreted score.
tempo ktempo, istartempo
csound doc: http://csound.com/docs/manual/tempo.html
Reads the current value of the tempo.
kres tempoval
csound doc: http://csound.com/docs/manual/tempoval.html
timedseq :: Sig -> Tab -> [Sig] -> Sig #
Time Variant Sequencer
An event-sequencer in which time can be controlled by a time-pointer. Sequence data are stored into a table.
ktrig timedseq ktimpnt, ifn, kp1 [,kp2, kp3, ...,kpN]
csound doc: http://csound.com/docs/manual/timedseq.html
trigger :: Sig -> Sig -> Sig -> Sig #
Informs when a krate signal crosses a threshold.
kout trigger ksig, kthreshold, kmode
csound doc: http://csound.com/docs/manual/trigger.html
trigseq :: Sig -> Sig -> Sig -> Sig -> Tab -> [Sig] -> SE () #
Accepts a trigger signal as input and outputs a group of values.
trigseq ktrig_in, kstart, kloop, kinitndx, kfn_values, kout1 [, kout2] [...]
csound doc: http://csound.com/docs/manual/trigseq.html
Envelope follower unit generator.
Envelope follower unit generator emmulating a Perkin Elmer Vactrole VTL5C3/2.
ares vactrol asig [iup, idown]
csound doc: http://csound.com/docs/manual/vactrol.html
wiiconnect :: D #
Reads data from a number of external Nintendo Wiimote controllers.
Opens and at control-rate polls up to four external Nintendo Wiimote controllers.
ires wiiconnect [itimeout, imaxnum]
csound doc: http://csound.com/docs/manual/wiiconnect.html
Reads data fields from a number of external Nintendo Wiimote controllers.
Reads data fields from upto four external Nintendo Wiimote controllers.
kres wiidata kcontrol[, knum]
csound doc: http://csound.com/docs/manual/wiidata.html
wiirange :: D -> D -> D -> SE () #
Sets scaling and range limits for certain Wiimote fields.
wiirange icontrol, iminimum, imaximum[, inum]
csound doc: http://csound.com/docs/manual/wiirange.html
wiisend :: Sig -> Sig -> Sig #
Sends data to one of a number of external Nintendo Wiimote controllers.
kres wiisend kcontrol, kvalue[, knum]
csound doc: http://csound.com/docs/manual/wiisend.html
writescratch :: D -> SE () #
writes a value into the scratchpad of the instance of an instrument.
The writescratch opcode writes one of four scalar values to be stored in the instance of an instrument.
writescratch ival[, index]
csound doc: http://csound.com/docs/manual/writescratch.html
xyin :: D -> D -> D -> D -> D -> (Sig, Sig) #
Sense the cursor position in an output window
Sense the cursor position in an output window. When xyin is called the position of the mouse within the output window is used to reply to the request. This simple mechanism does mean that only one xyin can be used accurately at once. The position of the mouse is reported in the output window.
kx, ky xyin iprd, ixmin, ixmax, iymin, iymax [, ixinit] [, iyinit]
csound doc: http://csound.com/docs/manual/xyin.html
Pops values from the global stack. Deprecated.
Pops values from the global stack.
xval1, [xval2, ... , xval31] pop ival1, [ival2, ... , ival31] pop
csound doc: http://csound.com/docs/manual/pop.html
Pops an f-sig frame from the global stack. Deprecated.
Pops an f-sig frame from the global stack.
fsig pop_f
csound doc: http://csound.com/docs/manual/pop_f.html
Pushes a value into the global stack. Deprecated.
Pushes a value into the global stack.
push xval1, [xval2, ... , xval31] push ival1, [ival2, ... , ival31]
csound doc: http://csound.com/docs/manual/push.html
Pushes an f-sig frame into the global stack. Deprecated.
Pushes an f-sig frame into the global stack.
push_f fsig
csound doc: http://csound.com/docs/manual/push_f.html
Initializes the stack. Deprecated.
Initializes and sets the size of the global stack.
stack iStackSize
csound doc: http://csound.com/docs/manual/stack.html
subinstr :: Tuple a => D -> [D] -> a #
Creates and runs a numbered instrument instance.
Creates an instance of another instrument and is used as if it were an opcode.
a1, [...] [, a8] subinstr instrnum [, p4] [, p5] [...] a1, [...] [, a8] subinstr "insname" [, p4] [, p5] [...]
csound doc: http://csound.com/docs/manual/subinstr.html
subinstrinit :: D -> [D] -> SE () #
Creates and runs a numbered instrument instance at init-time.
Same as subinstr, but init-time only and has no output arguments.
subinstrinit instrnum [, p4] [, p5] [...] subinstrinit "insname" [, p4] [, p5] [...]
csound doc: http://csound.com/docs/manual/subinstrinit.html
Returns the number seconds since a base date.
Returns the number seconds since a base date, using the operating system's clock. The base is 1 January 1970 for Csound using doubles, and 1 January 2010 for versions using floats. On operating systemms with sufficient resolution the date includes fractional seconds.
ir[, inano] date kr[, knano] date
csound doc: http://csound.com/docs/manual/date.html
Returns as a string the date and time specified.
Sir dates [ itime]
csound doc: http://csound.com/docs/manual/dates.html
Reads the value of an internal clock.
ir readclock inum
csound doc: http://csound.com/docs/manual/readclock.html
Read the real time clock from the operating system.
Read the real-time clock from the operating system.
ires rtclock kres rtclock
csound doc: http://csound.com/docs/manual/rtclock.html
Read absolute time in k-rate cycles.
Read absolute time, in k-rate cycles, since the start of an instance of an instrument. Called at both i-time as well as k-time.
kres timeinstk
csound doc: http://csound.com/docs/manual/timeinstk.html
Read absolute time in seconds.
Read absolute time, in seconds, since the start of an instance of an instrument.
kres timeinsts
csound doc: http://csound.com/docs/manual/timeinsts.html
Read absolute time in k-rate cycles.
Read absolute time, in k-rate cycles, since the start of the performance.
ires timek kres timek
csound doc: http://csound.com/docs/manual/timek.html
jackoAudioIn :: Str -> SE Sig #
Receives an audio signal from a Jack port.
Receives an audio signal from a Jack audio input port inside this instance of Csound, which in turn has received the signal from its connected external Jack audio output port.
asignal JackoAudioIn ScsoundPortName
csound doc: http://csound.com/docs/manual/JackoAudioIn.html
jackoAudioInConnect :: Str -> Str -> SE () #
Creates an audio connection from a Jack port to Csound.
In the orchestra header, creates an audio connection from an external Jack audio output port to a Jack audio input port inside this instance of Csound.
JackoAudioInConnect SexternalPortName, ScsoundPortName
csound doc: http://csound.com/docs/manual/JackoAudioInConnect.html
jackoAudioOut :: Str -> Sig -> SE () #
Sends an audio signal to a Jack port.
Sends an audio signal to an internal Jack audio output port, and in turn to its connected external Jack audio input port.
JackoAudioOut ScsoundPortName, asignal
csound doc: http://csound.com/docs/manual/JackoAudioOut.html
jackoAudioOutConnect :: Str -> Str -> SE () #
Creates an audio connection from Csound to a Jack port.
In the orchestra header, creates an audio connection from a Jack audio output port inside this instance of Csound to an external Jack audio input port.
JackoAudioOutConnect ScsoundPortName, SexternalPortName
csound doc: http://csound.com/docs/manual/JackoAudioOutConnect.html
jackoInit :: Str -> Str -> SE () #
Initializes Csound as a Jack client.
Initializes this instance of Csound as a Jack client.
JackoInit ServerName, SclientName
csound doc: http://csound.com/docs/manual/JackoInit.html
jackoMidiInConnect :: Str -> Str -> SE () #
Creates a MIDI connection from a Jack port to Csound.
In the orchestra header, creates a MIDI connection from an external Jack MIDI output port to this instance of Csound.
JackoMidiInConnect SexternalPortName, ScsoundPortName
csound doc: http://csound.com/docs/manual/JackoMidiInConnect.html
jackoMidiOut :: Str -> Sig -> Sig -> Sig -> SE () #
Sends a MIDI channel message to a Jack port.
Sends a MIDI channel message to a Jack MIDI output port inside this instance of Csound, and in turn to its connected external Jack MIDI input port.
JackoMidiOut ScsoundPortName, kstatus, kchannel, kdata1[, kdata2]
csound doc: http://csound.com/docs/manual/JackoMidiOut.html
jackoMidiOutConnect :: Str -> Str -> SE () #
Creates a MIDI connection from Csound to a Jack port.
In the orchestra header, creates a connection from a Jack MIDI output port inside this instance of Csound to an external Jack MIDI input port.
JackoMidiOutConnect ScsoundPortName, SexternalPortName
csound doc: http://csound.com/docs/manual/JackoMidiOutConnect.html
jackoNoteOut :: Str -> Sig -> Sig -> Sig -> SE () #
Sends a MIDI channel message to a Jack port.
Sends a MIDI channel message to a Jack MIDI output port inside this instance of Csound, and in turn to its connected external Jack MIDI input port.
JackoNoteOut ScsoundPortName, kstatus, kchannel, kdata1[, kdata2]
csound doc: http://csound.com/docs/manual/JackoNoteOut.html
Enables or disables all Jack ports.
In the orchestra header, after all Jack connections have been created, enables or disables all Jack input and output opcodes inside this instance of Csound to read or write data.
JackoOn [iactive]
csound doc: http://csound.com/docs/manual/JackoOn.html
jackoTransport :: Sig -> SE () #
Control the Jack transport.
Starts, stops, or repositions the Jack transport. This is useful, e.g., for starting an external sequencer playing to send MIDI messages to Csound.
JackoTransport kcommand, [kposition]
csound doc: http://csound.com/docs/manual/JackoTransport.html
vincr :: Sig -> Sig -> SE () #
Accumulates audio signals.
vincr increments one audio variable with another signal, i.e. it accumulates output.
vincr accum, aincr
csound doc: http://csound.com/docs/manual/vincr.html
Returns the amplitude equivalent of the decibel value x.
Returns the amplitude equivalent of the decibel value x. Thus:
ampdb (x) (no rate restriction)
csound doc: http://csound.com/docs/manual/ampdb.html
ampdbfs :: SigOrD a => a -> a #
Returns the amplitude equivalent (in 16-bit signed integer scale) of the full scale decibel (dB FS) value x.
Returns the amplitude equivalent of the full scale decibel (dB FS) value x. The logarithmic full scale decibel values will be converted to linear 16-bit signed integer values from â32,768 to +32,767.
ampdbfs (x) (no rate restriction)
csound doc: http://csound.com/docs/manual/ampdbfs.html
Returns the decibel equivalent of the raw amplitude x.
dbamp (x) (init-rate or control-rate args only)
csound doc: http://csound.com/docs/manual/dbamp.html
dbfsamp :: SigOrD a => a -> a #
Returns the decibel equivalent of the raw amplitude x, relative to full scale amplitude.
Returns the decibel equivalent of the raw amplitude x, relative to full scale amplitude. Full scale is assumed to be 16 bit. New is Csound version 4.10.
dbfsamp (x) (init-rate or control-rate args only)
csound doc: http://csound.com/docs/manual/dbfsamp.html
birnd :: SigOrD a => a -> SE a #
Returns a random number in a bi-polar range.
birnd (x) (init- or control-rate only)
csound doc: http://csound.com/docs/manual/birnd.html
rnd :: SigOrD a => a -> SE a #
Returns a random number in a unipolar range at the rate given by the input argument.
rnd (x) (init- or control-rate only)
csound doc: http://csound.com/docs/manual/rnd.html
divz :: SigOrD a => a -> a -> a #
Safely divides two numbers.
ares divz xa, xb, ksubst ires divz ia, ib, isubst kres divz ka, kb, ksubst ... divz (ka, kb, ksubst)... (no rate restriction)
csound doc: http://csound.com/docs/manual/divz.html
Multiplies and accumulates a- and k-rate signals.
ares mac ksig1, asig1 [, ksig2] [, asig2] [, ksig3] [, asig3] [...]
csound doc: http://csound.com/docs/manual/mac.html
Multiply and accumulate a-rate signals only.
ares maca asig1 , asig2 [, asig3] [, asig4] [, asig5] [...]
csound doc: http://csound.com/docs/manual/maca.html
polynomial :: Sig -> [Sig] -> Sig #
Efficiently evaluates a polynomial of arbitrary order.
The polynomial opcode calculates a polynomial with a single a-rate input variable. The polynomial is a sum of any number of terms in the form kn*x^n where kn is the nth coefficient of the expression. These coefficients are k-rate values.
aout polynomial ain, k0 [, k1 [, k2 [...]]]
csound doc: http://csound.com/docs/manual/polynomial.html
Computes one argument to the power of another argument.
Computes xarg to the power of kpow (or ipow) and scales the result by inorm.
ares pow aarg, kpow [, inorm] ires pow iarg, ipow [, inorm] kres pow karg, kpow [, inorm] ires[] pow iarg[], ipow[] kres[] pow karg[], kpow[] ires[] pow iarg[], ipow kres[] pow karg[], kpow
csound doc: http://csound.com/docs/manual/pow.html
Multiplies any number of a-rate signals.
ares product asig1, asig2 [, asig3] [...]
csound doc: http://csound.com/docs/manual/product.html
Sums any number of a-rate signals, or array elements.
ares sum asig1 [, asig2] [, asig3] [...] kres sum karr ires sum iarr
csound doc: http://csound.com/docs/manual/sum.html
taninv2 :: SigOrD a => a -> a -> a #
Returns an arctangent.
Returns the arctangent of iyix, kykx, or ay/ax.
ares taninv2 ay, ax ires taninv2 iy, ix kres taninv2 ky, kx ... taninv2 (ky, kx)... (no rate restriction)
csound doc: http://csound.com/docs/manual/taninv2.html
returns the length of a Farey Sequence.
This opcode can be used in conjunction with GENfarey. It calculates the length of Farey Sequence Fn. Its length is given by: |Fn| = 1 + SUM over n phi(m) where phi(m) is Euler's totient function, which gives the number of integers ⤠m that are coprime to m.
kfl fareylen kfn
csound doc: http://csound.com/docs/manual/fareylen.html
returns the length of a Farey Sequence.
This opcode can be used in conjunction with GENfarey. It calculates the length of Farey Sequence Fn. Its length is given by: |Fn| = 1 + SUM over n phi(m) where phi(m) is Euler's totient function, which gives the number of integers ⤠m that are coprime to m.
ifl fareyleni ifn
csound doc: http://csound.com/docs/manual/fareyleni.html
modmatrix :: Tab -> Tab -> Tab -> D -> D -> D -> Sig -> SE () #
Modulation matrix opcode with optimizations for sparse matrices.
The opcode can be used to let a large number of k-rate modulator variables modulate a large number of k-rate parameter variables, with arbitrary scaling of each modulator-to-parameter connection. Csound ftables are used to hold both the input (parameter) variables, the modulator variables, and the scaling coefficients. Output variables are written to another Csound ftable.
modmatrix iresfn, isrcmodfn, isrcparmfn, imodscale, inum_mod, \\ inum_parm, kupdate
csound doc: http://csound.com/docs/manual/modmatrix.html
Asks the underlying operating system for the current directory name as a string.
pwd call the operating system to determine the current directory (folder). pwd runs at i-time only.
Sres pwd
csound doc: http://csound.com/docs/manual/pwd.html
select :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
Select sample value based on audio-rate comparisons.
Select sample value from three based on audio-rate comparisons of two signals.
aout select a1, a2, aless, aequal, amore
csound doc: http://csound.com/docs/manual/select.html
Call an external program via the system call
system and system_i call any external command understood by the operating system, similarly to the C function system(). system_i runs at i-time only, while system runs both at initialization and performance time.
ires system_i itrig, Scmd, [inowait]
csound doc: http://csound.com/docs/manual/system.html
Call an external program via the system call
system and system_i call any external command understood by the operating system, similarly to the C function system(). system_i runs at i-time only, while system runs both at initialization and performance time.
kres system ktrig, Scmd, [knowait]
csound doc: http://csound.com/docs/manual/system.html
tableshuffle :: Sig -> SE () #
shuffles the content of a function table so that each element of the source table is put into a different random position.
This opcode can be used in order to shuffle the content of function tables into a random order but without loosing any of the elements. Imagine shuffling a deck of cards. Each element of the table is copied to a different random position. If that position was already chosen before then the next free position is chosen. The length of the table remains the same.
tableshuffle ktablenum
csound doc: http://csound.com/docs/manual/tableshuffle.html
tableshufflei :: D -> SE () #
shuffles the content of a function table so that each element of the source table is put into a different random position.
This opcode can be used in order to shuffle the content of function tables into a random order but without loosing any of the elements. Imagine shuffling a deck of cards. Each element of the table is copied to a different random position. If that position was already chosen before then the next free position is chosen. The length of the table remains the same.
tableshufflei itablenum
csound doc: http://csound.com/docs/manual/tableshuffle.html
mixerClear :: SE () #
Resets all channels of a buss to 0.
MixerClear
csound doc: http://csound.com/docs/manual/MixerClear.html
mixerGetLevel :: D -> D -> SE Sig #
Gets the level of a send to a buss.
Gets the level at which signals from the send are being added to the buss. The actual sending of the signal to the buss is performed by the MixerSend opcode.
kgain MixerGetLevel isend, ibuss
csound doc: http://csound.com/docs/manual/MixerGetLevel.html
mixerReceive :: D -> D -> SE Sig #
Receives an arate signal from a channel of a buss.
Receives an arate signal that has been mixed onto a channel of a buss.
asignal MixerReceive ibuss, ichannel
csound doc: http://csound.com/docs/manual/MixerReceive.html
mixerSend :: Sig -> D -> D -> D -> SE () #
Mixes an arate signal into a channel of a buss.
MixerSend asignal, isend, ibuss, ichannel
csound doc: http://csound.com/docs/manual/MixerSend.html
mixerSetLevel :: D -> D -> Sig -> SE () #
Sets the level of a send to a buss.
Sets the level at which signals from the send are added to the buss. The actual sending of the signal to the buss is performed by the MixerSend opcode.
MixerSetLevel isend, ibuss, kgain
csound doc: http://csound.com/docs/manual/MixerSetLevel.html
mixerSetLevel_i :: D -> D -> D -> SE () #
Sets the level of a send to a buss.
Sets the level at which signals from the send are added to the buss. This opcode, because all parameters are irate, may be used in the orchestra header. The actual sending of the signal to the buss is performed by the MixerSend opcode.
MixerSetLevel_i isend, ibuss, igain
csound doc: http://csound.com/docs/manual/MixerSetLevel_i.html
remoteport :: D -> SE () #
Defines the port for use with the remote system.
Defines the port for use with the insremot, midremot, insglobal and midglobal opcodes.
remoteport iportnum
csound doc: http://csound.com/docs/manual/remoteport.html
Receives data from other processes using the low-level UDP or TCP protocols
Receives directly using the UDP (sockrecv and sockrecvs) or TCP (strecv) protocol onto a network. The data is not subject to any encoding or special routing. The sockrecvs opcode receives a stereo signal interleaved.
asig sockrecv iport, ilength ksig sockrecv iport, ilength
csound doc: http://csound.com/docs/manual/sockrecv.html
sockrecvs :: D -> D -> (Sig, Sig) #
Receives data from other processes using the low-level UDP or TCP protocols
Receives directly using the UDP (sockrecv and sockrecvs) or TCP (strecv) protocol onto a network. The data is not subject to any encoding or special routing. The sockrecvs opcode receives a stereo signal interleaved.
asigl, asigr sockrecvs iport, ilength
csound doc: http://csound.com/docs/manual/sockrecv.html
Receives data from other processes using the low-level UDP or TCP protocols
Receives directly using the UDP (sockrecv and sockrecvs) or TCP (strecv) protocol onto a network. The data is not subject to any encoding or special routing. The sockrecvs opcode receives a stereo signal interleaved.
asig strecv Sipaddr, iport
csound doc: http://csound.com/docs/manual/sockrecv.html
socksend :: Sig -> Str -> D -> D -> SE () #
Sends data to other processes using the low-level UDP or TCP protocols
Transmits data directly using the UDP (socksend and socksends) or TCP (stsend) protocol onto a network. The data is not subject to any encoding or special routing. The socksends opcode send a stereo signal interleaved.
socksend asig, Sipaddr, iport, ilength socksend ksig, Sipaddr, iport, ilength
csound doc: http://csound.com/docs/manual/socksend.html
socksends :: Sig -> Sig -> Str -> D -> D -> SE () #
Sends data to other processes using the low-level UDP or TCP protocols
Transmits data directly using the UDP (socksend and socksends) or TCP (stsend) protocol onto a network. The data is not subject to any encoding or special routing. The socksends opcode send a stereo signal interleaved.
socksends asigl, asigr, Sipaddr, iport, ilength
csound doc: http://csound.com/docs/manual/socksend.html
stsend :: Sig -> Str -> D -> SE () #
Sends data to other processes using the low-level UDP or TCP protocols
Transmits data directly using the UDP (socksend and socksends) or TCP (stsend) protocol onto a network. The data is not subject to any encoding or special routing. The socksends opcode send a stereo signal interleaved.
stsend asig, Sipaddr, iport
csound doc: http://csound.com/docs/manual/socksend.html
Listen for all OSC messages at a given port.
On each k-cycle looks to see if an OSC message has been received at a given port and copies its contents to a string array. All messages are copied. If a bundle of messages is received, the output array will contain all of the messages in it.
Smess[],klen OSCraw iport
csound doc: http://csound.com/docs/manual/OSCraw.html
Calculates a factor to raise/lower a frequency by a given amount of cents.
cent (x)
csound doc: http://csound.com/docs/manual/cent.html
cpsmidinn :: SigOrD a => a -> a #
Converts a Midi note number value to cycles-per-second.
cpsmidinn (MidiNoteNumber) (init- or control-rate args only)
csound doc: http://csound.com/docs/manual/cpsmidinn.html
cpsoct :: SigOrD a => a -> a #
Converts an octave-point-decimal value to cycles-per-second.
cpsoct (oct) (no rate restriction)
csound doc: http://csound.com/docs/manual/cpsoct.html
cpspch :: SigOrD a => a -> a #
Converts a pitch-class value to cycles-per-second.
cpspch (pch) (init- or control-rate args only)
csound doc: http://csound.com/docs/manual/cpspch.html
Convert frequency to midi
Convert frequency to midi note number, taking global value of A4 into account.
imidi ftom ifreq kmidi ftom kfreq
csound doc: http://csound.com/docs/manual/ftom.html
Convert a midi to frequency
Convert a midi note number value to cycles per second, taking global value of A4 into account.
ifreq mtof imidi kfreq mtof kmidi
csound doc: http://csound.com/docs/manual/mtof.html
Convert midi note number to string note name
Convert midi note number to string note name, with an accuracy of 1 cent.
Snote mton kmidi Snote mton imidi
csound doc: http://csound.com/docs/manual/mton.html
Convert note name to midi note number
Convert note name to midi note number. It allows note name to include microtones or a deviation in cents.
kmidi ntom Snote imidi ntom Snote
csound doc: http://csound.com/docs/manual/ntom.html
octave :: SigOrD a => a -> a #
Calculates a factor to raise/lower a frequency by a given amount of octaves.
octave (x)
csound doc: http://csound.com/docs/manual/octave.html
octcps :: SigOrD a => a -> a #
Converts a cycles-per-second value to octave-point-decimal.
octcps (cps) (init- or control-rate args only)
csound doc: http://csound.com/docs/manual/octcps.html
octmidinn :: SigOrD a => a -> a #
Converts a Midi note number value to octave-point-decimal.
octmidinn (MidiNoteNumber) (init- or control-rate args only)
csound doc: http://csound.com/docs/manual/octmidinn.html
octpch :: SigOrD a => a -> a #
Converts a pitch-class value to octave-point-decimal.
octpch (pch) (init- or control-rate args only)
csound doc: http://csound.com/docs/manual/octpch.html
pchmidinn :: SigOrD a => a -> a #
Converts a Midi note number value to octave point pitch-class units.
pchmidinn (MidiNoteNumber) (init- or control-rate args only)
csound doc: http://csound.com/docs/manual/pchmidinn.html
pchoct :: SigOrD a => a -> a #
Converts an octave-point-decimal value to pitch-class.
pchoct (oct) (init- or control-rate args only)
csound doc: http://csound.com/docs/manual/pchoct.html
Convert pch to midi note number
Convert pch to midi note number. pch representation has the form Octave.pitchclass, pitchclass being a number between 00 and 12.
imidi pchtom ipch kmidi pchtom kpch
csound doc: http://csound.com/docs/manual/pchtom.html
semitone :: SigOrD a => a -> a #
Calculates a factor to raise/lower a frequency by a given amount of semitones.
semitone (x)
csound doc: http://csound.com/docs/manual/semitone.html
Converts a pitch-class value into cycles-per-second (Hz) for equal divisions of the octave.
icps cps2pch ipch, iequal
csound doc: http://csound.com/docs/manual/cps2pch.html
cpstun :: Sig -> Sig -> Tab -> Sig #
Returns micro-tuning values at k-rate.
kcps cpstun ktrig, kindex, kfn
csound doc: http://csound.com/docs/manual/cpstun.html
Returns micro-tuning values at init-rate.
icps cpstuni index, ifn
csound doc: http://csound.com/docs/manual/cpstuni.html
cpsxpch :: D -> D -> D -> D -> D #
Converts a pitch-class value into cycles-per-second (Hz) for equal divisions of any interval.
Converts a pitch-class value into cycles-per-second (Hz) for equal divisions of any interval. There is a restriction of no more than 100 equal divisions.
icps cpsxpch ipch, iequal, irepeat, ibase
csound doc: http://csound.com/docs/manual/cpsxpch.html
dssiactivate :: D -> Sig -> SE () #
Activates or deactivates a DSSI or LADSPA plugin.
dssiactivate is used to activate or deactivate a DSSI or LADSPA plugin. It calles the plugin's activate() and deactivate() functions if they are provided.
dssiactivate ihandle, ktoggle
csound doc: http://csound.com/docs/manual/dssiactivate.html
dssiaudio :: Tuple a => D -> [Sig] -> a #
Processes audio using a LADSPA or DSSI plugin.
dssiaudio generates audio by processing an input signal through a LADSPA plugin.
[aout1, aout2, ..., aout9] dssiaudio ihandle, [ain1, ain2, ..., ain9]
csound doc: http://csound.com/docs/manual/dssiaudio.html
dssictls :: D -> D -> Sig -> Sig -> SE () #
Send control information to a LADSPA or DSSI plugin.
dssictls sends control values to a plugin's control port
dssictls ihandle, iport, kvalue, ktrigger
csound doc: http://csound.com/docs/manual/dssictls.html
Loads a DSSI or LADSPA plugin.
dssiinit is used to load a DSSI or LADSPA plugin into memory for use with the other dssi4cs opcodes. Both LADSPA effects and DSSI instruments can be used.
ihandle dssiinit ilibraryname, iplugindex [, iverbose]
csound doc: http://csound.com/docs/manual/dssiinit.html
Lists all available DSSI and LADSPA plugins.
dssilist checks the variables DSSI_PATH and LADSPA_PATH and lists all plugins available in all plugin libraries there.
dssilist
csound doc: http://csound.com/docs/manual/dssilist.html
VST audio output.
vstaudio and vstaudiog are used for sending and receiving audio from a VST plugin.
aout1,aout2 vstaudio instance, [ain1, ain2]
csound doc: http://csound.com/docs/manual/vstaudio.html
vstaudiog :: D -> (Sig, Sig) #
VST audio output.
vstaudio and vstaudiog are used for sending and receiving audio from a VST plugin.
aout1,aout2 vstaudiog instance, [ain1, ain2]
csound doc: http://csound.com/docs/manual/vstaudio.html
vstbankload :: D -> D -> SE () #
Loads parameter banks to a VST plugin.
vstbankload is used for loading parameter banks to a VST plugin.
vstbankload instance, ipath
csound doc: http://csound.com/docs/manual/vstbankload.html
Opens the GUI editor window for a VST plugin.
vstedit opens the custom GUI editor window for a VST plugin. Note that not all VST plugins have custom GUI editors. It may be necessary to use the --displays command-line option to ensure that Csound handles events from the editor window and displays it properly.
vstedit instance
csound doc: http://csound.com/docs/manual/vstedit.html
Displays the parameters and the programs of a VST plugin.
vstinfo displays the parameters and the programs of a VST plugin.
vstinfo instance
csound doc: http://csound.com/docs/manual/vstinfo.html
Load a VST plugin into memory for use with the other vst4cs opcodes.
vstinit is used to load a VST plugin into memory for use with the other vst4cs opcodes. Both VST effects and instruments (synthesizers) can be used.
instance vstinit ilibrarypath [,iverbose]
csound doc: http://csound.com/docs/manual/vstinit.html
vstmidiout :: D -> Sig -> Sig -> Sig -> Sig -> SE () #
Sends MIDI information to a VST plugin.
vstmidiout is used for sending MIDI information to a VST plugin.
vstmidiout instance, kstatus, kchan, kdata1, kdata2
csound doc: http://csound.com/docs/manual/vstmidiout.html
vstnote :: D -> Sig -> Sig -> Sig -> Sig -> SE () #
Sends a MIDI note with definite duration to a VST plugin.
vstnote sends a MIDI note with definite duration to a VST plugin.
vstnote instance, kchan, knote, kveloc, kdur
csound doc: http://csound.com/docs/manual/vstnote.html
vstparamset :: D -> Sig -> Sig -> SE () #
Used for parameter comunication to and from a VST plugin.
vstparamset and vstparamget are used for parameter comunication to and from a VST plugin.
vstparamset instance, kparam, kvalue
csound doc: http://csound.com/docs/manual/vstparamset.html
vstparamget :: D -> Sig -> Sig #
Used for parameter comunication to and from a VST plugin.
vstparamset and vstparamget are used for parameter comunication to and from a VST plugin.
kvalue vstparamget instance, kparam
csound doc: http://csound.com/docs/manual/vstparamset.html
vstprogset :: D -> Sig -> SE () #
Loads parameter banks to a VST plugin.
vstprogset sets one of the programs in an .fxb bank.
vstprogset instance, kprogram
csound doc: http://csound.com/docs/manual/vstprogset.html
Get the current after-touch value for this channel.
kaft aftouch [imin] [, imax]
csound doc: http://csound.com/docs/manual/aftouch.html
Get the current value of a MIDI channel controller.
Get the current value of a controller and optionally map it onto specified range.
ival chanctrl ichnl, ictlno [, ilow] [, ihigh] kval chanctrl ichnl, ictlno [, ilow] [, ihigh]
csound doc: http://csound.com/docs/manual/chanctrl.html
ctrl14 :: D -> D -> D -> D -> D -> Sig #
Allows a floating-point 14-bit MIDI signal scaled with a minimum and a maximum range.
idest ctrl14 ichan, ictlno1, ictlno2, imin, imax [, ifn] kdest ctrl14 ichan, ictlno1, ictlno2, kmin, kmax [, ifn]
csound doc: http://csound.com/docs/manual/ctrl14.html
ctrl21 :: D -> D -> D -> D -> D -> D -> Sig #
Allows a floating-point 21-bit MIDI signal scaled with a minimum and a maximum range.
idest ctrl21 ichan, ictlno1, ictlno2, ictlno3, imin, imax [, ifn] kdest ctrl21 ichan, ictlno1, ictlno2, ictlno3, kmin, kmax [, ifn]
csound doc: http://csound.com/docs/manual/ctrl21.html
Sets the initial values for a set of MIDI controllers.
ctrlinit ichnl, ictlno1, ival1 [, ictlno2] [, ival2] [, ictlno3] \ [, ival3] [,...ival32]
csound doc: http://csound.com/docs/manual/ctrlinit.html
initc14 :: D -> D -> D -> D -> SE () #
Initializes the controllers used to create a 14-bit MIDI value.
initc14 ichan, ictlno1, ictlno2, ivalue
csound doc: http://csound.com/docs/manual/initc14.html
initc21 :: D -> D -> D -> D -> D -> SE () #
Initializes the controllers used to create a 21-bit MIDI value.
initc21 ichan, ictlno1, ictlno2, ictlno3, ivalue
csound doc: http://csound.com/docs/manual/initc21.html
Assigns a MIDI channel number to a Csound instrument.
massign ichnl, insnum[, ireset] massign ichnl, "insname"[, ireset]
csound doc: http://csound.com/docs/manual/massign.html
midic14 :: D -> D -> D -> D -> Sig #
Allows a floating-point 14-bit MIDI signal scaled with a minimum and a maximum range.
idest midic14 ictlno1, ictlno2, imin, imax [, ifn] kdest midic14 ictlno1, ictlno2, kmin, kmax [, ifn]
csound doc: http://csound.com/docs/manual/midic14.html
midic21 :: D -> D -> D -> D -> D -> Sig #
Allows a floating-point 21-bit MIDI signal scaled with a minimum and a maximum range.
idest midic21 ictlno1, ictlno2, ictlno3, imin, imax [, ifn] kdest midic21 ictlno1, ictlno2, ictlno3, kmin, kmax [, ifn]
csound doc: http://csound.com/docs/manual/midic21.html
midic7 :: D -> D -> D -> Sig #
Allows a floating-point 7-bit MIDI signal scaled with a minimum and a maximum range.
idest midic7 ictlno, imin, imax [, ifn] kdest midic7 ictlno, kmin, kmax [, ifn]
csound doc: http://csound.com/docs/manual/midic7.html
Get the current value (0-127) of a specified MIDI controller.
ival midictrl inum [, imin] [, imax] kval midictrl inum [, imin] [, imax]
csound doc: http://csound.com/docs/manual/midictrl.html
Get a note number from a MIDI event.
ival notnum
csound doc: http://csound.com/docs/manual/notnum.html
Get the current pitch-bend value for this channel.
ibend pchbend [imin] [, imax] kbend pchbend [imin] [, imax]
csound doc: http://csound.com/docs/manual/pchbend.html
pgmassign :: D -> D -> SE () #
Assigns an instrument number to a specified MIDI program.
Assigns an instrument number to a specified (or all) MIDI program(s).
pgmassign ipgm, inst[, ichn] pgmassign ipgm, "insname"[, ichn]
csound doc: http://csound.com/docs/manual/pgmassign.html
Returns the polyphonic after-touch pressure of the selected note number.
polyaft returns the polyphonic pressure of the selected note number, optionally mapped to an user-specified range.
ires polyaft inote [, ilow] [, ihigh] kres polyaft inote [, ilow] [, ihigh]
csound doc: http://csound.com/docs/manual/polyaft.html
Get the velocity from a MIDI event.
ival veloc [ilow] [, ihigh]
csound doc: http://csound.com/docs/manual/veloc.html
nrpn :: Sig -> Sig -> Sig -> SE () #
Sends a Non-Registered Parameter Number to the MIDI OUT port.
Sends a NPRN (Non-Registered Parameter Number) message to the MIDI OUT port each time one of the input arguments changes.
nrpn kchan, kparmnum, kparmvalue
csound doc: http://csound.com/docs/manual/nrpn.html
outiat :: D -> D -> D -> D -> SE () #
Sends MIDI aftertouch messages at i-rate.
outiat ichn, ivalue, imin, imax
csound doc: http://csound.com/docs/manual/outiat.html
outic :: D -> D -> D -> D -> D -> SE () #
Sends MIDI controller output at i-rate.
outic ichn, inum, ivalue, imin, imax
csound doc: http://csound.com/docs/manual/outic.html
outic14 :: D -> D -> D -> D -> D -> D -> SE () #
Sends 14-bit MIDI controller output at i-rate.
outic14 ichn, imsb, ilsb, ivalue, imin, imax
csound doc: http://csound.com/docs/manual/outic14.html
outipat :: D -> D -> D -> D -> D -> SE () #
Sends polyphonic MIDI aftertouch messages at i-rate.
outipat ichn, inotenum, ivalue, imin, imax
csound doc: http://csound.com/docs/manual/outipat.html
outipb :: D -> D -> D -> D -> SE () #
Sends MIDI pitch-bend messages at i-rate.
outipb ichn, ivalue, imin, imax
csound doc: http://csound.com/docs/manual/outipb.html
outipc :: D -> D -> D -> D -> SE () #
Sends MIDI program change messages at i-rate
outipc ichn, iprog, imin, imax
csound doc: http://csound.com/docs/manual/outipc.html
outkat :: Sig -> Sig -> Sig -> Sig -> SE () #
Sends MIDI aftertouch messages at k-rate.
outkat kchn, kvalue, kmin, kmax
csound doc: http://csound.com/docs/manual/outkat.html
outkc :: Sig -> Sig -> Sig -> Sig -> Sig -> SE () #
Sends MIDI controller messages at k-rate.
outkc kchn, knum, kvalue, kmin, kmax
csound doc: http://csound.com/docs/manual/outkc.html
outkc14 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE () #
Sends 14-bit MIDI controller output at k-rate.
outkc14 kchn, kmsb, klsb, kvalue, kmin, kmax
csound doc: http://csound.com/docs/manual/outkc14.html
outkpat :: Sig -> Sig -> Sig -> Sig -> Sig -> SE () #
Sends polyphonic MIDI aftertouch messages at k-rate.
outkpat kchn, knotenum, kvalue, kmin, kmax
csound doc: http://csound.com/docs/manual/outkpat.html
outkpb :: Sig -> Sig -> Sig -> Sig -> SE () #
Sends MIDI pitch-bend messages at k-rate.
outkpb kchn, kvalue, kmin, kmax
csound doc: http://csound.com/docs/manual/outkpb.html
outkpc :: Sig -> Sig -> Sig -> Sig -> SE () #
Sends MIDI program change messages at k-rate.
outkpc kchn, kprog, kmin, kmax
csound doc: http://csound.com/docs/manual/outkpc.html
Get the velocity of the current MIDI event.
iamp ampmidi iscal [, ifn]
csound doc: http://csound.com/docs/manual/ampmidi.html
Musically map MIDI velocity to peak amplitude within a specified dynamic range in decibels.
iamplitude ampmidid ivelocity, idecibels kamplitude ampmidid kvelocity, idecibels
csound doc: http://csound.com/docs/manual/ampmidid.html
Get the note number of the current MIDI event, expressed in cycles-per-second.
icps cpsmidi
csound doc: http://csound.com/docs/manual/cpsmidi.html
Get the note number of the current MIDI event and modify it by the current pitch-bend value, express it in cycles-per-second.
icps cpsmidib [irange] kcps cpsmidib [irange]
csound doc: http://csound.com/docs/manual/cpsmidib.html
Get a MIDI note number (allows customized micro-tuning scales).
This unit is similar to cpsmidi, but allows fully customized micro-tuning scales.
icps cpstmid ifn
csound doc: http://csound.com/docs/manual/cpstmid.html
Get the note number, in octave-point-decimal units, of the current MIDI event.
ioct octmidi
csound doc: http://csound.com/docs/manual/octmidi.html
Get the note number of the current MIDI event and modify it by the current pitch-bend value, express it in octave-point-decimal.
ioct octmidib [irange] koct octmidib [irange]
csound doc: http://csound.com/docs/manual/octmidib.html
Get the note number of the current MIDI event, expressed in pitch-class units.
ipch pchmidi
csound doc: http://csound.com/docs/manual/pchmidi.html
Get the note number of the current MIDI event and modify it by the current pitch-bend value, express it in pitch-class units.
ipch pchmidib [irange] kpch pchmidib [irange]
csound doc: http://csound.com/docs/manual/pchmidib.html
midiin :: (Sig, Sig, Sig, Sig) #
Returns a generic MIDI message received by the MIDI IN port.
Returns a generic MIDI message received by the MIDI IN port
kstatus, kchan, kdata1, kdata2 midiin
csound doc: http://csound.com/docs/manual/midiin.html
midiout :: Sig -> Sig -> Sig -> Sig -> SE () #
Sends a generic MIDI message to the MIDI OUT port.
midiout kstatus, kchan, kdata1, kdata2
csound doc: http://csound.com/docs/manual/midiout.html
midiout_i :: D -> D -> D -> D -> SE () #
Sends a generic MIDI message to the MIDI OUT port.
midiout_i istatus, ichan, idata1, idata2
csound doc: http://csound.com/docs/manual/midiout_i.html
Extend the duration of real-time generated events.
Extend the duration of real-time generated events and handle their extra life (Usually for usage along with release instead of linenr, linsegr, etc).
xtratim iextradur
csound doc: http://csound.com/docs/manual/xtratim.html
midion :: Sig -> Sig -> Sig -> SE () #
Generates MIDI note messages at k-rate.
midion kchn, knum, kvel
csound doc: http://csound.com/docs/manual/midion.html
midion2 :: Sig -> Sig -> Sig -> Sig -> SE () #
Sends noteon and noteoff messages to the MIDI OUT port.
Sends noteon and noteoff messages to the MIDI OUT port when triggered by a value different than zero.
midion2 kchn, knum, kvel, ktrig
csound doc: http://csound.com/docs/manual/midion2.html
moscil :: Sig -> Sig -> Sig -> Sig -> Sig -> SE () #
Sends a stream of the MIDI notes.
moscil kchn, knum, kvel, kdur, kpause
csound doc: http://csound.com/docs/manual/moscil.html
noteoff :: D -> D -> D -> SE () #
Send a noteoff message to the MIDI OUT port.
noteoff ichn, inum, ivel
csound doc: http://csound.com/docs/manual/noteoff.html
noteon :: D -> D -> D -> SE () #
Send a noteon message to the MIDI OUT port.
noteon ichn, inum, ivel
csound doc: http://csound.com/docs/manual/noteon.html
noteondur :: D -> D -> D -> D -> SE () #
Sends a noteon and a noteoff MIDI message both with the same channel, number and velocity.
noteondur ichn, inum, ivel, idur
csound doc: http://csound.com/docs/manual/noteondur.html
noteondur2 :: D -> D -> D -> D -> SE () #
Sends a noteon and a noteoff MIDI message both with the same channel, number and velocity.
noteondur2 ichn, inum, ivel, idur
csound doc: http://csound.com/docs/manual/noteondur2.html
midichannelaftertouch :: Sig -> SE () #
Gets a MIDI channel's aftertouch value.
midichannelaftertouch is designed to simplify writing instruments that can be used interchangeably for either score or MIDI input, and to make it easier to adapt instruments originally written for score input to work with MIDI input.
midichannelaftertouch xchannelaftertouch [, ilow] [, ihigh]
csound doc: http://csound.com/docs/manual/midichannelaftertouch.html
Returns the MIDI channel number from which the note was activated.
midichn returns the MIDI channel number (1 - 16) from which the note was activated. In the case of score notes, it returns 0.
ichn midichn
csound doc: http://csound.com/docs/manual/midichn.html
midicontrolchange :: Sig -> Sig -> SE () #
Gets a MIDI control change value.
midicontrolchange is designed to simplify writing instruments that can be used interchangeably for either score or MIDI input, and to make it easier to adapt instruments originally written for score input to work with MIDI input.
midicontrolchange xcontroller, xcontrollervalue [, ilow] [, ihigh]
csound doc: http://csound.com/docs/manual/midicontrolchange.html
mididefault :: Sig -> Sig -> SE () #
Changes values, depending on MIDI activation.
mididefault is designed to simplify writing instruments that can be used interchangeably for either score or MIDI input, and to make it easier to adapt instruments originally written for score input to work with MIDI input.
mididefault xdefault, xvalue
csound doc: http://csound.com/docs/manual/mididefault.html
midinoteoff :: Sig -> Sig -> SE () #
Gets a MIDI noteoff value.
midinoteoff is designed to simplify writing instruments that can be used interchangeably for either score or MIDI input, and to make it easier to adapt instruments originally written for score input to work with MIDI input.
midinoteoff xkey, xvelocity
csound doc: http://csound.com/docs/manual/midinoteoff.html
midinoteoncps :: Sig -> Sig -> SE () #
Gets a MIDI note number as a cycles-per-second frequency.
midinoteoncps is designed to simplify writing instruments that can be used interchangeably for either score or MIDI input, and to make it easier to adapt instruments originally written for score input to work with MIDI input.
midinoteoncps xcps, xvelocity
csound doc: http://csound.com/docs/manual/midinoteoncps.html
midinoteonkey :: Sig -> Sig -> SE () #
Gets a MIDI note number value.
midinoteonkey is designed to simplify writing instruments that can be used interchangeably for either score or MIDI input, and to make it easier to adapt instruments originally written for score input to work with MIDI input.
midinoteonkey xkey, xvelocity
csound doc: http://csound.com/docs/manual/midinoteonkey.html
midinoteonoct :: Sig -> Sig -> SE () #
Gets a MIDI note number value as octave-point-decimal value.
midinoteonoct is designed to simplify writing instruments that can be used interchangeably for either score or MIDI input, and to make it easier to adapt instruments originally written for score input to work with MIDI input.
midinoteonoct xoct, xvelocity
csound doc: http://csound.com/docs/manual/midinoteonoct.html
midinoteonpch :: Sig -> Sig -> SE () #
Gets a MIDI note number as a pitch-class value.
midinoteonpch is designed to simplify writing instruments that can be used interchangeably for either score or MIDI input, and to make it easier to adapt instruments originally written for score input to work with MIDI input.
midinoteonpch xpch, xvelocity
csound doc: http://csound.com/docs/manual/midinoteonpch.html
midipitchbend :: Sig -> SE () #
Gets a MIDI pitchbend value.
midipitchbend is designed to simplify writing instruments that can be used interchangeably for either score or MIDI input, and to make it easier to adapt instruments originally written for score input to work with MIDI input.
midipitchbend xpitchbend [, ilow] [, ihigh]
csound doc: http://csound.com/docs/manual/midipitchbend.html
midipolyaftertouch :: Sig -> Sig -> SE () #
Gets a MIDI polyphonic aftertouch value.
midipolyaftertouch is designed to simplify writing instruments that can be used interchangeably for either score or MIDI input, and to make it easier to adapt instruments originally written for score input to work with MIDI input.
midipolyaftertouch xpolyaftertouch, xcontrollervalue [, ilow] [, ihigh]
csound doc: http://csound.com/docs/manual/midipolyaftertouch.html
midiprogramchange :: Sig -> SE () #
Gets a MIDI program change value.
midiprogramchange is designed to simplify writing instruments that can be used interchangeably for either score or MIDI input, and to make it easier to adapt instruments originally written for score input to work with MIDI input.
midiprogramchange xprogram
csound doc: http://csound.com/docs/manual/midiprogramchange.html
Send system real-time messages to the MIDI OUT port.
mrtmsg imsgtype
csound doc: http://csound.com/docs/manual/mrtmsg.html
insglobal :: D -> D -> SE () #
An opcode which can be used to implement a remote orchestra. This opcode will send note events from a source machine to many destinations.
With the insremot and insglobal opcodes you are able to perform instruments on remote machines and control them from a master machine. The remote opcodes are implemented using the master/client model. All the machines involved contain the same orchestra but only the master machine contains the information of the score. During the performance the master machine sends the note events to the clients. The insglobal opcode sends the events to all the machines involved in the remote concert. These machines are determined by the insremot definitions made above the insglobal command. To send events to only one machine use insremot.
insglobal isource, instrnum [,instrnum...]
csound doc: http://csound.com/docs/manual/insglobal.html
insremot :: D -> D -> D -> SE () #
An opcode which can be used to implement a remote orchestra. This opcode will send note events from a source machine to one destination.
With the insremot and insglobal opcodes you are able to perform instruments on remote machines and control them from a master machine. The remote opcodes are implemented using the master/client model. All the machines involved contain the same orchestra but only the master machine contains the information of the score. During the performance the master machine sends the note events to the clients. The insremot opcode will send events from a source machine to one destination if you want to send events to many destinations (broadcast) use the insglobal opcode instead. These two opcodes can be used in combination.
insremot idestination, isource, instrnum [,instrnum...]
csound doc: http://csound.com/docs/manual/insremot.html
midglobal :: D -> D -> SE () #
An opcode which can be used to implement a remote midi orchestra. This opcode will broadcast the midi events to all the machines involved in the remote concert.
With the midremot and midglobal opcodes you are able to perform instruments on remote machines and control them from a master machine. The remote opcodes are implemented using the master/client model. All the machines involved contain the same orchestra but only the master machine contains the information of the midi score. During the performance the master machine sends the midi events to the clients. The midglobal opcode sends the events to all the machines involved in the remote concert. These machines are determined by the midremot definitions made above the midglobal command. To send events to only one machine use midremot.
midglobal isource, instrnum [,instrnum...]
csound doc: http://csound.com/docs/manual/midglobal.html
midremot :: D -> D -> D -> SE () #
An opcode which can be used to implement a remote midi orchestra. This opcode will send midi events from a source machine to one destination.
With the midremot and midglobal opcodes you are able to perform instruments on remote machines and control them from a master machine. The remote opcodes are implemented using the master/client model. All the machines involved contain the same orchestra but only the master machine contains the information of the midi score. During the performance the master machine sends the midi events to the clients. The midremot opcode will send events from a source machine to one destination if you want to send events to many destinations (broadcast) use the midglobal opcode instead. These two opcodes can be used in combination.
midremot idestination, isource, instrnum [,instrnum...]
csound doc: http://csound.com/docs/manual/midremot.html
serialBegin :: Str -> SE D #
Open a serial port.
Open a serial port for arduino.
iPort serialBegin SPortName [, ibaudRate]
csound doc: http://csound.com/docs/manual/serialBegin.html
Close a serial port.
Close a serial port for arduino.
serialEnd iPort
csound doc: http://csound.com/docs/manual/serialEnd.html
serialFlush :: D -> SE () #
Flush data from a serial port.
Flush to the screen any bytes (up to 32k) in the input buffer. Note that these bytes will be cleared from the buffer. use this opcode mainly for debugging messages. If you want to mix debugging and other communication messages over the same port, you will need to manually parse the data with the serialRead opcode.
serialFlush iPort
csound doc: http://csound.com/docs/manual/serialFlush.html
serialPrint :: D -> SE () #
Print data from a serial port.
Print to the screen any bytes (up to 32k) in the input buffer. Note that these bytes will be cleared from the buffer. use this opcode mainly for debugging messages. If you want to mix debugging and other communication messages over the same port, you will need to manually parse the data with the serialRead opcode.
serialPrint iPort
csound doc: http://csound.com/docs/manual/serialPrint.html
serialRead :: D -> Sig #
Read data from a serial port.
Read data from a serial port for arduino.
kByte serialRead iPort
csound doc: http://csound.com/docs/manual/serialRead.html
serialWrite :: D -> D -> SE () #
Write data to a serial port.
Write data to a serial port for arduino.
serialWrite iPort, iByte serialWrite iPort, kByte serialWrite iPort, SBytes
csound doc: http://csound.com/docs/manual/serialWrite.html
serialWrite_i :: D -> D -> SE () #
Write data to a serial port.
Write data to a serial port for arduino.
serialWrite_i iPort, iByte serialWrite_i iPort, SBytes
csound doc: http://csound.com/docs/manual/serialWrite_i.html
ftgenonce :: D -> D -> D -> D -> D -> [D] -> SE Tab #
Generate a function table from within an instrument definition, without duplication of data.
Enables the creation of function tables entirely inside instrument definitions, without any duplication of data.
ifno ftgenonce ip1, ip2dummy, isize, igen, iarga, iargb, ...
csound doc: http://csound.com/docs/manual/ftgenonce.html
Receives an arate signal into an instrument through a named port.
asignal inleta Sname
csound doc: http://csound.com/docs/manual/inleta.html
Receives an frate signal (fsig) into an instrument from a named port.
fsignal inletf Sname
csound doc: http://csound.com/docs/manual/inletf.html
Receives a krate signal into an instrument from a named port.
ksignal inletk Sname
csound doc: http://csound.com/docs/manual/inletk.html
inletkid :: Str -> Str -> Sig #
Receives a krate signal into an instrument from a named port.
ksignal inletkid Sname, SinstanceID
csound doc: http://csound.com/docs/manual/inletkid.html
Receives an arate array signal into an instrument through a named port.
array inletv Sname
csound doc: http://csound.com/docs/manual/inletv.html
outleta :: Str -> Sig -> SE () #
Sends an arate signal out from an instrument to a named port.
outleta Sname, asignal
csound doc: http://csound.com/docs/manual/outleta.html
outletf :: Str -> Spec -> SE () #
Sends a frate signal (fsig) out from an instrument to a named port.
outletf Sname, fsignal
csound doc: http://csound.com/docs/manual/outletf.html
outletk :: Str -> Sig -> SE () #
Sends a krate signal out from an instrument to a named port.
outletk Sname, ksignal
csound doc: http://csound.com/docs/manual/outletk.html
outletkid :: Str -> Str -> Sig -> SE () #
Sends a krate signal out from an instrument to a named port.
outletkid Sname, SinstanceID, ksignal
csound doc: http://csound.com/docs/manual/outletkid.html
outletv :: Str -> Sig -> SE () #
Sends an arate array signal out from an instrument to a named port.
outletv Sname, array
csound doc: http://csound.com/docs/manual/outletv.html
adsyn :: Sig -> Sig -> Sig -> Str -> Sig #
Output is an additive set of individually controlled sinusoids, using an oscillator bank.
ares adsyn kamod, kfmod, ksmod, ifilcod
csound doc: http://csound.com/docs/manual/adsyn.html
adsynt :: Sig -> Sig -> Tab -> Tab -> Tab -> D -> Sig #
Performs additive synthesis with an arbitrary number of partials, not necessarily harmonic.
ares adsynt kamp, kcps, iwfn, ifreqfn, iampfn, icnt [, iphs]
csound doc: http://csound.com/docs/manual/adsynt.html
adsynt2 :: Sig -> Sig -> Tab -> Tab -> Tab -> D -> Sig #
Performs additive synthesis with an arbitrary number of partials -not necessarily harmonic- with interpolation.
Performs additive synthesis with an arbitrary number of partials, not necessarily harmonic. (see adsynt for detailed manual)
ar adsynt2 kamp, kcps, iwfn, ifreqfn, iampfn, icnt [, iphs]
csound doc: http://csound.com/docs/manual/adsynt2.html
hsboscil :: Sig -> Sig -> Sig -> D -> Tab -> Tab -> Sig #
An oscillator which takes tonality and brightness as arguments.
An oscillator which takes tonality and brightness as arguments, relative to a base frequency.
ares hsboscil kamp, ktone, kbrite, ibasfreq, iwfn, ioctfn \ [, ioctcnt] [, iphs]
csound doc: http://csound.com/docs/manual/hsboscil.html
oscbnk :: Sig -> Sig -> Sig -> Sig -> D -> D -> Sig -> Sig -> Sig -> Sig -> D -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Tab -> Sig #
Mixes the output of any number of oscillators.
This unit generator mixes the output of any number of oscillators. The frequency, phase, and amplitude of each oscillator can be modulated by two LFOs (all oscillators have a separate set of LFOs, with different phase and frequency); additionally, the output of each oscillator can be filtered through an optional parametric equalizer (also controlled by the LFOs). This opcode is most useful for rendering ensemble (strings, choir, etc.) instruments.
ares oscbnk kcps, kamd, kfmd, kpmd, iovrlap, iseed, kl1minf, kl1maxf, \ kl2minf, kl2maxf, ilfomode, keqminf, keqmaxf, keqminl, keqmaxl, \ keqminq, keqmaxq, ieqmode, kfn [, il1fn] [, il2fn] [, ieqffn] \ [, ieqlfn] [, ieqqfn] [, itabl] [, ioutfn]
csound doc: http://csound.com/docs/manual/oscbnk.html
oscil :: Sig -> Sig -> Tab -> Sig #
A simple oscillator.
oscil reads table ifn sequentially and repeatedly at a frequency xcps. The amplitude is scaled by xamp.
ares oscil xamp, xcps [, ifn, iphs] kres oscil kamp, kcps [, ifn, iphs]
csound doc: http://csound.com/docs/manual/oscil.html
oscil3 :: Sig -> Sig -> Tab -> Sig #
A simple oscillator with cubic interpolation.
oscil3 reads table ifn sequentially and repeatedly at a frequency xcps. The amplitude is scaled by xamp. Cubic interpolation is applied for table look up from internal phase values.
ares oscil3 xamp, xcps [, ifn, iphs] kres oscil3 kamp, kcps [, ifn, iphs]
csound doc: http://csound.com/docs/manual/oscil3.html
oscili :: Sig -> Sig -> Tab -> Sig #
A simple oscillator with linear interpolation.
oscili reads table ifn sequentially and repeatedly at a frequency xcps. The amplitude is scaled by xamp. Linear interpolation is applied for table look up from internal phase values.
ares oscili xamp, xcps[, ifn, iphs] kres oscili kamp, kcps[, ifn, iphs]
csound doc: http://csound.com/docs/manual/oscili.html
oscilikt :: Sig -> Sig -> Tab -> Sig #
A linearly interpolated oscillator that allows changing the table number at k-rate.
oscilikt is very similar to oscili, but allows changing the table number at k-rate. It is slightly slower than oscili (especially with high control rate), although also more accurate as it uses a 31-bit phase accumulator, as opposed to the 24-bit one used by oscili.
ares oscilikt xamp, xcps, kfn [, iphs] [, istor] kres oscilikt kamp, kcps, kfn [, iphs] [, istor]
csound doc: http://csound.com/docs/manual/oscilikt.html
osciliktp :: Sig -> Tab -> Sig -> Sig #
A linearly interpolated oscillator that allows allows phase modulation.
osciliktp allows phase modulation (which is actually implemented as k-rate frequency modulation, by differentiating phase input). The disadvantage is that there is no amplitude control, and frequency can be varied only at the control-rate. This opcode can be faster or slower than oscilikt, depending on the control-rate.
ares osciliktp kcps, kfn, kphs [, istor]
csound doc: http://csound.com/docs/manual/osciliktp.html
oscilikts :: Sig -> Sig -> Tab -> Sig -> Sig -> Sig #
A linearly interpolated oscillator with sync status that allows changing the table number at k-rate.
oscilikts is the same as oscilikt. Except it has a sync input that can be used to re-initialize the oscillator to a k-rate phase value. It is slower than oscilikt and osciliktp.
ares oscilikts xamp, xcps, kfn, async, kphs [, istor]
csound doc: http://csound.com/docs/manual/oscilikts.html
osciln :: Sig -> D -> Tab -> D -> Sig #
Accesses table values at a user-defined frequency.
Accesses table values at a user-defined frequency. This opcode can also be written as oscilx.
ares osciln kamp, ifrq, ifn, itimes
csound doc: http://csound.com/docs/manual/osciln.html
oscils :: D -> D -> D -> Sig #
A simple, fast sine oscillator
Simple, fast sine oscillator, that uses only one multiply, and two add operations to generate one sample of output, and does not require a function table.
ares oscils iamp, icps, iphs [, iflg]
csound doc: http://csound.com/docs/manual/oscils.html
poscil :: Sig -> Sig -> Tab -> Sig #
High precision oscillator.
ares poscil aamp, acps [, ifn, iphs] ares poscil aamp, kcps [, ifn, iphs] ares poscil kamp, acps [, ifn, iphs] ares poscil kamp, kcps [, ifn, iphs] ires poscil kamp, kcps [, ifn, iphs] kres poscil kamp, kcps [, ifn, iphs]
csound doc: http://csound.com/docs/manual/poscil.html
poscil3 :: Sig -> Sig -> Tab -> Sig #
High precision oscillator with cubic interpolation.
ares poscil3 aamp, acps [, ifn, iphs] ares poscil3 aamp, kcps [, ifn, iphs] ares poscil3 kamp, acps [, ifn, iphs] ares poscil3 kamp, kcps [, ifn, iphs] ires poscil3 kamp, kcps [, ifn, iphs] kres poscil3 kamp, kcps [, ifn, iphs]
csound doc: http://csound.com/docs/manual/poscil3.html
vibr :: Sig -> Sig -> Tab -> Sig #
Easier-to-use user-controllable vibrato.
kout vibr kAverageAmp, kAverageFreq, ifn
csound doc: http://csound.com/docs/manual/vibr.html
vibrato :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig #
Generates a natural-sounding user-controllable vibrato.
kout vibrato kAverageAmp, kAverageFreq, kRandAmountAmp, kRandAmountFreq, kAmpMinRate, kAmpMaxRate, kcpsMinRate, kcpsMaxRate, ifn [, iphs
csound doc: http://csound.com/docs/manual/vibrato.html
buzz :: Sig -> Sig -> Sig -> Tab -> Sig #
Output is a set of harmonically related sine partials.
ares buzz xamp, xcps, knh, ifn [, iphs]
csound doc: http://csound.com/docs/manual/buzz.html
gbuzz :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig #
Output is a set of harmonically related cosine partials.
ares gbuzz xamp, xcps, knh, klh, kmul, ifn [, iphs]
csound doc: http://csound.com/docs/manual/gbuzz.html
Generates a set of impulses.
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.
ares mpulse kamp, kintvl [, ioffset]
csound doc: http://csound.com/docs/manual/mpulse.html
squinewave :: Tuple a => Sig -> Sig -> Sig -> a #
A mostly bandlimited shape-shifting square-pulse-saw-sinewave oscillator with hardsync.
This oscillator generates a variable shape waveform that can morph freely between classical shapes sine, square, pulse and saw. The shape is controlled by two interacting values: clip (squareness) and "skew" (symmetry). All shapes use a minimum number of samples per transition (ie, the sharp end of a saw or a pulse uses minimum N samples), this makes output bandlimited. At higher frequency, the minimum sweep rate takes over, so over a certain pitch all shapes "degrade" to sinewave. The minimum sweep rate is i-time configurable. Hardsync (a very quick sweep to phase=0) is supported, and a sync signal is output once per cycle.
aout [, asyncout] squinewave acps, aClip, aSkew [, asyncin] [, iMinSweep] [, iphase]
csound doc: http://csound.com/docs/manual/squinewave.html
vco :: Sig -> Sig -> D -> Sig -> Sig #
Implementation of a band limited, analog modeled oscillator.
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.
ares vco xamp, xcps, iwave, kpw [, ifn] [, imaxd] [, ileak] [, inyx] \ [, iphs] [, iskip]
csound doc: http://csound.com/docs/manual/vco.html
Implementation of a band-limited oscillator using pre-calculated tables.
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.
ares vco2 kamp, kcps [, imode] [, kpw] [, kphs] [, inyx]
csound doc: http://csound.com/docs/manual/vco2.html
Returns a table number at k-time for a given oscillator frequency and wavform.
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).
kfn vco2ft kcps, iwave [, inyx]
csound doc: http://csound.com/docs/manual/vco2ft.html
Returns a table number at i-time for a given oscillator frequency and wavform.
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).
ifn vco2ift icps, iwave [, inyx]
csound doc: http://csound.com/docs/manual/vco2ift.html
Calculates tables for use by vco2 opcode.
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.
ifn vco2init iwave [, ibasfn] [, ipmul] [, iminsiz] [, imaxsiz] [, isrcft]
csound doc: http://csound.com/docs/manual/vco2init.html
crossfm :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> (Sig, Sig) #
Two mutually frequency and/or phase modulated oscillators.
Two oscillators, mutually frequency and/or phase modulated by each other.
a1, a2 crossfm xfrq1, xfrq2, xndx1, xndx2, kcps, ifn1, ifn2 [, iphs1] [, iphs2]
csound doc: http://csound.com/docs/manual/crossfm.html
crossfmi :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> (Sig, Sig) #
Two mutually frequency and/or phase modulated oscillators.
Two oscillators, mutually frequency and/or phase modulated by each other.
a1, a2 crossfmi xfrq1, xfrq2, xndx1, xndx2, kcps, ifn1, ifn2 [, iphs1] [, iphs2]
csound doc: http://csound.com/docs/manual/crossfm.html
crosspm :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> (Sig, Sig) #
Two mutually frequency and/or phase modulated oscillators.
Two oscillators, mutually frequency and/or phase modulated by each other.
a1, a2 crosspm xfrq1, xfrq2, xndx1, xndx2, kcps, ifn1, ifn2 [, iphs1] [, iphs2]
csound doc: http://csound.com/docs/manual/crossfm.html
crosspmi :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> (Sig, Sig) #
Two mutually frequency and/or phase modulated oscillators.
Two oscillators, mutually frequency and/or phase modulated by each other.
a1, a2 crosspmi xfrq1, xfrq2, xndx1, xndx2, kcps, ifn1, ifn2 [, iphs1] [, iphs2]
csound doc: http://csound.com/docs/manual/crossfm.html
crossfmpm :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> (Sig, Sig) #
Two mutually frequency and/or phase modulated oscillators.
Two oscillators, mutually frequency and/or phase modulated by each other.
a1, a2 crossfmpm xfrq1, xfrq2, xndx1, xndx2, kcps, ifn1, ifn2 [, iphs1] [, iphs2]
csound doc: http://csound.com/docs/manual/crossfm.html
crossfmpmi :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> (Sig, Sig) #
Two mutually frequency and/or phase modulated oscillators.
Two oscillators, mutually frequency and/or phase modulated by each other.
a1, a2 crossfmpmi xfrq1, xfrq2, xndx1, xndx2, kcps, ifn1, ifn2 [, iphs1] [, iphs2]
csound doc: http://csound.com/docs/manual/crossfm.html
fmb3 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
Uses FM synthesis to create a Hammond B3 organ sound.
Uses FM synthesis to create a Hammond B3 organ sound. It comes from a family of FM sounds, all using 4 basic oscillators and various architectures, as used in the TX81Z synthesizer.
ares fmb3 kamp, kfreq, kc1, kc2, kvdepth, kvrate[, ifn1, ifn2, ifn3, \ ifn4, ivfn]
csound doc: http://csound.com/docs/manual/fmb3.html
fmbell :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
Uses FM synthesis to create a tublar bell sound.
Uses FM synthesis to create a tublar bell sound. It comes from a family of FM sounds, all using 4 basic oscillators and various architectures, as used in the TX81Z synthesizer.
ares fmbell kamp, kfreq, kc1, kc2, kvdepth, kvrate[, ifn1, ifn2, ifn3, \ ifn4, ivfn, isus]
csound doc: http://csound.com/docs/manual/fmbell.html
fmmetal :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Tab -> Tab -> Sig #
Uses FM synthesis to create a âHeavy Metalâ sound.
Uses FM synthesis to create a âHeavy Metalâ sound. It comes from a family of FM sounds, all using 4 basic oscillators and various architectures, as used in the TX81Z synthesizer.
ares fmmetal kamp, kfreq, kc1, kc2, kvdepth, kvrate, ifn1, ifn2, ifn3, \ ifn4, ivfn
csound doc: http://csound.com/docs/manual/fmmetal.html
fmpercfl :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
Uses FM synthesis to create a percussive flute sound.
Uses FM synthesis to create a percussive flute sound. It comes from a family of FM sounds, all using 4 basic oscillators and various architectures, as used in the TX81Z synthesizer.
ares fmpercfl kamp, kfreq, kc1, kc2, kvdepth, kvrate[, ifn1, ifn2, \ ifn3, ifn4, ivfn]
csound doc: http://csound.com/docs/manual/fmpercfl.html
fmrhode :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Tab -> Tab -> Sig #
Uses FM synthesis to create a Fender Rhodes electric piano sound.
Uses FM synthesis to create a Fender Rhodes electric piano sound. It comes from a family of FM sounds, all using 4 basic oscillators and various architectures, as used in the TX81Z synthesizer.
ares fmrhode kamp, kfreq, kc1, kc2, kvdepth, kvrate, ifn1, ifn2, \ ifn3, ifn4, ivfn
csound doc: http://csound.com/docs/manual/fmrhode.html
fmvoice :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
FM Singing Voice Synthesis
ares fmvoice kamp, kfreq, kvowel, ktilt, kvibamt, kvibrate[, ifn1, \ ifn2, ifn3, ifn4, ivibfn]
csound doc: http://csound.com/docs/manual/fmvoice.html
fmwurlie :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Tab -> Tab -> Sig #
Uses FM synthesis to create a Wurlitzer electric piano sound.
Uses FM synthesis to create a Wurlitzer electric piano sound. It comes from a family of FM sounds, all using 4 basic oscillators and various architectures, as used in the TX81Z synthesizer.
ares fmwurlie kamp, kfreq, kc1, kc2, kvdepth, kvrate, ifn1, ifn2, ifn3, \ ifn4, ivfn
csound doc: http://csound.com/docs/manual/fmwurlie.html
foscil :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig #
A basic frequency modulated oscillator.
ares foscil xamp, kcps, xcar, xmod, kndx, ifn [, iphs]
csound doc: http://csound.com/docs/manual/foscil.html
foscili :: Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig #
Basic frequency modulated oscillator with linear interpolation.
ares foscili xamp, kcps, xcar, xmod, kndx, ifn [, iphs]
csound doc: http://csound.com/docs/manual/foscili.html
diskgrain :: Str -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> Sig #
Synchronous granular synthesis, using a soundfile as source.
diskgrain implements synchronous granular synthesis. The source sound for the grains is obtained by reading a soundfile containing the samples of the source waveform.
asig diskgrain Sfname, kamp, kfreq, kpitch, kgrsize, kprate, \ ifun, iolaps [,imaxgrsize , ioffset]
csound doc: http://csound.com/docs/manual/diskgrain.html
fof :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Tab -> Tab -> D -> Sig #
Produces sinusoid bursts useful for formant and granular synthesis.
Audio output is a succession of sinusoid bursts initiated at frequency xfund with a spectral peak at xform. For xfund above 25 Hz these bursts produce a speech-like formant with spectral characteristics determined by the k-input parameters. For lower fundamentals this generator provides a special form of granular synthesis.
ares fof xamp, xfund, xform, koct, kband, kris, kdur, kdec, iolaps, \ ifna, ifnb, itotdur [, iphs] [, ifmode] [, iskip]
csound doc: http://csound.com/docs/manual/fof.html
fog :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Tab -> Tab -> D -> Sig #
Audio output is a succession of grains derived from data in a stored function table
Audio output is a succession of grains derived from data in a stored function table ifna. The local envelope of these grains and their timing is based on the model of fof synthesis and permits detailed control of the granular synthesis.
ares fog xamp, xdens, xtrans, aspd, koct, kband, kris, kdur, kdec, \ iolaps, ifna, ifnb, itotdur [, iphs] [, itmode] [, iskip]
csound doc: http://csound.com/docs/manual/fog.html
grain :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> D -> Sig #
Generates granular synthesis textures.
ares grain xamp, xpitch, xdens, kampoff, kpitchoff, kgdur, igfn, \ iwfn, imgdur [, igrnd]
csound doc: http://csound.com/docs/manual/grain.html
grain2 :: Sig -> Sig -> Sig -> D -> Tab -> Tab -> Sig #
Easy-to-use granular synthesis texture generator.
Generate granular synthesis textures. grain2 is simpler to use, but grain3 offers more control.
ares grain2 kcps, kfmd, kgdur, iovrlp, kfn, iwfn [, irpow] \ [, iseed] [, imode]
csound doc: http://csound.com/docs/manual/grain2.html
grain3 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Tab -> Tab -> Sig -> Sig -> Sig #
Generate granular synthesis textures with more user control.
Generate granular synthesis textures. grain2 is simpler to use but grain3 offers more control.
ares grain3 kcps, kphs, kfmd, kpmd, kgdur, kdens, imaxovr, kfn, iwfn, \ kfrpow, kprpow [, iseed] [, imode]
csound doc: http://csound.com/docs/manual/grain3.html
partikkelget :: Sig -> D -> Sig #
Get mask index for a specific mask parameter of a running partikkel instance.
partikkelget is an opcode for outputting partikkel mask index for a specific parameter. Used together with partikkelset, it can be used to synchronize partikkel masking between several running instances of the partikkel opcode. It can also be used to control other processes based on the internal mask index, for example to create more complex masking patterns than is available with the regular grain masking system.
kindex partikkelget kparameterindex, iopcode_id
csound doc: http://csound.com/docs/manual/partikkelget.html
partikkelset :: Sig -> Sig -> D -> SE () #
Set mask index for a specific mask parameter of a running partikkel instance.
partikkelset is an opcode for setting the partikkel mask index for a specific parameter. Used together with partikkelget, it can be used to synchronize partikkel masking between several running instances of the partikkel opcode. It can also be used to set the internal mask index basaed on other processes, for example to create more complex masking patterns than is available with the regular grain masking system.
partikkelset kparameterindex, kmaskindex, iopcode_id
csound doc: http://csound.com/docs/manual/partikkelset.html
partikkelsync :: Tuple a => D -> a #
Outputs partikkel's grain scheduler clock pulse and phase to synchronize several instances of the partikkel opcode to the same clock source.
partikkelsync is an opcode for outputting partikkel's grain scheduler clock pulse and phase. partikkelsync's output can be used to synchronize other instances of the partikkel opcode to the same clock.
async [,aphase] partikkelsync iopcode_id
csound doc: http://csound.com/docs/manual/partikkelsync.html
syncloop :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> D -> Sig #
Synchronous granular synthesis.
syncloop is a variation on syncgrain, which implements synchronous granular synthesis. syncloop adds loop start and end points and an optional start position. Loop start and end control grain start positions, so the actual grains can go beyond the loop points (if the loop points are not at the extremes of the table), enabling seamless crossfading. For more information on the granular synthesis process, check the syncgrain manual page.
asig syncloop kamp, kfreq, kpitch, kgrsize, kprate, klstart, \ klend, ifun1, ifun2, iolaps[,istart, iskip]
csound doc: http://csound.com/docs/manual/syncloop.html
vosim :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Sig #
Simple vocal simulation based on glottal pulses with formant characteristics.
This opcode produces a simple vocal simulation based on glottal pulses with formant characteristics. Output is a series of sound events, where each event is composed of a burst of squared sine pulses followed by silence. The VOSIM (VOcal SIMulation) synthesis method was developed by Kaegi and Tempelaars in the 1970's.
ar vosim kamp, kFund, kForm, kDecay, kPulseCount, kPulseFactor, ifn [, iskip]
csound doc: http://csound.com/docs/manual/vosim.html
hvs1 :: Sig -> D -> D -> D -> D -> D -> SE () #
Allows one-dimensional Hyper Vectorial Synthesis (HVS) controlled by externally-updated k-variables.
hvs1 allows one-dimensional Hyper Vectorial Synthesis (HVS) controlled by externally-updated k-variables.
hvs1 kx, inumParms, inumPointsX, iOutTab, iPositionsTab, iSnapTab [, iConfigTab]
csound doc: http://csound.com/docs/manual/hvs1.html
hvs2 :: Sig -> Sig -> D -> D -> D -> D -> D -> D -> SE () #
Allows two-dimensional Hyper Vectorial Synthesis (HVS) controlled by externally-updated k-variables.
hvs2 allows two-dimensional Hyper Vectorial Synthesis (HVS) controlled by externally-updated k-variables.
hvs2 kx, ky, inumParms, inumPointsX, inumPointsY, iOutTab, iPositionsTab, iSnapTab [, iConfigTab]
csound doc: http://csound.com/docs/manual/hvs2.html
hvs3 :: Sig -> Sig -> Sig -> D -> D -> D -> D -> D -> D -> D -> SE () #
Allows three-dimensional Hyper Vectorial Synthesis (HVS) controlled by externally-updated k-variables.
hvs3 allows three-dimensional Hyper Vectorial Synthesis (HVS) controlled by externally-updated k-variables.
hvs3 kx, ky, kz, inumParms, inumPointsX, inumPointsY, inumPointsZ, iOutTab, iPositionsTab, iSnapTab [, iConfigTab]
csound doc: http://csound.com/docs/manual/hvs3.html
bpf :: Sig -> Sig -> Sig -> [Sig] -> Sig #
Break point function with linear interpolation
Break-point function with linear interpolation. Useful when defining a table with GEN27 and scaling the x value would be overkill.
ky bpf kx, kx1, ky1, kx2, ..., kxn, kyn
csound doc: http://csound.com/docs/manual/bpf.html
Trace a series of line segments between specified points with cosine interpolation.
ares cosseg ia, idur1, ib [, idur2] [, ic] [...] kres cosseg ia, idur1, ib [, idur2] [, ic] [...]
csound doc: http://csound.com/docs/manual/cosseg.html
Trace a series of line segments between specified absolute points with cosine interpolation.
ares cossegb ia, itim1, ib [, itim2] [, ic] [...] kres cossegb ia, itim1, ib [, itim2] [, ic] [...]
csound doc: http://csound.com/docs/manual/cossegb.html
cossegr :: [D] -> D -> D -> Sig #
Trace a series of line segments between specified points with cosine interpolation, including a release segment.
ares cossegr ia, idur1, ib [, idur2] [, ic] [...], irel, iz kres cossegr ia, idur1, ib [, idur2] [, ic] [...], irel, iz
csound doc: http://csound.com/docs/manual/cossegr.html
expcurve :: Sig -> Sig -> Sig #
This opcode implements a formula for generating a normalised exponential curve in range 0 - 1. It is based on the Max / MSP work of Eric Singer (c) 1994.
Generates an exponential curve in range 0 to 1 of arbitrary steepness. Steepness index equal to or lower than 1.0 will result in Not-a-Number errors and cause unstable behavior.
kout expcurve kindex, ksteepness
csound doc: http://csound.com/docs/manual/expcurve.html
Trace an exponential curve between specified points.
ares expon ia, idur, ib kres expon ia, idur, ib
csound doc: http://csound.com/docs/manual/expon.html
Trace a series of exponential segments between specified points.
ares expseg ia, idur1, ib [, idur2] [, ic] [...] kres expseg ia, idur1, ib [, idur2] [, ic] [...]
csound doc: http://csound.com/docs/manual/expseg.html
An exponential segment generator operating at a-rate.
An exponential segment generator operating at a-rate. This unit is almost identical to expseg, but more precise when defining segments with very short durations (i.e., in a percussive attack phase) at audio rate.
ares expsega ia, idur1, ib [, idur2] [, ic] [...]
csound doc: http://csound.com/docs/manual/expsega.html
Trace a series of exponential segments between specified absolute points.
ares expsegb ia, itim1, ib [, itim2] [, ic] [...] kres expsegb ia, itim1, ib [, itim2] [, ic] [...]
csound doc: http://csound.com/docs/manual/expsegb.html
expsegba :: D -> D -> D -> Sig #
An exponential segment generator operating at a-rate with absolute times.
An exponential segment generator operating at a-rate. This unit is almost identical to expsegb, but more precise when defining segments with very short durations (i.e., in a percussive attack phase) at audio rate.
ares expsegba ia, itim1, ib [, itim2] [, ic] [...]
csound doc: http://csound.com/docs/manual/expsegba.html
expsegr :: [D] -> D -> D -> Sig #
Trace a series of exponential segments between specified points including a release segment.
ares expsegr ia, idur1, ib [, idur2] [, ic] [...], irel, iz kres expsegr ia, idur1, ib [, idur2] [, ic] [...], irel, iz
csound doc: http://csound.com/docs/manual/expsegr.html
gainslider :: Sig -> Sig #
An implementation of a logarithmic gain curve which is similar to the gainslider~ object from Cycling 74 Max / MSP.
This opcode is intended for use to multiply by an audio signal to give a console mixer like feel. There is no bounds in the source code so you can for example give higher than 127 values for extra amplitude but possibly clipped audio.
kout gainslider kindex
csound doc: http://csound.com/docs/manual/gainslider.html
linlin :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
Linear to linear interpolation
Maps a linear range of values to another linear range of values.
kout linlin kin, ksrclo, ksrchi, kdstlo, kdsthi
csound doc: http://csound.com/docs/manual/linlin.html
Trace a series of line segments between specified points.
ares linseg ia, idur1, ib [, idur2] [, ic] [...] kres linseg ia, idur1, ib [, idur2] [, ic] [...]
csound doc: http://csound.com/docs/manual/linseg.html
Trace a series of line segments between specified absolute points.
ares linsegb ia, itim1, ib [, itim2] [, ic] [...] kres linsegb ia, itim1, ib [, itim2] [, ic] [...]
csound doc: http://csound.com/docs/manual/linsegb.html
linsegr :: [D] -> D -> D -> Sig #
Trace a series of line segments between specified points including a release segment.
ares linsegr ia, idur1, ib [, idur2] [, ic] [...], irel, iz kres linsegr ia, idur1, ib [, idur2] [, ic] [...], irel, iz
csound doc: http://csound.com/docs/manual/linsegr.html
logcurve :: Sig -> Sig -> Sig #
This opcode implements a formula for generating a normalised logarithmic curve in range 0 - 1. It is based on the Max / MSP work of Eric Singer (c) 1994.
Generates a logarithmic curve in range 0 to 1 of arbitrary steepness. Steepness index equal to or lower than 1.0 will result in Not-a-Number errors and cause unstable behavior.
kout logcurve kindex, ksteepness
csound doc: http://csound.com/docs/manual/logcurve.html
loopsegp :: Sig -> [Sig] -> Sig #
Control signals based on linear segments.
Generate control signal consisiting of linear segments delimited by two or more specified points. The entire envelope can be looped at time-variant rate. Each segment coordinate can also be varied at k-rate.
ksig loopsegp kphase, kvalue0, kdur0, kvalue1 \ [, kdur1, ... , kdurN-1, kvalueN]
csound doc: http://csound.com/docs/manual/loopsegp.html
looptseg :: Sig -> Sig -> [Sig] -> Sig #
Generate control signal consisting of exponential or linear segments delimited by two or more specified points.
Generate control signal consisting of controllable exponential segments or linear segments delimited by two or more specified points. The entire envelope is looped at kfreq rate. Each parameter can be varied at k-rate.
ksig looptseg kfreq, ktrig, iphase, kvalue0, ktype0, ktime0, [, kvalue1] [,ktype1] [, ktime1] \ [, kvalue2] [,ktype2] [, ktime2] [...] [, kvalueN] [,ktypeN] [, ktimeN]
csound doc: http://csound.com/docs/manual/looptseg.html
lpsholdp :: Sig -> Sig -> [Sig] -> Sig #
Control signals based on held segments.
Generate control signal consisiting of held segments delimited by two or more specified points. The entire envelope can be looped at time-variant rate. Each segment coordinate can also be varied at k-rate.
ksig lpsholdp kphase, kvalue0, ktime0 [, kvalue1] [, ktime1] \ [, kvalue2] [, ktime2] [...]
csound doc: http://csound.com/docs/manual/lpsholdp.html
Constructs a user-definable envelope.
ares transeg ia, idur, itype, ib [, idur2] [, itype] [, ic] ... kres transeg ia, idur, itype, ib [, idur2] [, itype] [, ic] ...
csound doc: http://csound.com/docs/manual/transeg.html
Constructs a user-definable envelope in absolute time.
ares transegb ia, itim, itype, ib [, itim2] [, itype] [, ic] ... kres transegb ia, itim, itype, ib [, itim2] [, itype] [, ic] ...
csound doc: http://csound.com/docs/manual/transegb.html
transegr :: [D] -> D -> D -> D -> Sig #
Constructs a user-definable envelope with extended release segment.
Constructs a user-definable envelope. It is the same as transeg, with an extended release segment.
ares transegr ia, idur, itype, ib [, idur2] [, itype] [, ic] ... kres transegr ia, idur, itype, ib [, idur2] [, itype] [, ic] ...
csound doc: http://csound.com/docs/manual/transegr.html
xyscale :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
2D linear interpolation
2D linear interpolation between 4 points at (0,0), (1,0), (0,1), (1,1)
kout xyscale kx, ky, k00, k10, k01, k11
csound doc: http://csound.com/docs/manual/xyscale.html
adsr :: D -> D -> D -> D -> Sig #
Calculates the classical ADSR envelope using linear segments.
ares adsr iatt, idec, islev, irel [, idel] kres adsr iatt, idec, islev, irel [, idel]
csound doc: http://csound.com/docs/manual/adsr.html
envlpx :: Sig -> D -> D -> D -> Tab -> D -> D -> Sig #
Applies an envelope consisting of 3 segments.
envlpx -- apply an envelope consisting of 3 segments:
ares envlpx xamp, irise, idur, idec, ifn, iatss, iatdec [, ixmod] kres envlpx kamp, irise, idur, idec, ifn, iatss, iatdec [, ixmod]
csound doc: http://csound.com/docs/manual/envlpx.html
envlpxr :: Sig -> D -> D -> Tab -> D -> D -> Sig #
The envlpx opcode with a final release segment.
envlpxr is the same as envlpx except that the final segment is entered only on sensing a MIDI note release. The note is then extended by the decay time.
ares envlpxr xamp, irise, idec, ifn, iatss, iatdec [, ixmod] [,irind] kres envlpxr kamp, irise, idec, ifn, iatss, iatdec [, ixmod] [,irind]
csound doc: http://csound.com/docs/manual/envlpxr.html
linenr :: Sig -> D -> D -> D -> Sig #
The linen opcode extended with a final release segment.
linenr -- same as linen except that the final segment is entered only on sensing a MIDI note release. The note is then extended by the decay time.
ares linenr xamp, irise, idec, iatdec kres linenr kamp, irise, idec, iatdec
csound doc: http://csound.com/docs/manual/linenr.html
madsr :: D -> D -> D -> D -> Sig #
Calculates the classical ADSR envelope using the linsegr mechanism.
ares madsr iatt, idec, islev, irel [, idel] [, ireltim] kres madsr iatt, idec, islev, irel [, idel] [, ireltim]
csound doc: http://csound.com/docs/manual/madsr.html
mxadsr :: D -> D -> D -> D -> Sig #
Calculates the classical ADSR envelope using the expsegr mechanism.
ares mxadsr iatt, idec, islev, irel [, idel] [, ireltim] kres mxadsr iatt, idec, islev, irel [, idel] [, ireltim]
csound doc: http://csound.com/docs/manual/mxadsr.html
xadsr :: D -> D -> D -> D -> Sig #
Calculates the classical ADSR envelope.
Calculates the classical ADSR envelope
ares xadsr iatt, idec, islev, irel [, idel] kres xadsr iatt, idec, islev, irel [, idel]
csound doc: http://csound.com/docs/manual/xadsr.html
Semi-physical model of a bamboo sound.
bamboo is a semi-physical model of a bamboo sound. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.
ares bamboo kamp, idettack [, inum] [, idamp] [, imaxshake] [, ifreq] \ [, ifreq1] [, ifreq2]
csound doc: http://csound.com/docs/manual/bamboo.html
barmodel :: Sig -> Sig -> D -> D -> Sig -> D -> D -> D -> D -> Sig #
Creates a tone similar to a struck metal bar.
Audio output is a tone similar to a struck metal bar, using a physical model developed from solving the partial differential equation. There are controls over the boundary conditions as well as the bar characteristics.
ares barmodel kbcL, kbcR, iK, ib, kscan, iT30, ipos, ivel, iwid
csound doc: http://csound.com/docs/manual/barmodel.html
Semi-physical model of a cabasa sound.
cabasa is a semi-physical model of a cabasa sound. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.
ares cabasa iamp, idettack [, inum] [, idamp] [, imaxshake]
csound doc: http://csound.com/docs/manual/cabasa.html
chuap :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> D -> Sig -> (Sig, Sig, Sig) #
Simulates Chua's oscillator, an LRC oscillator with an active resistor, proved capable of bifurcation and chaotic attractors, with k-rate control of circuit elements.
aI3, aV2, aV1 chuap kL, kR0, kC1, kG, kGa, kGb, kE, kC2, iI3, iV2, iV1, ktime_step
csound doc: http://csound.com/docs/manual/chuap.html
Semi-physical model of a crunch sound.
crunch is a semi-physical model of a crunch sound. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.
ares crunch iamp, idettack [, inum] [, idamp] [, imaxshake]
csound doc: http://csound.com/docs/manual/crunch.html
dripwater :: Sig -> D -> Sig #
Semi-physical model of a water drop.
dripwater is a semi-physical model of a water drop. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.
ares dripwater kamp, idettack [, inum] [, idamp] [, imaxshake] [, ifreq] \ [, ifreq1] [, ifreq2]
csound doc: http://csound.com/docs/manual/dripwater.html
gendy :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
Dynamic stochastic approach to waveform synthesis conceived by Iannis Xenakis.
Implementation of the Génération Dynamique Stochastique (GENDYN), a dynamic stochastic approach to waveform synthesis conceived by Iannis Xenakis.
ares gendy kamp, kampdist, kdurdist, kadpar, kddpar, kminfreq, kmaxfreq, \ kampscl, kdurscl [, initcps] [, knum] kres gendy kamp, kampdist, kdurdist, kadpar, kddpar, kminfreq, kmaxfreq, \ kampscl, kdurscl [, initcps] [, knum]
csound doc: http://csound.com/docs/manual/gendy.html
gendyc :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
Dynamic stochastic approach to waveform synthesis using cubic interpolation.
Implementation with cubic interpolation of the Génération Dynamique Stochastique (GENDYN), a dynamic stochastic approach to waveform synthesis conceived by Iannis Xenakis.
ares gendyc kamp, kampdist, kdurdist, kadpar, kddpar, kminfreq, kmaxfreq, \ kampscl, kdurscl [, initcps] [, knum] kres gendyc kamp, kampdist, kdurdist, kadpar, kddpar, kminfreq, kmaxfreq, \ kampscl, kdurscl [, initcps] [, knum]
csound doc: http://csound.com/docs/manual/gendyc.html
gendyx :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
Variation of the dynamic stochastic approach to waveform synthesis conceived by Iannis Xenakis.
gendyx (gendy eXtended) is an implementation of the Génération Dynamique Stochastique (GENDYN), a dynamic stochastic approach to waveform synthesis conceived by Iannis Xenakis, using curves instead of segments.
ares gendyx kamp, kampdist, kdurdist, kadpar, kddpar, kminfreq, kmaxfreq, \ kampscl, kdurscl, kcurveup, kcurvedown [, initcps] [, knum] kres gendyx kamp, kampdist, kdurdist, kadpar, kddpar, kminfreq, kmaxfreq, \ kampscl, kdurscl, kcurveup, kcurvedown [, initcps] [, knum]
csound doc: http://csound.com/docs/manual/gendyx.html
gogobel :: Sig -> Sig -> D -> D -> D -> Sig -> Sig -> Tab -> Sig #
Audio output is a tone related to the striking of a cow bell or similar.
Audio output is a tone related to the striking of a cow bell or similar. The method is a physical model developed from Perry Cook, but re-coded for Csound.
ares gogobel kamp, kfreq, ihrd, ipos, imp, kvibf, kvamp, ivfn
csound doc: http://csound.com/docs/manual/gogobel.html
Semi-physical model of a guiro sound.
guiro is a semi-physical model of a guiro sound. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.
ares guiro kamp, idettack [, inum] [, idamp] [, imaxshake] [, ifreq] [, ifreq1]
csound doc: http://csound.com/docs/manual/guiro.html
lorenz :: Sig -> Sig -> Sig -> Sig -> D -> D -> D -> D -> (Sig, Sig, Sig) #
Implements the Lorenz system of equations.
Implements the Lorenz system of equations. The Lorenz system is a chaotic-dynamic system which was originally used to simulate the motion of a particle in convection currents and simplified weather systems. Small differences in initial conditions rapidly lead to diverging values. This is sometimes expressed as the butterfly effect. If a butterfly flaps its wings in Australia, it will have an effect on the weather in Alaska. This system is one of the milestones in the development of chaos theory. It is useful as a chaotic audio source or as a low frequency modulation source.
ax, ay, az lorenz ksv, krv, kbv, kh, ix, iy, iz, iskip [, iskipinit]
csound doc: http://csound.com/docs/manual/lorenz.html
mandel :: Sig -> Sig -> Sig -> Sig -> (Sig, Sig) #
Mandelbrot set
Returns the number of iterations corresponding to a given point of complex plane by applying the Mandelbrot set formula.
kiter, koutrig mandel ktrig, kx, ky, kmaxIter
csound doc: http://csound.com/docs/manual/mandel.html
mandol :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
An emulation of a mandolin.
ares mandol kamp, kfreq, kpluck, kdetune, kgain, ksize \ [, ifn] [, iminfreq]
csound doc: http://csound.com/docs/manual/mandol.html
marimba :: Sig -> Sig -> D -> D -> D -> Sig -> Sig -> Tab -> D -> Sig #
Physical model related to the striking of a wooden block.
Audio output is a tone related to the striking of a wooden block as found in a marimba. The method is a physical model developed from Perry Cook but re-coded for Csound.
ares marimba kamp, kfreq, ihrd, ipos, imp, kvibf, kvamp, ivibfn, idec \ [, idoubles] [, itriples]
csound doc: http://csound.com/docs/manual/marimba.html
moog :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Tab -> Sig #
An emulation of a mini-Moog synthesizer.
ares moog kamp, kfreq, kfiltq, kfiltrate, kvibf, kvamp, iafn, iwfn, ivfn
csound doc: http://csound.com/docs/manual/moog.html
planet :: Sig -> Sig -> Sig -> D -> D -> D -> D -> D -> D -> D -> (Sig, Sig, Sig) #
Simulates a planet orbiting in a binary star system.
planet simulates a planet orbiting in a binary star system. The outputs are the x, y and z coordinates of the orbiting planet. It is possible for the planet to achieve escape velocity by a close encounter with a star. This makes this system somewhat unstable.
ax, ay, az planet kmass1, kmass2, ksep, ix, iy, iz, ivx, ivy, ivz, idelta \ [, ifriction] [, iskip]
csound doc: http://csound.com/docs/manual/planet.html
prepiano :: D -> D -> D -> D -> D -> D -> Sig -> Sig -> D -> D -> D -> D -> D -> D -> D -> (Sig, Sig) #
Creates a tone similar to a piano string prepared in a Cageian fashion.
Audio output is a tone similar to a piano string, prepared with a number of rubbers and rattles. The method uses a physical model developed from solving the partial differential equation.
ares prepiano ifreq, iNS, iD, iK, \ iT30,iB, kbcl, kbcr, imass, ihvfreq, iinit, ipos, ivel, isfreq, \ isspread[, irattles, irubbers] al,ar prepiano ifreq, iNS, iD, iK, \ iT30,iB, kbcl, kbcr, imass, ihvfreq, iinit, ipos, ivel, isfreq, \ isspread[, irattles, irubbers]
csound doc: http://csound.com/docs/manual/prepiano.html
Semi-physical model of a sandpaper sound.
sandpaper is a semi-physical model of a sandpaper sound. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.
ares sandpaper iamp, idettack [, inum] [, idamp] [, imaxshake]
csound doc: http://csound.com/docs/manual/sandpaper.html
Semi-physical model of a sekere sound.
sekere is a semi-physical model of a sekere sound. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.
ares sekere iamp, idettack [, inum] [, idamp] [, imaxshake]
csound doc: http://csound.com/docs/manual/sekere.html
shaker :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
Sounds like the shaking of a maraca or similar gourd instrument.
Audio output is a tone related to the shaking of a maraca or similar gourd instrument. The method is a physically inspired model developed from Perry Cook, but re-coded for Csound.
ares shaker kamp, kfreq, kbeans, kdamp, ktimes [, idecay]
csound doc: http://csound.com/docs/manual/shaker.html
sleighbells :: Sig -> D -> Sig #
Semi-physical model of a sleighbell sound.
sleighbells is a semi-physical model of a sleighbell sound. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.
ares sleighbells kamp, idettack [, inum] [, idamp] [, imaxshake] [, ifreq] \ [, ifreq1] [, ifreq2]
csound doc: http://csound.com/docs/manual/sleighbells.html
Semi-physical model of a stick sound.
stix is a semi-physical model of a stick sound. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.
ares stix iamp, idettack [, inum] [, idamp] [, imaxshake]
csound doc: http://csound.com/docs/manual/stix.html
tambourine :: Sig -> D -> Sig #
Semi-physical model of a tambourine sound.
tambourine is a semi-physical model of a tambourine sound. It is one of the PhISEM percussion opcodes. PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects.
ares tambourine kamp, idettack [, inum] [, idamp] [, imaxshake] [, ifreq] \ [, ifreq1] [, ifreq2]
csound doc: http://csound.com/docs/manual/tambourine.html
vibes :: Sig -> Sig -> D -> D -> D -> Sig -> Sig -> Tab -> D -> Sig #
Physical model related to the striking of a metal block.
Audio output is a tone related to the striking of a metal block as found in a vibraphone. The method is a physical model developed from Perry Cook, but re-coded for Csound.
ares vibes kamp, kfreq, ihrd, ipos, imp, kvibf, kvamp, ivibfn, idec
csound doc: http://csound.com/docs/manual/vibes.html
voice :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> Tab -> Sig #
An emulation of a human voice.
ares voice kamp, kfreq, kphoneme, kform, kvibf, kvamp, ifn, ivfn
csound doc: http://csound.com/docs/manual/voice.html
Produce a normalized moving phase value.
ares phasor xcps [, iphs] kres phasor kcps [, iphs]
csound doc: http://csound.com/docs/manual/phasor.html
phasorbnk :: Sig -> Sig -> D -> Sig #
Produce an arbitrary number of normalized moving phase values.
Produce an arbitrary number of normalized moving phase values, accessable by an index.
ares phasorbnk xcps, kndx, icnt [, iphs] kres phasorbnk kcps, kndx, icnt [, iphs]
csound doc: http://csound.com/docs/manual/phasorbnk.html
sc_phasor :: Sig -> Sig -> Sig -> Sig -> Sig #
A resettable linear ramp between two levels
A resettable linear ramp between two levels. Port of Supercollider's Phasor.
aindex sc_phasor xtrig, xrate, kstart, kend [, kresetPos] kindex sc_phasor xtrig, xrate, kstart, kend [, kresetPos]
csound doc: http://csound.com/docs/manual/sc_phasor.html
syncphasor :: Sig -> Sig -> (Sig, Sig) #
Produces a normalized moving phase value with sync input and output.
Produces a moving phase value between zero and one and an extra impulse output ("sync out") whenever its phase value crosses or is reset to zero. The phase can be reset at any time by an impulse on the "sync in" parameter.
aphase, asyncout syncphasor xcps, asyncin, [, iphs]
csound doc: http://csound.com/docs/manual/syncphasor.html
betarand :: SigOrD a => a -> a -> a -> SE a #
Beta distribution random number generator (positive values only).
Beta distribution random number generator (positive values only). This is an x-class noise generator.
ares betarand krange, kalpha, kbeta ires betarand krange, kalpha, kbeta kres betarand krange, kalpha, kbeta
csound doc: http://csound.com/docs/manual/betarand.html
bexprnd :: SigOrD a => a -> SE a #
Exponential distribution random number generator.
Exponential distribution random number generator. This is an x-class noise generator.
ares bexprnd krange ires bexprnd krange kres bexprnd krange
csound doc: http://csound.com/docs/manual/bexprnd.html
cauchy :: SigOrD a => a -> SE a #
Cauchy distribution random number generator.
Cauchy distribution random number generator. This is an x-class noise generator.
ares cauchy kalpha ires cauchy kalpha kres cauchy kalpha
csound doc: http://csound.com/docs/manual/cauchy.html
cauchyi :: SigOrD a => a -> a -> a -> SE a #
Cauchy distribution random number generator with interpolation.
Cauchy distribution random number generator with controlled interpolation between values. This is an x-class noise generator.
ares cauchyi klambda, xamp, xcps ires cauchyi klambda, xamp, xcps kres cauchyi klambda, xamp, xcps
csound doc: http://csound.com/docs/manual/cauchyi.html
dust2 :: Sig -> Sig -> SE Sig #
Random impulses.
Generates random impulses from -1 to 1.
ares dust2 kamp, kdensity kres dust2 kamp, kdensity
csound doc: http://csound.com/docs/manual/dust2.html
exprand :: SigOrD a => a -> SE a #
Exponential distribution random number generator (positive values only).
Exponential distribution random number generator (positive values only). This is an x-class noise generator.
ares exprand klambda ires exprand klambda kres exprand klambda
csound doc: http://csound.com/docs/manual/exprand.html
exprandi :: SigOrD a => a -> a -> a -> SE a #
Exponential distribution random number generator with interpolation (positive values only).
Exponential distribution random number generator with controlled interpolation between values (positive values only). This is an x-class noise generator.
ares exprandi klambda, xamp, xcps ires exprandi klambda, xamp, xcps kres exprandi klambda, xamp, xcps
csound doc: http://csound.com/docs/manual/exprandi.html
fractalnoise :: Sig -> Sig -> SE Sig #
A fractal noise generator.
A fractal noise generator implemented as a white noise filtered by a cascade of 15 first-order filters.
ares fractalnoise kamp, kbeta
csound doc: http://csound.com/docs/manual/fractalnoise.html
Gaussian distribution random number generator.
Gaussian distribution random number generator. This is an x-class noise generator.
ares gauss krange ires gauss krange kres gauss krange
csound doc: http://csound.com/docs/manual/gauss.html
gaussi :: SigOrD a => a -> a -> a -> SE a #
Gaussian distribution random number generator with interpolation.
Gaussian distribution random number generator with controlled interpolation between values. This is an x-class noise generator.
ares gaussi krange, xamp, xcps ires gaussi krange, xamp, xcps kres gaussi krange, xamp, xcps
csound doc: http://csound.com/docs/manual/gaussi.html
gausstrig :: Sig -> Sig -> Sig -> SE Sig #
Random impulses around a certain frequency.
Generates random impulses around a certain frequency.
ares gausstrig kamp, kcps, kdev [, imode] [, ifrst1] kres gausstrig kamp, kcps, kdev [, imode] [, ifrst1]
csound doc: http://csound.com/docs/manual/gausstrig.html
Reads the global seed value.
Returns the global seed value used for all x-class noise generators.
ians getseed kans getseed
csound doc: http://csound.com/docs/manual/getseed.html
jitter :: Sig -> Sig -> Sig -> SE Sig #
Generates a segmented line whose segments are randomly generated.
kout jitter kamp, kcpsMin, kcpsMax
csound doc: http://csound.com/docs/manual/jitter.html
jitter2 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE Sig #
Generates a segmented line with user-controllable random segments.
kout jitter2 ktotamp, kamp1, kcps1, kamp2, kcps2, kamp3, kcps3[ , iopt]
csound doc: http://csound.com/docs/manual/jitter2.html
jspline :: Sig -> Sig -> Sig -> SE Sig #
A jitter-spline generator.
ares jspline xamp, kcpsMin, kcpsMax kres jspline kamp, kcpsMin, kcpsMax
csound doc: http://csound.com/docs/manual/jspline.html
linrand :: SigOrD a => a -> SE a #
Linear distribution random number generator (positive values only).
Linear distribution random number generator (positive values only). This is an x-class noise generator.
ares linrand krange ires linrand krange kres linrand krange
csound doc: http://csound.com/docs/manual/linrand.html
noise :: Sig -> Sig -> SE Sig #
A white noise generator with an IIR lowpass filter.
ares noise xamp, kbeta
csound doc: http://csound.com/docs/manual/noise.html
pcauchy :: SigOrD a => a -> SE a #
Cauchy distribution random number generator (positive values only).
Cauchy distribution random number generator (positive values only). This is an x-class noise generator.
ares pcauchy kalpha ires pcauchy kalpha kres pcauchy kalpha
csound doc: http://csound.com/docs/manual/pcauchy.html
Generates pink noise.
Generates pink noise (-3dB/oct response) by the New Shade of Pink algorithm of Stefan Stenzel.
ares pinker
csound doc: http://csound.com/docs/manual/pinker.html
Generates approximate pink noise.
Generates approximate pink noise (-3dB/oct response) by one of two different methods:
ares pinkish xin [, imethod] [, inumbands] [, iseed] [, iskip]
csound doc: http://csound.com/docs/manual/pinkish.html
poisson :: SigOrD a => a -> SE a #
Poisson distribution random number generator (positive values only).
Poisson distribution random number generator (positive values only). This is an x-class noise generator.
ares poisson klambda ires poisson klambda kres poisson klambda
csound doc: http://csound.com/docs/manual/poisson.html
Generates a controlled random number series.
Output is a controlled random number series between -amp and +amp
ares rand xamp [, iseed] [, isel] [, ioffset] kres rand xamp [, iseed] [, isel] [, ioffset]
csound doc: http://csound.com/docs/manual/rand.html
randh :: Sig -> Sig -> SE Sig #
Generates random numbers and holds them for a period of time.
ares randh xamp, xcps [, iseed] [, isize] [, ioffset] kres randh kamp, kcps [, iseed] [, isize] [, ioffset]
csound doc: http://csound.com/docs/manual/randh.html
randi :: Sig -> Sig -> SE Sig #
Generates a controlled random number series with interpolation between each new number.
ares randi xamp, xcps [, iseed] [, isize] [, ioffset] kres randi kamp, kcps [, iseed] [, isize] [, ioffset]
csound doc: http://csound.com/docs/manual/randi.html
random :: SigOrD a => a -> a -> SE a #
Generates a controlled pseudo-random number series between min and max values.
Generates is a controlled pseudo-random number series between min and max values.
ares random kmin, kmax ires random imin, imax kres random kmin, kmax
csound doc: http://csound.com/docs/manual/random.html
randomh :: Sig -> Sig -> Sig -> SE Sig #
Generates random numbers with a user-defined limit and holds them for a period of time.
ares randomh kmin, kmax, xcps [,imode] [,ifirstval] kres randomh kmin, kmax, kcps [,imode] [,ifirstval]
csound doc: http://csound.com/docs/manual/randomh.html
randomi :: Sig -> Sig -> Sig -> SE Sig #
Generates a user-controlled random number series with interpolation between each new number.
ares randomi kmin, kmax, xcps [,imode] [,ifirstval] kres randomi kmin, kmax, kcps [,imode] [,ifirstval]
csound doc: http://csound.com/docs/manual/randomi.html
rnd31 :: SigOrD a => a -> a -> SE a #
31-bit bipolar random opcodes with controllable distribution.
31-bit bipolar random opcodes with controllable distribution. These units are portable, i.e. using the same seed value will generate the same random sequence on all systems. The distribution of generated random numbers can be varied at k-rate.
ax rnd31 kscl, krpow [, iseed] ix rnd31 iscl, irpow [, iseed] kx rnd31 kscl, krpow [, iseed]
csound doc: http://csound.com/docs/manual/rnd31.html
rspline :: Sig -> Sig -> Sig -> Sig -> SE Sig #
Generate random spline curves.
ares rspline xrangeMin, xrangeMax, kcpsMin, kcpsMax kres rspline krangeMin, krangeMax, kcpsMin, kcpsMax
csound doc: http://csound.com/docs/manual/rspline.html
Sets the global seed value.
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
csound doc: http://csound.com/docs/manual/seed.html
trandom :: Sig -> Sig -> Sig -> SE Sig #
Generates a controlled pseudo-random number series between min and max values according to a trigger.
Generates a controlled pseudo-random number series between min and max values at k-rate whenever the trigger parameter is different to 0.
kout trandom ktrig, kmin, kmax
csound doc: http://csound.com/docs/manual/trandom.html
trirand :: SigOrD a => a -> SE a #
Triangular distribution random number generator
Triangular distribution random number generator. This is an x-class noise generator.
ares trirand krange ires trirand krange kres trirand krange
csound doc: http://csound.com/docs/manual/trirand.html
unirand :: SigOrD a => a -> SE a #
Uniform distribution random number generator (positive values only).
Uniform distribution random number generator (positive values only). This is an x-class noise generator.
ares unirand krange ires unirand krange kres unirand krange
csound doc: http://csound.com/docs/manual/unirand.html
truly random opcodes with controllable range.
Truly random opcodes with controllable range. These units are for Unix-like systems only and use devurandom to construct Csound random values
ax urandom [imin, imax] ix urandom [imin, imax] kx urandom [imin, imax]
csound doc: http://csound.com/docs/manual/urandom.html
weibull :: SigOrD a => a -> a -> SE a #
Weibull distribution random number generator (positive values only).
Weibull distribution random number generator (positive values only). This is an x-class noise generator
ares weibull ksigma, ktau ires weibull ksigma, ktau kres weibull ksigma, ktau
csound doc: http://csound.com/docs/manual/weibull.html
bbcutm :: Sig -> D -> D -> D -> D -> D -> Sig #
Generates breakbeat-style cut-ups of a mono audio stream.
The BreakBeat Cutter automatically generates cut-ups of a source audio stream in the style of drum and bass/jungle breakbeat manipulations. There are two versions, for mono (bbcutm) or stereo (bbcuts) sources. Whilst originally based on breakbeat cutting, the opcode can be applied to any type of source audio.
a1 bbcutm asource, ibps, isubdiv, ibarlength, iphrasebars, inumrepeats \ [, istutterspeed] [, istutterchance] [, ienvchoice ]
csound doc: http://csound.com/docs/manual/bbcutm.html
bbcuts :: Sig -> Sig -> D -> D -> D -> D -> D -> (Sig, Sig) #
Generates breakbeat-style cut-ups of a stereo audio stream.
The BreakBeat Cutter automatically generates cut-ups of a source audio stream in the style of drum and bass/jungle breakbeat manipulations. There are two versions, for mono (bbcutm) or stereo (bbcuts) sources. Whilst originally based on breakbeat cutting, the opcode can be applied to any type of source audio.
a1,a2 bbcuts asource1, asource2, ibps, isubdiv, ibarlength, iphrasebars, \ inumrepeats [, istutterspeed] [, istutterchance] [, ienvchoice]
csound doc: http://csound.com/docs/manual/bbcuts.html
flooper :: Tuple a => Sig -> Sig -> D -> D -> D -> Tab -> a #
Function-table-based crossfading looper.
This opcode reads audio from a function table and plays it back in a loop with user-defined start time, duration and crossfade time. It also allows the pitch of the loop to be controlled, including reversed playback. It accepts non-power-of-two tables, such as deferred-allocation GEN01 tables, with one or two channels.
asig1[, asig2] flooper kamp, kpitch, istart, idur, ifad, ifn
csound doc: http://csound.com/docs/manual/flooper.html
flooper2 :: Tuple a => Sig -> Sig -> Sig -> Sig -> Sig -> Tab -> a #
Function-table-based crossfading looper.
This opcode implements a crossfading looper with variable loop parameters and three looping modes, optionally using a table for its crossfade shape. It accepts non-power-of-two tables for its source sounds, such as deferred-allocation GEN01 tables, with one or two channels.
asig1[,asig2] flooper2 kamp, kpitch, kloopstart, kloopend, kcrossfade, ifn \ [, istart, imode, ifenv, iskip]
csound doc: http://csound.com/docs/manual/flooper2.html
fluidAllOut :: (Sig, Sig) #
Collects all audio from all Fluidsynth engines in a performance
aleft, aright fluidAllOut
csound doc: http://csound.com/docs/manual/fluidAllOut.html
fluidCCi :: D -> D -> D -> D -> SE () #
Sends a MIDI controller data message to fluid.
Sends a MIDI controller data (MIDI controller number and value to use) message to a fluid engine by number on the user specified MIDI channel number.
fluidCCi iEngineNumber, iChannelNumber, iControllerNumber, iValue
csound doc: http://csound.com/docs/manual/fluidCCi.html
fluidCCk :: D -> D -> D -> Sig -> SE () #
Sends a MIDI controller data message to fluid.
Sends a MIDI controller data (MIDI controller number and value to use) message to a fluid engine by number on the user specified MIDI channel number.
fluidCCk iEngineNumber, iChannelNumber, iControllerNumber, kValue
csound doc: http://csound.com/docs/manual/fluidCCk.html
fluidControl :: D -> Sig -> Sig -> Sig -> Sig -> SE () #
Sends MIDI note on, note off, and other messages to a SoundFont preset.
The fluid opcodes provide a simple Csound opcode wrapper around Peter Hanappe's Fluidsynth SoundFont2 synthesizer. This implementation accepts any MIDI note on, note off, controller, pitch bend, or program change message at k-rate. Maximum polyphony is 4096 simultaneously sounding voices. Any number of SoundFonts may be loaded and played simultaneously.
fluidControl ienginenum, kstatus, kchannel, kdata1, kdata2
csound doc: http://csound.com/docs/manual/fluidControl.html
fluidEngine :: D #
Instantiates a fluidsynth engine.
Instantiates a fluidsynth engine, and returns ienginenum to identify the engine. ienginenum is passed to other other opcodes for loading and playing SoundFonts and gathering the generated sound.
ienginenum fluidEngine [iReverbEnabled] [, iChorusEnabled] [,iNumChannels] [, iPolyphony]
csound doc: http://csound.com/docs/manual/fluidEngine.html
Loads a SoundFont into a fluidEngine, optionally listing SoundFont contents.
Loads a SoundFont into an instance of a fluidEngine, optionally listing banks and presets for SoundFont.
isfnum fluidLoad soundfont, ienginenum[, ilistpresets]
csound doc: http://csound.com/docs/manual/fluidLoad.html
fluidNote :: D -> D -> D -> D -> SE () #
Plays a note on a channel in a fluidSynth engine.
Plays a note at imidikey pitch and imidivel velocity on ichannelnum channel of number ienginenum fluidEngine.
fluidNote ienginenum, ichannelnum, imidikey, imidivel
csound doc: http://csound.com/docs/manual/fluidNote.html
Outputs sound from a given fluidEngine
Outputs the sound from a fluidEngine.
aleft, aright fluidOut ienginenum
csound doc: http://csound.com/docs/manual/fluidOut.html
fluidProgramSelect :: D -> D -> Tab -> D -> D -> SE () #
Assigns a preset from a SoundFont to a channel on a fluidEngine.
fluidProgramSelect ienginenum, ichannelnum, isfnum, ibanknum, ipresetnum
csound doc: http://csound.com/docs/manual/fluidProgramSelect.html
fluidSetInterpMethod :: D -> D -> D -> SE () #
Set interpolation method for channel in Fluid Engine
Set interpolation method for channel in Fluid Engine. Lower order interpolation methods will render faster at lower fidelity while higher order interpolation methods will render slower at higher fidelity. Default interpolation for a channel is 4th order interpolation.
fluidSetInterpMethod ienginenum, ichannelnum, iInterpMethod
csound doc: http://csound.com/docs/manual/fluidSetInterpMethod.html
loscil :: Tuple a => Sig -> Sig -> Tab -> a #
Read sampled sound from a table.
Read sampled sound (mono or stereo) from a table, with optional sustain and release looping.
ar1 [,ar2] loscil xamp, kcps, ifn [, ibas] [, imod1] [, ibeg1] [, iend1] \ [, imod2] [, ibeg2] [, iend2]
csound doc: http://csound.com/docs/manual/loscil.html
loscil3 :: Tuple a => Sig -> Sig -> Tab -> a #
Read sampled sound from a table using cubic interpolation.
Read sampled sound (mono or stereo) from a table, with optional sustain and release looping, using cubic interpolation.
ar1 [,ar2] loscil3 xamp, kcps, ifn [, ibas] [, imod1] [, ibeg1] [, iend1] \ [, imod2] [, ibeg2] [, iend2]
csound doc: http://csound.com/docs/manual/loscil3.html
loscilx :: Tuple a => Sig -> Sig -> Tab -> a #
Read multi-channel sampled sound from a table.
Read sampled sound (up to 16 channels) from a table, with optional sustain and release looping.
ar1 [, ar2, ar3, ar4, ar5, ar6, ar7, ar8, ar9, ar10, ar11, ar12, ar13, ar14, \ ar15, ar16] loscilx xamp, kcps, ifn \ [, iwsize, ibas, istrt, imod, ibeg, iend]
csound doc: http://csound.com/docs/manual/loscilx.html
Generates a table index for sample playback
This opcode can be used to generate table index for sample playback (e.g. tablexkt).
ares lphasor xtrns [, ilps] [, ilpe] [, imode] [, istrt] [, istor]
csound doc: http://csound.com/docs/manual/lphasor.html
lposcil :: Sig -> Sig -> Sig -> Sig -> Tab -> Sig #
Read sampled sound from a table with looping and high precision.
Read sampled sound (mono or stereo) from a table, with looping, and high precision.
ares lposcil kamp, kfreqratio, kloop, kend, ifn [, iphs]
csound doc: http://csound.com/docs/manual/lposcil.html
lposcil3 :: Sig -> Sig -> Sig -> Sig -> Tab -> Sig #
Read sampled sound from a table with high precision and cubic interpolation.
Read sampled sound (mono or stereo) from a table, with looping, and high precision. lposcil3 uses cubic interpolation.
ares lposcil3 kamp, kfreqratio, kloop, kend, ifn [, iphs]
csound doc: http://csound.com/docs/manual/lposcil3.html
lposcila :: Sig -> Sig -> Sig -> Sig -> D -> Sig #
Read sampled sound from a table with looping and high precision.
lposcila reads sampled sound from a table with looping and high precision.
ar lposcila aamp, kfreqratio, kloop, kend, ift [,iphs]
csound doc: http://csound.com/docs/manual/lposcila.html
lposcilsa :: Sig -> Sig -> Sig -> Sig -> D -> (Sig, Sig) #
Read stereo sampled sound from a table with looping and high precision.
lposcilsa reads stereo sampled sound from a table with looping and high precision.
ar1, ar2 lposcilsa aamp, kfreqratio, kloop, kend, ift [,iphs]
csound doc: http://csound.com/docs/manual/lposcilsa.html
lposcilsa2 :: Sig -> Sig -> Sig -> Sig -> D -> (Sig, Sig) #
Read stereo sampled sound from a table with looping and high precision.
lposcilsa2 reads stereo sampled sound from a table with looping and high precision.
ar1, ar2 lposcilsa2 aamp, kfreqratio, kloop, kend, ift [,iphs]
csound doc: http://csound.com/docs/manual/lposcilsa2.html
Prints a list of all instruments of a previously loaded SoundFont2 (SF2) file.
Prints a list of all instruments of a previously loaded SoundFont2 (SF2) sample file. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.
sfilist ifilhandle
csound doc: http://csound.com/docs/manual/sfilist.html
sfinstr :: D -> D -> Sig -> Sig -> D -> Sf -> (Sig, Sig) #
Plays a SoundFont2 (SF2) sample instrument, generating a stereo sound.
Plays a SoundFont2 (SF2) sample instrument, generating a stereo sound. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.
ar1, ar2 sfinstr ivel, inotenum, xamp, xfreq, instrnum, ifilhandle \ [, iflag] [, ioffset]
csound doc: http://csound.com/docs/manual/sfinstr.html
sfinstr3 :: D -> D -> Sig -> Sig -> D -> Sf -> (Sig, Sig) #
Plays a SoundFont2 (SF2) sample instrument, generating a stereo sound with cubic interpolation.
Plays a SoundFont2 (SF2) sample instrument, generating a stereo sound with cubic interpolation. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.
ar1, ar2 sfinstr3 ivel, inotenum, xamp, xfreq, instrnum, ifilhandle \ [, iflag] [, ioffset]
csound doc: http://csound.com/docs/manual/sfinstr3.html
sfinstr3m :: D -> D -> Sig -> Sig -> D -> Sf -> Sig #
Plays a SoundFont2 (SF2) sample instrument, generating a mono sound with cubic interpolation.
Plays a SoundFont2 (SF2) sample instrument, generating a mono sound with cubic interpolation. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.
ares sfinstr3m ivel, inotenum, xamp, xfreq, instrnum, ifilhandle \ [, iflag] [, ioffset]
csound doc: http://csound.com/docs/manual/sfinstr3m.html
sfinstrm :: D -> D -> Sig -> Sig -> D -> Sf -> Sig #
Plays a SoundFont2 (SF2) sample instrument, generating a mono sound.
Plays a SoundFont2 (SF2) sample instrument, generating a mono sound. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.
ares sfinstrm ivel, inotenum, xamp, xfreq, instrnum, ifilhandle \ [, iflag] [, ioffset]
csound doc: http://csound.com/docs/manual/sfinstrm.html
Loads an entire SoundFont2 (SF2) sample file into memory.
Loads an entire SoundFont2 (SF2) sample file into memory. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.
ir sfload "filename"
csound doc: http://csound.com/docs/manual/sfload.html
sflooper :: D -> D -> Sig -> Sig -> Sf -> Sig -> Sig -> Sig -> (Sig, Sig) #
Plays a SoundFont2 (SF2) sample preset, generating a stereo sound, with user-defined time-varying crossfade looping.
Plays a SoundFont2 (SF2) sample preset, generating a stereo sound, similarly to sfplay. Unlike that opcode, though, it ignores the looping points set in the SF2 file and substitutes them for a user-defined crossfade loop. It is a cross between sfplay and flooper2.
ar1, ar2 sflooper ivel, inotenum, kamp, kpitch, ipreindex, kloopstart, kloopend, kcrossfade \ [, istart, imode, ifenv, iskip]
csound doc: http://csound.com/docs/manual/sflooper.html
sfpassign :: D -> Sf -> SE () #
Assigns all presets of a SoundFont2 (SF2) sample file to a sequence of progressive index numbers.
Assigns all presets of a previously loaded SoundFont2 (SF2) sample file to a sequence of progressive index numbers. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.
sfpassign istartindex, ifilhandle[, imsgs]
csound doc: http://csound.com/docs/manual/sfpassign.html
sfplay :: D -> D -> Sig -> Sig -> Sf -> (Sig, Sig) #
Plays a SoundFont2 (SF2) sample preset, generating a stereo sound.
Plays a SoundFont2 (SF2) sample preset, generating a stereo sound. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.
ar1, ar2 sfplay ivel, inotenum, xamp, xfreq, ipreindex [, iflag] [, ioffset] [, ienv]
csound doc: http://csound.com/docs/manual/sfplay.html
sfplay3 :: D -> D -> Sig -> Sig -> Sf -> (Sig, Sig) #
Plays a SoundFont2 (SF2) sample preset, generating a stereo sound with cubic interpolation.
Plays a SoundFont2 (SF2) sample preset, generating a stereo sound with cubic interpolation. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.
ar1, ar2 sfplay3 ivel, inotenum, xamp, xfreq, ipreindex [, iflag] [, ioffset] [, ienv]
csound doc: http://csound.com/docs/manual/sfplay3.html
sfplay3m :: D -> D -> Sig -> Sig -> Sf -> Sig #
Plays a SoundFont2 (SF2) sample preset, generating a mono sound with cubic interpolation.
Plays a SoundFont2 (SF2) sample preset, generating a mono sound with cubic interpolation. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.
ares sfplay3m ivel, inotenum, xamp, xfreq, ipreindex [, iflag] [, ioffset] [, ienv]
csound doc: http://csound.com/docs/manual/sfplay3m.html
sfplaym :: D -> D -> Sig -> Sig -> Sf -> Sig #
Plays a SoundFont2 (SF2) sample preset, generating a mono sound.
Plays a SoundFont2 (SF2) sample preset, generating a mono sound. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.
ares sfplaym ivel, inotenum, xamp, xfreq, ipreindex [, iflag] [, ioffset] [, ienv]
csound doc: http://csound.com/docs/manual/sfplaym.html
Prints a list of all presets of a SoundFont2 (SF2) sample file.
Prints a list of all presets of a previously loaded SoundFont2 (SF2) sample file. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.
sfplist ifilhandle
csound doc: http://csound.com/docs/manual/sfplist.html
sfpreset :: D -> D -> Sf -> Sf -> D #
Assigns an existing preset of a SoundFont2 (SF2) sample file to an index number.
Assigns an existing preset of a previously loaded SoundFont2 (SF2) sample file to an index number. These opcodes allow management the sample-structure of SF2 files. In order to understand the usage of these opcodes, the user must have some knowledge of the SF2 format, so a brief description of this format can be found in the SoundFont2 File Format Appendix.
ir sfpreset iprog, ibank, ifilhandle, ipreindex
csound doc: http://csound.com/docs/manual/sfpreset.html
sndloop :: Sig -> Sig -> Sig -> D -> D -> (Sig, Sig) #
A sound looper with pitch control.
This opcode records input audio and plays it back in a loop with user-defined duration and crossfade time. It also allows the pitch of the loop to be controlled, including reversed playback.
asig, krec sndloop ain, kpitch, ktrig, idur, ifad
csound doc: http://csound.com/docs/manual/sndloop.html
waveset :: Sig -> Sig -> Sig #
A simple time stretch by repeating cycles.
ares waveset ain, krep [, ilen]
csound doc: http://csound.com/docs/manual/waveset.html
scanhammer :: D -> D -> D -> D -> SE () #
Copies from one table to another with a gain control.
This is is a variant of tablecopy, copying from one table to another, starting at ipos, and with a gain control. The number of points copied is determined by the length of the source. Other points are not changed. This opcode can be used to âhitâ a string in the scanned synthesis code.
scanhammer isrc, idst, ipos, imult
csound doc: http://csound.com/docs/manual/scanhammer.html
scans :: Sig -> Sig -> Tab -> D -> Sig #
Generate audio output using scanned synthesis.
ares scans kamp, kfreq, ifn, id [, iorder]
csound doc: http://csound.com/docs/manual/scans.html
scantable :: Sig -> Sig -> D -> D -> D -> D -> D -> Sig #
A simpler scanned synthesis implementation.
A simpler scanned synthesis implementation. This is an implementation of a circular string scanned using external tables. This opcode will allow direct modification and reading of values with the table opcodes.
aout scantable kamp, kpch, ipos, imass, istiff, idamp, ivel
csound doc: http://csound.com/docs/manual/scantable.html
scanu :: D -> D -> Tab -> Tab -> Tab -> Tab -> Tab -> Sig -> Sig -> Sig -> Sig -> D -> D -> Sig -> Sig -> Sig -> D -> D -> SE () #
Compute the waveform and the wavetable for use in scanned synthesis.
scanu init, irate, ifnvel, ifnmass, ifnstif, ifncentr, ifndamp, kmass, \ kstif, kcentr, kdamp, ileft, iright, kpos, kstrngth, ain, idisp, id
csound doc: http://csound.com/docs/manual/scanu.html
xscanmap :: D -> Sig -> Sig -> (Sig, Sig) #
Allows the position and velocity of a node in a scanned process to be read.
kpos, kvel xscanmap iscan, kamp, kvamp [, iwhich]
csound doc: http://csound.com/docs/manual/xscanmap.html
xscans :: Sig -> Sig -> Tab -> D -> Sig #
Fast scanned synthesis waveform and the wavetable generator.
Experimental version of scans. Allows much larger matrices and is faster and smaller but removes some (unused?) flexibility. If liked, it will replace the older opcode as it is syntax compatible but extended.
ares xscans kamp, kfreq, ifntraj, id [, iorder]
csound doc: http://csound.com/docs/manual/xscans.html
xscansmap :: Sig -> Sig -> D -> Sig -> Sig -> SE () #
Allows the position and velocity of a node in a scanned process to be read.
xscansmap kpos, kvel, iscan, kamp, kvamp [, iwhich]
csound doc: http://csound.com/docs/manual/xscansmap.html
xscanu :: D -> D -> Tab -> Tab -> Tab -> Tab -> Tab -> Sig -> Sig -> Sig -> Sig -> D -> D -> Sig -> Sig -> Sig -> D -> D -> SE () #
Compute the waveform and the wavetable for use in scanned synthesis.
Experimental version of scanu. Allows much larger matrices and is faster and smaller but removes some (unused?) flexibility. If liked, it will replace the older opcode as it is syntax compatible but extended.
xscanu init, irate, ifnvel, ifnmass, ifnstif, ifncentr, ifndamp, kmass, \ kstif, kcentr, kdamp, ileft, iright, kpos, kstrngth, ain, idisp, id
csound doc: http://csound.com/docs/manual/xscanu.html
stkBandedWG :: D -> D -> Sig #
STKBandedWG uses banded waveguide techniques to model a variety of sounds.
This opcode uses banded waveguide techniques to model a variety of sounds, including bowed bars, glasses, and bowls.
asignal STKBandedWG ifrequency, iamplitude, [kpress, kv1[, kmot, kv2[, klfo, kv3[, klfodepth, kv4[, kvel, kv5[, kstrk, kv6[, kinstr, kv7]]]]]]]
csound doc: http://csound.com/docs/manual/STKBandedWG.html
stkBeeThree :: D -> D -> Sig #
STK Hammond-oid organ-like FM synthesis instrument.
asignal STKBeeThree ifrequency, iamplitude, [kop4, kv1[, kop3, kv2[, klfo, kv3[, klfodepth, kv4[, kadsr, kv5]]]]]
csound doc: http://csound.com/docs/manual/STKBeeThree.html
stkBlowBotl :: D -> D -> Sig #
STKBlowBotl uses a helmholtz resonator (biquad filter) with a polynomial jet excitation.
This opcode implements a helmholtz resonator (biquad filter) with a polynomial jet excitation (a la Cook).
asignal STKBlowBotl ifrequency, iamplitude, [knoise, kv1[, klfo, kv2[, klfodepth, kv3[, kvol, kv4]]]]
csound doc: http://csound.com/docs/manual/STKBlowBotl.html
stkBlowHole :: D -> D -> Sig #
STK clarinet physical model with one register hole and one tonehole.
This opcode is based on the clarinet model, with the addition of a two-port register hole and a three-port dynamic tonehole implementation.
asignal STKBlowHole ifrequency, iamplitude, [kreed, kv1[, knoise, kv2[, khole, kv3[, kreg, kv4[, kbreath, kv5]]]]]
csound doc: http://csound.com/docs/manual/STKBlowHole.html
STKBowed is a bowed string instrument.
STKBowed is a bowed string instrument, using a waveguide model.
asignal STKBowed ifrequency, iamplitude, [kpress, kv1[, kpos, kv2[, klfo, kv3[, klfodepth, kv4[, kvol, kv5]]]]]
csound doc: http://csound.com/docs/manual/STKBowed.html
STKBrass is a simple brass instrument.
STKBrass uses a simple brass instrument waveguide model, a la Cook.
asignal STKBrass ifrequency, iamplitude, [klip, kv1[, kslide, kv2[, klfo, kv3[, klfodepth, kv4[, kvol, kv5]]]]]
csound doc: http://csound.com/docs/manual/STKBrass.html
stkClarinet :: D -> D -> Sig #
STKClarinet uses a simple clarinet physical model.
asignal STKClarinet ifrequency, iamplitude, [kstiff, kv1[, knoise, kv2[, klfo, kv3[, klfodepth, kv4[, kbreath, kv5]]]]]
csound doc: http://csound.com/docs/manual/STKClarinet.html
stkDrummer :: D -> D -> Sig #
STKDrummer is a drum sampling synthesizer.
STKDrummer is a drum sampling synthesizer using raw waves and one-pole filters, The drum rawwave files are sampled at 22050 Hz, but will be appropriately interpolated for other sample rates.
asignal STKDrummer ifrequency, iamplitude
csound doc: http://csound.com/docs/manual/STKDrummer.html
stkFMVoices :: D -> D -> Sig #
STKFMVoices is a singing FM synthesis instrument.
STKFMVoices is a singing FM synthesis instrument. It has 3 carriers and a common modulator, also referred to as algorithm 6 of the TX81Z.
asignal STKFMVoices ifrequency, iamplitude, [kvowel, kv1[, kspec, kv2[, klfo, kv3[, klfodepth, kv4[, kadsr, kv5]]]]]
csound doc: http://csound.com/docs/manual/STKFMVoices.html
STKFlute uses a simple flute physical model.
STKFlute uses a simple flute physical model. The jet model uses a polynomial, a la Cook.
asignal STKFlute ifrequency, iamplitude, [kjet, kv1[, knoise, kv2[, klfo, kv3[, klfodepth, kv4[, kbreath, kv5]]]]]
csound doc: http://csound.com/docs/manual/STKFlute.html
stkHevyMetl :: D -> D -> Sig #
STKHevyMetl produces metal sounds.
STKHevyMetl produces metal sounds, using FM synthesis. It uses 3 cascade operators with feedback modulation, also referred to as algorithm 3 of the TX81Z.
asignal STKHevyMetl ifrequency, iamplitude, [kmod, kv1[, kcross, kv2[, klfo, kv3[, klfodepth, kv4[, kadsr, kv5]]]]]
csound doc: http://csound.com/docs/manual/STKHevyMetl.html
stkMandolin :: D -> D -> Sig #
STKMandolin produces mamdolin-like sounds.
STKMandolin produces mamdolin-like sounds, using "commuted synthesis" techniques to model a mandolin instrument.
asignal STKMandolin ifrequency, iamplitude, [kbody, kv1[, kpos, kv2[, ksus, kv3[, kdetune, kv4[, kmic, kv5]]]]]
csound doc: http://csound.com/docs/manual/STKMandolin.html
stkModalBar :: D -> D -> Sig #
STKModalBar is a resonant bar instrument.
This opcode is a resonant bar instrument.It has a number of different struck bar instruments.
asignal STKModalBar ifrequency, iamplitude, [khard, kv1[, kpos, kv2[, klfo, kv3[, klfodepth, kv4[, kmix, kv5[, kvol, kv6[, kinstr, kv7]]]]]]]
csound doc: http://csound.com/docs/manual/STKModalBar.html
STKMoog produces moog-like swept filter sounds.
STKMoog produces moog-like swept filter sounds, using one attack wave, one looped wave, and an ADSR envelope and adds two sweepable formant filters.
asignal STKMoog ifrequency, iamplitude, [kq, kv1[, krate, kv2[, klfo, kv3[, klfodepth, kv4[, kvol, kv5]]]]]
csound doc: http://csound.com/docs/manual/STKMoog.html
stkPercFlut :: D -> D -> Sig #
STKPercFlut is a percussive flute FM synthesis instrument.
STKPercFlut is a percussive flute FM synthesis instrument. The instrument uses an algorithm like the algorithm 4 of the TX81Z.
asignal STKPercFlut ifrequency, iamplitude, [kmod, kv1[, kcross, kv2[, klfo, kv3[, klfodepth, kv4[, kadsr, kv5]]]]]
csound doc: http://csound.com/docs/manual/STKPercFlut.html
stkPlucked :: D -> D -> Sig #
STKPlucked uses a plucked string physical model.
STKPlucked uses a plucked string physical model based on the Karplus-Strong algorithm.
asignal STKPlucked ifrequency, iamplitude
csound doc: http://csound.com/docs/manual/STKPlucked.html
stkResonate :: D -> D -> Sig #
STKResonate is a noise driven formant filter.
STKResonate is a noise driven formant filter. This instrument contains a noise source, which excites a biquad resonance filter, with volume controlled by an ADSR.
asignal STKResonate ifrequency, iamplitude, [kfreq, kv1[, kpole, kv2[, knotch, kv3[, kzero, kv4[, kenv, kv5]]]]]
csound doc: http://csound.com/docs/manual/STKResonate.html
STK Fender Rhodes-like electric piano FM synthesis instrument.
asignal STKRhodey ifrequency, iamplitude, [kmod, kv1[, kcross, kv2[, klfo, kv3[, klfodepth, kv4[, kadsr, kv5]]]]]
csound doc: http://csound.com/docs/manual/STKRhodey.html
stkSaxofony :: D -> D -> Sig #
STKSaxofony is a faux conical bore reed instrument.
STKSaxofony is a faux conical bore reed instrument. This opcode uses a "hybrid" digital waveguide instrument that can generate a variety of wind-like sounds. It has also been referred to as the "blowed string" model. The waveguide section is essentially that of a string, with one rigid and one lossy termination. The non-linear function is a reed table. The string can be "blown" at any point between the terminations, though just as with strings, it is impossible to excite the system at either end. If the excitation is placed at the string mid-point, the sound is that of a clarinet. At points closer to the "bridge", the sound is closer to that of a saxophone.
asignal STKSaxofony ifrequency, iamplitude, [kstiff, kv1[, kapert, kv2[, kblow, kv3[, knoise, kv4[, klfo, kv5[, klfodepth, kv6[, kbreath, kv7]]]]]]]
csound doc: http://csound.com/docs/manual/STKSaxofony.html
stkShakers :: D -> D -> Sig #
STKShakers is an instrument that simulates environmental sounds or collisions of multiple independent sound producing objects.
STKShakers are a set of PhISEM and PhOLIES instruments: PhISEM (Physically Informed Stochastic Event Modeling) is an algorithmic approach for simulating collisions of multiple independent sound producing objects. It can simulate a Maraca, Sekere, Cabasa, Bamboo Wind Chimes, Water Drops, Tambourine, Sleighbells, and a Guiro. On http://soundlab.cs.princeton.edu/research/controllers/shakers/ PhOLIES (Physically-Oriented Library of Imitated Environmental Sounds) there is a similar approach for the synthesis of environmental sounds. It simulates of breaking sticks, crunchy snow (or not), a wrench, sandpaper, and more..
asignal STKShakers ifrequency, iamplitude, [kenerg, kv1[, kdecay, kv2[, kshake, kv3[, knum, kv4[, kres, kv5[, kinstr, kv6]]]]]]
csound doc: http://csound.com/docs/manual/STKShakers.html
STKSimple is a wavetable/noise instrument.
STKSimple is a wavetable/noise instrument. It combines a looped wave, a noise source, a biquad resonance filter, a one-pole filter, and an ADSR envelope to create some interesting sounds.
asignal STKSimple ifrequency, iamplitude, [kpos, kv1[, kcross, kv2[, kenv, kv3[, kgain, kv4]]]]
csound doc: http://csound.com/docs/manual/STKSimple.html
STKSitar uses a plucked string physical model.
STKSitar uses a plucked string physical model based on the Karplus-Strong algorithm.
asignal STKSitar ifrequency, iamplitude
csound doc: http://csound.com/docs/manual/STKSitar.html
stkStifKarp :: D -> D -> Sig #
STKStifKarp is a plucked stiff string instrument.
STKStifKarp is a plucked stiff string instrument. It a simple plucked string algorithm (Karplus Strong) with enhancements, including string stiffness and pluck position controls. The stiffness is modeled with allpass filters.
asignal STKStifKarp ifrequency, iamplitude, [kpos, kv1[, ksus, kv2[, kstretch, kv3]]]
csound doc: http://csound.com/docs/manual/STKStifKarp.html
stkTubeBell :: D -> D -> Sig #
STKTubeBell is a tubular bell (orchestral chime) FM synthesis instrument.
STKTubeBell is a tubular bell (orchestral chime) FM synthesis instrument. It uses two simple FM Pairs summed together, also referred to as algorithm 5 of the TX81Z.
asignal STKTubeBell ifrequency, iamplitude, [kmod, kv1[, kcross, kv2[, klfo, kv3[, klfodepth, kv4[, kadsr, kv5]]]]]
csound doc: http://csound.com/docs/manual/STKTubeBell.html
stkVoicForm :: D -> D -> Sig #
STKVoicForm is a four formant synthesis instrument.
STKVoicForm is a four formant synthesis instrument. This instrument contains an excitation singing wavetable (looping wave with random and periodic vibrato, smoothing on frequency, etc.), excitation noise, and four sweepable complex resonances. Measured formant data is included, and enough data is there to support either parallel or cascade synthesis. In the floating point case cascade synthesis is the most natural so that's what you'll find here.
asignal STKVoicForm ifrequency, iamplitude, [kmix, kv1[, ksel, kv2[, klfo, kv3[, klfodepth, kv4[, kloud, kv5]]]]]
csound doc: http://csound.com/docs/manual/STKVoicForm.html
stkWhistle :: D -> D -> Sig #
STKWhistle produces whistle sounds.
STKWhistle produces (police) whistle sounds. It uses a hybrid physical/spectral model of a police whistle (a la Cook).
asignal STKWhistle ifrequency, iamplitude, [kmod, kv1[, knoise, kv2[, kfipfreq, kv3[, kfipgain, kv4[, kvol, kv5]]]]]
csound doc: http://csound.com/docs/manual/STKWhistle.html
STKWurley simulates a Wurlitzer electric piano FM synthesis instrument.
STKWurley simulates a Wurlitzer electric piano FM synthesis instrument. It uses two simple FM Pairs summed together, also referred to as algorithm 5 of the TX81Z.
asignal STKWurley ifrequency, iamplitude, [kmod, kv1[, kcross, kv2[, klfo, kv3[, klfodepth, kv4[, kadsr, kv5]]]]]
csound doc: http://csound.com/docs/manual/STKWurley.html
oscil1 :: D -> Sig -> D -> Sig #
Accesses table values by incremental sampling.
kres oscil1 idel, kamp, idur [, ifn]
csound doc: http://csound.com/docs/manual/oscil1.html
oscil1i :: D -> Sig -> D -> Sig #
Accesses table values by incremental sampling with linear interpolation.
kres oscil1i idel, kamp, idur [, ifn]
csound doc: http://csound.com/docs/manual/oscil1i.html
Accesses table values by direct indexing.
ares ptable andx, ifn [, ixmode] [, ixoff] [, iwrap] ires ptable indx, ifn [, ixmode] [, ixoff] [, iwrap] kres ptable kndx, ifn [, ixmode] [, ixoff] [, iwrap]
csound doc: http://csound.com/docs/manual/ptable.html
ptable3 :: Sig -> Tab -> Sig #
Accesses table values by direct indexing with cubic interpolation.
ares ptable3 andx, ifn [, ixmode] [, ixoff] [, iwrap] ires ptable3 indx, ifn [, ixmode] [, ixoff] [, iwrap] kres ptable3 kndx, ifn [, ixmode] [, ixoff] [, iwrap]
csound doc: http://csound.com/docs/manual/ptable3.html
ptablei :: Sig -> Tab -> Sig #
Accesses table values by direct indexing with linear interpolation.
ares ptablei andx, ifn [, ixmode] [, ixoff] [, iwrap] ires ptablei indx, ifn [, ixmode] [, ixoff] [, iwrap] kres ptablei kndx, ifn [, ixmode] [, ixoff] [, iwrap]
csound doc: http://csound.com/docs/manual/ptablei.html
Fast table opcodes.
Fast table opcodes. Faster than table and tablew because don't allow wrap-around and limit and don't check index validity. Have been implemented in order to provide fast access to arrays. Support non-power of two tables (can be generated by any GEN function by giving a negative length value).
ir tab_i indx, ifn[, ixmode]
csound doc: http://csound.com/docs/manual/tab.html
Fast table opcodes.
Fast table opcodes. Faster than table and tablew because don't allow wrap-around and limit and don't check index validity. Have been implemented in order to provide fast access to arrays. Support non-power of two tables (can be generated by any GEN function by giving a negative length value).
kr tab kndx, ifn[, ixmode] ar tab xndx, ifn[, ixmode]
csound doc: http://csound.com/docs/manual/tab.html
tabw_i :: D -> D -> Tab -> SE () #
Fast table opcodes.
Fast table opcodes. Faster than table and tablew because don't allow wrap-around and limit and don't check index validity. Have been implemented in order to provide fast access to arrays. Support non-power of two tables (can be generated by any GEN function by giving a negative length value).
tabw_i isig, indx, ifn [,ixmode]
csound doc: http://csound.com/docs/manual/tab.html
tabw :: Sig -> Sig -> Tab -> SE () #
Fast table opcodes.
Fast table opcodes. Faster than table and tablew because don't allow wrap-around and limit and don't check index validity. Have been implemented in order to provide fast access to arrays. Support non-power of two tables (can be generated by any GEN function by giving a negative length value).
tabw ksig, kndx, ifn [,ixmode] tabw asig, andx, ifn [,ixmode]
csound doc: http://csound.com/docs/manual/tab.html
table :: SigOrD a => a -> Tab -> a #
Accesses table values by direct indexing.
ares table andx, ifn [, ixmode] [, ixoff] [, iwrap] ires table indx, ifn [, ixmode] [, ixoff] [, iwrap] kres table kndx, ifn [, ixmode] [, ixoff] [, iwrap]
csound doc: http://csound.com/docs/manual/table.html
table3 :: SigOrD a => a -> Tab -> a #
Accesses table values by direct indexing with cubic interpolation.
ares table3 andx, ifn [, ixmode] [, ixoff] [, iwrap] ires table3 indx, ifn [, ixmode] [, ixoff] [, iwrap] kres table3 kndx, ifn [, ixmode] [, ixoff] [, iwrap]
csound doc: http://csound.com/docs/manual/table3.html
tablei :: SigOrD a => a -> Tab -> a #
Accesses table values by direct indexing with linear interpolation.
ares tablei andx, ifn [, ixmode] [, ixoff] [, iwrap] ires tablei indx, ifn [, ixmode] [, ixoff] [, iwrap] kres tablei kndx, ifn [, ixmode] [, ixoff] [, iwrap]
csound doc: http://csound.com/docs/manual/tablei.html
wterrain :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> Sig #
A simple wave-terrain synthesis opcode.
aout wterrain kamp, kpch, k_xcenter, k_ycenter, k_xradius, k_yradius, \ itabx, itaby
csound doc: http://csound.com/docs/manual/wterrain.html
pluck :: Sig -> Sig -> D -> Tab -> D -> Sig #
Produces a naturally decaying plucked string or drum sound.
Audio output is a naturally decaying plucked string or drum sound based on the Karplus-Strong algorithms.
ares pluck kamp, kcps, icps, ifn, imeth [, iparm1] [, iparm2]
csound doc: http://csound.com/docs/manual/pluck.html
repluck :: D -> Sig -> D -> Sig -> Sig -> Sig -> Sig #
Physical model of the plucked string.
repluck is an implementation of the physical model of the plucked string. A user can control the pluck point, the pickup point, the filter, and an additional audio signal, axcite. axcite is used to excite the string
. Based on the Karplus-Strong algorithm.
ares repluck iplk, kamp, icps, kpick, krefl, axcite
csound doc: http://csound.com/docs/manual/repluck.html
streson :: Sig -> Sig -> Sig -> Sig #
A string resonator with variable fundamental frequency.
An audio signal is modified by a string resonator with variable fundamental frequency.
ares streson asig, kfr, kfdbgain
csound doc: http://csound.com/docs/manual/streson.html
wgbow :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
Creates a tone similar to a bowed string.
Audio output is a tone similar to a bowed string, using a physical model developed from Perry Cook, but re-coded for Csound.
ares wgbow kamp, kfreq, kpres, krat, kvibf, kvamp \ [, ifn] [, iminfreq]
csound doc: http://csound.com/docs/manual/wgbow.html
wgbowedbar :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
A physical model of a bowed bar.
A physical model of a bowed bar, belonging to the Perry Cook family of waveguide instruments.
ares wgbowedbar kamp, kfreq, kpos, kbowpres, kgain [, iconst] [, itvel] \ [, ibowpos] [, ilow]
csound doc: http://csound.com/docs/manual/wgbowedbar.html
wgbrass :: Sig -> Sig -> Sig -> D -> Sig -> Sig -> Sig #
Creates a tone related to a brass instrument.
Audio output is a tone related to a brass instrument, using a physical model developed from Perry Cook, but re-coded for Csound.
ares wgbrass kamp, kfreq, ktens, iatt, kvibf, kvamp \ [, ifn] [, iminfreq]
csound doc: http://csound.com/docs/manual/wgbrass.html
wgclar :: Sig -> Sig -> Sig -> D -> D -> Sig -> Sig -> Sig -> Sig #
Creates a tone similar to a clarinet.
Audio output is a tone similar to a clarinet, using a physical model developed from Perry Cook, but re-coded for Csound.
ares wgclar kamp, kfreq, kstiff, \ iatt, idetk, kngain, kvibf, kvamp [, ifn] [, iminfreq]
csound doc: http://csound.com/docs/manual/wgclar.html
wgflute :: Sig -> Sig -> Sig -> D -> D -> Sig -> Sig -> Sig -> Sig #
Creates a tone similar to a flute.
Audio output is a tone similar to a flute, using a physical model developed from Perry Cook, but re-coded for Csound.
ares wgflute kamp, kfreq, kjet, iatt, idetk, kngain, kvibf, kvamp [, ifn] [, iminfreq] [, ijetrf] [, iendrf]
csound doc: http://csound.com/docs/manual/wgflute.html
wgpluck :: D -> D -> Sig -> D -> D -> D -> Sig -> Sig #
A high fidelity simulation of a plucked string.
A high fidelity simulation of a plucked string, using interpolating delay-lines.
ares wgpluck icps, iamp, kpick, iplk, idamp, ifilt, axcite
csound doc: http://csound.com/docs/manual/wgpluck.html
wgpluck2 :: D -> Sig -> D -> Sig -> Sig -> Sig #
Physical model of the plucked string.
wgpluck2 is an implementation of the physical model of the plucked string, with control over the pluck point, the pickup point and the filter. Based on the Karplus-Strong algorithm.
ares wgpluck2 iplk, kamp, icps, kpick, krefl
csound doc: http://csound.com/docs/manual/wgpluck2.html
dumpk :: Sig -> Str -> D -> D -> SE () #
Periodically writes an orchestra control-signal value to an external file.
Periodically writes an orchestra control-signal value to a named external file in a specific format.
dumpk ksig, ifilname, iformat, iprd
csound doc: http://csound.com/docs/manual/dumpk.html
dumpk2 :: Sig -> Sig -> Str -> D -> D -> SE () #
Periodically writes two orchestra control-signal values to an external file.
Periodically writes two orchestra control-signal values to a named external file in a specific format.
dumpk2 ksig1, ksig2, ifilname, iformat, iprd
csound doc: http://csound.com/docs/manual/dumpk2.html
dumpk3 :: Sig -> Sig -> Sig -> Str -> D -> D -> SE () #
Periodically writes three orchestra control-signal values to an external file.
Periodically writes three orchestra control-signal values to a named external file in a specific format.
dumpk3 ksig1, ksig2, ksig3, ifilname, iformat, iprd
csound doc: http://csound.com/docs/manual/dumpk3.html
dumpk4 :: Sig -> Sig -> Sig -> Sig -> Str -> D -> D -> SE () #
Periodically writes four orchestra control-signal values to an external file.
Periodically writes four orchestra control-signal values to a named external file in a specific format.
dumpk4 ksig1, ksig2, ksig3, ksig4, ifilname, iformat, iprd
csound doc: http://csound.com/docs/manual/dumpk4.html
Closes a previously opened file.
ficlose can be used to close a file which was opened with fiopen.
ficlose ihandle ficlose Sfilename
csound doc: http://csound.com/docs/manual/ficlose.html
fin :: Str -> D -> D -> [Sig] -> SE () #
Read signals from a file at a-rate.
fin ifilename, iskipframes, iformat, ain1 [, ain2] [, ain3] [,...] fin ifilename, iskipframes, iformat, arr[]
csound doc: http://csound.com/docs/manual/fin.html
fini :: Str -> D -> D -> [D] -> SE () #
Read signals from a file at i-rate.
fini ifilename, iskipframes, iformat, in1 [, in2] [, in3] [, ...]
csound doc: http://csound.com/docs/manual/fini.html
fink :: Str -> D -> D -> [Sig] -> SE () #
Read signals from a file at k-rate.
fink ifilename, iskipframes, iformat, kin1 [, kin2] [, kin3] [,...]
csound doc: http://csound.com/docs/manual/fink.html
Opens a file in a specific mode.
fiopen can be used to open a file in one of the specified modes.
ihandle fiopen ifilename, imode
csound doc: http://csound.com/docs/manual/fiopen.html
fout :: Str -> D -> [Sig] -> SE () #
Outputs a-rate signals to an arbitrary number of channels.
fout outputs N a-rate signals to a specified file of N channels.
fout ifilename, iformat, aout1 [, aout2, aout3,...,aoutN] fout ifilename, iformat, array[]
csound doc: http://csound.com/docs/manual/fout.html
fouti :: Str -> D -> D -> [D] -> SE () #
Outputs i-rate signals of an arbitrary number of channels to a specified file.
fouti output N i-rate signals to a specified file of N channels.
fouti ihandle, iformat, iflag, iout1 [, iout2, iout3,....,ioutN]
csound doc: http://csound.com/docs/manual/fouti.html
foutir :: Str -> D -> D -> [D] -> SE () #
Outputs i-rate signals from an arbitrary number of channels to a specified file.
foutir output N i-rate signals to a specified file of N channels.
foutir ihandle, iformat, iflag, iout1 [, iout2, iout3,....,ioutN]
csound doc: http://csound.com/docs/manual/foutir.html
foutk :: Str -> D -> [Sig] -> SE () #
Outputs k-rate signals of an arbitrary number of channels to a specified file, in raw (headerless) format.
foutk outputs N k-rate signals to a specified file of N channels.
foutk ifilename, iformat, kout1 [, kout2, kout3,....,koutN]
csound doc: http://csound.com/docs/manual/foutk.html
fprintks :: Str -> Str -> [Sig] -> SE () #
Similar to printks but prints to a file.
fprintks "filename", "string", [, kval1] [, kval2] [...]
csound doc: http://csound.com/docs/manual/fprintks.html
fprints :: Str -> Str -> [D] -> SE () #
Similar to prints but prints to a file.
fprints "filename", "string" [, ival1] [, ival2] [...]
csound doc: http://csound.com/docs/manual/fprints.html
hdf5read :: Tuple a => Str -> D -> a #
Read signals and arrays from an hdf5 file.
hdf5read reads N signals and arrays from a specified hdf5 file.
xout1[, xout2, xout3, ..., xoutN] hdf5read ifilename, ivariablename1[, ivariablename2, ivariablename3, ..., ivariablenameN]
csound doc: http://csound.com/docs/manual/hdf5read.html
hdf5write :: Str -> Sig -> SE () #
Write signals and arrays to an hdf5 file.
hdf5write writes N signals and arrays to a specified hdf5 file.
hdf5write ifilename, xout1[, xout2, xout3, ..., xoutN]
csound doc: http://csound.com/docs/manual/hdf5write.html
Read a line of text from an external file.
Read a line of text from an external file once each k-cycle.
Sres, kline readf ifilname
csound doc: http://csound.com/docs/manual/readf.html
Read a line of text from an external file.
Read a line of text from an external file once on initialisation.
Sres, iline readfi ifilname
csound doc: http://csound.com/docs/manual/readfi.html
readk :: Str -> D -> D -> Sig #
Periodically reads an orchestra control-signal value from an external file.
Periodically reads an orchestra control-signal value from a named external file in a specific format.
kres readk ifilname, iformat, iprd
csound doc: http://csound.com/docs/manual/readk.html
readk2 :: Str -> D -> D -> (Sig, Sig) #
Periodically reads two orchestra control-signal values from an external file.
kr1, kr2 readk2 ifilname, iformat, iprd
csound doc: http://csound.com/docs/manual/readk2.html
readk3 :: Str -> D -> D -> (Sig, Sig, Sig) #
Periodically reads three orchestra control-signal values from an external file.
kr1, kr2, kr3 readk3 ifilname, iformat, iprd
csound doc: http://csound.com/docs/manual/readk3.html
readk4 :: Str -> D -> D -> (Sig, Sig, Sig, Sig) #
Periodically reads four orchestra control-signal values from an external file.
kr1, kr2, kr3, kr4 readk4 ifilname, iformat, iprd
csound doc: http://csound.com/docs/manual/readk4.html
diskin :: Tuple a => Str -> a #
Reads audio data from an external device or stream and can alter its pitch.
ar1 [, ar2 [, ar3 [, ... arN]]] diskin ifilcod[, kpitch[, iskiptim \ [, iwraparound[, iformat[, iskipinit]]]]] ar1[] diskin ifilcod[, kpitch[, iskiptim \ [, iwraparound[, iformat[, iskipinit]]]]]
csound doc: http://csound.com/docs/manual/diskin.html
diskin2 :: Tuple a => Str -> a #
Reads audio data from a file, and can alter its pitch using one of several available interpolation types, as well as convert the sample rate to match the orchestra sr setting.
Reads audio data from a file, and can alter its pitch using one of several available interpolation types, as well as convert the sample rate to match the orchestra sr setting. diskin2 can also read multichannel files with any number of channels in the range 1 to 24 in versions before 5.14, and 40 after.
a1[, a2[, ... aN]] diskin2 ifilcod[, kpitch[, iskiptim \ [, iwrap[, iformat[, iwsize[, ibufsize[, iskipinit]]]]]]] ar1[] diskin2 ifilcod[, kpitch[, iskiptim \ [, iwrap[, iformat[, iwsize[, ibufsize[, iskipinit]]]]]]]
csound doc: http://csound.com/docs/manual/diskin2.html
Reads mono audio data from an external device or stream.
Reads audio data from an external device or stream.
ar1 in aarray in
csound doc: http://csound.com/docs/manual/in.html
Reads a 32-channel audio signal from an external device or stream.
ar1, ar2, ar3, ar4, ar5, ar6, ar7, ar8, ar9, ar10, ar11, ar12, ar13, ar14, \ ar15, ar16, ar17, ar18, ar19, ar20, ar21, ar22, ar23, ar24, ar25, ar26, \ ar27, ar28, ar29, ar30, ar31, ar32 in32
csound doc: http://csound.com/docs/manual/in32.html
inch :: Tuple a => [Sig] -> a #
Reads from numbered channels in an external audio signal or stream.
ain1[, ...] inch kchan1[,...]
csound doc: http://csound.com/docs/manual/inch.html
Reads six-channel audio data from an external device or stream.
ar1, ar2, ar3, ar4, ar5, ar6 inh
csound doc: http://csound.com/docs/manual/inh.html
Reads eight-channel audio data from an external device or stream.
ar1, ar2, ar3, ar4, ar5, ar6, ar7, ar8 ino
csound doc: http://csound.com/docs/manual/ino.html
Reads quad audio data from an external device or stream.
ar1, ar2, ar3, a4 inq
csound doc: http://csound.com/docs/manual/inq.html
inrg :: Sig -> [Sig] -> SE () #
Allow input from a range of adjacent audio channels from the audio input device
inrg reads audio from a range of adjacent audio channels from the audio input device.
inrg kstart, ain1 [,ain2, ain3, ..., ainN]
csound doc: http://csound.com/docs/manual/inrg.html
Reads stereo audio data from an external device or stream.
ar1, ar2 ins
csound doc: http://csound.com/docs/manual/ins.html
Reads a k-rate signal from a user-defined channel.
Reads a k-rate or i-rate signal or string from a user-defined channel.
ivalue invalue "channel name" kvalue invalue "channel name" Sname invalue "channel name"
csound doc: http://csound.com/docs/manual/invalue.html
Reads a 16-channel audio signal from an external device or stream.
ar1, ar2, ar3, ar4, ar5, ar6, ar7, ar8, ar9, ar10, ar11, ar12, \ ar13, ar14, ar15, ar16 inx
csound doc: http://csound.com/docs/manual/inx.html
Reads multi-channel audio samples into a ZAK array from an external device or stream.
inz ksig1
csound doc: http://csound.com/docs/manual/inz.html
Reads mono or stereo audio data from an external MP3 file.
ar1, ar2 mp3in ifilcod[, iskptim, iformat, iskipinit, ibufsize] ar1 mp3in ifilcod[, iskptim, iformat, iskipinit, ibufsize]
csound doc: http://csound.com/docs/manual/mp3in.html
soundin :: Tuple a => Str -> a #
Reads audio data from an external device or stream.
Reads audio data from an external device or stream. Up to 24 channels may be read before v5.14, extended to 40 in later versions.
ar1[, ar2[, ar3[, ... a24]]] soundin ifilcod [, iskptim] [, iformat] \ [, iskipinit] [, ibufsize]
csound doc: http://csound.com/docs/manual/soundin.html
mdelay :: Sig -> Sig -> Sig -> Sig -> Sig -> SE () #
A MIDI delay opcode.
mdelay kstatus, kchan, kd1, kd2, kdelay
csound doc: http://csound.com/docs/manual/mdelay.html
Returns the audio spout frame.
Returns the audio spout frame (if active), otherwise it returns zero.
aout1 [,aout2 ... aoutX] monitor aarra monitor
csound doc: http://csound.com/docs/manual/monitor.html
Writes audio data to an external device or stream.
Writes audio data to an external device or stream, either from audio variables or from an audio array.
out asig1[, asig2,....] out aarray
csound doc: http://csound.com/docs/manual/out.html
out32 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE () #
Writes 32-channel audio data to an external device or stream.
out32 asig1, asig2, asig3, asig4, asig5, asig6, asig7, asig8, asig10, \ asig11, asig12, asig13, asig14, asig15, asig16, asig17, asig18, \ asig19, asig20, asig21, asig22, asig23, asig24, asig25, asig26, \ asig27, asig28, asig29, asig30, asig31, asig32
csound doc: http://csound.com/docs/manual/out32.html
Writes audio data with an arbitrary number of channels to an external device or stream.
outc asig1 [, asig2] [...]
csound doc: http://csound.com/docs/manual/outc.html
outch :: Sig -> [Sig] -> SE () #
Writes multi-channel audio data, with user-controllable channels, to an external device or stream.
outch kchan1, asig1 [, kchan2] [, asig2] [...]
csound doc: http://csound.com/docs/manual/outch.html
outh :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE () #
Writes 6-channel audio data to an external device or stream.
outh asig1, asig2, asig3, asig4, asig5, asig6
csound doc: http://csound.com/docs/manual/outh.html
outo :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE () #
Writes 8-channel audio data to an external device or stream.
outo asig1, asig2, asig3, asig4, asig5, asig6, asig7, asig8
csound doc: http://csound.com/docs/manual/outo.html
outq :: Sig -> Sig -> Sig -> Sig -> SE () #
Writes 4-channel audio data to an external device or stream.
outq asig1, asig2, asig3, asig4
csound doc: http://csound.com/docs/manual/outq.html
Writes samples to quad channel 1 of an external device or stream.
outq1 asig
csound doc: http://csound.com/docs/manual/outq1.html
Writes samples to quad channel 2 of an external device or stream.
outq2 asig
csound doc: http://csound.com/docs/manual/outq2.html
Writes samples to quad channel 3 of an external device or stream.
outq3 asig
csound doc: http://csound.com/docs/manual/outq3.html
Writes samples to quad channel 4 of an external device or stream.
outq4 asig
csound doc: http://csound.com/docs/manual/outq4.html
outrg :: Sig -> [Sig] -> SE () #
Allow output to a range of adjacent audio channels on the audio output device
outrg outputs audio to a range of adjacent audio channels on the audio output device.
outrg kstart, aout1 [,aout2, aout3, ..., aoutN]
csound doc: http://csound.com/docs/manual/outrg.html
Writes stereo audio data to an external device or stream.
outs asig1, asig2
csound doc: http://csound.com/docs/manual/outs.html
Writes samples to stereo channel 1 of an external device or stream.
outs1 asig
csound doc: http://csound.com/docs/manual/outs1.html
Writes samples to stereo channel 2 of an external device or stream.
outs2 asig
csound doc: http://csound.com/docs/manual/outs2.html
outvalue :: Str -> D -> SE () #
Sends an i-rate or k-rate signal or string to a user-defined channel.
Sends an irate or k-rate signal or string to a user-defined channel.
outvalue "channel name", ivalue outvalue "channel name", kvalue outvalue "channel name", "string"
csound doc: http://csound.com/docs/manual/outvalue.html
outx :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE () #
Writes 16-channel audio data to an external device or stream.
outx asig1, asig2, asig3, asig4, asig5, asig6, asig7, asig8, \ asig9, asig10, asig11, asig12, asig13, asig14, asig15, asig16
csound doc: http://csound.com/docs/manual/outx.html
Writes multi-channel audio data from a ZAK array to an external device or stream.
outz ksig1
csound doc: http://csound.com/docs/manual/outz.html
soundout :: Sig -> Str -> SE () #
Deprecated. Writes audio output to a disk file.
The usage of soundout is discouraged. Please use fout instead.
soundout asig1, ifilcod [, iformat]
csound doc: http://csound.com/docs/manual/soundout.html
soundouts :: Sig -> Sig -> Str -> SE () #
Deprecated. Writes audio output to a disk file.
The usage of soundouts is discouraged. Please use fout instead.
soundouts asigl, asigr, ifilcod [, iformat]
csound doc: http://csound.com/docs/manual/soundouts.html
Reads data from the software bus
Reads data from a channel of the inward software bus.
kval chani kchan aval chani kchan
csound doc: http://csound.com/docs/manual/chani.html
chano :: Sig -> Sig -> SE () #
Send data to the outwards software bus
Send data to a channel of the outward software bus.
chano kval, kchan chano aval, kchan
csound doc: http://csound.com/docs/manual/chano.html
Declare a channel of the named software bus.
Declare a channel of the named software bus, with setting optional parameters in the case of a control channel. If the channel does not exist yet, it is created, with an inital value of zero or empty string. Otherwise, the type (control, audio, or string) of the existing channel must match the declaration, or an init error occurs. The input/output mode of an existing channel is updated so that it becomes the bitwise OR of the previous and the newly specified value.
chn_k Sname, imode[, itype, idflt, imin, ima, ix, iy, iwidth, iheight, Sattributes]
csound doc: http://csound.com/docs/manual/chn.html
Declare a channel of the named software bus.
Declare a channel of the named software bus, with setting optional parameters in the case of a control channel. If the channel does not exist yet, it is created, with an inital value of zero or empty string. Otherwise, the type (control, audio, or string) of the existing channel must match the declaration, or an init error occurs. The input/output mode of an existing channel is updated so that it becomes the bitwise OR of the previous and the newly specified value.
chn_a Sname, imode
csound doc: http://csound.com/docs/manual/chn.html
Declare a channel of the named software bus.
Declare a channel of the named software bus, with setting optional parameters in the case of a control channel. If the channel does not exist yet, it is created, with an inital value of zero or empty string. Otherwise, the type (control, audio, or string) of the existing channel must match the declaration, or an init error occurs. The input/output mode of an existing channel is updated so that it becomes the bitwise OR of the previous and the newly specified value.
chn_S Sname, imode
csound doc: http://csound.com/docs/manual/chn.html
Clears an audio output channel of the named software bus.
Clears an audio channel of the named software bus to zero. Implies declaring the channel with imode=2 (see also chn_a).
chnclear Sname
csound doc: http://csound.com/docs/manual/chnclear.html
chnexport :: Str -> D -> Str #
Export a global variable as a channel of the bus.
Export a global variable as a channel of the bus; the channel should not already exist, otherwise an init error occurs. This opcode is normally called from the orchestra header, and allows the host application to read or write orchestra variables directly, without having to use chnget or chnset to copy data.
gival chnexport Sname, imode[, itype, idflt, imin, imax] gkval chnexport Sname, imode[, itype, idflt, imin, imax] gaval chnexport Sname, imode gSval chnexport Sname, imode
csound doc: http://csound.com/docs/manual/chnexport.html
Reads data from the software bus.
Reads data from a channel of the inward named software bus. Implies declaring the channel with imode=1 (see also chn_k, chn_a, and chn_S).
ival chnget Sname kval chnget Sname aval chnget Sname Sval chnget Sname
csound doc: http://csound.com/docs/manual/chnget.html
Reads data from the software bus.
Reads data from a channel of the inward named software bus. Implies declaring the channel with imode=1 (see also chn_k, chn_a, and chn_S).
Sval chngetks Sname
csound doc: http://csound.com/docs/manual/chnget.html
chnmix :: Sig -> Str -> SE () #
Writes audio data to the named software bus, mixing to the previous output.
Adds an audio signal to a channel of the named software bus. Implies declaring the channel with imode=2 (see also chn_a).
chnmix aval, Sname
csound doc: http://csound.com/docs/manual/chnmix.html
chnparams :: Tuple a => Str -> a #
Query parameters of a channel.
Query parameters of a channel (if it does not exist, all returned values are zero).
itype, imode, ictltype, idflt, imin, imax chnparams Sname
csound doc: http://csound.com/docs/manual/chnparams.html
Writes data to the named software bus.
Write to a channel of the named software bus. Implies declaring the channel with imod=2 (see also chn_k, chn_a, and chn_S).
chnset ival, Sname chnset kval, Sname chnset aval, Sname chnset Sval, Sname
csound doc: http://csound.com/docs/manual/chnset.html
chnsetks :: Str -> Str -> SE () #
Writes data to the named software bus.
Write to a channel of the named software bus. Implies declaring the channel with imod=2 (see also chn_k, chn_a, and chn_S).
chnsetks Sval, Sname
csound doc: http://csound.com/docs/manual/chnset.html
Sets the local ksmps value in an instrument or user-defined opcode block
Sets the local ksmps value in an instrument or user-defined opcode block.
setksmps iksmps
csound doc: http://csound.com/docs/manual/setksmps.html
Passes variables to a user-defined opcode block,
The xin and xout opcodes copy variables to and from the opcode definition, allowing communication with the calling instrument.
xinarg1 [, xinarg2] ... [xinargN] xin
csound doc: http://csound.com/docs/manual/xin.html
Retrieves variables from a user-defined opcode block,
The xin and xout opcodes copy variables to and from the opcode definition, allowing communication with the calling instrument.
xout xoutarg1 [, xoutarg2] ... [, xoutargN]
csound doc: http://csound.com/docs/manual/xout.html
dispfft :: Sig -> D -> D -> SE () #
Displays the Fourier Transform of an audio or control signal.
These units will print orchestra init-values, or produce graphic display of orchestra control signals and audio signals. Uses X11 windows if enabled, else (or if -g flag is set) displays are approximated in ASCII characters.
dispfft xsig, iprd, iwsiz [, iwtyp] [, idbout] [, iwtflg] [,imin] [,imax]
csound doc: http://csound.com/docs/manual/dispfft.html
flashtxt :: D -> Str -> SE () #
Allows text to be displayed from instruments like sliders
Allows text to be displayed from instruments like sliders etc. (only on Unix and Windows at present)
flashtxt iwhich, String
csound doc: http://csound.com/docs/manual/flashtxt.html
Displays the values init (i-rate) variables.
These units will print orchestra init-values.
print iarg [, iarg1] [, iarg2] [...]
csound doc: http://csound.com/docs/manual/print.html
printf_i :: Str -> D -> [D] -> SE () #
printf-style formatted output
printf and printf_i write formatted output, similarly to the C function printf(). printf_i runs at i-time only, while printf runs both at initialization and performance time.
printf_i Sfmt, itrig, [iarg1[, iarg2[, ... ]]]
csound doc: http://csound.com/docs/manual/printf.html
Prints one k-rate value at specified intervals.
printk itime, kval [, ispace]
csound doc: http://csound.com/docs/manual/printk.html
Prints a new value every time a control variable changes.
printk2 kvar [, inumspaces]
csound doc: http://csound.com/docs/manual/printk2.html
printks :: Str -> D -> [Sig] -> SE () #
Prints at k-rate using a printf() style syntax.
printks "string", itime [, kval1] [, kval2] [...]
csound doc: http://csound.com/docs/manual/printks.html
printks2 :: Str -> Sig -> SE () #
Prints a new value every time a control variable changes using a printf() style syntax.
printks2 "string", kval
csound doc: http://csound.com/docs/manual/printks2.html
prints :: Str -> [Sig] -> SE () #
Prints at init-time using a printf() style syntax.
prints "string" [, kval1] [, kval2] [...]
csound doc: http://csound.com/docs/manual/prints.html
Returns the number of bits in each sample in a sound file.
ir filebit ifilcod [, iallowraw]
csound doc: http://csound.com/docs/manual/filebit.html
Returns the length of a sound file.
ir filelen ifilcod, [iallowraw]
csound doc: http://csound.com/docs/manual/filelen.html
filenchnls :: Str -> D #
Returns the number of channels in a sound file.
ir filenchnls ifilcod [, iallowraw]
csound doc: http://csound.com/docs/manual/filenchnls.html
Returns the peak absolute value of a sound file.
ir filepeak ifilcod [, ichnl]
csound doc: http://csound.com/docs/manual/filepeak.html
Returns the sample rate of a sound file.
ir filesr ifilcod [, iallowraw]
csound doc: http://csound.com/docs/manual/filesr.html
Checks that a file can be used.
Returns 1 if the sound file is valid, or 0 if not.
ir filevalid ifilcod
csound doc: http://csound.com/docs/manual/filevalid.html
Returns the length of an MP3 sound file.
ir mp3len ifilcod
csound doc: http://csound.com/docs/manual/mp3len.html
clip :: Sig -> D -> D -> Sig #
Clips a signal to a predefined limit.
Clips an a-rate signal to a predefined limit, in a âsoftâ manner, using one of three methods.
ares clip asig, imeth, ilimit [, iarg]
csound doc: http://csound.com/docs/manual/clip.html
compress :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Sig #
Compress, limit, expand, duck or gate an audio signal.
This unit functions as an audio compressor, limiter, expander, or noise gate, using either soft-knee or hard-knee mapping, and with dynamically variable performance characteristics. It takes two audio input signals, aasig and acsig, the first of which is modified by a running analysis of the second. Both signals can be the same, or the first can be modified by a different controlling signal.
ar compress aasig, acsig, kthresh, kloknee, khiknee, kratio, katt, krel, ilook
csound doc: http://csound.com/docs/manual/compress.html
compress2 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> Sig #
Compress, limit, expand, duck or gate an audio signal.
This unit functions as an audio compressor, limiter, expander, or noise gate, using either soft-knee or hard-knee mapping, and with dynamically variable performance characteristics. It takes two audio input signals, aasig and acsig, the first of which is modified by a running analysis of the second. Both signals can be the same, or the first can be modified by a different controlling signal.
ar compress2 aasig, acsig, kthresh, kloknee, khiknee, kratio, katt, krel, ilook
csound doc: http://csound.com/docs/manual/compress2.html
dam :: Sig -> Sig -> D -> D -> D -> D -> Sig #
A dynamic compressor/expander.
This opcode dynamically modifies a gain value applied to the input sound ain by comparing its power level to a given threshold level. The signal will be compressed/expanded with different factors regarding that it is over or under the threshold.
ares dam asig, kthreshold, icomp1, icomp2, irtime, iftime
csound doc: http://csound.com/docs/manual/dam.html
Adjusts the amplitude audio signal according to a root-mean-square value.
ares gain asig, krms [, ihp] [, iskip]
csound doc: http://csound.com/docs/manual/gain.html
convolve :: Tuple a => Sig -> Str -> a #
Convolves a signal and an impulse response.
Output is the convolution of signal ain and the impulse response contained in ifilcod. If more than one output signal is supplied, each will be convolved with the same impulse response. Note that it is considerably more efficient to use one instance of the operator when processing a mono input to create stereo, or quad, outputs.
ar1 [, ar2] [, ar3] [, ar4] convolve ain, ifilcod [, ichannel]
csound doc: http://csound.com/docs/manual/convolve.html
cross2 :: Sig -> Sig -> D -> D -> D -> Sig -> Sig #
Cross synthesis using FFT's.
This is an implementation of cross synthesis using FFT's.
ares cross2 ain1, ain2, isize, ioverlap, iwin, kbias
csound doc: http://csound.com/docs/manual/cross2.html
dconv :: Sig -> D -> Tab -> Sig #
A direct convolution opcode.
ares dconv asig, isize, ifn
csound doc: http://csound.com/docs/manual/dconv.html
ftconv :: Tuple a => Sig -> D -> D -> a #
Low latency multichannel convolution, using a function table as impulse response source.
Low latency multichannel convolution, using a function table as impulse response source. The algorithm is to split the impulse response to partitions of length determined by the iplen parameter, and delay and mix partitions so that the original, full length impulse response is reconstructed without gaps. The output delay (latency) is iplen samples, and does not depend on the control rate, unlike in the case of other convolve opcodes.
a1[, a2[, a3[, ... a8]]] ftconv ain, ift, iplen[, iskipsamples \ [, iirlen[, iskipinit]]]
csound doc: http://csound.com/docs/manual/ftconv.html
ftmorf :: Sig -> Tab -> Tab -> SE () #
Morphs between multiple ftables as specified in a list.
Uses an index into a table of ftable numbers to morph between adjacent tables in the list.This morphed function is written into the table referenced by iresfn on every k-cycle.
ftmorf kftndx, iftfn, iresfn
csound doc: http://csound.com/docs/manual/ftmorf.html
liveconv :: Sig -> D -> D -> Sig -> Sig -> Sig #
Partitioned convolution with dynamically reloadable impulse response
Computationally efficient, partitioned convolution, using a function table as impulse response (IR) source, similar to the ftconv opcode. The liveconv opcode allows dynamic reload of IR data at any time while the convolution is running, controlled by the kupdate parameter. Due to the manner in which the IR is updated, the operation can be done without audio artifacts in the convolution output.
ares liveconv ain, ift, iplen, kupdate, kclear
csound doc: http://csound.com/docs/manual/liveconv.html
pconvolve :: Tuple a => Sig -> Str -> a #
Convolution based on a uniformly partitioned overlap-save algorithm
Convolution based on a uniformly partitioned overlap-save algorithm. Compared to the convolve opcode, pconvolve has these benefits:
ar1 [, ar2] [, ar3] [, ar4] pconvolve ain, ifilcod [, ipartitionsize, ichannel]
csound doc: http://csound.com/docs/manual/pconvolve.html
tvconv :: Sig -> Sig -> Sig -> Sig -> D -> D -> Sig #
A time-varying convolution (FIR filter) opcode.
An opcode that takes two incoming signals and
interprets one of them as the coefficients of linear
time-variable finite impulse response filter. This is
implemented via direct convolution (for partition sizes of
1 sample) or DFT-based partitioned convolution.
The signals can be frozen
(i.e. the filter coefficients are
kept the same) at any point in time, at a-rate or k-rate.
ares tvconv asig1, asig2, xfreez1, xfreez2, iparts, ifils
csound doc: http://csound.com/docs/manual/tvconv.html
Delays an input signal by one sample.
ares delay1 asig [, iskip]
csound doc: http://csound.com/docs/manual/delay1.html
Delays an input signal by some time interval.
k-rate delay opcodes
kr delayk ksig, idel[, imode]
csound doc: http://csound.com/docs/manual/delayk.html
vdel_k :: Sig -> Sig -> D -> Sig #
Delays an input signal by some time interval.
k-rate delay opcodes
kr vdel_k ksig, kdel, imdel[, imode]
csound doc: http://csound.com/docs/manual/delayk.html
Reads from an automatically established digital delay line.
ares delayr idlt [, iskip]
csound doc: http://csound.com/docs/manual/delayr.html
Writes the audio signal to a digital delay line.
delayw asig
csound doc: http://csound.com/docs/manual/delayw.html
Taps a delay line at variable offset times.
Tap a delay line at variable offset times.
ares deltap kdlt
csound doc: http://csound.com/docs/manual/deltap.html
Taps a delay line at variable offset times, uses cubic interpolation.
ares deltap3 xdlt
csound doc: http://csound.com/docs/manual/deltap3.html
Taps a delay line at variable offset times, uses interpolation.
ares deltapi xdlt
csound doc: http://csound.com/docs/manual/deltapi.html
Taps a delay line at variable offset times.
Tap a delay line at variable offset times.
ares deltapn xnumsamps
csound doc: http://csound.com/docs/manual/deltapn.html
deltapx :: Sig -> D -> SE Sig #
Read from or write to a delay line with interpolation.
deltapx is similar to deltapi or deltap3. However, it allows higher quality interpolation. This opcode can read from and write to a delayr/delayw delay line with interpolation.
aout deltapx adel, iwsize
csound doc: http://csound.com/docs/manual/deltapx.html
deltapxw :: Sig -> Sig -> D -> SE () #
Mixes the input signal to a delay line.
deltapxw mixes the input signal to a delay line. This opcode can be mixed with reading units (deltap, deltapn, deltapi, deltap3, and deltapx) in any order; the actual delay time is the difference of the read and write time. This opcode can read from and write to a delayr/delayw delay line with interpolation.
deltapxw ain, adel, iwsize
csound doc: http://csound.com/docs/manual/deltapxw.html
multitap :: Sig -> [D] -> Sig #
Multitap delay line implementation.
ares multitap asig [, itime1, igain1] [, itime2, igain2] [...]
csound doc: http://csound.com/docs/manual/multitap.html
vdelay :: Sig -> Sig -> D -> Sig #
An interpolating variable time delay.
This is an interpolating variable time delay, it is not very different from the existing implementation (deltapi), it is only easier to use.
ares vdelay asig, adel, imaxdel [, iskip]
csound doc: http://csound.com/docs/manual/vdelay.html
vdelay3 :: Sig -> Sig -> D -> Sig #
A variable time delay with cubic interpolation.
vdelay3 is experimental. It is the same as vdelay except that it uses cubic interpolation. (New in Version 3.50.)
ares vdelay3 asig, adel, imaxdel [, iskip]
csound doc: http://csound.com/docs/manual/vdelay3.html
vdelayx :: Sig -> Sig -> D -> D -> Sig #
A variable delay opcode with high quality interpolation.
aout vdelayx ain, adl, imd, iws [, ist]
csound doc: http://csound.com/docs/manual/vdelayx.html
vdelayxq :: Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> (Sig, Sig, Sig, Sig) #
A 4-channel variable delay opcode with high quality interpolation.
aout1, aout2, aout3, aout4 vdelayxq ain1, ain2, ain3, ain4, adl, imd, iws [, ist]
csound doc: http://csound.com/docs/manual/vdelayxq.html
vdelayxs :: Sig -> Sig -> Sig -> D -> D -> (Sig, Sig) #
A stereo variable delay opcode with high quality interpolation.
aout1, aout2 vdelayxs ain1, ain2, adl, imd, iws [, ist]
csound doc: http://csound.com/docs/manual/vdelayxs.html
vdelayxw :: Sig -> Sig -> D -> D -> Sig #
Variable delay opcodes with high quality interpolation.
aout vdelayxw ain, adl, imd, iws [, ist]
csound doc: http://csound.com/docs/manual/vdelayxw.html
vdelayxwq :: Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> (Sig, Sig, Sig, Sig) #
Variable delay opcodes with high quality interpolation.
aout1, aout2, aout3, aout4 vdelayxwq ain1, ain2, ain3, ain4, adl, \ imd, iws [, ist]
csound doc: http://csound.com/docs/manual/vdelayxwq.html
vdelayxws :: Sig -> Sig -> Sig -> D -> D -> (Sig, Sig) #
Variable delay opcodes with high quality interpolation.
aout1, aout2 vdelayxws ain1, ain2, adl, imd, iws [, ist]
csound doc: http://csound.com/docs/manual/vdelayxws.html
bformdec :: Tuple a => D -> Sig -> Sig -> Sig -> Sig -> a #
Deprecated. Decodes an ambisonic B format signal.
Decodes an ambisonic B format signal into loudspeaker specific signals. Note that this opcode is deprecated as it is inaccurate, and is replaced by the much better opcode bformdec1 which replicates all the important features.
ao1, ao2 bformdec isetup, aw, ax, ay, az [, ar, as, at, au, av \ [, abk, al, am, an, ao, ap, aq]] ao1, ao2, ao3, ao4 bformdec isetup, aw, ax, ay, az [, ar, as, at, \ au, av [, abk, al, am, an, ao, ap, aq]] ao1, ao2, ao3, ao4, ao5 bformdec isetup, aw, ax, ay, az [, ar, as, \ at, au, av [, abk, al, am, an, ao, ap, aq]] ao1, ao2, ao3, ao4, ao5, ao6, ao7, ao8 bformdec isetup, aw, ax, ay, az \ [, ar, as, at, au, av [, abk, al, am, an, ao, ap, aq]]]
csound doc: http://csound.com/docs/manual/bformdec.html
bformdec1 :: Tuple a => D -> Sig -> Sig -> Sig -> Sig -> a #
Decodes an ambisonic B format signal
Decodes an ambisonic B format signal into loudspeaker specific signals.
ao1, ao2 bformdec1 isetup, aw, ax, ay, az [, ar, as, at, au, av \ [, abk, al, am, an, ao, ap, aq]] ao1, ao2, ao3, ao4 bformdec1 isetup, aw, ax, ay, az [, ar, as, at, \ au, av [, abk, al, am, an, ao, ap, aq]] ao1, ao2, ao3, ao4, ao5 bformdec1 isetup, aw, ax, ay, az [, ar, as, \ at, au, av [, abk, al, am, an, ao, ap, aq]] ao1, ao2, ao3, ao4, ao5, ao6, ao7, ao8 bformdec1 isetup, aw, ax, ay, az \ [, ar, as, at, au, av [, abk, al, am, an, ao, ap, aq]]] aout[] bformdec1 isetup, abform[]
csound doc: http://csound.com/docs/manual/bformdec1.html
bformenc :: Tuple a => Sig -> Sig -> Sig -> Sig -> Sig -> a #
Deprecated. Codes a signal into the ambisonic B format.
Codes a signal into the ambisonic B format. Note that this opcode is deprecated as it is inaccurate, and is replaced by the much better opcode bformenc1 which replicates all the important features; also note that the gain arguments are not available in bformenc1.
aw, ax, ay, az bformenc asig, kalpha, kbeta, kord0, kord1 aw, ax, ay, az, ar, as, at, au, av bformenc asig, kalpha, kbeta, \ kord0, kord1 , kord2 aw, ax, ay, az, ar, as, at, au, av, ak, al, am, an, ao, ap, aq bformenc \ asig, kalpha, kbeta, kord0, kord1, kord2, kord3
csound doc: http://csound.com/docs/manual/bformenc.html
bformenc1 :: Tuple a => Sig -> Sig -> Sig -> a #
Codes a signal into the ambisonic B format.
Codes a signal into the ambisonic B format
aw, ax, ay, az bformenc1 asig, kalpha, kbeta aw, ax, ay, az, ar, as, at, au, av bformenc1 asig, kalpha, kbeta aw, ax, ay, az, ar, as, at, au, av, ak, al, am, an, ao, ap, aq bformenc1 \ asig, kalpha, kbeta aarray[] bformenc1 asig, kalpha, kbeta
csound doc: http://csound.com/docs/manual/bformenc1.html
hrtfearly :: Tuple a => Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> D -> a #
Generates 3D binaural audio with high-fidelity early reflections in a parametric room using a Phase Truncation algorithm.
This opcode essentially nests the hrtfmove opcode in an image model for a user-definable shoebox-shaped room. A default room can be selected, or advanced room parameters can be used. Room surfaces can be controlled with high and low-frequency absorption coefficients and gain factors of a three-band equaliser.
aleft, aright, irt60low, irt60high, imfp hrtfearly asrc, ksrcx, ksrcy, ksrcz, klstnrx, klstnry, klstnrz, \ ifilel, ifiler, idefroom [,ifade, isr, iorder, ithreed, kheadrot, iroomx, iroomy, iroomz, iwallhigh, \ iwalllow, iwallgain1, iwallgain2, iwallgain3, ifloorhigh, ifloorlow, ifloorgain1, ifloorgain2, \ ifloorgain3, iceilinghigh, iceilinglow, iceilinggain1, iceilinggain2, iceilinggain3]
csound doc: http://csound.com/docs/manual/hrtfearly.html
hrtfmove :: Sig -> Sig -> Sig -> D -> D -> (Sig, Sig) #
Generates dynamic 3d binaural audio for headphones using magnitude interpolation and phase truncation.
This opcode takes a source signal and spatialises it in the 3 dimensional space around a listener by convolving the source with stored head related transfer function (HRTF) based filters.
aleft, aright hrtfmove asrc, kAz, kElev, ifilel, ifiler [, imode, ifade, isr]
csound doc: http://csound.com/docs/manual/hrtfmove.html
hrtfmove2 :: Sig -> Sig -> Sig -> D -> D -> (Sig, Sig) #
Generates dynamic 3d binaural audio for headphones using a Woodworth based spherical head model with improved low frequency phase accuracy.
This opcode takes a source signal and spatialises it in the 3 dimensional space around a listener using head related transfer function (HRTF) based filters.
aleft, aright hrtfmove2 asrc, kAz, kElev, ifilel, ifiler [,ioverlap, iradius, isr]
csound doc: http://csound.com/docs/manual/hrtfmove2.html
hrtfreverb :: Sig -> D -> D -> D -> D -> (Sig, Sig, D) #
A binaural, dynamic FDN based diffuse-field reverberator. The opcode works independently as an efficient, flexible reverberator.
A frequency-dependent, efficient reverberant field is created based on low and high frequency desired reverb times. The opcode is designed to work with hrtfearly, ideally using its outputs as inputs. However, hrtfreverb can be used as a standalone tool. Stability is enforced.
aleft, aright, idel hrtfreverb asrc, ilowrt60, ihighrt60, ifilel, ifiler [,isr, imfp, iorder]
csound doc: http://csound.com/docs/manual/hrtfreverb.html
hrtfstat :: Sig -> D -> D -> D -> D -> (Sig, Sig) #
Generates static 3d binaural audio for headphones using a Woodworth based spherical head model with improved low frequency phase accuracy.
This opcode takes a source signal and spatialises it in the 3 dimensional space around a listener using head related transfer function (HRTF) based filters. It produces a static output (azimuth and elevation parameters are i-rate), because a static source allows much more efficient processing than hrtfmove and hrtfmove2,.
aleft, aright hrtfstat asrc, iAz, iElev, ifilel, ifiler [,iradius, isr]
csound doc: http://csound.com/docs/manual/hrtfstat.html
locsend :: (Sig, Sig, Sig, Sig) #
Distributes the audio signals of a previous locsig opcode.
locsend depends upon the existence of a previously defined locsig. The number of output signals must match the number in the previous locsig. The output signals from locsend are derived from the values given for distance and reverb in the locsig and are ready to be sent to local or global reverb units (see example below). The reverb amount and the balance between the 2 or 4 channels are calculated in the same way as described in the Dodge book (an essential text!).
a1, a2 locsend a1, a2, a3, a4 locsend
csound doc: http://csound.com/docs/manual/locsend.html
locsig :: Sig -> Sig -> Sig -> Sig -> (Sig, Sig, Sig, Sig) #
Takes an input signal and distributes between 2 or 4 channels.
locsig takes an input signal and distributes it among 2 or 4 channels using values in degrees to calculate the balance between adjacent channels. It also takes arguments for distance (used to attenuate signals that are to sound as if they are some distance further than the loudspeaker itself), and for the amount the signal that will be sent to reverberators. This unit is based upon the example in the Charles Dodge/Thomas Jerse book, Computer Music, page 320.
a1, a2 locsig asig, kdegree, kdistance, kreverbsend a1, a2, a3, a4 locsig asig, kdegree, kdistance, kreverbsend
csound doc: http://csound.com/docs/manual/locsig.html
pan :: Sig -> Sig -> Sig -> Tab -> (Sig, Sig, Sig, Sig) #
Distribute an audio signal amongst four channels.
Distribute an audio signal amongst four channels with localization control.
a1, a2, a3, a4 pan asig, kx, ky, ifn [, imode] [, ioffset]
csound doc: http://csound.com/docs/manual/pan.html
pan2 :: Sig -> Sig -> (Sig, Sig) #
Distribute an audio signal across two channels.
Distribute an audio signal across two channels with a choice of methods.
a1, a2 pan2 asig, xp [, imode]
csound doc: http://csound.com/docs/manual/pan2.html
spat3d :: Sig -> Sig -> Sig -> Sig -> D -> D -> D -> D -> D -> (Sig, Sig, Sig, Sig) #
Positions the input sound in a 3D space and allows moving the sound at k-rate.
This opcode positions the input sound in a 3D space, with optional simulation of room acoustics, in various output formats. spat3d allows moving the sound at k-rate (this movement is interpolated internally to eliminate "zipper noise" if sr not equal to kr).
aW, aX, aY, aZ spat3d ain, kX, kY, kZ, idist, ift, imode, imdel, iovr [, istor]
csound doc: http://csound.com/docs/manual/spat3d.html
spat3di :: Sig -> D -> D -> D -> D -> D -> D -> (Sig, Sig, Sig, Sig) #
Positions the input sound in a 3D space with the sound source position set at i-time.
This opcode positions the input sound in a 3D space, with optional simulation of room acoustics, in various output formats. With spat3di, sound source position is set at i-time.
aW, aX, aY, aZ spat3di ain, iX, iY, iZ, idist, ift, imode [, istor]
csound doc: http://csound.com/docs/manual/spat3di.html
spat3dt :: D -> D -> D -> D -> D -> D -> D -> D -> SE () #
Can be used to render an impulse response for a 3D space at i-time.
This opcode positions the input sound in a 3D space, with optional simulation of room acoustics, in various output formats. spat3dt can be used to render the impulse response at i-time, storing output in a function table, suitable for convolution.
spat3dt ioutft, iX, iY, iZ, idist, ift, imode, irlen [, iftnocl]
csound doc: http://csound.com/docs/manual/spat3dt.html
spdist :: Tab -> Sig -> Sig -> Sig -> Sig #
Calculates distance values from xy coordinates.
spdist uses the same xy data as space, also either from a text file using Gen28 or from x and y arguments given to the unit directly. The purpose of this unit is to make available the values for distance that are calculated from the xy coordinates.
k1 spdist ifn, ktime, kx, ky
csound doc: http://csound.com/docs/manual/spdist.html
spsend :: (Sig, Sig, Sig, Sig) #
Generates output signals based on a previously defined space opcode.
spsend depends upon the existence of a previously defined space. The output signals from spsend are derived from the values given for xy and reverb in the space and are ready to be sent to local or global reverb units (see example below).
a1, a2, a3, a4 spsend
csound doc: http://csound.com/docs/manual/spsend.html
vbap :: Tuple a => Sig -> Sig -> a #
Distributes an audio signal among many channels.
Distributes an audio signal amongmany channels, up to 64 in the first form, arbitrary in the second.
ar1[, ar2...] vbap asig, kazim [, kelev] [, kspread] [, ilayout] array[] vbap asig, kazim [, kelev] [, kspread] [, ilayout]
csound doc: http://csound.com/docs/manual/vbap.html
vbap16 :: Tuple a => Sig -> Sig -> a #
Distributes an audio signal among 16 channels.
ar1, ..., ar16 vbap16 asig, kazim [, kelev] [, kspread]
csound doc: http://csound.com/docs/manual/vbap16.html
vbap16move :: Tuple a => Sig -> D -> D -> D -> [D] -> a #
Distribute an audio signal among 16 channels with moving virtual sources.
ar1, ..., ar16 vbap16move asig, idur, ispread, ifldnum, ifld1 \ [, ifld2] [...]
csound doc: http://csound.com/docs/manual/vbap16move.html
vbap4 :: Sig -> Sig -> (Sig, Sig, Sig, Sig) #
Distributes an audio signal among 4 channels.
ar1, ar2, ar3, ar4 vbap4 asig, kazim [, kelev] [, kspread]
csound doc: http://csound.com/docs/manual/vbap4.html
vbap4move :: Tuple a => Sig -> D -> D -> D -> [D] -> a #
Distributes an audio signal among 4 channels with moving virtual sources.
ar1, ar2, ar3, ar4 vbap4move asig, idur, ispread, ifldnum, ifld1 \ [, ifld2] [...]
csound doc: http://csound.com/docs/manual/vbap4move.html
vbap8 :: Tuple a => Sig -> Sig -> a #
Distributes an audio signal among 8 channels.
ar1, ..., ar8 vbap8 asig, kazim [, kelev] [, kspread]
csound doc: http://csound.com/docs/manual/vbap8.html
vbap8move :: Tuple a => Sig -> D -> D -> D -> [D] -> a #
Distributes an audio signal among 8 channels with moving virtual sources.
ar1, ..., ar8 vbap8move asig, idur, ispread, ifldnum, ifld1 \ [, ifld2] [...]
csound doc: http://csound.com/docs/manual/vbap8move.html
vbapg :: Tuple a => Sig -> a #
Calculates the gains for a sound location between multiple channels.
Calculates the gains for a sound location for up to 64.
k1[, k2...] vbapg kazim [,kelev] [, kspread] [, ilayout] karray[] vbapg kazim [,kelev] [, kspread] [, ilayout]
csound doc: http://csound.com/docs/manual/vbapg.html
vbapgmove :: Tuple a => D -> D -> D -> D -> a #
Calculates the gains for a sound location between multiple channels with moving virtual sources.
kr1[, kr2...] vbapgmove idur, ispread, ifldnum, ifld1 \ [, ifld2] [...] karray[] vbapgmove idur, ispread, ifldnum, ifld1 \ [, ifld2] [...]
csound doc: http://csound.com/docs/manual/vbapgmove.html
vbaplsinit :: D -> D -> SE () #
Configures VBAP output according to loudspeaker parameters.
vbaplsinit idim, ilsnum [, idir1] [, idir2] [...] [, idir32] vbaplsinit idim, ilsnum, ilsarray
csound doc: http://csound.com/docs/manual/vbaplsinit.html
vbapmove :: Tuple a => Sig -> D -> D -> D -> [D] -> a #
Distributes an audio signal among many channels with moving virtual sources.
Distributes an audio signal among upto 64 channels with moving virtual sources.
ar1[, ar2...] vbapmove asig, idur, ispread, ifldnum, ifld1 \ [, ifld2] [...] aarray[] vbapmove asig, idur, ispread, ifldnum, ifld1 \ [, ifld2] [...]
csound doc: http://csound.com/docs/manual/vbapmove.html
vbapz :: D -> D -> Sig -> Sig -> SE () #
Writes a multi-channel audio signal to a ZAK array.
vbapz inumchnls, istartndx, asig, kazim [, kelev] [, kspread]
csound doc: http://csound.com/docs/manual/vbapz.html
vbapzmove :: Sig -> D -> D -> D -> [D] -> SE () #
Writes a multi-channel audio signal to a ZAK array with moving virtual sources.
vbapzmove inumchnls, istartndx, asig, idur, ispread, ifldnum, ifld1, \ ifld2, [...]
csound doc: http://csound.com/docs/manual/vbapzmove.html
alpass :: Sig -> Sig -> D -> Sig #
Reverberates an input signal with a flat frequency response.
ares alpass asig, xrvt, ilpt [, iskip] [, insmps]
csound doc: http://csound.com/docs/manual/alpass.html
babo :: Sig -> Sig -> Sig -> Sig -> D -> D -> D -> (Sig, Sig) #
A physical model reverberator.
babo stands for ball-within-the-box. It is a physical model reverberator based on the paper by Davide Rocchesso "The Ball within the Box: a sound-processing metaphor", Computer Music Journal, Vol 19, N.4, pp.45-47, Winter 1995.
a1, a2 babo asig, ksrcx, ksrcy, ksrcz, irx, iry, irz [, idiff] [, ifno]
csound doc: http://csound.com/docs/manual/babo.html
comb :: Sig -> Sig -> D -> Sig #
Reverberates an input signal with a âcoloredâ frequency response.
ares comb asig, krvt, ilpt [, iskip] [, insmps]
csound doc: http://csound.com/docs/manual/comb.html
combinv :: Sig -> Sig -> D -> Sig #
Reverberates an input signal with a âcoloredâ frequency response.
Reverberates an input signal with a âcoloredâ frequency response with a FIR filter.
ares combinv asig, krvt, ilpt [, iskip] [, insmps]
csound doc: http://csound.com/docs/manual/combinv.html
freeverb :: Sig -> Sig -> Sig -> Sig -> (Sig, Sig) #
Opcode version of Jezar's Freeverb
freeverb is a stereo reverb unit based on Jezar's public domain C++ sources, composed of eight parallel comb filters on both channels, followed by four allpass units in series. The filters on the right channel are slightly detuned compared to the left channel in order to create a stereo effect.
aoutL, aoutR freeverb ainL, ainR, kRoomSize, kHFDamp[, iSRate[, iSkip]]
csound doc: http://csound.com/docs/manual/freeverb.html
nestedap :: Sig -> D -> D -> D -> D -> Sig #
Three different nested all-pass filters.
Three different nested all-pass filters, useful for implementing reverbs.
ares nestedap asig, imode, imaxdel, idel1, igain1 [, idel2] [, igain2] \ [, idel3] [, igain3] [, istor]
csound doc: http://csound.com/docs/manual/nestedap.html
nreverb :: Sig -> Sig -> Sig -> Sig #
A reverberator consisting of 6 parallel comb-lowpass filters.
This is a reverberator consisting of 6 parallel comb-lowpass filters being fed into a series of 5 allpass filters. nreverb replaces reverb2 (version 3.48) and so both opcodes are identical.
ares nreverb asig, ktime, khdif [, iskip] [,inumCombs] [, ifnCombs] \ [, inumAlpas] [, ifnAlpas]
csound doc: http://csound.com/docs/manual/nreverb.html
platerev :: Tuple a => D -> D -> Sig -> D -> D -> D -> D -> [Sig] -> a #
Models the reverberation of a metal plate.
Models the reverberation of a rectangular metal plate with settable physical characteristics when excited by audio signal(s).
a1[, a2, ...] platerev itabexcite. itabouts, kbndry, iaspect, istiff, idecay, iloss, aexcite1[, aexcite2, ...]
csound doc: http://csound.com/docs/manual/platerev.html
Reverberates an input signal with a ânatural roomâ frequency response.
ares reverb asig, krvt [, iskip]
csound doc: http://csound.com/docs/manual/reverb.html
reverb2 :: Sig -> Sig -> Sig -> Sig #
Same as the nreverb opcode.
ares reverb2 asig, ktime, khdif [, iskip] [,inumCombs] \ [, ifnCombs] [, inumAlpas] [, ifnAlpas]
csound doc: http://csound.com/docs/manual/reverb2.html
reverbsc :: Sig -> Sig -> Sig -> Sig -> (Sig, Sig) #
8 delay line stereo FDN reverb, based on work by Sean Costello
8 delay line stereo FDN reverb, with feedback matrix based upon physical modeling scattering junction of 8 lossless waveguides of equal characteristic impedance. Based on Csound orchestra version by Sean Costello.
aoutL, aoutR reverbsc ainL, ainR, kfblvl, kfco[, israte[, ipitchm[, iskip]]]
csound doc: http://csound.com/docs/manual/reverbsc.html
valpass :: Sig -> Sig -> Sig -> D -> Sig #
Variably reverberates an input signal with a flat frequency response.
ares valpass asig, krvt, xlpt, imaxlpt [, iskip] [, insmps]
csound doc: http://csound.com/docs/manual/valpass.html
vcomb :: Sig -> Sig -> Sig -> D -> Sig #
Variably reverberates an input signal with a âcoloredâ frequency response.
ares vcomb asig, krvt, xlpt, imaxlpt [, iskip] [, insmps]
csound doc: http://csound.com/docs/manual/vcomb.html
Mixes low level noise to a list of a-rate signals
Mixes low level (~1e-20 for floats, and ~1e-56 for doubles) noise to a list of a-rate signals. Can be used before IIR filters and reverbs to avoid denormalized numbers which may otherwise result in significantly increased CPU usage.
denorm a1[, a2[, a3[, ... ]]]
csound doc: http://csound.com/docs/manual/denorm.html
Modify a signal by down-sampling.
kres downsamp asig [, iwlen]
csound doc: http://csound.com/docs/manual/downsamp.html
Modify a signal by integration.
ares integ asig [, iskip] kres integ ksig [, iskip]
csound doc: http://csound.com/docs/manual/integ.html
Converts a control signal to an audio signal using linear interpolation.
ares interp ksig [, iskip] [, imode] [, ivalue]
csound doc: http://csound.com/docs/manual/interp.html
ntrpol :: Sig -> Sig -> Sig -> Sig #
Calculates the weighted mean value of two input signals.
Calculates the weighted mean value (i.e. linear interpolation) of two input signals
ares ntrpol asig1, asig2, kpoint [, imin] [, imax] ires ntrpol isig1, isig2, ipoint [, imin] [, imax] kres ntrpol ksig1, ksig2, kpoint [, imin] [, imax]
csound doc: http://csound.com/docs/manual/ntrpol.html
samphold :: Sig -> Sig -> Sig #
Performs a sample-and-hold operation on its input.
ares samphold asig, agate [, ival] [, ivstor] kres samphold ksig, kgate [, ival] [, ivstor]
csound doc: http://csound.com/docs/manual/samphold.html
Modify a signal by up-sampling.
ares upsamp ksig
csound doc: http://csound.com/docs/manual/upsamp.html
Access values of the current buffer of an a-rate variable by indexing.
Access values of the current buffer of an a-rate variable by indexing. Useful for doing sample-by-sample manipulation at k-rate without using setksmps 1.
kval vaget kndx, avar
csound doc: http://csound.com/docs/manual/vaget.html
vaset :: Sig -> Sig -> Sig -> SE () #
Write value of into the current buffer of an a-rate variable by index.
Write values into the current buffer of an a-rate variable at the given index. Useful for doing sample-by-sample manipulation at k-rate without using setksmps 1.
vaset kval, kndx, avar
csound doc: http://csound.com/docs/manual/vaset.html
limit :: Sig -> Sig -> Sig -> Sig #
Sets the lower and upper limits of the value it processes.
ares limit asig, klow, khigh ires limit isig, ilow, ihigh kres limit ksig, klow, khigh ires[] limit isig[], ilow, ihigh kres[] limit ksig[], klow, khigh
csound doc: http://csound.com/docs/manual/limit.html
mirror :: Sig -> Sig -> Sig -> Sig #
Reflects the signal that exceeds the low and high thresholds.
ares mirror asig, klow, khigh ires mirror isig, ilow, ihigh kres mirror ksig, klow, khigh
csound doc: http://csound.com/docs/manual/mirror.html
wrap :: Sig -> Sig -> Sig -> Sig #
Wraps-around the signal that exceeds the low and high thresholds.
ares wrap asig, klow, khigh ires wrap isig, ilow, ihigh kres wrap ksig, klow, khigh
csound doc: http://csound.com/docs/manual/wrap.html
distort :: Sig -> Sig -> Tab -> Sig #
Distort an audio signal via waveshaping and optional clipping.
ar distort asig, kdist, ifn[, ihp, istor]
csound doc: http://csound.com/docs/manual/distort.html
distort1 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
Modified hyperbolic tangent distortion.
Implementation of modified hyperbolic tangent distortion. distort1 can be used to generate wave shaping distortion based on a modification of the tanh function.
ares distort1 asig, kpregain, kpostgain, kshape1, kshape2[, imode]
csound doc: http://csound.com/docs/manual/distort1.html
flanger :: Sig -> Sig -> Sig -> Sig #
A user controlled flanger.
ares flanger asig, adel, kfeedback [, imaxd]
csound doc: http://csound.com/docs/manual/flanger.html
harmon :: Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> D -> Sig #
Analyze an audio input and generate harmonizing voices in synchrony.
ares harmon asig, kestfrq, kmaxvar, kgenfreq1, kgenfreq2, imode, \ iminfrq, iprd
csound doc: http://csound.com/docs/manual/harmon.html
harmon2 :: Sig -> Sig -> Sig -> Sig -> D -> D -> Sig #
Analyze an audio input and generate harmonizing voices in synchrony with formants preserved.
Generate harmonizing voices with formants preserved.
ares harmon2 asig, koct, kfrq1, kfrq2, icpsmode, ilowest[, ipolarity]
csound doc: http://csound.com/docs/manual/harmon2.html
harmon3 :: Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> Sig #
Analyze an audio input and generate harmonizing voices in synchrony with formants preserved.
Generate harmonizing voices with formants preserved.
ares harmon3 asig, koct, kfrq1, \ kfrq2, kfrq3, icpsmode, ilowest[, ipolarity]
csound doc: http://csound.com/docs/manual/harmon2.html
harmon4 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> D -> D -> Sig #
Analyze an audio input and generate harmonizing voices in synchrony with formants preserved.
Generate harmonizing voices with formants preserved.
ares harmon4 asig, koct, kfrq1, \ kfrq2, kfrq3, kfrq4, icpsmode, ilowest[, ipolarity]
csound doc: http://csound.com/docs/manual/harmon2.html
phaser1 :: Sig -> Sig -> Sig -> Sig -> Sig #
First-order allpass filters arranged in a series.
An implementation of iord number of first-order allpass filters in series.
ares phaser1 asig, kfreq, kord, kfeedback [, iskip]
csound doc: http://csound.com/docs/manual/phaser1.html
phaser2 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
Second-order allpass filters arranged in a series.
An implementation of iord number of second-order allpass filters in series.
ares phaser2 asig, kfreq, kq, kord, kmode, ksep, kfeedback
csound doc: http://csound.com/docs/manual/phaser2.html
A hi-pass filter whose transfer functions are the complements of the tone opcode.
ares atone asig, khp [, iskip]
csound doc: http://csound.com/docs/manual/atone.html
Emulates a stack of filters using the atone opcode.
atonex is equivalent to a filter consisting of more layers of atone with the same arguments, serially connected. Using a stack of a larger number of filters allows a sharper cutoff. They are faster than using a larger number instances in a Csound orchestra of the old opcodes, because only one initialization and k- cycle are needed at time and the audio loop falls entirely inside the cache memory of processor.
ares atonex asig, khp [, inumlayer] [, iskip] ares atonex asig, ahp [, inumlayer] [, iskip]
csound doc: http://csound.com/docs/manual/atonex.html
biquad :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
A sweepable general purpose biquadratic digital filter.
ares biquad asig, kb0, kb1, kb2, ka0, ka1, ka2 [, iskip]
csound doc: http://csound.com/docs/manual/biquad.html
biquada :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
A sweepable general purpose biquadratic digital filter with a-rate parameters.
A sweepable general purpose biquadratic digital filter.
ares biquada asig, ab0, ab1, ab2, aa0, aa1, aa2 [, iskip]
csound doc: http://csound.com/docs/manual/biquada.html
butbp :: Sig -> Sig -> Sig -> Sig #
Same as the butterbp opcode.
ares butbp asig, kfreq, kband [, iskip]
csound doc: http://csound.com/docs/manual/butbp.html
butbr :: Sig -> Sig -> Sig -> Sig #
Same as the butterbr opcode.
ares butbr asig, kfreq, kband [, iskip]
csound doc: http://csound.com/docs/manual/butbr.html
Same as the butterhp opcode.
ares buthp asig, kfreq [, iskip] ares buthp asig, afreq [, iskip]
csound doc: http://csound.com/docs/manual/buthp.html
Same as the butterlp opcode.
ares butlp asig, kfreq [, iskip] ares butlp asig, afreq [, iskip]
csound doc: http://csound.com/docs/manual/butlp.html
butterbp :: Sig -> Sig -> Sig -> Sig #
A band-pass Butterworth filter.
Implementation of a second-order band-pass Butterworth filter. This opcode can also be written as butbp.
ares butterbp asig, xfreq, xband [, iskip]
csound doc: http://csound.com/docs/manual/butterbp.html
butterbr :: Sig -> Sig -> Sig -> Sig #
A band-reject Butterworth filter.
Implementation of a second-order band-reject Butterworth filter. This opcode can also be written as butbr.
ares butterbr asig, xfreq, xband [, iskip]
csound doc: http://csound.com/docs/manual/butterbr.html
butterhp :: Sig -> Sig -> Sig #
A high-pass Butterworth filter.
Implementation of second-order high-pass Butterworth filter. This opcode can also be written as buthp.
ares butterhp asig, kfreq [, iskip] ares butterhp asig, afreq [, iskip]
csound doc: http://csound.com/docs/manual/butterhp.html
butterlp :: Sig -> Sig -> Sig #
A low-pass Butterworth filter.
Implementation of a second-order low-pass Butterworth filter. This opcode can also be written as butlp.
ares butterlp asig, kfreq [, iskip] ares butterlp asig, afreq [, iskip]
csound doc: http://csound.com/docs/manual/butterlp.html
clfilt :: Sig -> Sig -> D -> D -> Sig #
Implements low-pass and high-pass filters of different styles.
Implements the classical standard analog filter types: low-pass and high-pass. They are implemented with the four classical kinds of filters: Butterworth, Chebyshev Type I, Chebyshev Type II, and Elliptical. The number of poles may be any even number from 2 to 80.
ares clfilt asig, kfreq, itype, inpol [, ikind] [, ipbr] [, isba] [, iskip]
csound doc: http://csound.com/docs/manual/clfilt.html
diode_ladder :: Sig -> Sig -> Sig -> Sig #
Zero-delay feedback implementation of 4 pole diode ladder filter.
Zero-delay feedback implementation of a 4 pole (24 dB/oct) diode low-pass filter. This filter design was originally used in the EMS VCS3 and was the resonant filter in the Roland TB-303.
asig diode_ladder ain, xcf, xk [, inlp, isaturation, istor]
csound doc: http://csound.com/docs/manual/diode_ladder.html
doppler :: Sig -> Sig -> Sig -> Sig #
A fast and robust method for approximating sound propagation, achieving convincing Doppler shifts without having to solve equations.
A fast and robust method for approximating sound propagation, achieving convincing Doppler shifts without having to solve equations. The method computes frequency shifts based on reading an input delay line at a delay time computed from the distance between source and mic and the speed of sound. One instance of the opcode is required for each dimension of space through which the sound source moves. If the source sound moves at a constant speed from in front of the microphone, through the microphone, to behind the microphone, then the output will be frequency shifted above the source frequency at a constant frequency while the source approaches, then discontinuously will be shifted below the source frequency at a constant frequency as the source recedes from the microphone. If the source sound moves at a constant speed through a point to one side of the microphone, then the rate of change of position will not be constant, and the familiar Doppler frequency shift typical of a siren or engine approaching and receding along a road beside a listener will be heard.
ashifted doppler asource, ksourceposition, kmicposition [, isoundspeed, ifiltercutoff]
csound doc: http://csound.com/docs/manual/doppler.html
k35_hpf :: Sig -> Sig -> Sig -> Sig #
Zero-delay feedback implementation of Korg35 resonant high-pass filter.
Zero-delay feedback implementation of Korg35 resonant high-pass filter. This filter design is found in the Korg MS10 early MS20.
asig K35_hpf ain, xcf, xQ [, inlp, isaturation, istor]
csound doc: http://csound.com/docs/manual/k35_hpf.html
k35_lpf :: Sig -> Sig -> Sig -> Sig #
Zero-delay feedback implementation of Korg35 resonant low-pass filter.
Zero-delay feedback implementation of Korg35 resonant low-pass filter. This filter design is found in the Korg MS10, early MS20, and Monotron series.
asig K35_lpf ain, xcf, xQ [, inlp, isaturation, istor]
csound doc: http://csound.com/docs/manual/k35_lpf.html
median :: Sig -> Sig -> D -> Sig #
A median filter, a variant FIR lowpass filter.
Implementation of a median filter.
ares median asig, ksize, imaxsize [, iskip]
csound doc: http://csound.com/docs/manual/median.html
mediank :: Sig -> Sig -> D -> Sig #
A median filter, a variant FIR lowpass filter.
Implementation of a median filter.
kres mediank kin, ksize, imaxsize [, iskip]
csound doc: http://csound.com/docs/manual/mediank.html
mode :: Sig -> Sig -> Sig -> Sig #
A filter that simulates a mass-spring-damper system
Filters the incoming signal with the specified resonance frequency and quality factor. It can also be seen as a signal generator for high quality factor, with an impulse for the excitation. You can combine several modes to built complex instruments such as bells or guitar tables.
aout mode ain, xfreq, xQ [, iskip]
csound doc: http://csound.com/docs/manual/mode.html
A first-order recursive low-pass filter with variable frequency response.
ares tone asig, khp [, iskip]
csound doc: http://csound.com/docs/manual/tone.html
Emulates a stack of filters using the tone opcode.
tonex is equivalent to a filter consisting of more layers of tone with the same arguments, serially connected. Using a stack of a larger number of filters allows a sharper cutoff. They are faster than using a larger number instances in a Csound orchestra of the old opcodes, because only one initialization and k- cycle are needed at time and the audio loop falls entirely inside the cache memory of processor.
ares tonex asig, khp [, inumlayer] [, iskip] ares tonex asig, ahp [, inumlayer] [, iskip]
csound doc: http://csound.com/docs/manual/tonex.html
zdf_1pole :: Sig -> Sig -> Sig #
Zero-delay feedback implementation of 1 pole filter.
Zero-delay feedback implementation of a 1 pole (6 dB/oct) filter. Offers low-pass (default), high-pass, and allpass output modes.
asig zdf_1pole ain, xcf [, kmode, istor]
csound doc: http://csound.com/docs/manual/zdf_1pole.html
zdf_1pole_mode :: Sig -> Sig -> (Sig, Sig) #
Zero-delay feedback implementation of 1 pole filter with multimode output.
Zero-delay feedback implementation of a 1 pole (6 dB/oct) filter. Offers low-pass and high-pass output.
alp, ahp zdf_1pole_mode ain, xcf [, istor]
csound doc: http://csound.com/docs/manual/zdf_1pole_mode.html
zdf_2pole :: Sig -> Sig -> Sig -> Sig #
Zero-delay feedback implementation of 2 pole filter.
Zero-delay feedback implementation of a 2 pole (12 dB/oct) filter. Offers low-pass (default), high-pass, and allpass output modes.
asig zdf_2pole ain, xcf, xQ [, kmode, istor]
csound doc: http://csound.com/docs/manual/zdf_2pole.html
zdf_2pole_mode :: Sig -> Sig -> Sig -> (Sig, Sig, Sig) #
Zero-delay feedback implementation of 2 pole filter with multimode output.
Zero-delay feedback implementation of a 2 pole (12 dB/oct) filter. Offers low-pass, band-pass, and high-pass output.
alp, abp, ahp zdf_2pole_mode ain, xcf, Q [, istor]
csound doc: http://csound.com/docs/manual/zdf_2pole_mode.html
zdf_ladder :: Sig -> Sig -> Sig -> Sig #
Zero-delay feedback implementation of 4 pole ladder filter.
Zero-delay feedback implementation of a 4 pole (24 dB/oct) low-pass filter based on the Moog ladder filter.
asig zdf_ladder ain, xcf, xQ [, istor]
csound doc: http://csound.com/docs/manual/zdf_ladder.html
areson :: Sig -> Sig -> Sig -> Sig #
A notch filter whose transfer functions are the complements of the reson opcode.
ares areson asig, kcf, kbw [, iscl] [, iskip] ares areson asig, acf, kbw [, iscl] [, iskip] ares areson asig, kcf, abw [, iscl] [, iskip] ares areson asig, acf, abw [, iscl] [, iskip]
csound doc: http://csound.com/docs/manual/areson.html
bqrez :: Sig -> Sig -> Sig -> Sig #
A second-order multi-mode filter.
ares bqrez asig, xfco, xres [, imode] [, iskip]
csound doc: http://csound.com/docs/manual/bqrez.html
lowpass2 :: Sig -> Sig -> Sig -> Sig #
A resonant lowpass filter.
Implementation of a resonant second-order lowpass filter.
ares lowpass2 asig, kcf, kq [, iskip]
csound doc: http://csound.com/docs/manual/lowpass2.html
lowres :: Sig -> Sig -> Sig -> Sig #
Another resonant lowpass filter.
lowres is a resonant lowpass filter.
ares lowres asig, kcutoff, kresonance [, iskip]
csound doc: http://csound.com/docs/manual/lowres.html
lowresx :: Sig -> Sig -> Sig -> Sig #
Simulates layers of serially connected resonant lowpass filters.
lowresx is equivalent to more layers of lowres with the same arguments serially connected.
ares lowresx asig, xcutoff, xresonance [, inumlayer] [, iskip]
csound doc: http://csound.com/docs/manual/lowresx.html
lpf18 :: Sig -> Sig -> Sig -> Sig -> Sig #
A 3-pole sweepable resonant lowpass filter.
Implementation of a 3 pole sweepable resonant lowpass filter.
ares lpf18 asig, xfco, xres, xdist [, iskip]
csound doc: http://csound.com/docs/manual/lpf18.html
moogladder :: Sig -> Sig -> Sig -> Sig #
Moog ladder lowpass filter.
Moogladder is an new digital implementation of the Moog ladder filter based on the work of Antti Huovilainen, described in the paper "Non-Linear Digital Implementation of the Moog Ladder Filter" (Proceedings of DaFX04, Univ of Napoli). This implementation is probably a more accurate digital representation of the original analogue filter.
asig moogladder ain, kcf, kres[, istor] asig moogladder ain, acf, kres[, istor] asig moogladder ain, kcf, ares[, istor] asig moogladder ain, acf, ares[, istor]
csound doc: http://csound.com/docs/manual/moogladder.html
moogladder2 :: Sig -> Sig -> Sig -> Sig #
Moog ladder lowpass filter.
Moogladder2 is an new digital implementation of the Moog ladder filter based on the work of Antti Huovilainen, described in the paper "Non-Linear Digital Implementation of the Moog Ladder Filter" (Proceedings of DaFX04, Univ of Napoli). This implementation uses approximations to the tanh function and so is faster but less accurate than moogladder.
asig moogladder2 ain, kcf, kres[, istor] asig moogladder2 ain, acf, kres[, istor] asig moogladder2 ain, kcf, ares[, istor] asig moogladder2 ain, acf, ares[, istor]
csound doc: http://csound.com/docs/manual/moogladder2.html
moogvcf :: Sig -> Sig -> Sig -> Sig #
A digital emulation of the Moog diode ladder filter configuration.
ares moogvcf asig, xfco, xres [,iscale, iskip]
csound doc: http://csound.com/docs/manual/moogvcf.html
moogvcf2 :: Sig -> Sig -> Sig -> Sig #
A digital emulation of the Moog diode ladder filter configuration.
ares moogvcf2 asig, xfco, xres [,iscale, iskip]
csound doc: http://csound.com/docs/manual/moogvcf2.html
Moog voltage-controlled highpass filter emulation.
Mvchpf is an digital implementation of the 4th-order (24 dB/oct) Moog high-pass filter, originally written by Fons Andriaensen. According to the author, mvchpf "...is based on the voltage controlled highpass filter by Robert Moog. again with some attention to the nonlinear effects."
asig mvchpf ain, xcf[, istor]
csound doc: http://csound.com/docs/manual/mvchpf.html
mvclpf1 :: Sig -> Sig -> Sig -> Sig #
Moog voltage-controlled lowpass filter emulation.
Mvclpf1 is an digital implementation of the 4th-order (24 dB/oct) Moog ladder filter originally written by Fons Andriaensen. According to the author, mvclpf1 "is a fairly simple design, and it does not even pretend to come close the 'real thing'. It uses a very crude approximation of the non-linear resistor in the first filter section only. [...] [I]t's [a] cheap (in terms of CPU usage) general purpose 24 dB/oct lowpass filter that could be useful".
asig mvclpf1 ain, xcf, xres[,istor]
csound doc: http://csound.com/docs/manual/mvclpf1.html
mvclpf2 :: Sig -> Sig -> Sig -> Sig #
Moog voltage-controlled lowpass filter emulation.
Mvclpf2 is an digital implementation of the 4th-order (24 dB/oct) Moog ladder filter originally written by Fons Andriaensen. According to the author, mvclpf2 "uses five non-linear elements, in the input and in all four filter sections. It works by using the derivative of the nonlinearity (for which 1 / (1 + x * x) is reasonable approximation). The main advantage of this is that only one evaluation of the non-linear function is required for each section".
asig mvclpf2 ain, xcf, xres[, istor]
csound doc: http://csound.com/docs/manual/mvclpf2.html
mvclpf3 :: Sig -> Sig -> Sig -> Sig #
Moog voltage-controlled lowpass filter emulation.
Mvclpf3 is an digital implementation of the 4th-order (24 dB/oct) Moog ladder filter
originally written by Fons Andriaensen. According to the author,
mvclpf3 "is based on mvclpf2 , with two differences. It uses the
the technique described by Stilson and Smith to extend the constant-Q
range, and the internal sample frequency is doubled, giving a better
approximation to the non-linear behaviour at high freqencies.
This version has high Q over the entire frequency range and will
oscillate up to above 10 kHz, while the two others show a decreasing
Q at high frequencies. Mvclpf3 is reasonably well tuned, and can be
played
as a VCO up to at least 5 kHz".
asig mvclpf3 ain, xcf, xres[, istor]
csound doc: http://csound.com/docs/manual/mvclpf3.html
mvclpf4 :: Sig -> Sig -> Sig -> (Sig, Sig, Sig, Sig) #
Moog voltage-controlled lowpass filter emulation.
Mvclpf4 is an digital implementation of the 4th-order (24 dB/oct) Moog ladder filter originally written by Fons Andriaensen. It is a version of the mvclpf3 opcode with four outputs, for 6dB, 12dB, 18dB, and 24 dB/octave responses.
asig1,asig2,asig3,asig4 mvclpf4 ain, xcf, xres[, istor]
csound doc: http://csound.com/docs/manual/mvclpf4.html
reson :: Sig -> Sig -> Sig -> Sig #
A second-order resonant filter.
ares reson asig, xcf, xbw [, iscl] [, iskip]
csound doc: http://csound.com/docs/manual/reson.html
resonr :: Sig -> Sig -> Sig -> Sig #
A bandpass filter with variable frequency response.
Implementations of a second-order, two-pole two-zero bandpass filter with variable frequency response.
ares resonr asig, xcf, xbw [, iscl] [, iskip]
csound doc: http://csound.com/docs/manual/resonr.html
resonx :: Sig -> Sig -> Sig -> Sig #
Emulates a stack of filters using the reson opcode.
resonx is equivalent to a filters consisting of more layers of reson with the same arguments, serially connected. Using a stack of a larger number of filters allows a sharper cutoff. They are faster than using a larger number instances in a Csound orchestra of the old opcodes, because only one initialization and k- cycle are needed at time and the audio loop falls entirely inside the cache memory of processor.
ares resonx asig, xcf, xbw [, inumlayer] [, iscl] [, iskip]
csound doc: http://csound.com/docs/manual/resonx.html
resony :: Sig -> Sig -> Sig -> D -> Sig -> Sig #
A bank of second-order bandpass filters, connected in parallel.
ares resony asig, kbf, kbw, inum, ksep [, isepmode] [, iscl] [, iskip]
csound doc: http://csound.com/docs/manual/resony.html
resonz :: Sig -> Sig -> Sig -> Sig #
A bandpass filter with variable frequency response.
Implementations of a second-order, two-pole two-zero bandpass filter with variable frequency response.
ares resonz asig, xcf, xbw [, iscl] [, iskip]
csound doc: http://csound.com/docs/manual/resonz.html
rezzy :: Sig -> Sig -> Sig -> Sig #
A resonant low-pass filter.
ares rezzy asig, xfco, xres [, imode, iskip]
csound doc: http://csound.com/docs/manual/rezzy.html
statevar :: Sig -> Sig -> Sig -> (Sig, Sig, Sig, Sig) #
State-variable filter.
Statevar is a new digital implementation of the analogue state-variable filter. This filter has four simultaneous outputs: high-pass, low-pass, band-pass and band-reject. This filter uses oversampling for sharper resonance (default: 3 times oversampling). It includes a resonance limiter that prevents the filter from getting unstable.
ahp,alp,abp,abr statevar ain, xcf, xq [, iosamps, istor]
csound doc: http://csound.com/docs/manual/statevar.html
svfilter :: Sig -> Sig -> Sig -> (Sig, Sig, Sig) #
A resonant second order filter, with simultaneous lowpass, highpass and bandpass outputs.
Implementation of a resonant second order filter, with simultaneous lowpass, highpass and bandpass outputs.
alow, ahigh, aband svfilter asig, kcf, kq [, iscl] [, iskip]
csound doc: http://csound.com/docs/manual/svfilter.html
tbvcf :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
Models some of the filter characteristics of a Roland TB303 voltage-controlled filter.
This opcode attempts to model some of the filter characteristics of a Roland TB303 voltage-controlled filter. Euler's method is used to approximate the system, rather than traditional filter methods. Cutoff frequency, Q, and distortion are all coupled. Empirical methods were used to try to unentwine, but frequency is only approximate as a result. Future fixes for some problems with this opcode may break existing orchestras relying on this version of tbvcf.
ares tbvcf asig, xfco, xres, kdist, kasym [, iskip]
csound doc: http://csound.com/docs/manual/tbvcf.html
vlowres :: Sig -> Sig -> Sig -> D -> Sig -> Sig #
A bank of filters in which the cutoff frequency can be separated under user control.
A bank of filters in which the cutoff frequency can be separated under user control
ares vlowres asig, kfco, kres, iord, ksep
csound doc: http://csound.com/docs/manual/vlowres.html
aresonk :: Sig -> Sig -> Sig -> Sig #
A notch filter whose transfer functions are the complements of the reson opcode.
kres aresonk ksig, kcf, kbw [, iscl] [, iskip]
csound doc: http://csound.com/docs/manual/aresonk.html
A hi-pass filter whose transfer functions are the complements of the tonek opcode.
kres atonek ksig, khp [, iskip]
csound doc: http://csound.com/docs/manual/atonek.html
Generate glissandos starting from a control signal.
kres lineto ksig, ktime
csound doc: http://csound.com/docs/manual/lineto.html
Applies portamento to a step-valued control signal.
kres port ksig, ihtim [, isig]
csound doc: http://csound.com/docs/manual/port.html
Applies portamento to a step-valued control signal.
kres portk ksig, khtim [, isig]
csound doc: http://csound.com/docs/manual/portk.html
resonk :: Sig -> Sig -> Sig -> Sig #
A second-order resonant filter.
kres resonk ksig, kcf, kbw [, iscl] [, iskip]
csound doc: http://csound.com/docs/manual/resonk.html
resonxk :: Sig -> Sig -> Sig -> Sig #
Control signal resonant filter stack.
resonxk is equivalent to a group of resonk filters, with the same arguments, serially connected. Using a stack of a larger number of filters allows a sharper cutoff.
kres resonxk ksig, kcf, kbw[, inumlayer, iscl, istor]
csound doc: http://csound.com/docs/manual/resonxk.html
Exponential Lag
Exponential lag with 60dB lag time. Port of Supercollider's Lag
aout sc_lag ain, klagtime [, initialvalue=0] kout sc_lag kin, klagtime [, initialvalue=0]
csound doc: http://csound.com/docs/manual/sc_lag.html
sc_lagud :: Sig -> Sig -> Sig -> Sig #
Exponential Lag
Exponential lag with different smoothing time for up- and downgoing signals. Port of Supercollider's LagUD
aout sc_lagud ain, klagup, klagdown kout sc_lagud kin, klagup, klagdown
csound doc: http://csound.com/docs/manual/sc_lagud.html
sc_trig :: Sig -> Sig -> Sig #
Timed trigger
Timed trigger. Port of Supercollider's Trig ugen
aout sc_trig ain, kdur kout sc_trig kin, kdur
csound doc: http://csound.com/docs/manual/sc_trig.html
tlineto :: Sig -> Sig -> Sig -> Sig #
Generate glissandos starting from a control signal.
Generate glissandos starting from a control signal with a trigger.
kres tlineto ksig, ktime, ktrig
csound doc: http://csound.com/docs/manual/tlineto.html
A first-order recursive low-pass filter with variable frequency response.
kres tonek ksig, khp [, iskip]
csound doc: http://csound.com/docs/manual/tonek.html
A DC blocking filter.
Implements the DC blocking filter
ares dcblock ain [, igain]
csound doc: http://csound.com/docs/manual/dcblock.html
A DC blocking filter.
Implements a DC blocking filter with improved DC attenuation.
ares dcblock2 ain [, iorder] [, iskip]
csound doc: http://csound.com/docs/manual/dcblock2.html
eqfil :: Sig -> Sig -> Sig -> Sig -> Sig #
Equalizer filter
The opcode eqfil is a 2nd order tunable equalisation filter based on Regalia and Mitra design ("Tunable Digital Frequency Response Equalization Filters", IEEE Trans. on Ac., Sp. and Sig Proc., 35 (1), 1987). It provides a peak/notch filter for building parametric/graphic equalisers.
asig eqfil ain, kcf, kbw, kgain[, istor]
csound doc: http://csound.com/docs/manual/eqfil.html
filter2 :: Sig -> D -> D -> [D] -> Sig #
Performs filtering using a transposed form-II digital filter lattice with no time-varying control.
General purpose custom filter with no time-varying pole control. The filter coefficients implement the following difference equation:
ares filter2 asig, iM, iN, ib0, ib1, ..., ibM, ia1, ia2, ..., iaN kres filter2 ksig, iM, iN, ib0, ib1, ..., ibM, ia1, ia2, ..., iaN
csound doc: http://csound.com/docs/manual/filter2.html
fmanal :: Sig -> Sig -> (Sig, Sig) #
AM/FM analysis from quadrature signal.
This opcode attempts to extract the AM and FM signals off a quadrature signal (e.g. from a Hilbert transform).
am, af fmanal are, aim
csound doc: http://csound.com/docs/manual/fmanal.html
fofilter :: Sig -> Sig -> Sig -> Sig -> Sig #
Formant filter.
Fofilter generates a stream of overlapping sinewave grains, when fed with a pulse train. Each grain is the impulse response of a combination of two BP filters. The grains are defined by their attack time (determining the skirtwidth of the formant region at -60dB) and decay time (-6dB bandwidth). Overlapping will occur when 1/freq < decay, but, unlike FOF, there is no upper limit on the number of overlaps. The original idea for this opcode came from J McCartney's formlet class in SuperCollider, but this is possibly implemented differently(?).
asig fofilter ain, xcf, xris, xdec[, istor]
csound doc: http://csound.com/docs/manual/fofilter.html
hilbert :: Sig -> (Sig, Sig) #
A Hilbert transformer.
An IIR implementation of a Hilbert transformer.
ar1, ar2 hilbert asig
csound doc: http://csound.com/docs/manual/hilbert.html
hilbert2 :: Sig -> D -> D -> (Sig, Sig) #
A Hilbert rransformer.
A DFT-based implementation of a Hilbert transformer.
ar1, ar2 hilbert2 asig, ifftsize, ihopsize
csound doc: http://csound.com/docs/manual/hilbert2.html
nlfilt :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
A filter with a non-linear effect.
Implements the filter:
ares nlfilt ain, ka, kb, kd, kC, kL
csound doc: http://csound.com/docs/manual/nlfilt.html
nlfilt2 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
A filter with a non-linear effect and blowup protection.
Implements the filter:
ares nlfilt2 ain, ka, kb, kd, kC, kL
csound doc: http://csound.com/docs/manual/nlfilt2.html
pareq :: Sig -> Sig -> Sig -> Sig -> Sig #
Implementation of Zoelzer's parametric equalizer filters.
Implementation of Zoelzer's parametric equalizer filters, with some modifications by the author.
ares pareq asig, kc, kv, kq [, imode] [, iskip]
csound doc: http://csound.com/docs/manual/pareq.html
rbjeq :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
Parametric equalizer and filter opcode with 7 filter types, based on algorithm by Robert Bristow-Johnson.
Parametric equalizer and filter opcode with 7 filter types, based on algorithm by Robert Bristow-Johnson.
ar rbjeq asig, kfco, klvl, kQ, kS[, imode]
csound doc: http://csound.com/docs/manual/rbjeq.html
zfilter2 :: Sig -> Sig -> Sig -> D -> D -> [D] -> Sig #
Performs filtering using a transposed form-II digital filter lattice with radial pole-shearing and angular pole-warping.
General purpose custom filter with time-varying pole control. The filter coefficients implement the following difference equation:
ares zfilter2 asig, kdamp, kfreq, iM, iN, ib0, ib1, ..., ibM, \ ia1,ia2, ..., iaN
csound doc: http://csound.com/docs/manual/zfilter2.html
wguide1 :: Sig -> Sig -> Sig -> Sig -> Sig #
A simple waveguide model consisting of one delay-line and one first-order lowpass filter.
ares wguide1 asig, xfreq, kcutoff, kfeedback
csound doc: http://csound.com/docs/manual/wguide1.html
wguide2 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
A model of beaten plate consisting of two parallel delay-lines and two first-order lowpass filters.
ares wguide2 asig, xfreq1, xfreq2, kcutoff1, kcutoff2, \ kfeedback1, kfeedback2
csound doc: http://csound.com/docs/manual/wguide2.html
chebyshevpoly :: Sig -> [Sig] -> Sig #
Efficiently evaluates the sum of Chebyshev polynomials of arbitrary order.
The chebyshevpoly opcode calculates the value of a polynomial expression with a single a-rate input variable that is made up of a linear combination of the first N Chebyshev polynomials of the first kind. Each Chebyshev polynomial, Tn(x), is weighted by a k-rate coefficient, kn, so that the opcode is calculating a sum of any number of terms in the form kn*Tn(x). Thus, the chebyshevpoly opcode allows for the waveshaping of an audio signal with a dynamic transfer function that gives precise control over the harmonic content of the output.
aout chebyshevpoly ain, k0 [, k1 [, k2 [...]]]
csound doc: http://csound.com/docs/manual/chebyshevpoly.html
pdclip :: Sig -> Sig -> Sig -> Sig #
Performs linear clipping on an audio signal or a phasor.
The pdclip opcode allows a percentage of the input range of a signal to be clipped to fullscale. It is similar to simply multiplying the signal and limiting the range of the result, but pdclip allows you to think about how much of the signal range is being distorted instead of the scalar factor and has a offset parameter for assymetric clipping of the signal range. pdclip is also useful for remapping phasors for phase distortion synthesis.
aout pdclip ain, kWidth, kCenter [, ibipolar [, ifullscale]]
csound doc: http://csound.com/docs/manual/pdclip.html
Distorts a phasor for reading the two halves of a table at different rates.
The pdhalf opcode is designed to emulate the "classic" phase distortion synthesis method of the Casio CZ-series of synthesizers from the mid-1980's. This technique reads the first and second halves of a function table at different rates in order to warp the waveform. For example, pdhalf can smoothly transform a sine wave into something approximating the shape of a saw wave.
aout pdhalf ain, kShapeAmount [, ibipolar [, ifullscale]]
csound doc: http://csound.com/docs/manual/pdhalf.html
pdhalfy :: Sig -> Sig -> Sig #
Distorts a phasor for reading two unequal portions of a table in equal periods.
The pdhalfy opcode is a variation on the phase distortion synthesis method of the pdhalf opcode. It is useful for distorting a phasor in order to read two unequal portions of a table in the same number of samples.
aout pdhalfy ain, kShapeAmount [, ibipolar [, ifullscale]]
csound doc: http://csound.com/docs/manual/pdhalfy.html
powershape :: Sig -> Sig -> Sig #
Waveshapes a signal by raising it to a variable exponent.
The powershape opcode raises an input signal to a power with pre- and post-scaling of the signal so that the output will be in a predictable range. It also processes negative inputs in a symmetrical way to positive inputs, calculating a dynamic transfer function that is useful for waveshaping.
aout powershape ain, kShapeAmount [, ifullscale]
csound doc: http://csound.com/docs/manual/powershape.html
cmp :: Sig -> Str -> Sig -> Sig #
Compares two audio signals
Compares two audio signals using the standard math operators
aout cmp aL, S_operator, aR
csound doc: http://csound.com/docs/manual/cmp.html
Produces a signal that is the maximum of any number of input signals.
The max opcode takes any number of a-rate, k-rate or i-rate signals as input (all of the same rate), and outputs a signal at the same rate that is the maximum of all of the inputs. For a-rate signals, the inputs are compared one sample at a time (i.e. max does not scan an entire ksmps period of a signal for its local maximum as the max_k opcode does).
amax max ain1, ain2 [, ain3] [, ain4] [...] kmax max kin1, kin2 [, kin3] [, kin4] [...] imax max iin1, iin2 [, iin3] [, iin4] [...]
csound doc: http://csound.com/docs/manual/max.html
max_k :: Sig -> Sig -> D -> Sig #
Local maximum (or minimum) value of an incoming asig signal
max_k outputs the local maximum (or minimum) value of the incoming asig signal, checked in the time interval between ktrig has become true twice.
knumkout max_k asig, ktrig, itype
csound doc: http://csound.com/docs/manual/max_k.html
Produces a signal that is the maximum of the absolute values of any number of input signals.
The maxabs opcode takes any number of a-rate or k-rate signals as input (all of the same rate), and outputs a signal at the same rate that is the maximum of all of the inputs. It is identical to the max opcode except that it takes the absolute value of each input before comparing them. Therefore, the output is always non-negative. For a-rate signals, the inputs are compared one sample at a time (i.e. maxabs does not scan an entire ksmps period of a signal for its local maximum as the max_k opcode does).
amax maxabs ain1, ain2 [, ain3] [, ain4] [...] kmax maxabs kin1, kin2 [, kin3] [, kin4] [...]
csound doc: http://csound.com/docs/manual/maxabs.html
maxabsaccum :: Sig -> Sig -> SE () #
Accumulates the maximum of the absolute values of audio signals.
maxabsaccum compares two audio-rate variables and stores the maximum of their absolute values into the first.
maxabsaccum aAccumulator, aInput
csound doc: http://csound.com/docs/manual/maxabsaccum.html
maxaccum :: Sig -> Sig -> SE () #
Accumulates the maximum value of audio signals.
maxaccum compares two audio-rate variables and stores the maximum value between them into the first.
maxaccum aAccumulator, aInput
csound doc: http://csound.com/docs/manual/maxaccum.html
Produces a signal that is the minimum of any number of input signals.
The min opcode takes any number of a-rate, k-rate or i-rate signals as input (all of the same rate), and outputs a signal at the same rate that is the minimum of all of the inputs. For a-rate signals, the inputs are compared one sample at a time (i.e. min does not scan an entire ksmps period of a signal for its local minimum as the max_k opcode does).
amin min ain1, ain2 [, ain3] [, ain4] [...] kmin min kin1, kin2 [, kin3] [, kin4] [...] imin min iin1, iin2 [, iin3] [, iin4] [...]
csound doc: http://csound.com/docs/manual/min.html
Produces a signal that is the minimum of the absolute values of any number of input signals.
The minabs opcode takes any number of a-rate or k-rate signals as input (all of the same rate), and outputs a signal at the same rate that is the minimum of all of the inputs. It is identical to the min opcode except that it takes the absolute value of each input before comparing them. Therefore, the output is always non-negative. For a-rate signals, the inputs are compared one sample at a time (i.e. minabs does not scan an entire ksmps period of a signal for its local minimum as the max_k opcode does).
amin minabs ain1, ain2 [, ain3] [, ain4] [...] kmin minabs kin1, kin2 [, kin3] [, kin4] [...]
csound doc: http://csound.com/docs/manual/minabs.html
minabsaccum :: Sig -> Sig -> SE () #
Accumulates the minimum of the absolute values of audio signals.
minabsaccum compares two audio-rate variables and stores the minimum of their absolute values into the first.
minabsaccum aAccumulator, aInput
csound doc: http://csound.com/docs/manual/minabsaccum.html
minaccum :: Sig -> Sig -> SE () #
Accumulates the minimum value of audio signals.
minaccum compares two audio-rate variables and stores the minimum value between them into the first.
minaccum aAccumulator, aInput
csound doc: http://csound.com/docs/manual/minaccum.html
ktableseg :: Tab -> D -> Tab -> SE () #
Deprecated.
Deprecated. Use the tableseg opcode instead.
ktableseg ifn1, idur1, ifn2 [, idur2] [, ifn3] [...]
csound doc: http://csound.com/docs/manual/ktableseg.html
pvadd :: Sig -> Sig -> Str -> Tab -> D -> Sig #
Reads from a pvoc file and uses the data to perform additive synthesis.
pvadd reads from a pvoc file and uses the data to perform additive synthesis using an internal array of interpolating oscillators. The user supplies the wave table (usually one period of a sine wave), and can choose which analysis bins will be used in the re-synthesis.
ares pvadd ktimpnt, kfmod, ifilcod, ifn, ibins [, ibinoffset] \ [, ibinincr] [, iextractmode] [, ifreqlim] [, igatefn]
csound doc: http://csound.com/docs/manual/pvadd.html
pvbufread :: Sig -> Str -> SE () #
Reads from a phase vocoder analysis file and makes the retrieved data available.
pvbufread reads from a pvoc file and makes the retrieved data available to any following pvinterp and pvcross units that appear in an instrument before a subsequent pvbufread (just as lpread and lpreson work together). The data is passed internally and the unit has no output of its own.
pvbufread ktimpnt, ifile
csound doc: http://csound.com/docs/manual/pvbufread.html
pvcross :: Sig -> Sig -> Str -> Sig -> Sig -> Sig #
Applies the amplitudes from one phase vocoder analysis file to the data from a second file.
pvcross applies the amplitudes from one phase vocoder analysis file to the data from a second file and then performs the resynthesis. The data is passed, as described above, from a previously called pvbufread unit. The two k-rate amplitude arguments are used to scale the amplitudes of each files separately before they are added together and used in the resynthesis (see below for further explanation). The frequencies of the first file are not used at all in this process. This unit simply allows for cross-synthesis through the application of the amplitudes of the spectra of one signal to the frequencies of a second signal. Unlike pvinterp, pvcross does allow for the use of the ispecwp as in pvoc and vpvoc.
ares pvcross ktimpnt, kfmod, ifile, kampscale1, kampscale2 [, ispecwp]
csound doc: http://csound.com/docs/manual/pvcross.html
pvinterp :: Sig -> Sig -> Str -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> Sig #
Interpolates between the amplitudes and frequencies of two phase vocoder analysis files.
pvinterp interpolates between the amplitudes and frequencies, on a bin by bin basis, of two phase vocoder analysis files (one from a previously called pvbufread unit and the other from within its own argument list), allowing for user defined transitions between analyzed sounds. It also allows for general scaling of the amplitudes and frequencies of each file separately before the interpolated values are calculated and sent to the resynthesis routines. The kfmod argument in pvinterp performs its frequency scaling on the frequency values after their derivation from the separate scaling and subsequent interpolation is performed so that this acts as an overall scaling value of the new frequency components.
ares pvinterp ktimpnt, kfmod, ifile, kfreqscale1, kfreqscale2, \ kampscale1, kampscale2, kfreqinterp, kampinterp
csound doc: http://csound.com/docs/manual/pvinterp.html
pvoc :: Sig -> Sig -> Str -> Sig #
Implements signal reconstruction using an fft-based phase vocoder.
ares pvoc ktimpnt, kfmod, ifilcod [, ispecwp] [, iextractmode] \ [, ifreqlim] [, igatefn]
csound doc: http://csound.com/docs/manual/pvoc.html
pvread :: Sig -> Str -> D -> (Sig, Sig) #
Reads from a phase vocoder analysis file and returns the frequency and amplitude from a single analysis channel or bin.
pvread reads from a pvoc file and returns the frequency and amplitude from a single analysis channel or bin. The returned values can be used anywhere else in the Csound instrument. For example, one can use them as arguments to an oscillator to synthesize a single component from an analyzed signal or a bank of pvreads can be used to resynthesize the analyzed sound using additive synthesis by passing the frequency and magnitude values to a bank of oscillators.
kfreq, kamp pvread ktimpnt, ifile, ibin
csound doc: http://csound.com/docs/manual/pvread.html
tableseg :: Tab -> D -> Tab -> SE () #
Creates a new function table by making linear segments between values in stored function tables.
tableseg is like linseg but interpolate between values in a stored function tables. The result is a new function table passed internally to any following vpvoc which occurs before a subsequent tableseg (much like lpread/lpreson pairs work). The uses of these are described below under vpvoc.
tableseg ifn1, idur1, ifn2 [, idur2] [, ifn3] [...]
csound doc: http://csound.com/docs/manual/tableseg.html
tablexseg :: Tab -> D -> Tab -> SE () #
Creates a new function table by making exponential segments between values in stored function tables.
tablexseg is like expseg but interpolate between values in a stored function tables. The result is a new function table passed internally to any following vpvoc which occurs before a subsequent tablexseg (much like lpread/lpreson pairs work). The uses of these are described below under vpvoc.
tablexseg ifn1, idur1, ifn2 [, idur2] [, ifn3] [...]
csound doc: http://csound.com/docs/manual/tablexseg.html
vpvoc :: Sig -> Sig -> Str -> Sig #
Implements signal reconstruction using an fft-based phase vocoder and an extra envelope.
ares vpvoc ktimpnt, kfmod, ifile [, ispecwp] [, ifn]
csound doc: http://csound.com/docs/manual/vpvoc.html
lpfreson :: Sig -> Sig -> Sig #
Resynthesises a signal from the data passed internally by a previous lpread, applying formant shifting.
ares lpfreson asig, kfrqratio
csound doc: http://csound.com/docs/manual/lpfreson.html
lpinterp :: D -> D -> Sig -> SE () #
Computes a new set of poles from the interpolation between two analysis.
lpinterp islot1, islot2, kmix
csound doc: http://csound.com/docs/manual/lpinterp.html
lpread :: Sig -> Str -> (Sig, Sig, Sig, Sig) #
Reads a control file of time-ordered information frames.
krmsr, krmso, kerr, kcps lpread ktimpnt, ifilcod [, inpoles] [, ifrmrate]
csound doc: http://csound.com/docs/manual/lpread.html
Resynthesises a signal from the data passed internally by a previous lpread.
ares lpreson asig
csound doc: http://csound.com/docs/manual/lpreson.html
Selects the slot to be use by further lp opcodes.
lpslot islot
csound doc: http://csound.com/docs/manual/lpslot.html
specaddm :: Wspec -> Wspec -> Wspec #
Perform a weighted add of two input spectra.
wsig specaddm wsig1, wsig2 [, imul2]
csound doc: http://csound.com/docs/manual/specaddm.html
Finds the positive difference values between consecutive spectral frames.
wsig specdiff wsigin
csound doc: http://csound.com/docs/manual/specdiff.html
specdisp :: Wspec -> D -> SE () #
Displays the magnitude values of the spectrum.
specdisp wsig, iprd [, iwtflg]
csound doc: http://csound.com/docs/manual/specdisp.html
specfilt :: Wspec -> D -> Wspec #
Filters each channel of an input spectrum.
wsig specfilt wsigin, ifhtim
csound doc: http://csound.com/docs/manual/specfilt.html
Accumulates the values of successive spectral frames.
wsig spechist wsigin
csound doc: http://csound.com/docs/manual/spechist.html
specptrk :: Wspec -> Sig -> D -> D -> D -> D -> D -> D -> (Sig, Sig) #
Estimates the pitch of the most prominent complex tone in the spectrum.
Estimate the pitch of the most prominent complex tone in the spectrum.
koct, kamp specptrk wsig, kvar, ilo, ihi, istr, idbthresh, inptls, \ irolloff [, iodd] [, iconfs] [, interp] [, ifprd] [, iwtflg]
csound doc: http://csound.com/docs/manual/specptrk.html
specscal :: Wspec -> D -> D -> Wspec #
Scales an input spectral datablock with spectral envelopes.
wsig specscal wsigin, ifscale, ifthresh
csound doc: http://csound.com/docs/manual/specscal.html
Sums the magnitudes across all channels of the spectrum.
ksum specsum wsig [, interp]
csound doc: http://csound.com/docs/manual/specsum.html
spectrum :: Sig -> D -> D -> D -> Wspec #
Generate a constant-Q, exponentially-spaced DFT.
Generate a constant-Q, exponentially-spaced DFT across all octaves of a multiply-downsampled control or audio input signal.
wsig spectrum xsig, iprd, iocts, ifrqa [, iq] [, ihann] [, idbout] \ [, idsprd] [, idsinrs]
csound doc: http://csound.com/docs/manual/spectrum.html
PVS tracks to amplitude+frequency conversion.
The binit opcode takes an input containg a TRACKS pv streaming signal (as generated,
for instance by partials) and converts it into a equal-bandwidth bin-frame containing amplitude
and frequency pairs (PVS_AMP_FREQ), suitable for overlap-add resynthesis (such as performed by
pvsynth) or further PVS streaming phase vocoder signal transformations. For each frequency bin,
it will look for a suitable track signal to fill it; if not found, the bin will be empty (0 amplitude).
If more than one track fits a certain bin, the one with highest amplitude will be chosen. This
means that not all of the input signal is actually binned
, the operation is lossy. However, in
many situations this loss is not perceptually relevant.
fsig binit fin, isize
csound doc: http://csound.com/docs/manual/binit.html
cudanal :: Sig -> D -> D -> D -> D -> Spec #
Generate an fsig from a mono audio source ain, using phase vocoder overlap-add analysis and GPU hardware. Experimental and only available as source code at the moment.
Generate an fsig from a mono audio source ain, using phase vocoder overlap-add analysis and GPU hardware.
fsig cudanal ain, ifftsize, ioverlap, iwinsize, iwintype [, iformat] [, iinit]
csound doc: http://csound.com/docs/manual/cudanal.html
cudasliding :: Sig -> Sig -> D -> Sig #
Perform sliding phase vocoder algorithm with simplified transformational FM using GPU hardware. Experimental and only available as source code at the moment.
Perform sliding phase vocoder algorithm with simplified transformational FM using GPU hardware.
asig cudasliding ain, amod, iwinsize
csound doc: http://csound.com/docs/manual/cudasliding.html
cudasynth :: Sig -> Sig -> Tab -> D -> D -> Sig #
Synthesis by additive synthesis and inverse FFT. Experimental and only available as source code at the moment.
Synthesis by additive synthesis and inverse FFT.
asig cudasynth kamp, kfreq, itab, iftab, iatab[, inum] asig cudasynth fsig, kamp, kfreq[, inum] asig cudasynth fsig
csound doc: http://csound.com/docs/manual/cudasynth.html
partials :: Spec -> Spec -> Sig -> Sig -> Sig -> D -> Spec #
Partial track spectral analysis.
The partials opcode takes two input PV streaming signals containg AMP_FREQ and AMP_PHASE signals (as generated for instance by pvsifd or in the first case, by pvsanal) and performs partial track analysis, as described in Lazzarini et al, "Time-stretching using the Instantaneous Frequency Distribution and Partial Tracking", Proc.of ICMC05, Barcelona. It generates a TRACKS PV streaming signal, containing amplitude, frequency, phase and track ID for each output track. This type of signal will contain a variable number of output tracks, up to the total number of analysis bins contained in the inputs (fftsize/2 + 1 bins). The second input (AMP_PHASE) is optional, as it can take the same signal as the first input. In this case, however, all phase information will be NULL and resynthesis using phase information cannot be performed.
ftrks partials ffr, fphs, kthresh, kminpts, kmaxgap, imaxtracks
csound doc: http://csound.com/docs/manual/partials.html
pvsadsyn :: Spec -> D -> Sig -> Sig #
Resynthesize using a fast oscillator-bank.
ares pvsadsyn fsrc, inoscs, kfmod [, ibinoffset] [, ibinincr] [, iinit]
csound doc: http://csound.com/docs/manual/pvsadsyn.html
pvsanal :: Sig -> D -> D -> D -> D -> Spec #
Generate an fsig from a mono audio source ain, using phase vocoder overlap-add analysis.
fsig pvsanal ain, ifftsize, ioverlap, iwinsize, iwintype [, iformat] [, iinit]
csound doc: http://csound.com/docs/manual/pvsanal.html
pvsarp :: Spec -> Sig -> Sig -> Sig -> Spec #
Arpeggiate the spectral components of a streaming pv signal.
This opcode arpeggiates spectral components, by amplifying one bin and attenuating all the others around it. Used with an LFO it will provide a spectral arpeggiator similar to Trevor Wishart's CDP program specarp.
fsig pvsarp fsigin, kbin, kdepth, kgain
csound doc: http://csound.com/docs/manual/pvsarp.html
pvsbandp :: Spec -> Sig -> Sig -> Sig -> Sig -> Spec #
A band pass filter working in the spectral domain.
Filter the pvoc frames, passing bins whose frequency is within a band, and with linear interpolation for transitional bands.
fsig pvsbandp fsigin, xlowcut, xlowfull, \ xhighfull, xhighcut[, ktype]
csound doc: http://csound.com/docs/manual/pvsbandp.html
pvsbandr :: Spec -> Sig -> Sig -> Sig -> Sig -> Spec #
A band reject filter working in the spectral domain.
Filter the pvoc frames, rejecting bins whose frequency is within a band, and with linear interpolation for transitional bands.
fsig pvsbandr fsigin, xlowcut, xlowfull, \ xhighfull, xhighcut[, ktype]
csound doc: http://csound.com/docs/manual/pvsbandr.html
pvsbin :: Spec -> Sig -> (Sig, Sig) #
Obtain the amp and freq values off a PVS signal bin.
Obtain the amp and freq values off a PVS signal bin as k-rate variables.
kamp, kfr pvsbin fsig, kbin
csound doc: http://csound.com/docs/manual/pvsbin.html
pvsblur :: Spec -> Sig -> D -> Spec #
Average the amp/freq time functions of each analysis channel for a specified time.
Average the amp/freq time functions of each analysis channel for a specified time (truncated to number of frames). As a side-effect the input pvoc stream will be delayed by that amount.
fsig pvsblur fsigin, kblurtime, imaxdel
csound doc: http://csound.com/docs/manual/pvsblur.html
pvsbuffer :: Spec -> D -> (D, Sig) #
This opcode creates and writes to a circular buffer for f-signals (streaming PV signals).
This opcode sets up and writes to a circular buffer of length ilen (secs), giving a handle for the buffer and a time pointer, which holds the current write position (also in seconds). It can be used with one or more pvsbufread opcodes. Writing is circular, wrapping around at the end of the buffer.
ihandle, ktime pvsbuffer fsig, ilen
csound doc: http://csound.com/docs/manual/pvsbuffer.html
pvsbufread :: Sig -> Sig -> Spec #
This opcode reads a circular buffer of f-signals (streaming PV signals).
This opcode reads from a circular buffer of length ilen (secs), taking a handle for the buffer and a time pointer, which holds the current read position (also in seconds). It is used in conjunction with a pvsbuffer opocde. Reading is circular, wrapping around at the end of the buffer.
fsig pvsbufread ktime, khandle[, ilo, ihi, iclear]
csound doc: http://csound.com/docs/manual/pvsbufread.html
pvsbufread2 :: Sig -> Sig -> D -> D -> Spec #
This opcode reads a circular buffer of f-signals (streaming PV signals), with binwise additional delays.
This opcode reads from a circular buffer of length ilen (secs), taking a handle for the buffer and a time pointer, which holds the current read position (also in seconds). It is used in conjunction with a pvsbuffer opocde. Reading is circular, wrapping around at the end of the buffer. Extra delay times are taken from a function table, with each point on it defining a delay time in seconds affecting the corresponding bin.
fsig pvsbufread2 ktime, khandle, ift1, ift2
csound doc: http://csound.com/docs/manual/pvsbufread2.html
pvscale :: Spec -> Sig -> Spec #
Scale the frequency components of a pv stream.
Scale the frequency components of a pv stream, resulting in pitch shift. Output amplitudes can be optionally modified in order to attempt formant preservation.
fsig pvscale fsigin, kscal[, kkeepform, kgain, kcoefs]
csound doc: http://csound.com/docs/manual/pvscale.html
Calculate the spectral centroid of a signal.
Calculate the spectral centroid of a signal from its discrete Fourier transform.
kcent pvscent fsig
csound doc: http://csound.com/docs/manual/pvscent.html
pvscross :: Spec -> Spec -> Sig -> Sig -> Spec #
Performs cross-synthesis between two source fsigs.
fsig pvscross fsrc, fdest, kamp1, kamp2
csound doc: http://csound.com/docs/manual/pvscross.html
pvsdemix :: Spec -> Spec -> Sig -> Sig -> D -> Spec #
Spectral azimuth-based de-mixing of stereo sources.
Spectral azimuth-based de-mixing of stereo sources, with a reverse-panning result. This opcode implements the Azimuth Discrimination and Resynthesis (ADRess) algorithm, developed by Dan Barry (Barry et Al. "Sound Source Separation Azimuth Discrimination and Resynthesis". DAFx'04, Univ. of Napoli). The source separation, or de-mixing, is controlled by two parameters: an azimuth position (kpos) and a subspace width (kwidth). The first one is used to locate the spectral peaks of individual sources on a stereo mix, whereas the second widens the 'search space', including/exclufing the peaks around kpos. These two parameters can be used interactively to extract source sounds from a stereo mix. The algorithm is particularly successful with studio recordings where individual instruments occupy individual panning positions; it is, in fact, a reverse-panning algorithm.
fsig pvsdemix fleft, fright, kpos, kwidth, ipoints
csound doc: http://csound.com/docs/manual/pvsdemix.html
pvsdiskin :: Str -> Sig -> Sig -> Spec #
Read a selected channel from a PVOC-EX analysis file.
Create an fsig stream by reading a selected channel from a PVOC-EX analysis file, with frame interpolation.
fsig pvsdiskin SFname,ktscal,kgain[,ioffset, ichan]
csound doc: http://csound.com/docs/manual/pvsdiskin.html
Displays a PVS signal as an amplitude vs. freq graph.
This opcode will display a PVS signal fsig. Uses X11 or FLTK windows if enabled, else (or if -g flag is set) displays are approximated in ASCII characters.
pvsdisp fsig[, ibins, iwtflg]
csound doc: http://csound.com/docs/manual/pvsdisp.html
pvsfilter :: Spec -> Spec -> Sig -> Spec #
Multiply amplitudes of a pvoc stream by those of a second pvoc stream, with dynamic scaling.
fsig pvsfilter fsigin, fsigfil, kdepth[, igain]
csound doc: http://csound.com/docs/manual/pvsfilter.html
pvsfread :: Sig -> Tab -> Spec #
Read a selected channel from a PVOC-EX analysis file.
Create an fsig stream by reading a selected channel from a PVOC-EX analysis file loaded into memory, with frame interpolation. Only format 0 files (amplitude+frequency) are currently supported. The operation of this opcode mirrors that of pvoc, but outputs an fsig instead of a resynthesized signal.
fsig pvsfread ktimpt, ifn [, ichan]
csound doc: http://csound.com/docs/manual/pvsfread.html
pvsfreeze :: Spec -> Sig -> Sig -> Spec #
Freeze the amplitude and frequency time functions of a pv stream according to a control-rate trigger.
This opcodes freezes
the evolution of pvs stream by locking into steady amplitude and/or
frequency values for each bin. The freezing is controlled, independently for amplitudes and
frequencies, by a control-rate trigger, which switches the freezing on
if equal to or above
1 and off
if below 1.
fsig pvsfreeze fsigin, kfreeza, kfreezf
csound doc: http://csound.com/docs/manual/pvsfreeze.html
pvsftr :: Spec -> Tab -> SE () #
Reads amplitude and/or frequency data from function tables.
pvsftr fsrc, ifna [, ifnf]
csound doc: http://csound.com/docs/manual/pvsftr.html
pvsftw :: Spec -> Tab -> Sig #
Writes amplitude and/or frequency data to function tables.
kflag pvsftw fsrc, ifna [, ifnf]
csound doc: http://csound.com/docs/manual/pvsftw.html
pvsfwrite :: Spec -> Str -> SE () #
Write a fsig to a PVOCEX file.
This opcode writes a fsig to a PVOCEX file (which in turn can be read by pvsfread or other programs that support PVOCEX file input).
pvsfwrite fsig, ifile
csound doc: http://csound.com/docs/manual/pvsfwrite.html
pvsgain :: Spec -> Sig -> Spec #
Scale the amplitude of a pv stream.
fsig pvsgain fsigin, kgain
csound doc: http://csound.com/docs/manual/pvsgain.html
pvshift :: Spec -> Sig -> Sig -> Spec #
Shift the frequency components of a pv stream, stretching/compressing its spectrum.
fsig pvshift fsigin, kshift, klowest[, kkeepform, igain, kcoefs]
csound doc: http://csound.com/docs/manual/pvshift.html
pvsifd :: Sig -> D -> D -> D -> (Spec, Spec) #
Instantaneous Frequency Distribution, magnitude and phase analysis.
The pvsifd opcode takes an input a-rate signal and performs an Instantaneous Frequency, magnitude and phase analysis, using the STFT and pvsifd (Instantaneous Frequency Distribution), as described in Lazzarini et al, "Time-stretching using the Instantaneous Frequency Distribution and Partial Tracking", Proc.of ICMC05, Barcelona. It generates two PV streaming signals, one containing the amplitudes and frequencies (a similar output to pvsanal) and another containing amplitudes and unwrapped phases.
ffr,fphs pvsifd ain, ifftsize, ihopsize, iwintype[,iscal]
csound doc: http://csound.com/docs/manual/pvsifd.html
Retrieve an fsig from the input software bus; a pvs equivalent to chani.
This opcode retrieves an f-sig from the pvs in software bus, which can be used to get data from an external source, using the Csound 5 API. A channel is created if not already existing. The fsig channel is in that case initialised with the given parameters. It is important to note that the pvs input and output (pvsout opcode) busses are independent and data is not shared between them.
fsig pvsin kchan[, isize, iolap, iwinsize, iwintype, iformat]
csound doc: http://csound.com/docs/manual/pvsin.html
pvsinfo :: Spec -> (D, D, D, D) #
Get information from a PVOC-EX formatted source.
Get format information about fsrc, whether created by an opcode such as pvsanal, or obtained from a PVOCEX file by pvsfread. This information is available at init time, and can be used to set parameters for other pvs opcodes, and in particular for creating function tables (e.g. for pvsftw), or setting the number of oscillators for pvsadsyn.
ioverlap, inumbins, iwinsize, iformat pvsinfo fsrc
csound doc: http://csound.com/docs/manual/pvsinfo.html
Initialise a spectral (f) variable to zero.
Performs the equivalent to an init operation on an f-variable.
fsig pvsinit isize[, iolap, iwinsize, iwintype, iformat]
csound doc: http://csound.com/docs/manual/pvsinit.html
pvslock :: Spec -> Sig -> Spec #
Frequency lock an input fsig
This opcode searches for spectral peaks and then locks the frequencies around those peaks. This is similar to phase-locking in non-streaming PV processing. It can be used to improve timestretching and pitch-shifting quality in PV processing.
fsig pvslock fsigin, klock
csound doc: http://csound.com/docs/manual/pvslock.html
pvsmaska :: Spec -> Tab -> Sig -> Spec #
Modify amplitudes using a function table, with dynamic scaling.
Modify amplitudes of fsrc using function table, with dynamic scaling.
fsig pvsmaska fsrc, ifn, kdepth
csound doc: http://csound.com/docs/manual/pvsmaska.html
pvsmix :: Spec -> Spec -> Spec #
Mix seamlessly
two pv signals.
Mix seamlessly
two pv signals. This opcode combines the
most prominent components of two pvoc streams into a single
mixed stream.
fsig pvsmix fsigin1, fsigin2
csound doc: http://csound.com/docs/manual/pvsmix.html
pvsmooth :: Spec -> Sig -> Sig -> Spec #
Smooth the amplitude and frequency time functions of a pv stream using parallel 1st order lowpass IIR filters with time-varying cutoff frequency.
Smooth the amplitude and frequency time functions of a pv stream using a 1st order lowpass IIR with time-varying cutoff frequency. This opcode uses the same filter as the tone opcode, but this time acting separately on the amplitude and frequency time functions that make up a pv stream. The cutoff frequency parameter runs at the control-rate, but unlike tone and tonek, it is not specified in Hz, but as fractions of 1/2 frame-rate (actually the pv stream sampling rate), which is easier to understand. This means that the highest cutoff frequency is 1 and the lowest 0; the lower the frequency the smoother the functions and more pronounced the effect will be.
fsig pvsmooth fsigin, kacf, kfcf
csound doc: http://csound.com/docs/manual/pvsmooth.html
pvsmorph :: Spec -> Spec -> Sig -> Sig -> Spec #
Performs morphing (or interpolation) between two source fsigs.
Performs morphing (or interpolation) between two source fsigs.
fsig pvsmorph fsig1, fsig2, kampint, kfrqint
csound doc: http://csound.com/docs/manual/pvsmorph.html
pvsosc :: Sig -> Sig -> Sig -> D -> Spec #
PVS-based oscillator simulator.
Generates periodic signal spectra in AMP-FREQ format, with the option of four wave types:
fsig pvsosc kamp, kfreq, ktype, isize [,ioverlap] [, iwinsize] [, iwintype] [, iformat]
csound doc: http://csound.com/docs/manual/pvsosc.html
pvsout :: Spec -> Sig -> SE () #
Write a fsig to the pvs output bus.
This opcode writes a fsig to a channel of the pvs output bus. Note that the pvs out bus and the pvs in bus are separate and independent. A new channel is created if non-existent.
pvsout fsig, kchan
csound doc: http://csound.com/docs/manual/pvsout.html
pvspitch :: Spec -> Sig -> (Sig, Sig) #
Track the pitch and amplitude of a PVS signal.
Track the pitch and amplitude of a PVS signal as k-rate variables.
kfr, kamp pvspitch fsig, kthresh
csound doc: http://csound.com/docs/manual/pvspitch.html
pvstanal :: Sig -> Sig -> Sig -> Tab -> Spec #
Phase vocoder analysis processing with onset detection/processing.
pvstanal implements phase vocoder analysis by reading function tables containing sampled-sound sources, with GEN01, and pvstanal will accept deferred allocation tables.
fsig pvstanal ktimescal, kamp, kpitch, ktab, [kdetect, kwrap, ioffset,ifftsize, ihop, idbthresh]
csound doc: http://csound.com/docs/manual/pvstanal.html
pvstencil :: Spec -> Sig -> Sig -> D -> Spec #
Transforms a pvoc stream according to a masking function table.
Transforms a pvoc stream according to a masking function table; if the pvoc stream amplitude falls below the value of the function for a specific pvoc channel, it applies a gain to that channel.
fsig pvstencil fsigin, kgain, klevel, iftable
csound doc: http://csound.com/docs/manual/pvstencil.html
pvstrace :: Spec -> Sig -> Spec #
Retain only the N loudest bins.
Process a PV stream by retaining only the N bins with the highest amplitude, zeroing the others.
fsig pvstrace fsigin, kn
csound doc: http://csound.com/docs/manual/pvstrace.html
pvsvoc :: Spec -> Spec -> Sig -> Sig -> Spec #
Combine the spectral envelope of one fsig with the excitation (frequencies) of another.
This opcode provides support for cross-synthesis of amplitudes and frequencies. It takes the amplitudes of one input fsig and combines with frequencies from another. It is a spectral version of the well-known channel vocoder.
fsig pvsvoc famp, fexc, kdepth, kgain [,kcoefs]
csound doc: http://csound.com/docs/manual/pvsvoc.html
pvswarp :: Spec -> Sig -> Sig -> Spec #
Warp the spectral envelope of a PVS signal
Warp the spectral envelope of a PVS signal by means of shifting and scaling.
fsig pvswarp fsigin, kscal, kshift[, klowest, kmeth, kgain, kcoefs]
csound doc: http://csound.com/docs/manual/pvswarp.html
Resynthesise using a FFT overlap-add.
Resynthesise phase vocoder data (f-signal) using a FFT overlap-add.
ares pvsynth fsrc, [iinit]
csound doc: http://csound.com/docs/manual/pvsynth.html
resyn :: Spec -> Sig -> Sig -> Sig -> Tab -> Sig #
Streaming partial track additive synthesis with cubic phase interpolation with pitch control and support for timescale-modified input
The resyn opcode takes an input containg a TRACKS pv streaming signal (as generated, for instance by partials). It resynthesises the signal using linear amplitude and cubic phase interpolation to drive a bank of interpolating oscillators with amplitude and pitch scaling controls. Resyn is a modified version of sinsyn, allowing for the resynthesis of data with pitch and timescale changes.
asig resyn fin, kscal, kpitch, kmaxtracks, ifn
csound doc: http://csound.com/docs/manual/resyn.html
sinsyn :: Spec -> Sig -> Sig -> Tab -> Sig #
Streaming partial track additive synthesis with cubic phase interpolation
The sinsyn opcode takes an input containg a TRACKS pv streaming signal (as generated, for instance by the partials opcode). It resynthesises the signal using linear amplitude and cubic phase interpolation to drive a bank of interpolating oscillators with amplitude scaling control. sinsyn attempts to preserve the phase of the partials in the original signal and in so doing it does not allow for pitch or timescale modifications of the signal.
asig sinsyn fin, kscal, kmaxtracks, ifn
csound doc: http://csound.com/docs/manual/sinsyn.html
tabifd :: Sig -> Sig -> Sig -> D -> D -> D -> Tab -> (Spec, Spec) #
Instantaneous Frequency Distribution, magnitude and phase analysis.
The tabifd opcode takes an input function table and performs an Instantaneous Frequency, magnitude and phase analysis, using the STFT and tabifd (Instantaneous Frequency Distribution), as described in Lazzarini et al, "Time-stretching using the Instantaneous Frequency Distribution and Partial Tracking", Proc.of ICMC05, Barcelona. It generates two PV streaming signals, one containing the amplitudes and frequencies (a similar output to pvsanal) and another containing amplitudes and unwrapped phases.
ffr,fphs tabifd ktimpt, kamp, kpitch, ifftsize, ihopsize, iwintype,ifn
csound doc: http://csound.com/docs/manual/tabifd.html
tradsyn :: Spec -> Sig -> Sig -> Sig -> Tab -> Sig #
Streaming partial track additive synthesis
The tradsyn opcode takes an input containg a TRACKS pv streaming signal (as generated, for instance by partials),as described in Lazzarini et al, "Time-stretching using the Instantaneous Frequency Distribution and Partial Tracking", Proc.of ICMC05, Barcelona. It resynthesises the signal using linear amplitude and frequency interpolation to drive a bank of interpolating oscillators with amplitude and pitch scaling controls.
asig tradsyn fin, kscal, kpitch, kmaxtracks, ifn
csound doc: http://csound.com/docs/manual/tradsyn.html
trcross :: Spec -> Spec -> Sig -> Sig -> Spec #
Streaming partial track cross-synthesis.
The trcross opcode takes two inputs containg TRACKS pv streaming signals (as generated, for instance by partials) and cross-synthesises them into a single TRACKS stream. Two different modes of operation are used: mode 0, cross-synthesis by multiplication of the amplitudes of the two inputs and mode 1, cross-synthesis by the substititution of the amplitudes of input 1 by the input 2. Frequencies and phases of input 1 are preserved in the output. The cross-synthesis is done by matching tracks between the two inputs using a 'search interval'. The matching algorithm will look for tracks in the second input that are within the search interval around each track in the first input. This interval can be changed at the control rate. Wider search intervals will find more matches.
fsig trcross fin1, fin2, ksearch, kdepth [, kmode]
csound doc: http://csound.com/docs/manual/trcross.html
trfilter :: Spec -> Sig -> Tab -> Spec #
Streaming partial track filtering.
The trfilter opcode takes an input containg a TRACKS pv streaming signal (as generated, for instance by partials) and filters it using an amplitude response curve stored in a function table. The function table can have any size (no restriction to powers-of-two). The table lookup is done by linear-interpolation. It is possible to create time-varying filter curves by updating the amlitude response table with a table-writing opcode.
fsig trfilter fin, kamnt, ifn
csound doc: http://csound.com/docs/manual/trfilter.html
trhighest :: Spec -> Sig -> (Spec, Sig, Sig) #
Extracts the highest-frequency track from a streaming track input signal.
The trhighest opcode takes an input containg TRACKS pv streaming signals (as generated, for instance by partials) and outputs only the highest track. In addition it outputs two k-rate signals, corresponding to the frequency and amplitude of the highest track signal.
fsig, kfr, kamp trhighest fin1, kscal
csound doc: http://csound.com/docs/manual/trhighest.html
trlowest :: Spec -> Sig -> (Spec, Sig, Sig) #
Extracts the lowest-frequency track from a streaming track input signal.
The trlowest opcode takes an input containg TRACKS pv streaming signals (as generated, for instance by partials) and outputs only the lowest track. In addition it outputs two k-rate signals, corresponding to the frequency and amplitude of the lowest track signal.
fsig, kfr, kamp trlowest fin1, kscal
csound doc: http://csound.com/docs/manual/trlowest.html
trmix :: Spec -> Spec -> Spec #
Streaming partial track mixing.
The trmix opcode takes two inputs containg TRACKS pv streaming signals (as generated, for instance by partials) and mixes them into a single TRACKS stream. Tracks will be mixed up to the available space (defined by the original number of FFT bins in the analysed signals). If the sum of the input tracks exceeds this space, the higher-ordered tracks in the second input will be pruned.
fsig trmix fin1, fin2
csound doc: http://csound.com/docs/manual/trmix.html
trscale :: Spec -> Sig -> Spec #
Streaming partial track frequency scaling.
The trscale opcode takes an input containg a TRACKS pv streaming signal (as generated, for instance by partials) and scales all frequencies by a k-rate amount. It can also, optionally, scale the gain of the signal by a k-rate amount (default 1). The result is pitch shifting of the input tracks.
fsig trscale fin, kpitch[, kgain]
csound doc: http://csound.com/docs/manual/trscale.html
trshift :: Spec -> Sig -> Spec #
Streaming partial track frequency scaling.
The trshift opcode takes an input containg a TRACKS pv streaming signal (as generated, for instance by partials) and shifts all frequencies by a k-rate frequency. It can also, optionally, scale the gain of the signal by a k-rate amount (default 1). The result is frequency shifting of the input tracks.
fsig trshift fin, kpshift[, kgain]
csound doc: http://csound.com/docs/manual/trshift.html
trsplit :: Spec -> Sig -> (Spec, Spec) #
Streaming partial track frequency splitting.
The trsplit opcode takes an input containg a TRACKS pv streaming signal (as generated, for instance by partials) and splits it into two signals according to a k-rate frequency 'split point'. The first output will contain all tracks up from 0Hz to the split frequency and the second will contain the tracks from the split frequency up to the Nyquist. It can also, optionally, scale the gain of the output signals by a k-rate amount (default 1). The result is two output signals containing only part of the original spectrum.
fsiglow, fsighi trsplit fin, ksplit[, kgainlow, kgainhigh]
csound doc: http://csound.com/docs/manual/trsplit.html
atsAdd :: Sig -> Sig -> D -> Tab -> D -> Sig #
uses the data from an ATS analysis file to perform additive synthesis.
ATSadd reads from an ATS analysis file and uses the data to perform additive synthesis using an internal array of interpolating oscillators.
ar ATSadd ktimepnt, kfmod, iatsfile, ifn, ipartials[, ipartialoffset, \ ipartialincr, igatefn]
csound doc: http://csound.com/docs/manual/ATSadd.html
atsAddnz :: Sig -> D -> D -> Sig #
uses the data from an ATS analysis file to perform noise resynthesis.
ATSaddnz reads from an ATS analysis file and uses the data to perform additive synthesis using a modified randi function.
ar ATSaddnz ktimepnt, iatsfile, ibands[, ibandoffset, ibandincr]
csound doc: http://csound.com/docs/manual/ATSaddnz.html
atsBufread :: Sig -> Sig -> D -> D -> SE () #
reads data from and ATS data file and stores it in an internal data table of frequency, amplitude pairs.
ATSbufread reads data from and ATS data file and stores it in an internal data table of frequency, amplitude pairs.
ATSbufread ktimepnt, kfmod, iatsfile, ipartials[, ipartialoffset, \ ipartialincr]
csound doc: http://csound.com/docs/manual/ATSbufread.html
atsCross :: Sig -> Sig -> D -> Tab -> Sig -> Sig -> D -> Sig #
perform cross synthesis from ATS analysis files.
ATScross uses data from an ATS analysis file and data from an ATSbufread to perform cross synthesis.
ar ATScross ktimepnt, kfmod, iatsfile, ifn, kmylev, kbuflev, ipartials \ [, ipartialoffset, ipartialincr]
csound doc: http://csound.com/docs/manual/ATScross.html
reads data out of the header of an ATS file.
atsinfo reads data out of the header of an ATS file.
idata ATSinfo iatsfile, ilocation
csound doc: http://csound.com/docs/manual/ATSinfo.html
atsInterpread :: Sig -> Sig #
allows a user to determine the frequency envelope of any ATSbufread.
ATSinterpread allows a user to determine the frequency envelope of any ATSbufread.
kamp ATSinterpread kfreq
csound doc: http://csound.com/docs/manual/ATSinterpread.html
atsPartialtap :: D -> (Sig, Sig) #
returns a frequency, amplitude pair from an ATSbufread opcode.
ATSpartialtap takes a partial number and returns a frequency, amplitude pair. The frequency and amplitude data comes from an ATSbufread opcode.
kfrq, kamp ATSpartialtap ipartialnum
csound doc: http://csound.com/docs/manual/ATSpartialtap.html
atsRead :: Sig -> D -> D -> (Sig, Sig) #
reads data from an ATS file.
ATSread returns the amplitude (kamp) and frequency (kfreq) information of a user specified partial contained in the ATS analysis file at the time indicated by the time pointer ktimepnt.
kfreq, kamp ATSread ktimepnt, iatsfile, ipartial
csound doc: http://csound.com/docs/manual/ATSread.html
atsReadnz :: Sig -> D -> D -> Sig #
reads data from an ATS file.
ATSreadnz returns the energy (kenergy) of a user specified noise band (1-25 bands) at the time indicated by the time pointer ktimepnt.
kenergy ATSreadnz ktimepnt, iatsfile, iband
csound doc: http://csound.com/docs/manual/ATSreadnz.html
atsSinnoi :: Sig -> Sig -> Sig -> Sig -> D -> D -> Sig #
uses the data from an ATS analysis file to perform resynthesis.
ATSsinnoi reads data from an ATS data file and uses the information to synthesize sines and noise together.
ar ATSsinnoi ktimepnt, ksinlev, knzlev, kfmod, iatsfile, ipartials \ [, ipartialoffset, ipartialincr]
csound doc: http://csound.com/docs/manual/ATSsinnoi.html
lorismorph :: D -> D -> D -> Sig -> Sig -> Sig -> SE () #
Morphs two stored sets of bandwidth-enhanced partials and stores a new set of partials representing the morphed sound. The morph is performed by linearly interpolating the parameter envelopes (frequency, amplitude, and bandwidth, or noisiness) of the bandwidth-enhanced partials according to control-rate frequency, amplitude, and bandwidth morphing functions.
lorismorph morphs two stored sets of bandwidth-enhanced partials and stores a new set of partials representing the morphed sound. The morph is performed by linearly interpolating the parameter envelopes (frequency, amplitude, and bandwidth, or noisiness) of the bandwidth-enhanced partials according to control-rate frequency, amplitude, and bandwidth morphing functions.
lorismorph isrcidx, itgtidx, istoreidx, kfreqmorphenv, kampmorphenv, kbwmorphenv
csound doc: http://csound.com/docs/manual/lorismorph.html
lorisplay :: D -> Sig -> Sig -> Sig -> Sig #
renders a stored set of bandwidth-enhanced partials using the method of Bandwidth-Enhanced Additive Synthesis implemented in the Loris software, applying control-rate frequency, amplitude, and bandwidth scaling envelopes.
lorisplay renders a stored set of bandwidth-enhanced partials using the method of Bandwidth-Enhanced Additive Synthesis implemented in the Loris software, applying control-rate frequency, amplitude, and bandwidth scaling envelopes.
ar lorisplay ireadidx, kfreqenv, kampenv, kbwenv
csound doc: http://csound.com/docs/manual/lorisplay.html
lorisread :: Sig -> Str -> D -> Sig -> Sig -> Sig -> SE () #
Imports a set of bandwidth-enhanced partials from a SDIF-format data file, applying control-rate frequency, amplitude, and bandwidth scaling envelopes, and stores the modified partials in memory.
lorisread imports a set of bandwidth-enhanced partials from a SDIF-format data file, applying control-rate frequency, amplitude, and bandwidth scaling envelopes, and stores the modified partials in memory.
lorisread ktimpnt, ifilcod, istoreidx, kfreqenv, kampenv, kbwenv[, ifadetime]
csound doc: http://csound.com/docs/manual/lorisread.html
centroid :: Sig -> Sig -> D -> Sig #
Calculate the spectral centroid of a signal.
Calculate the spectral centroid of an audio signal on a given trigger.
kcent centroid asig, ktrig, ifftsize
csound doc: http://csound.com/docs/manual/centroid.html
filescal :: Tuple a => Sig -> Sig -> Sig -> Str -> Sig -> a #
Phase-locked vocoder processing with onset detection/processing, 'tempo-scaling'.
filescal implements phase-locked vocoder processing from disk files, resampling if necessary.
asig[,asig2] filescal ktimescal, kamp, kpitch, Sfile, klock [,ifftsize, idecim, ithresh]
csound doc: http://csound.com/docs/manual/filescal.html
mincer :: Sig -> Sig -> Sig -> Tab -> Sig -> Sig #
Phase-locked vocoder processing.
mincer implements phase-locked vocoder processing using function tables containing sampled-sound sources, with GEN01, and mincer will accept deferred allocation tables.
asig mincer atimpt, kamp, kpitch, ktab, klock[,ifftsize,idecim]
csound doc: http://csound.com/docs/manual/mincer.html
mp3scal :: Str -> Sig -> Sig -> Sig -> (Sig, Sig, Sig) #
Phase-locked vocoder processing with onset detection/processing, 'tempo-scaling'.
mp3scal implements phase-locked vocoder processing from mp3-format disk files, resampling if necessary.
asig, asig2, ktime mp3scal Sfile, ktimescal, kpitch, kamp[, iskip, ifftsize, idecim, ilock]
csound doc: http://csound.com/docs/manual/mp3scal.html
paulstretch :: D -> D -> D -> Sig #
Extreme time-stretching algorithm by Nasca Octavian Paul.
The paulstretch opcode is a lightweight implementation of the PaulStretch time-stretching algorithm by Nasca Octavian Paul. It is ideal for timestretching a signal by very large amounts.
asig paulstretch istretch, iwindowsize, ift
csound doc: http://csound.com/docs/manual/paulstretch.html
temposcal :: Sig -> Sig -> Sig -> Tab -> Sig -> Sig #
Phase-locked vocoder processing with onset detection/processing, 'tempo-scaling'.
temposcal implements phase-locked vocoder processing using function tables containing sampled-sound sources, with GEN01, and temposcal will accept deferred allocation tables.
asig temposcal ktimescal, kamp, kpitch, ktab, klock [,ifftsize, idecim, ithresh]
csound doc: http://csound.com/docs/manual/temposcal.html
strfromurl :: Str -> Str #
Set string variable to value read from an URL
strfromurl sets a string variable at initialization time to the value found from reading an URL.
Sdst strfromurl StringURL
csound doc: http://csound.com/docs/manual/strfromurl.html
Set string variable to value from strset table or string p-field
strget sets a string variable at initialization time to the value stored in strset table at the specified index, or a string p-field from the score. If there is no string defined for the index, the variable is set to an empty string.
Sdst strget indx
csound doc: http://csound.com/docs/manual/strget.html
Allows a string to be linked with a numeric value.
strset iarg, istring
csound doc: http://csound.com/docs/manual/strset.html
sprintf :: Str -> Sig -> Str #
printf-style formatted output to a string variable.
sprintf write printf-style formatted output to a string variable, similarly to the C function sprintf(). sprintf runs at i-time only.
Sdst sprintf Sfmt, xarg1[, xarg2[, ... ]]
csound doc: http://csound.com/docs/manual/sprintf.html
sprintfk :: Str -> Sig -> Str #
printf-style formatted output to a string variable at k-rate.
sprintfk writes printf-style formatted output to a string variable, similarly to the C function sprintf(). sprintfk runs both at initialization and performance time.
Sdst sprintfk Sfmt, xarg1[, xarg2[, ... ]]
csound doc: http://csound.com/docs/manual/sprintfk.html
Concatenate strings
Concatenate two strings and store the result in a variable. strcat runs at i-time only. It is allowed for any of the input arguments to be the same as the output variable.
Sdst strcat Ssrc1, Ssrc2
csound doc: http://csound.com/docs/manual/strcat.html
strcatk :: Str -> Str -> Str #
Concatenate strings (k-rate)
Concatenate two strings and store the result in a variable. strcatk does the concatenation both at initialization and performance time. It is allowed for any of the input arguments to be the same as the output variable.
Sdst strcatk Ssrc1, Ssrc2
csound doc: http://csound.com/docs/manual/strcatk.html
Compare strings
Compare strings and set the result to -1, 0, or 1 if the first string is less than, equal to, or greater than the second, respectively. strcmp compares at i-time only.
ires strcmp S1, S2
csound doc: http://csound.com/docs/manual/strcmp.html
strcmpk :: Str -> Str -> Sig #
Compare strings
Compare strings and set the result to -1, 0, or 1 if the first string is less than, equal to, or greater than the second, respectively. strcmpk does the comparison both at initialization and performance time.
kres strcmpk S1, S2
csound doc: http://csound.com/docs/manual/strcmpk.html
Assign value to a string variable
Assign to a string variable by copying the source which may be a constant or another string variable. strcpy and = copy the string at i-time only.
Sdst strcpy Ssrc
csound doc: http://csound.com/docs/manual/strcpy.html
Assign value to a string variable (k-rate)
Assign to a string variable by copying the source which may be a constant or another string variable. strcpyk does the assignment both at initialization and performance time.
Sdst strcpyk Ssrc
csound doc: http://csound.com/docs/manual/strcpyk.html
Return the position of the first occurence of a string in another string
Return the position of the first occurence of S2 in S1, or -1 if not found. If S2 is empty, 0 is returned. strindex runs at init time only.
ipos strindex S1, S2
csound doc: http://csound.com/docs/manual/strindex.html
strindexk :: Str -> Str -> Sig #
Return the position of the first occurence of a string in another string
Return the position of the first occurence of S2 in S1, or -1 if not found. If S2 is empty, 0 is returned. strindexk runs both at init and performance time.
kpos strindexk S1, S2
csound doc: http://csound.com/docs/manual/strindexk.html
Return the length of a string
Return the length of a string, or zero if it is empty. strlen runs at init time only.
ilen strlen Sstr
csound doc: http://csound.com/docs/manual/strlen.html
Return the length of a string
Return the length of a string, or zero if it is empty. strlenk runs both at init and performance time.
klen strlenk Sstr
csound doc: http://csound.com/docs/manual/strlenk.html
strrindex :: Str -> Str -> D #
Return the position of the last occurence of a string in another string
Return the position of the last occurence of S2 in S1, or -1 if not found. If S2 is empty, the length of S1 is returned. strrindex runs at init time only.
ipos strrindex S1, S2
csound doc: http://csound.com/docs/manual/strrindex.html
strrindexk :: Str -> Str -> Sig #
Return the position of the last occurence of a string in another string
Return the position of the last occurence of S2 in S1, or -1 if not found. If S2 is empty, the length of S1 is returned. strrindexk runs both at init and performance time.
kpos strrindexk S1, S2
csound doc: http://csound.com/docs/manual/strrindexk.html
Extract a substring
Return a substring of the source string. strsub runs at init time only.
Sdst strsub Ssrc[, istart[, iend]]
csound doc: http://csound.com/docs/manual/strsub.html
strsubk :: Str -> Sig -> Sig -> Str #
Extract a substring
Return a substring of the source string. strsubk runs both at init and performance time.
Sdst strsubk Ssrc, kstart, kend
csound doc: http://csound.com/docs/manual/strsubk.html
Return the ASCII code of a character in a string
Return the ASCII code of the character in Sstr at ipos (defaults to zero which means the first character), or zero if ipos is out of range. strchar runs at init time only.
ichr strchar Sstr[, ipos]
csound doc: http://csound.com/docs/manual/strchar.html
Return the ASCII code of a character in a string
Return the ASCII code of the character in Sstr at kpos (defaults to zero which means the first character), or zero if kpos is out of range. strchark runs both at init and performance time.
kchr strchark Sstr[, kpos]
csound doc: http://csound.com/docs/manual/strchark.html
Convert a string to lower case
Convert Ssrc to lower case, and write the result to Sdst. strlower runs at init time only.
Sdst strlower Ssrc
csound doc: http://csound.com/docs/manual/strlower.html
Convert a string to lower case
Convert Ssrc to lower case, and write the result to Sdst. strlowerk runs both at init and performance time.
Sdst strlowerk Ssrc
csound doc: http://csound.com/docs/manual/strlowerk.html
Converts a string to a float (i-rate).
Convert a string to a floating point value. It is also possible to pass an strset index or a string p-field from the score instead of a string argument. If the string cannot be parsed as a floating point or integer number, an init or perf error occurs and the instrument is deactivated.
ir strtod Sstr ir strtod indx
csound doc: http://csound.com/docs/manual/strtod.html
Converts a string to a float (k-rate).
Convert a string to a floating point value at i- or k-rate. It is also possible to pass an strset index or a string p-field from the score instead of a string argument. If the string cannot be parsed as a floating point or integer number, an init or perf error occurs and the instrument is deactivated.
kr strtodk Sstr kr strtodk kndx
csound doc: http://csound.com/docs/manual/strtodk.html
Converts a string to a signed integer (i-rate).
Convert a string to a signed integer value. It is also possible to pass an strset index or a string p-field from the score instead of a string argument. If the string cannot be parsed as an integer number, an init error occurs and the instrument is deactivated.
ir strtol Sstr ir strtol indx
csound doc: http://csound.com/docs/manual/strtol.html
Converts a string to a signed integer (k-rate).
Convert a string to a signed integer value at i- or k-rate. It is also possible to pass an strset index or a string p-field from the score instead of a string argument. If the string cannot be parsed as an integer number, an init or perf error occurs and the instrument is deactivated.
kr strtolk Sstr kr strtolk kndx
csound doc: http://csound.com/docs/manual/strtolk.html
Convert a string to upper case
Convert Ssrc to upper case, and write the result to Sdst. strupper runs at init time only.
Sdst strupper Ssrc
csound doc: http://csound.com/docs/manual/strupper.html
Convert a string to upper case
Convert Ssrc to upper case, and write the result to Sdst. strupperk runs both at init and performance time.
Sdst strupperk Ssrc
csound doc: http://csound.com/docs/manual/strupperk.html
ftgen :: Tab -> D -> D -> D -> D -> SE D #
Generate a score function table from within the orchestra.
gir ftgen ifn, itime, isize, igen, iarga [, iargb ] [...] gir ftgen ifn, itime, isize, igen, iarray
csound doc: http://csound.com/docs/manual/ftgen.html
ftgentmp :: D -> D -> D -> D -> D -> [D] -> SE Tab #
Generate a score function table from within the orchestra, which is deleted at the end of the note.
Generate a score function table from within the orchestra, which is optionally deleted at the end of the note.
ifno ftgentmp ip1, ip2dummy, isize, igen, iarga, iargb, ...
csound doc: http://csound.com/docs/manual/ftgentmp.html
getftargs :: D -> Sig -> Str #
Fill a string variable with the arguments used to create a function table at k-rate.
getftargs writes the arguments used to create a function table to a string variable. getftargs runs both at initialization and performance time.
Sdst getftargs iftno, ktrig
csound doc: http://csound.com/docs/manual/getftargs.html
Loads a sound file into memory for use by loscilx
sndload loads a sound file into memory for use by loscilx.
sndload Sfname[, ifmt[, ichns[, isr[, ibas[, iamp[, istrt \ [, ilpmod[, ilps[, ilpe]]]]]]]]]
csound doc: http://csound.com/docs/manual/sndload.html
vtaba :: Sig -> Tab -> Sig -> SE () #
Read vectors (from tables -or arrays of vectors).
This opcode reads vectors from tables at a-rate.
vtaba andx, ifn, aout1 [, aout2, aout3, .... , aoutN ]
csound doc: http://csound.com/docs/manual/vtaba.html
vtabi :: D -> Tab -> D -> SE () #
Read vectors (from tables -or arrays of vectors).
This opcode reads vectors from tables.
vtabi indx, ifn, iout1 [, iout2, iout3, .... , ioutN ]
csound doc: http://csound.com/docs/manual/vtabi.html
vtabk :: Sig -> Tab -> Sig -> SE () #
Read vectors (from tables -or arrays of vectors).
This opcode reads vectors from tables at k-rate.
vtabk kndx, ifn, kout1 [, kout2, kout3, .... , koutN ]
csound doc: http://csound.com/docs/manual/vtabk.html
vtable1k :: Tab -> Sig -> SE () #
Read a vector (several scalars simultaneously) from a table.
This opcode reads vectors from tables at k-rate.
vtable1k kfn,kout1 [, kout2, kout3, .... , koutN ]
csound doc: http://csound.com/docs/manual/vtable1k.html
vtablea :: Sig -> Tab -> Sig -> D -> Sig -> SE () #
Read vectors (from tables -or arrays of vectors).
This opcode reads vectors from tables at a-rate.
vtablea andx, kfn, kinterp, ixmode, aout1 [, aout2, aout3, .... , aoutN ]
csound doc: http://csound.com/docs/manual/vtablea.html
vtablei :: D -> Tab -> D -> D -> D -> SE () #
Read vectors (from tables -or arrays of vectors).
This opcode reads vectors from tables.
vtablei indx, ifn, interp, ixmode, iout1 [, iout2, iout3, .... , ioutN ]
csound doc: http://csound.com/docs/manual/vtablei.html
vtablek :: Sig -> Tab -> Sig -> D -> Sig -> SE () #
Read vectors (from tables -or arrays of vectors).
This opcode reads vectors from tables at k-rate.
vtablek kndx, kfn, kinterp, ixmode, kout1 [, kout2, kout3, .... , koutN ]
csound doc: http://csound.com/docs/manual/vtablek.html
vtablewa :: Sig -> Tab -> D -> Sig -> SE () #
Write vectors (to tables -or arrays of vectors).
This opcode writes vectors to tables at a-rate.
vtablewa andx, kfn, ixmode, ainarg1 [, ainarg2, ainarg3 , .... , ainargN ]
csound doc: http://csound.com/docs/manual/vtablewa.html
vtablewi :: D -> Tab -> D -> D -> SE () #
Write vectors (to tables -or arrays of vectors).
This opcode writes vectors to tables at init time.
vtablewi indx, ifn, ixmode, inarg1 [, inarg2, inarg3 , .... , inargN ]
csound doc: http://csound.com/docs/manual/vtablewi.html
vtablewk :: Sig -> Tab -> D -> Sig -> SE () #
Write vectors (to tables -or arrays of vectors).
This opcode writes vectors to tables at k-rate.
vtablewk kndx, kfn, ixmode, kinarg1 [, kinarg2, kinarg3 , .... , kinargN ]
csound doc: http://csound.com/docs/manual/vtablewk.html
vtabwa :: Sig -> Tab -> Sig -> SE () #
Write vectors (to tables -or arrays of vectors).
This opcode writes vectors to tables at a-rate.
vtabwa andx, ifn, ainarg1 [, ainarg2, ainarg3 , .... , ainargN ]
csound doc: http://csound.com/docs/manual/vtabwa.html
vtabwi :: D -> Tab -> D -> SE () #
Write vectors (to tables -or arrays of vectors).
This opcode writes vectors to tables at init time.
vtabwi indx, ifn, inarg1 [, inarg2, inarg3 , .... , inargN ]
csound doc: http://csound.com/docs/manual/vtabwi.html
vtabwk :: Sig -> Tab -> Sig -> SE () #
Write vectors (to tables -or arrays of vectors).
This opcode writes vectors to tables at k-rate.
vtabwk kndx, ifn, kinarg1 [, kinarg2, kinarg3 , .... , kinargN ]
csound doc: http://csound.com/docs/manual/vtabwk.html
vadd :: Tab -> Sig -> Sig -> SE () #
Adds a scalar value to a vector in a table.
vadd ifn, kval, kelements [, kdstoffset] [, kverbose]
csound doc: http://csound.com/docs/manual/vadd.html
vadd_i :: Tab -> D -> D -> SE () #
Adds a scalar value to a vector in a table.
vadd_i ifn, ival, ielements [, idstoffset]
csound doc: http://csound.com/docs/manual/vadd_i.html
vexp :: Tab -> Sig -> Sig -> SE () #
Performs power-of operations between a vector and a scalar
vexp ifn, kval, kelements [, kdstoffset] [, kverbose]
csound doc: http://csound.com/docs/manual/vexp.html
vexp_i :: Tab -> D -> D -> SE () #
Performs power-of operations between a vector and a scalar
vexp_i ifn, ival, ielements[, idstoffset]
csound doc: http://csound.com/docs/manual/vexp_i.html
vmult :: Tab -> Sig -> Sig -> SE () #
Multiplies a vector in a table by a scalar value.
vmult ifn, kval, kelements [, kdstoffset] [, kverbose]
csound doc: http://csound.com/docs/manual/vmult.html
vmult_i :: Tab -> D -> D -> SE () #
Multiplies a vector in a table by a scalar value.
vmult_i ifn, ival, ielements [, idstoffset]
csound doc: http://csound.com/docs/manual/vmult_i.html
vpow :: Tab -> Sig -> Sig -> SE () #
Raises each element of a vector to a scalar power.
vpow ifn, kval, kelements [, kdstoffset] [, kverbose]
csound doc: http://csound.com/docs/manual/vpow.html
vpow_i :: Tab -> D -> D -> SE () #
Raises each element of a vector to a scalar power
vpow_i ifn, ival, ielements [, idstoffset]
csound doc: http://csound.com/docs/manual/vpow_i.html
vaddv :: Tab -> Tab -> Sig -> SE () #
Performs addition between two vectorial control signals.
vaddv ifn1, ifn2, kelements [, kdstoffset] [, ksrcoffset] [,kverbose]
csound doc: http://csound.com/docs/manual/vaddv.html
vaddv_i :: Tab -> Tab -> D -> SE () #
Performs addition between two vectorial control signals at init time.
vaddv_i ifn1, ifn2, ielements [, idstoffset] [, isrcoffset]
csound doc: http://csound.com/docs/manual/vaddv_i.html
vcopy :: Tab -> Tab -> Sig -> SE () #
Copies between two vectorial control signals
vcopy ifn1, ifn2, kelements [, kdstoffset] [, ksrcoffset] [, kverbose]
csound doc: http://csound.com/docs/manual/vcopy.html
vcopy_i :: Tab -> Tab -> D -> SE () #
Copies a vector from one table to another.
vcopy_i ifn1, ifn2, ielements [,idstoffset, isrcoffset]
csound doc: http://csound.com/docs/manual/vcopy_i.html
vdivv :: Tab -> Tab -> Sig -> SE () #
Performs division between two vectorial control signals
vdivv ifn1, ifn2, kelements [, kdstoffset] [, ksrcoffset] [,kverbose]
csound doc: http://csound.com/docs/manual/vdivv.html
vdivv_i :: Tab -> Tab -> D -> SE () #
Performs division between two vectorial control signals at init time.
vdivv_i ifn1, ifn2, ielements [, idstoffset] [, isrcoffset]
csound doc: http://csound.com/docs/manual/vdivv_i.html
vexpv :: Tab -> Tab -> Sig -> SE () #
Performs exponential operations between two vectorial control signals
vexpv ifn1, ifn2, kelements [, kdstoffset] [, ksrcoffset] [,kverbose]
csound doc: http://csound.com/docs/manual/vexpv.html
vexpv_i :: Tab -> Tab -> D -> SE () #
Performs exponential operations between two vectorial control signals at init time.
vexpv_i ifn1, ifn2, ielements [, idstoffset] [, isrcoffset]
csound doc: http://csound.com/docs/manual/vexpv_i.html
vmap :: Tab -> Tab -> D -> SE () #
Maps elements from a vector according to indexes contained in another vector.
Maps elements from a vector onto another according to the indexes of a this vector.
vmap ifn1, ifn2, ielements [,idstoffset, isrcoffset]
csound doc: http://csound.com/docs/manual/vmap.html
vmultv :: Tab -> Tab -> Sig -> SE () #
Performs mutiplication between two vectorial control signals
vmultv ifn1, ifn2, kelements [, kdstoffset] [, ksrcoffset] [,kverbose]
csound doc: http://csound.com/docs/manual/vmultv.html
vmultv_i :: Tab -> Tab -> D -> SE () #
Performs mutiplication between two vectorial control signals at init time.
vmultv_i ifn1, ifn2, ielements [, idstoffset] [, isrcoffset]
csound doc: http://csound.com/docs/manual/vmultv_i.html
vpowv :: Tab -> Tab -> Sig -> SE () #
Performs power-of operations between two vectorial control signals
vpowv ifn1, ifn2, kelements [, kdstoffset] [, ksrcoffset] [,kverbose]
csound doc: http://csound.com/docs/manual/vpowv.html
vpowv_i :: Tab -> Tab -> D -> SE () #
Performs power-of operations between two vectorial control signals at init time.
vpowv_i ifn1, ifn2, ielements [, idstoffset] [, isrcoffset]
csound doc: http://csound.com/docs/manual/vpowv_i.html
vsubv :: Tab -> Tab -> Sig -> SE () #
Performs subtraction between two vectorial control signals
vsubv ifn1, ifn2, kelements [, kdstoffset] [, ksrcoffset] [,kverbose]
csound doc: http://csound.com/docs/manual/vsubv.html
vsubv_i :: Tab -> Tab -> D -> SE () #
Performs subtraction between two vectorial control signals at init time.
vsubv_i ifn1, ifn2, ielements [, idstoffset] [, isrcoffset]
csound doc: http://csound.com/docs/manual/vsubv_i.html
vexpseg :: Tab -> D -> Tab -> D -> Tab -> SE () #
Vectorial envelope generator
Generate exponential vectorial segments
vexpseg ifnout, ielements, ifn1, idur1, ifn2 [, idur2, ifn3 [...]]
csound doc: http://csound.com/docs/manual/vexpseg.html
vlinseg :: Tab -> D -> Tab -> D -> Tab -> SE () #
Vectorial envelope generator
Generate linear vectorial segments
vlinseg ifnout, ielements, ifn1, idur1, ifn2 [, idur2, ifn3 [...]]
csound doc: http://csound.com/docs/manual/vlinseg.html
vlimit :: Tab -> Sig -> Sig -> D -> SE () #
Limiting and Wrapping Vectorial Signals
Limits elements of vectorial control signals.
vlimit ifn, kmin, kmax, ielements
csound doc: http://csound.com/docs/manual/vlimit.html
vmirror :: Tab -> Sig -> Sig -> D -> SE () #
Limiting and Wrapping Vectorial Signals
Reflects
elements of vectorial control signals on thresholds.
vmirror ifn, kmin, kmax, ielements
csound doc: http://csound.com/docs/manual/vmirror.html
vwrap :: Tab -> Sig -> Sig -> D -> SE () #
Limiting and Wrapping Vectorial Signals
Wraps elements of vectorial control signals.
vwrap ifn, kmin, kmax, ielements
csound doc: http://csound.com/docs/manual/vwrap.html
vdelayk :: Sig -> Sig -> D -> Sig #
k-rate variable time delay.
Variable delay applied to a k-rate signal
kout vdelayk ksig, kdel, imaxdel [, iskip, imode]
csound doc: http://csound.com/docs/manual/vdelayk.html
vecdelay :: Tab -> Tab -> Tab -> D -> D -> SE () #
Vectorial Control-rate Delay Paths
Generate a sort of vectorial
delay
vecdelay ifn, ifnIn, ifnDel, ielements, imaxdel [, iskip]
csound doc: http://csound.com/docs/manual/vecdelay.html
vport :: Tab -> Sig -> D -> SE () #
Vectorial Control-rate Delay Paths
Generate a sort of vectorial
portamento
vport ifn, khtime, ielements [, ifnInit]
csound doc: http://csound.com/docs/manual/vport.html
vrandh :: Tab -> Sig -> Sig -> D -> SE () #
Generates a vector of random numbers stored into a table, holding the values for a period of time.
Generates a vector of random numbers stored into a table, holding the values for a period of time. Generates a sort of 'vectorial band-limited noise'.
vrandh ifn, krange, kcps, ielements [, idstoffset] [, iseed] \ [, isize] [, ioffset]
csound doc: http://csound.com/docs/manual/vrandh.html
vrandi :: Tab -> Sig -> Sig -> D -> SE () #
Generate a sort of 'vectorial band-limited noise'
vrandi ifn, krange, kcps, ielements [, idstoffset] [, iseed] \ [, isize] [, ioffset]
csound doc: http://csound.com/docs/manual/vrandi.html
cell :: Sig -> Sig -> D -> D -> D -> D -> SE () #
Cellular Automaton
One-Dimensional Cellular Automaton. This opcode is the modified version of vcella by Gabriel Maldonado.
cell ktrig, kreinit, ioutFunc, initStateFunc, iRuleFunc, ielements
csound doc: http://csound.com/docs/manual/cell.html
vcella :: Sig -> Sig -> D -> D -> D -> D -> D -> SE () #
Cellular Automata
Unidimensional Cellular Automata applied to Csound vectors
vcella ktrig, kreinit, ioutFunc, initStateFunc, \ iRuleFunc, ielements, irulelen [, iradius]
csound doc: http://csound.com/docs/manual/vcella.html
Clears one or more variables in the za space.
zacl kfirst, klast
csound doc: http://csound.com/docs/manual/zacl.html
Establishes zak space.
Establishes zak space. Must be called only once.
zakinit isizea, isizek
csound doc: http://csound.com/docs/manual/zakinit.html
Modulates one a-rate signal by a second one.
ares zamod asig, kzamod
csound doc: http://csound.com/docs/manual/zamod.html
Reads from a location in za space at a-rate.
ares zar kndx
csound doc: http://csound.com/docs/manual/zar.html
Reads from a location in za space at a-rate, adds some gain.
ares zarg kndx, kgain
csound doc: http://csound.com/docs/manual/zarg.html
Writes to a za variable at a-rate without mixing.
zaw asig, kndx
csound doc: http://csound.com/docs/manual/zaw.html
Writes to a za variable at a-rate with mixing.
zawm asig, kndx [, imix]
csound doc: http://csound.com/docs/manual/zawm.html
Reads from a location in zk space at i-rate.
ir zir indx
csound doc: http://csound.com/docs/manual/zir.html
Writes to a zk variable at i-rate without mixing.
ziw isig, indx
csound doc: http://csound.com/docs/manual/ziw.html
Writes to a zk variable to an i-rate variable with mixing.
ziwm isig, indx [, imix]
csound doc: http://csound.com/docs/manual/ziwm.html
Clears one or more variables in the zk space.
zkcl kfirst, klast
csound doc: http://csound.com/docs/manual/zkcl.html
Facilitates the modulation of one signal by another.
kres zkmod ksig, kzkmod
csound doc: http://csound.com/docs/manual/zkmod.html
Reads from a location in zk space at k-rate.
kres zkr kndx
csound doc: http://csound.com/docs/manual/zkr.html
Writes to a zk variable at k-rate without mixing.
zkw ksig, kndx
csound doc: http://csound.com/docs/manual/zkw.html