csound-expression-0.3.4: Csound combinator library

Safe HaskellNone

CsoundExpr.Opcodes.Control.Sensing

Description

Sensing and Control

Synopsis

Documentation

button :: K k0 => k0 -> KrateSource

  • opcode : button
  • syntax :
   kres button knum
  • description :

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

checkbox :: K k0 => k0 -> KrateSource

  • opcode : checkbox
  • syntax :
   kres checkbox knum
  • description :

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

control :: K k0 => k0 -> KrateSource

  • opcode : control
  • syntax :
   kres control knum
  • description :

Configurable slider controls for realtime user input. Requires Winsound or TCL/TK. control reads a slider's value.

setctrl :: Irate -> Irate -> Irate -> SignalOutSource

  • opcode : setctrl
  • syntax :
   setctrl inum, ival, itype
  • description :

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.

sensekey :: MultiOutSource

  • opcode : sensekey
  • syntax :
   kres[, kkeydown] sensekey
  • description :

Returns the ASCII code of a key that has been pressed, or -1 if no key has been pressed.

xyin :: [Irate] -> Irate -> Irate -> Irate -> Irate -> Irate -> MultiOutSource

  • opcode : xyin
  • syntax :
   kx, ky xyin iprd, ixmin, ixmax, iymin, iymax [, ixinit] [, iyinit]
  • description :

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.

follow :: Arate -> Irate -> ArateSource

  • opcode : follow
  • syntax :
   ares follow asig, idt
  • description :

Envelope follower unit generator.

follow2 :: (K k0, K k1) => Arate -> k0 -> k1 -> ArateSource

  • opcode : follow2
  • syntax :
   ares follow2 asig, katt, krel
  • description :

A controllable envelope extractor using the algorithm attributed to Jean-Marc Jot.

peakA :: Arate -> KrateSource

  • opcode : peak
  • syntax :
   kres peak asig
   kres peak ksig
  • description :

These opcodes maintain the output k-rate variable as the peak absolute level so far received.

peakK :: K k0 => k0 -> KrateSource

  • opcode : peak
  • syntax :
   kres peak asig
   kres peak ksig
  • description :

These opcodes maintain the output k-rate variable as the peak absolute level so far received.

rms :: [Irate] -> Arate -> KrateSource

  • opcode : rms
  • syntax :
   kres rms asig [, ihp] [, iskip]
  • description :

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.

ptrack :: [Irate] -> Arate -> Irate -> MultiOutSource

  • opcode : ptrack
  • syntax :
   kcps, kamp ptrack asig, ihopsize[,ipeaks]
  • description :

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.

pitch :: [Irate] -> Arate -> Irate -> Irate -> Irate -> Irate -> MultiOutSource

  • opcode : pitch
  • syntax :
   koct, kamp pitch asig, iupdte, ilo, ihi, idbthresh [, ifrqs] [, iconf] 
       [, istrt] [, iocts] [, iq] [, inptls] [, irolloff] [, iskip]
  • description :

Using the same techniques as spectrum and specptrk, pitch tracks the pitch of the signal in octave point decimal form, and amplitude in dB.

pitchamdf :: [Irate] -> Arate -> Irate -> Irate -> MultiOutSource

  • opcode : pitchamdf
  • syntax :
   kcps, krms pitchamdf asig, imincps, imaxcps [, icps] [, imedi] 
       [, idowns] [, iexcps] [, irmsmedi]
  • description :

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.

tempest :: K k0 => [Irate] -> k0 -> Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> KrateSource

  • opcode : tempest
  • syntax :
   ktemp tempest kin, iprd, imindur, imemdur, ihp, ithresh, ihtim, ixfdbak, 
       istartempo, ifn [, idisprd] [, itweek]
  • description :

Estimate the tempo of beat patterns in a control signal.

tempo :: K k0 => k0 -> Irate -> SignalOutSource

  • opcode : tempo
  • syntax :
   tempo ktempo, istartempo
  • description :

Apply tempo control to an uninterpreted score.

miditempo :: KrateSource

  • opcode : miditempo
  • syntax :
   ksig miditempo
  • description :

Returns the current tempo at k-rate, of either the MIDI file (if available) or the score

tempoval :: KrateSource

  • opcode : tempoval
  • syntax :
   kres tempoval
  • description :

Reads the current value of the tempo.

seqtime :: (K k0, K k1, K k2, K k3, K k4) => k0 -> k1 -> k2 -> k3 -> k4 -> KrateSource

  • opcode : seqtime
  • syntax :
   ktrig_out seqtime ktime_unit, kstart, kloop, kinitndx, kfn_times
  • description :

Generates a trigger signal according to the values stored in a table.

seqtime2 :: (K k0, K k1, K k2, K k3, K k4, K k5) => k0 -> k1 -> k2 -> k3 -> k4 -> k5 -> KrateSource

  • opcode : seqtime2
  • syntax :
   ktrig_out seqtime2 ktrig_in, ktime_unit, kstart, kloop, kinitndx, kfn_times
  • description :

Generates a trigger signal according to the values stored in a table.

trigger :: (K k0, K k1, K k2) => k0 -> k1 -> k2 -> KrateSource

  • opcode : trigger
  • syntax :
   kout trigger ksig, kthreshold, kmode
  • description :

Informs when a krate signal crosses a threshold.

timedseq :: (K k0, K k1) => k0 -> Irate -> [k1] -> KrateSource

  • opcode : timedseq
  • syntax :
   ktrig timedseq ktimpnt, ifn, kp1 [,kp2, kp3,...,kpN]
  • description :

An event-sequencer in which time can be controlled by a time-pointer. Sequence data are stored into a table.

changed :: K k0 => [k0] -> KrateSource

  • opcode : changed
  • syntax :
   ktrig changed kvar1 [, kvar2,..., kvarN]
  • description :

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.

getcfg :: Irate -> StringSource

  • opcode : getcfg
  • syntax :
   Svalue getcfg iopt
  • description :

Return various configuration settings in Svalue as a string at init time.

rewindscore :: SignalOutSource

  • opcode : rewindscore
  • syntax :
   rewindscore
  • description :

Rewinds the playback position of the current score performance..