csound-expression-opcodes-0.0.5.1: opcodes for the library csound-expression
Safe HaskellNone
LanguageHaskell2010

Csound.Typed.Opcode.InstrumentControl

Synopsis

Clock Control.

clockoff :: D -> SE () Source #

Stops one of a number of internal clocks.

 clockoff  inum

csound doc: http://csound.com/docs/manual/clockoff.html

clockon :: D -> SE () Source #

Starts one of a number of internal clocks.

 clockon  inum

csound doc: http://csound.com/docs/manual/clockon.html

Compilation.

compilecsd :: Str -> D Source #

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 Source #

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 Source #

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

evalstr :: Str -> Sig Source #

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

Duration Control.

ihold :: SE () Source #

Creates a held note.

Causes a finite-duration note to become a “held” note

 ihold 

csound doc: http://csound.com/docs/manual/ihold.html

turnoff :: SE () Source #

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

turnon :: D -> SE () Source #

Activate an instrument for an indefinite time.

 turnon  insnum [, itime]

csound doc: http://csound.com/docs/manual/turnon.html

Invocation.

event :: Str -> Sig -> Sig -> Sig -> [Sig] -> SE () Source #

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 () Source #

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

mute :: D -> SE () Source #

Mutes/unmutes new instances of a given instrument.

 mute  insnum [, iswitch]
 mute  "insname" [, iswitch]

csound doc: http://csound.com/docs/manual/mute.html

nstance :: D -> D -> D -> D Source #

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

readscore :: Str -> SE () Source #

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

remove :: D -> SE () Source #

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 () Source #

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 () Source #

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 () Source #

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 () Source #

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 () Source #

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 () Source #

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

Realtime Performance Control.

active :: D -> Sig Source #

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 Source #

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

cpuprc :: D -> D -> SE () Source #

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

exitnow :: SE () Source #

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 () Source #

Start/stop jack_transport and can optionally relocate the playback head.

 jacktransport  icommand [, ilocation]

csound doc: http://csound.com/docs/manual/jacktransport.html

maxalloc :: D -> D -> SE () Source #

Limits the number of allocations of an instrument.

 maxalloc  insnum, icount
 maxalloc  Sinsname, icount

csound doc: http://csound.com/docs/manual/maxalloc.html

prealloc :: D -> D -> SE () Source #

Creates space for instruments but does not run them.

 prealloc  insnum, icount
 prealloc  "insname", icount

csound doc: http://csound.com/docs/manual/prealloc.html

Sensing and Control.

button :: Sig -> Sig Source #

Sense on-screen controls.

Sense on-screen controls. Requires Winsound or TCL/TK.

kres  button  knum

csound doc: http://csound.com/docs/manual/button.html

changed :: [Sig] -> Sig Source #

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

changed2 :: Sig -> Sig Source #

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

checkbox :: Sig -> Sig Source #

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

control :: Sig -> Sig Source #

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

follow :: Sig -> D -> Sig Source #

Envelope follower unit generator.

ares  follow  asig, idt

csound doc: http://csound.com/docs/manual/follow.html

follow2 :: Sig -> Sig -> Sig -> Sig Source #

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

getcfg :: D -> Str Source #

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 Source #

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

metro :: Sig -> Sig Source #

Trigger Metronome

Generate a metronomic signal to be used in any circumstance an isochronous trigger is needed.

ktrig   metro   kfreq [, initphase]

csound doc: http://csound.com/docs/manual/metro.html

midifilestatus :: Sig Source #

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

miditempo :: Sig Source #

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 () Source #

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

p5gdata :: Sig -> Sig Source #

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

pcount :: D Source #

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

peak :: Sig -> Sig Source #

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

pindex :: D -> D Source #

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) Source #

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) Source #

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) Source #

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) Source #

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 Source #

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 () Source #

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

rms :: Sig -> Sig Source #

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

sensekey :: Tuple a => a Source #

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 Source #

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 Source #

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 () Source #

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 () Source #

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 () Source #

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 Source #

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

tempo :: Sig -> D -> SE () Source #

Apply tempo control to an uninterpreted score.

 tempo  ktempo, istartempo

csound doc: http://csound.com/docs/manual/tempo.html

tempoval :: Sig Source #

Reads the current value of the tempo.

kres  tempoval 

csound doc: http://csound.com/docs/manual/tempoval.html

timedseq :: Sig -> Tab -> [Sig] -> Sig Source #

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 Source #

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 () Source #

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

vactrol :: Sig -> Sig Source #

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 Source #

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

wiidata :: Sig -> Sig Source #

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 () Source #

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 Source #

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 () Source #

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) Source #

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

Stacks.

pop :: Tuple a => a Source #

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

pop_f :: Spec Source #

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

push :: [Sig] -> SE () Source #

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

push_f :: Spec -> SE () Source #

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

stack :: D -> SE () Source #

Initializes the stack. Deprecated.

Initializes and sets the size of the global stack.

 stack   iStackSize

csound doc: http://csound.com/docs/manual/stack.html

Subinstrument Control.

subinstr :: Tuple a => D -> [D] -> a Source #

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 () Source #

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

Time Reading.

date :: Tuple a => a Source #

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

dates :: Str Source #

Returns as a string the date and time specified.

Sir  dates  [ itime]

csound doc: http://csound.com/docs/manual/dates.html

readclock :: D -> D Source #

Reads the value of an internal clock.

ir  readclock  inum

csound doc: http://csound.com/docs/manual/readclock.html

rtclock :: Sig Source #

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

timeinstk :: Sig Source #

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

timeinsts :: Sig Source #

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

timek :: SE Sig Source #

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

times :: SE Sig Source #

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