module Csound.Typed.Opcode.RealtimeMIDI ( -- * Input. aftouch, chanctrl, ctrl14, ctrl21, ctrl7, ctrlinit, initc14, initc21, initc7, massign, midic14, midic21, midic7, midictrl, notnum, pchbend, pgmassign, polyaft, veloc, -- * Output. nrpn, outiat, outic, outic14, outipat, outipb, outipc, outkat, outkc, outkc14, outkpat, outkpb, outkpc, -- * Converters. ampmidi, ampmidid, cpsmidi, cpsmidib, cpstmid, octmidi, octmidib, pchmidi, pchmidib, -- * Generic I/O. midiin, midiout, -- * Event Extenders. release, xtratim, -- * Note Output. midion, midion2, moscil, noteoff, noteon, noteondur, noteondur2, -- * MIDI/Score Interoperability. midichannelaftertouch, midichn, midicontrolchange, mididefault, midinoteoff, midinoteoncps, midinoteonkey, midinoteonoct, midinoteonpch, midipitchbend, midipolyaftertouch, midiprogramchange, -- * System Realtime. mclock, mrtmsg) where import Control.Applicative import Control.Monad.Trans.Class import Csound.Dynamic import Csound.Typed -- Input. -- | -- Get the current after-touch value for this channel. -- -- > kaft aftouch [imin] [, imax] -- -- csound doc: aftouch :: Sig aftouch = Sig $ return $ f where f = opcs "aftouch" [(Kr,[Ir,Ir])] [] -- | -- 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: chanctrl :: D -> D -> Sig chanctrl b1 b2 = Sig $ f <$> unD b1 <*> unD b2 where f a1 a2 = opcs "chanctrl" [(Ir,[Ir,Ir,Ir,Ir]),(Kr,[Ir,Ir,Ir,Ir])] [a1,a2] -- | -- 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: ctrl14 :: D -> D -> D -> D -> D -> Sig ctrl14 b1 b2 b3 b4 b5 = Sig $ f <$> unD b1 <*> unD b2 <*> unD b3 <*> unD b4 <*> unD b5 where f a1 a2 a3 a4 a5 = opcs "ctrl14" [(Ir,[Ir,Ir,Ir,Ir,Ir,Ir]),(Kr,[Ir,Ir,Ir,Kr,Kr,Ir])] [a1 ,a2 ,a3 ,a4 ,a5] -- | -- 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: ctrl21 :: D -> D -> D -> D -> D -> D -> Sig ctrl21 b1 b2 b3 b4 b5 b6 = Sig $ f <$> unD b1 <*> unD b2 <*> unD b3 <*> unD b4 <*> unD b5 <*> unD b6 where f a1 a2 a3 a4 a5 a6 = opcs "ctrl21" [(Ir,[Ir,Ir,Ir,Ir,Ir,Ir,Ir]) ,(Kr,[Ir,Ir,Ir,Ir,Kr,Kr,Ir])] [a1,a2,a3,a4,a5,a6] -- | -- 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: ctrl7 :: D -> D -> D -> D -> Sig ctrl7 b1 b2 b3 b4 = Sig $ f <$> unD b1 <*> unD b2 <*> unD b3 <*> unD b4 where f a1 a2 a3 a4 = opcs "ctrl7" [(Ir,[Ir,Ir,Ir,Ir,Ir]) ,(Kr,[Ir,Ir,Kr,Kr,Ir]) ,(Ar,[Ir,Ir,Kr,Kr,Ir,Ir])] [a1,a2,a3,a4] -- | -- Sets the initial values for a set of MIDI controllers. -- -- > ctrlinit ichnl, ictlno1, ival1 [, ictlno2] [, ival2] [, ictlno3] \ -- > [, ival3] [,...ival32] -- -- csound doc: ctrlinit :: [D] -> SE () ctrlinit b1 = SE $ (depT_ =<<) $ lift $ f <$> mapM unD b1 where f a1 = opcs "ctrlinit" [(Xr,(repeat Ir))] a1 -- | -- Initializes the controllers used to create a 14-bit MIDI value. -- -- > initc14 ichan, ictlno1, ictlno2, ivalue -- -- csound doc: initc14 :: D -> D -> D -> D -> SE () initc14 b1 b2 b3 b4 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 <*> unD b3 <*> unD b4 where f a1 a2 a3 a4 = opcs "initc14" [(Xr,[Ir,Ir,Ir,Ir])] [a1,a2,a3,a4] -- | -- Initializes the controllers used to create a 21-bit MIDI value. -- -- > initc21 ichan, ictlno1, ictlno2, ictlno3, ivalue -- -- csound doc: initc21 :: D -> D -> D -> D -> D -> SE () initc21 b1 b2 b3 b4 b5 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 <*> unD b3 <*> unD b4 <*> unD b5 where f a1 a2 a3 a4 a5 = opcs "initc21" [(Xr,[Ir,Ir,Ir,Ir,Ir])] [a1,a2,a3,a4,a5] -- | -- Initializes the controller used to create a 7-bit MIDI value. -- -- Initializes MIDI controller ictlno with ivalue -- -- > initc7 ichan, ictlno, ivalue -- -- csound doc: initc7 :: D -> D -> D -> SE () initc7 b1 b2 b3 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 <*> unD b3 where f a1 a2 a3 = opcs "initc7" [(Xr,[Ir,Ir,Ir])] [a1,a2,a3] -- | -- Assigns a MIDI channel number to a Csound instrument. -- -- > massign ichnl, insnum[, ireset] -- > massign ichnl, "insname"[, ireset] -- -- csound doc: massign :: D -> D -> SE () massign b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 where f a1 a2 = opcs "massign" [(Xr,[Ir,Ir,Ir])] [a1,a2] -- | -- 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: midic14 :: D -> D -> D -> D -> Sig midic14 b1 b2 b3 b4 = Sig $ f <$> unD b1 <*> unD b2 <*> unD b3 <*> unD b4 where f a1 a2 a3 a4 = opcs "midic14" [(Ir,[Ir,Ir,Ir,Ir,Ir]),(Kr,[Ir,Ir,Kr,Kr,Ir])] [a1,a2,a3,a4] -- | -- 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: midic21 :: D -> D -> D -> D -> D -> Sig midic21 b1 b2 b3 b4 b5 = Sig $ f <$> unD b1 <*> unD b2 <*> unD b3 <*> unD b4 <*> unD b5 where f a1 a2 a3 a4 a5 = opcs "midic21" [(Ir,[Ir,Ir,Ir,Ir,Ir,Ir]),(Kr,[Ir,Ir,Ir,Kr,Kr,Ir])] [a1 ,a2 ,a3 ,a4 ,a5] -- | -- 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: midic7 :: D -> D -> D -> Sig midic7 b1 b2 b3 = Sig $ f <$> unD b1 <*> unD b2 <*> unD b3 where f a1 a2 a3 = opcs "midic7" [(Ir,[Ir,Ir,Ir,Ir]),(Kr,[Ir,Kr,Kr,Ir])] [a1,a2,a3] -- | -- Get the current value (0-127) of a specified MIDI controller. -- -- > ival midictrl inum [, imin] [, imax] -- > kval midictrl inum [, imin] [, imax] -- -- csound doc: midictrl :: D -> Sig midictrl b1 = Sig $ f <$> unD b1 where f a1 = opcs "midictrl" [(Ir,[Ir,Ir,Ir]),(Kr,[Ir,Ir,Ir])] [a1] -- | -- Get a note number from a MIDI event. -- -- > ival notnum   -- -- csound doc: notnum :: Msg -> D notnum _ = D $ return $ f where f = opcs "notnum" [(Ir,[])] [] -- | -- Get the current pitch-bend value for this channel. -- -- > ibend pchbend [imin] [, imax] -- > kbend pchbend [imin] [, imax] -- -- csound doc: pchbend :: Msg -> Sig pchbend _ = Sig $ return $ f where f = opcs "pchbend" [(Ir,[Ir,Ir]),(Kr,[Ir,Ir])] [] -- | -- 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: pgmassign :: D -> D -> SE () pgmassign b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 where f a1 a2 = opcs "pgmassign" [(Xr,[Ir,Ir,Ir])] [a1,a2] -- | -- 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: polyaft :: D -> Sig polyaft b1 = Sig $ f <$> unD b1 where f a1 = opcs "polyaft" [(Ir,[Ir,Ir,Ir]),(Kr,[Ir,Ir,Ir])] [a1] -- | -- Get the velocity from a MIDI event. -- -- > ival veloc [ilow] [, ihigh] -- -- csound doc: veloc :: D veloc = D $ return $ f where f = opcs "veloc" [(Ir,[Ir,Ir])] [] -- Output. -- | -- 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: nrpn :: Sig -> Sig -> Sig -> SE () nrpn b1 b2 b3 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 where f a1 a2 a3 = opcs "nrpn" [(Xr,[Kr,Kr,Kr])] [a1,a2,a3] -- | -- Sends MIDI aftertouch messages at i-rate. -- -- > outiat ichn, ivalue, imin, imax -- -- csound doc: outiat :: D -> D -> D -> D -> SE () outiat b1 b2 b3 b4 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 <*> unD b3 <*> unD b4 where f a1 a2 a3 a4 = opcs "outiat" [(Xr,[Ir,Ir,Ir,Ir])] [a1,a2,a3,a4] -- | -- Sends MIDI controller output at i-rate. -- -- > outic ichn, inum, ivalue, imin, imax -- -- csound doc: outic :: D -> D -> D -> D -> D -> SE () outic b1 b2 b3 b4 b5 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 <*> unD b3 <*> unD b4 <*> unD b5 where f a1 a2 a3 a4 a5 = opcs "outic" [(Xr,[Ir,Ir,Ir,Ir,Ir])] [a1,a2,a3,a4,a5] -- | -- Sends 14-bit MIDI controller output at i-rate. -- -- > outic14 ichn, imsb, ilsb, ivalue, imin, imax -- -- csound doc: outic14 :: D -> D -> D -> D -> D -> D -> SE () outic14 b1 b2 b3 b4 b5 b6 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 <*> unD b3 <*> unD b4 <*> unD b5 <*> unD b6 where f a1 a2 a3 a4 a5 a6 = opcs "outic14" [(Xr,[Ir,Ir,Ir,Ir,Ir,Ir])] [a1,a2,a3,a4,a5,a6] -- | -- Sends polyphonic MIDI aftertouch messages at i-rate. -- -- > outipat ichn, inotenum, ivalue, imin, imax -- -- csound doc: outipat :: D -> D -> D -> D -> D -> SE () outipat b1 b2 b3 b4 b5 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 <*> unD b3 <*> unD b4 <*> unD b5 where f a1 a2 a3 a4 a5 = opcs "outipat" [(Xr,[Ir,Ir,Ir,Ir,Ir])] [a1,a2,a3,a4,a5] -- | -- Sends MIDI pitch-bend messages at i-rate. -- -- > outipb ichn, ivalue, imin, imax -- -- csound doc: outipb :: D -> D -> D -> D -> SE () outipb b1 b2 b3 b4 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 <*> unD b3 <*> unD b4 where f a1 a2 a3 a4 = opcs "outipb" [(Xr,[Ir,Ir,Ir,Ir])] [a1,a2,a3,a4] -- | -- Sends MIDI program change messages at i-rate -- -- > outipc ichn, iprog, imin, imax -- -- csound doc: outipc :: D -> D -> D -> D -> SE () outipc b1 b2 b3 b4 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 <*> unD b3 <*> unD b4 where f a1 a2 a3 a4 = opcs "outipc" [(Xr,[Ir,Ir,Ir,Ir])] [a1,a2,a3,a4] -- | -- Sends MIDI aftertouch messages at k-rate. -- -- > outkat kchn, kvalue, kmin, kmax -- -- csound doc: outkat :: Sig -> Sig -> Sig -> Sig -> SE () outkat b1 b2 b3 b4 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 where f a1 a2 a3 a4 = opcs "outkat" [(Xr,[Kr,Kr,Kr,Kr])] [a1,a2,a3,a4] -- | -- Sends MIDI controller messages at k-rate. -- -- > outkc kchn, knum, kvalue, kmin, kmax -- -- csound doc: outkc :: Sig -> Sig -> Sig -> Sig -> Sig -> SE () outkc b1 b2 b3 b4 b5 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 <*> unSig b5 where f a1 a2 a3 a4 a5 = opcs "outkc" [(Xr,[Kr,Kr,Kr,Kr,Kr])] [a1,a2,a3,a4,a5] -- | -- Sends 14-bit MIDI controller output at k-rate. -- -- > outkc14 kchn, kmsb, klsb, kvalue, kmin, kmax -- -- csound doc: outkc14 :: Sig -> Sig -> Sig -> Sig -> Sig -> Sig -> SE () outkc14 b1 b2 b3 b4 b5 b6 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 <*> unSig b5 <*> unSig b6 where f a1 a2 a3 a4 a5 a6 = opcs "outkc14" [(Xr,[Kr,Kr,Kr,Kr,Kr,Kr])] [a1,a2,a3,a4,a5,a6] -- | -- Sends polyphonic MIDI aftertouch messages at k-rate. -- -- > outkpat kchn, knotenum, kvalue, kmin, kmax -- -- csound doc: outkpat :: Sig -> Sig -> Sig -> Sig -> Sig -> SE () outkpat b1 b2 b3 b4 b5 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 <*> unSig b5 where f a1 a2 a3 a4 a5 = opcs "outkpat" [(Xr,[Kr,Kr,Kr,Kr,Kr])] [a1,a2,a3,a4,a5] -- | -- Sends MIDI pitch-bend messages at k-rate. -- -- > outkpb kchn, kvalue, kmin, kmax -- -- csound doc: outkpb :: Sig -> Sig -> Sig -> Sig -> SE () outkpb b1 b2 b3 b4 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 where f a1 a2 a3 a4 = opcs "outkpb" [(Xr,[Kr,Kr,Kr,Kr])] [a1,a2,a3,a4] -- | -- Sends MIDI program change messages at k-rate. -- -- > outkpc kchn, kprog, kmin, kmax -- -- csound doc: outkpc :: Sig -> Sig -> Sig -> Sig -> SE () outkpc b1 b2 b3 b4 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 where f a1 a2 a3 a4 = opcs "outkpc" [(Xr,[Kr,Kr,Kr,Kr])] [a1,a2,a3,a4] -- Converters. -- | -- Get the velocity of the current MIDI event. -- -- > iamp ampmidi iscal [, ifn] -- -- csound doc: ampmidi :: Msg -> D -> D ampmidi _ b1 = D $ f <$> unD b1 where f a1 = opcs "ampmidi" [(Ir,[Ir,Ir])] [a1] -- | -- Musically map MIDI velocity to peak amplitude within a specified dynamic range in decibels. -- -- > iamplitude ampmidid ivelocity, idecibels -- > kamplitude ampmidid kvelocity, idecibels -- -- csound doc: ampmidid :: Msg -> D -> D -> Sig ampmidid _ b1 b2 = Sig $ f <$> unD b1 <*> unD b2 where f a1 a2 = opcs "ampmidid" [(Ir,[Ir,Ir]),(Kr,[Kr,Ir])] [a1,a2] -- | -- Get the note number of the current MIDI event, expressed in cycles-per-second. -- -- > icps cpsmidi   -- -- csound doc: cpsmidi :: Msg -> D cpsmidi _ = D $ return $ f where f = opcs "cpsmidi" [(Ir,[])] [] -- | -- 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: cpsmidib :: Msg -> Sig cpsmidib _ = Sig $ return $ f where f = opcs "cpsmidib" [(Ir,[Ir]),(Kr,[Ir])] [] -- | -- 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: cpstmid :: Msg -> Tab -> D cpstmid _ b1 = D $ f <$> unTab b1 where f a1 = opcs "cpstmid" [(Ir,[Ir])] [a1] -- | -- Get the note number, in octave-point-decimal units, of the current MIDI event. -- -- > ioct octmidi   -- -- csound doc: octmidi :: Msg -> D octmidi _ = D $ return $ f where f = opcs "octmidi" [(Ir,[])] [] -- | -- 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: octmidib :: Msg -> Sig octmidib _ = Sig $ return $ f where f = opcs "octmidib" [(Ir,[Ir]),(Kr,[Ir])] [] -- | -- Get the note number of the current MIDI event, expressed in pitch-class units. -- -- > ipch pchmidi   -- -- csound doc: pchmidi :: Msg -> D pchmidi _ = D $ return $ f where f = opcs "pchmidi" [(Ir,[])] [] -- | -- 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: pchmidib :: Msg -> Sig pchmidib _ = Sig $ return $ f where f = opcs "pchmidib" [(Ir,[Ir]),(Kr,[Ir])] [] -- Generic I/O. -- | -- 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: midiin :: Tuple a => a midiin = pureTuple $ return $ f where f = mopcs "midiin" ([Kr,Kr,Kr,Kr],[]) [] -- | -- Sends a generic MIDI message to the MIDI OUT port. -- -- > midiout kstatus, kchan, kdata1, kdata2 -- -- csound doc: midiout :: Sig -> Sig -> Sig -> Sig -> SE () midiout b1 b2 b3 b4 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 where f a1 a2 a3 a4 = opcs "midiout" [(Xr,[Kr,Kr,Kr,Kr])] [a1,a2,a3,a4] -- Event Extenders. -- | -- 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: release :: Sig release = Sig $ return $ f where f = opcs "release" [(Kr,[])] [] -- | -- 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: xtratim :: D -> SE () xtratim b1 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 where f a1 = opcs "xtratim" [(Xr,[Ir])] [a1] -- Note Output. -- | -- Generates MIDI note messages at k-rate. -- -- > midion kchn, knum, kvel -- -- csound doc: midion :: Sig -> Sig -> Sig -> SE () midion b1 b2 b3 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 where f a1 a2 a3 = opcs "midion" [(Xr,[Kr,Kr,Kr])] [a1,a2,a3] -- | -- 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: midion2 :: Sig -> Sig -> Sig -> Sig -> SE () midion2 b1 b2 b3 b4 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 where f a1 a2 a3 a4 = opcs "midion2" [(Xr,[Kr,Kr,Kr,Kr])] [a1,a2,a3,a4] -- | -- Sends a stream of the MIDI notes. -- -- > moscil kchn, knum, kvel, kdur, kpause -- -- csound doc: moscil :: Sig -> Sig -> Sig -> Sig -> Sig -> SE () moscil b1 b2 b3 b4 b5 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 <*> unSig b3 <*> unSig b4 <*> unSig b5 where f a1 a2 a3 a4 a5 = opcs "moscil" [(Xr,[Kr,Kr,Kr,Kr,Kr])] [a1,a2,a3,a4,a5] -- | -- Send a noteoff message to the MIDI OUT port. -- -- > noteoff ichn, inum, ivel -- -- csound doc: noteoff :: D -> D -> D -> SE () noteoff b1 b2 b3 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 <*> unD b3 where f a1 a2 a3 = opcs "noteoff" [(Xr,[Ir,Ir,Ir])] [a1,a2,a3] -- | -- Send a noteon message to the MIDI OUT port. -- -- > noteon ichn, inum, ivel -- -- csound doc: noteon :: D -> D -> D -> SE () noteon b1 b2 b3 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 <*> unD b3 where f a1 a2 a3 = opcs "noteon" [(Xr,[Ir,Ir,Ir])] [a1,a2,a3] -- | -- Sends a noteon and a noteoff MIDI message both with the same channel, number and velocity. -- -- > noteondur ichn, inum, ivel, idur -- -- csound doc: noteondur :: D -> D -> D -> D -> SE () noteondur b1 b2 b3 b4 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 <*> unD b3 <*> unD b4 where f a1 a2 a3 a4 = opcs "noteondur" [(Xr,[Ir,Ir,Ir,Ir])] [a1,a2,a3,a4] -- | -- Sends a noteon and a noteoff MIDI message both with the same channel, number and velocity. -- -- > noteondur2 ichn, inum, ivel, idur -- -- csound doc: noteondur2 :: D -> D -> D -> D -> SE () noteondur2 b1 b2 b3 b4 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 <*> unD b2 <*> unD b3 <*> unD b4 where f a1 a2 a3 a4 = opcs "noteondur2" [(Xr,[Ir,Ir,Ir,Ir])] [a1,a2,a3,a4] -- MIDI/Score Interoperability. -- | -- 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: midichannelaftertouch :: Sig -> SE () midichannelaftertouch b1 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 where f a1 = opcs "midichannelaftertouch" [(Xr,[Xr,Ir,Ir])] [a1] -- | -- 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: midichn :: D midichn = D $ return $ f where f = opcs "midichn" [(Ir,[])] [] -- | -- 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: midicontrolchange :: Sig -> Sig -> SE () midicontrolchange b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 where f a1 a2 = opcs "midicontrolchange" [(Xr,[Xr,Xr,Ir,Ir])] [a1,a2] -- | -- 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: mididefault :: Sig -> Sig -> SE () mididefault b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 where f a1 a2 = opcs "mididefault" [(Xr,[Xr,Xr])] [a1,a2] -- | -- 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: midinoteoff :: Sig -> Sig -> SE () midinoteoff b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 where f a1 a2 = opcs "midinoteoff" [(Xr,[Xr,Xr])] [a1,a2] -- | -- 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: midinoteoncps :: Sig -> Sig -> SE () midinoteoncps b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 where f a1 a2 = opcs "midinoteoncps" [(Xr,[Xr,Xr])] [a1,a2] -- | -- 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: midinoteonkey :: Sig -> Sig -> SE () midinoteonkey b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 where f a1 a2 = opcs "midinoteonkey" [(Xr,[Xr,Xr])] [a1,a2] -- | -- 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: midinoteonoct :: Sig -> Sig -> SE () midinoteonoct b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 where f a1 a2 = opcs "midinoteonoct" [(Xr,[Xr,Xr])] [a1,a2] -- | -- 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: midinoteonpch :: Sig -> Sig -> SE () midinoteonpch b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 where f a1 a2 = opcs "midinoteonpch" [(Xr,[Xr,Xr])] [a1,a2] -- | -- 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: midipitchbend :: Sig -> SE () midipitchbend b1 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 where f a1 = opcs "midipitchbend" [(Xr,[Xr,Ir,Ir])] [a1] -- | -- 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: midipolyaftertouch :: Sig -> Sig -> SE () midipolyaftertouch b1 b2 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 <*> unSig b2 where f a1 a2 = opcs "midipolyaftertouch" [(Xr,[Xr,Xr,Ir,Ir])] [a1,a2] -- | -- 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: midiprogramchange :: Sig -> SE () midiprogramchange b1 = SE $ (depT_ =<<) $ lift $ f <$> unSig b1 where f a1 = opcs "midiprogramchange" [(Xr,[Xr])] [a1] -- System Realtime. -- | -- Sends a MIDI CLOCK message. -- -- > mclock ifreq -- -- csound doc: mclock :: D -> SE () mclock b1 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 where f a1 = opcs "mclock" [(Xr,[Ir])] [a1] -- | -- Send system real-time messages to the MIDI OUT port. -- -- > mrtmsg imsgtype -- -- csound doc: mrtmsg :: D -> SE () mrtmsg b1 = SE $ (depT_ =<<) $ lift $ f <$> unD b1 where f a1 = opcs "mrtmsg" [(Xr,[Ir])] [a1]