csound-expression-opcodes-0.0.1: opcodes for the library csound-expression

Safe HaskellNone

Csound.Typed.Opcode.RealtimeMIDI

Contents

Synopsis

Input.

aftouch :: SigSource

Get the current after-touch value for this channel.

 kaft  aftouch  [imin] [, imax]

csound doc: http://www.csounds.com/manual/html/aftouch.html

chanctrl :: D -> D -> SigSource

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://www.csounds.com/manual/html/chanctrl.html

ctrl14 :: D -> D -> D -> D -> D -> SigSource

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://www.csounds.com/manual/html/ctrl14.html

ctrl21 :: D -> D -> D -> D -> D -> D -> SigSource

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://www.csounds.com/manual/html/ctrl21.html

ctrl7 :: D -> D -> D -> D -> SigSource

Allows a floating-point 7-bit MIDI signal scaled with a minimum and a maximum range.

 idest  ctrl7  ichan, ictlno, imin, imax [, ifn]
 kdest  ctrl7  ichan, ictlno, kmin, kmax [, ifn]
 adest  ctrl7  ichan, ictlno, kmin, kmax [, ifn] [, icutoff]

csound doc: http://www.csounds.com/manual/html/ctrl7.html

ctrlinit :: [D] -> SE ()Source

Sets the initial values for a set of MIDI controllers.

  ctrlinit  ichnl, ictlno1, ival1 [, ictlno2] [, ival2] [, ictlno3] \
           [, ival3] [,...ival32]

csound doc: http://www.csounds.com/manual/html/ctrlinit.html

initc14 :: D -> D -> D -> D -> SE ()Source

Initializes the controllers used to create a 14-bit MIDI value.

  initc14  ichan, ictlno1, ictlno2, ivalue

csound doc: http://www.csounds.com/manual/html/initc14.html

initc21 :: D -> D -> D -> D -> D -> SE ()Source

Initializes the controllers used to create a 21-bit MIDI value.

  initc21  ichan, ictlno1, ictlno2, ictlno3, ivalue

csound doc: http://www.csounds.com/manual/html/initc21.html

initc7 :: D -> D -> D -> SE ()Source

Initializes the controller used to create a 7-bit MIDI value.

Initializes MIDI controller ictlno with ivalue

  initc7  ichan, ictlno, ivalue

csound doc: http://www.csounds.com/manual/html/initc7.html

massign :: D -> D -> SE ()Source

Assigns a MIDI channel number to a Csound instrument.

  massign  ichnl, insnum[, ireset]
  massign  ichnl, "insname"[, ireset]

csound doc: http://www.csounds.com/manual/html/massign.html

midic14 :: D -> D -> D -> D -> SigSource

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://www.csounds.com/manual/html/midic14.html

midic21 :: D -> D -> D -> D -> D -> SigSource

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://www.csounds.com/manual/html/midic21.html

midic7 :: D -> D -> D -> SigSource

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://www.csounds.com/manual/html/midic7.html

midictrl :: D -> SigSource

Get the current value (0-127) of a specified MIDI controller.

 ival  midictrl  inum [, imin] [, imax]
 kval  midictrl  inum [, imin] [, imax]

csound doc: http://www.csounds.com/manual/html/midictrl.html

notnum :: Msg -> DSource

Get a note number from a MIDI event.

 ival  notnum  

csound doc: http://www.csounds.com/manual/html/notnum.html

pchbend :: Msg -> SigSource

Get the current pitch-bend value for this channel.

 ibend  pchbend  [imin] [, imax]
 kbend  pchbend  [imin] [, imax]

csound doc: http://www.csounds.com/manual/html/pchbend.html

pgmassign :: D -> D -> SE ()Source

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://www.csounds.com/manual/html/pgmassign.html

polyaft :: D -> SigSource

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://www.csounds.com/manual/html/polyaft.html

veloc :: Msg -> DSource

Get the velocity from a MIDI event.

 ival  veloc  [ilow] [, ihigh]

csound doc: http://www.csounds.com/manual/html/veloc.html

Output.

nrpn :: Sig -> Sig -> Sig -> SE ()Source

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://www.csounds.com/manual/html/nrpn.html

outiat :: D -> D -> D -> D -> SE ()Source

Sends MIDI aftertouch messages at i-rate.

  outiat  ichn, ivalue, imin, imax

csound doc: http://www.csounds.com/manual/html/outiat.html

outic :: D -> D -> D -> D -> D -> SE ()Source

Sends MIDI controller output at i-rate.

  outic  ichn, inum, ivalue, imin, imax

csound doc: http://www.csounds.com/manual/html/outic.html

outic14 :: D -> D -> D -> D -> D -> D -> SE ()Source

Sends 14-bit MIDI controller output at i-rate.

  outic14  ichn, imsb, ilsb, ivalue, imin, imax

csound doc: http://www.csounds.com/manual/html/outic14.html

outipat :: D -> D -> D -> D -> D -> SE ()Source

Sends polyphonic MIDI aftertouch messages at i-rate.

  outipat  ichn, inotenum, ivalue, imin, imax

csound doc: http://www.csounds.com/manual/html/outipat.html

outipb :: D -> D -> D -> D -> SE ()Source

Sends MIDI pitch-bend messages at i-rate.

  outipb  ichn, ivalue, imin, imax

csound doc: http://www.csounds.com/manual/html/outipb.html

outipc :: D -> D -> D -> D -> SE ()Source

Sends MIDI program change messages at i-rate

  outipc  ichn, iprog, imin, imax

csound doc: http://www.csounds.com/manual/html/outipc.html

outkat :: Sig -> Sig -> Sig -> Sig -> SE ()Source

Sends MIDI aftertouch messages at k-rate.

  outkat  kchn, kvalue, kmin, kmax

csound doc: http://www.csounds.com/manual/html/outkat.html

outkc :: Sig -> Sig -> Sig -> Sig -> Sig -> SE ()Source

Sends MIDI controller messages at k-rate.

  outkc  kchn, knum, kvalue, kmin, kmax

csound doc: http://www.csounds.com/manual/html/outkc.html

outkc14 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE ()Source

Sends 14-bit MIDI controller output at k-rate.

  outkc14  kchn, kmsb, klsb, kvalue, kmin, kmax

csound doc: http://www.csounds.com/manual/html/outkc14.html

outkpat :: Sig -> Sig -> Sig -> Sig -> Sig -> SE ()Source

Sends polyphonic MIDI aftertouch messages at k-rate.

  outkpat  kchn, knotenum, kvalue, kmin, kmax

csound doc: http://www.csounds.com/manual/html/outkpat.html

outkpb :: Sig -> Sig -> Sig -> Sig -> SE ()Source

Sends MIDI pitch-bend messages at k-rate.

  outkpb  kchn, kvalue, kmin, kmax

csound doc: http://www.csounds.com/manual/html/outkpb.html

outkpc :: Sig -> Sig -> Sig -> Sig -> SE ()Source

Sends MIDI program change messages at k-rate.

  outkpc  kchn, kprog, kmin, kmax

csound doc: http://www.csounds.com/manual/html/outkpc.html

Converters.

ampmidi :: Msg -> D -> DSource

Get the velocity of the current MIDI event.

 iamp  ampmidi  iscal [, ifn]

csound doc: http://www.csounds.com/manual/html/ampmidi.html

ampmidid :: Msg -> D -> D -> SigSource

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://www.csounds.com/manual/html/ampmidid.html

cpsmidi :: Msg -> DSource

Get the note number of the current MIDI event, expressed in cycles-per-second.

 icps  cpsmidi  

csound doc: http://www.csounds.com/manual/html/cpsmidi.html

cpsmidib :: Msg -> SigSource

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://www.csounds.com/manual/html/cpsmidib.html

cpstmid :: Msg -> Tab -> DSource

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://www.csounds.com/manual/html/cpstmid.html

octmidi :: Msg -> DSource

Get the note number, in octave-point-decimal units, of the current MIDI event.

 ioct  octmidi  

csound doc: http://www.csounds.com/manual/html/octmidi.html

octmidib :: Msg -> SigSource

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://www.csounds.com/manual/html/octmidib.html

pchmidi :: Msg -> DSource

Get the note number of the current MIDI event, expressed in pitch-class units.

 ipch  pchmidi  

csound doc: http://www.csounds.com/manual/html/pchmidi.html

pchmidib :: Msg -> SigSource

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://www.csounds.com/manual/html/pchmidib.html

Generic I/O.

midiin :: (Sig, Sig, Sig, Sig)Source

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://www.csounds.com/manual/html/midiin.html

midiout :: Sig -> Sig -> Sig -> Sig -> SE ()Source

Sends a generic MIDI message to the MIDI OUT port.

  midiout  kstatus, kchan, kdata1, kdata2

csound doc: http://www.csounds.com/manual/html/midiout.html

Event Extenders.

release :: SigSource

Indicates whether a note is in its “release” sta

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://www.csounds.com/manual/html/release.html

xtratim :: D -> SE ()Source

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://www.csounds.com/manual/html/xtratim.html

Note Output.

midion :: Sig -> Sig -> Sig -> SE ()Source

Generates MIDI note messages at k-rate.

  midion  kchn, knum, kvel

csound doc: http://www.csounds.com/manual/html/midion.html

midion2 :: Sig -> Sig -> Sig -> Sig -> SE ()Source

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://www.csounds.com/manual/html/midion2.html

moscil :: Sig -> Sig -> Sig -> Sig -> Sig -> SE ()Source

Sends a stream of the MIDI notes.

  moscil  kchn, knum, kvel, kdur, kpause

csound doc: http://www.csounds.com/manual/html/moscil.html

noteoff :: D -> D -> D -> SE ()Source

Send a noteoff message to the MIDI OUT port.

  noteoff  ichn, inum, ivel

csound doc: http://www.csounds.com/manual/html/noteoff.html

noteon :: D -> D -> D -> SE ()Source

Send a noteon message to the MIDI OUT port.

  noteon  ichn, inum, ivel

csound doc: http://www.csounds.com/manual/html/noteon.html

noteondur :: D -> D -> D -> D -> SE ()Source

Sends a noteon and a noteoff MIDI message both with the same channel, number and velocity.

  noteondur  ichn, inum, ivel, idur

csound doc: http://www.csounds.com/manual/html/noteondur.html

noteondur2 :: D -> D -> D -> D -> SE ()Source

Sends a noteon and a noteoff MIDI message both with the same channel, number and velocity.

  noteondur2  ichn, inum, ivel, idur

csound doc: http://www.csounds.com/manual/html/noteondur2.html

MIDI/Score Interoperability.

midichannelaftertouch :: Sig -> SE ()Source

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://www.csounds.com/manual/html/midichannelaftertouch.html

midichn :: DSource

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://www.csounds.com/manual/html/midichn.html

midicontrolchange :: Sig -> Sig -> SE ()Source

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://www.csounds.com/manual/html/midicontrolchange.html

mididefault :: Sig -> Sig -> SE ()Source

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://www.csounds.com/manual/html/mididefault.html

midinoteoff :: Sig -> Sig -> SE ()Source

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://www.csounds.com/manual/html/midinoteoff.html

midinoteoncps :: Sig -> Sig -> SE ()Source

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://www.csounds.com/manual/html/midinoteoncps.html

midinoteonkey :: Sig -> Sig -> SE ()Source

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://www.csounds.com/manual/html/midinoteonkey.html

midinoteonoct :: Sig -> Sig -> SE ()Source

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://www.csounds.com/manual/html/midinoteonoct.html

midinoteonpch :: Sig -> Sig -> SE ()Source

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://www.csounds.com/manual/html/midinoteonpch.html

midipitchbend :: Sig -> SE ()Source

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://www.csounds.com/manual/html/midipitchbend.html

midipolyaftertouch :: Sig -> Sig -> SE ()Source

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://www.csounds.com/manual/html/midipolyaftertouch.html

midiprogramchange :: Sig -> SE ()Source

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://www.csounds.com/manual/html/midiprogramchange.html

System Realtime.

mclock :: D -> SE ()Source

Sends a MIDI CLOCK message.

  mclock  ifreq

csound doc: http://www.csounds.com/manual/html/mclock.html

mrtmsg :: D -> SE ()Source

Send system real-time messages to the MIDI OUT port.

  mrtmsg  imsgtype

csound doc: http://www.csounds.com/manual/html/mrtmsg.html