-- | MIDI input
module CsoundExpr.Opcodes.Midi.Input
    (aftouch,
     chanctrlI,
     chanctrlK,
     polyaftI,
     polyaftK,
     pchbendI,
     pchbendK,
     veloc,
     midictrlI,
     midictrlK,
     notnum,
     ctrl7A,
     ctrl7I,
     ctrl7K,
     ctrl14I,
     ctrl14K,
     ctrl21I,
     ctrl21K,
     midic7I,
     midic7K,
     midic14I,
     midic14K,
     midic21I,
     midic21K,
     initc7,
     initc14,
     initc21)
where



import CsoundExpr.Base.Types
import CsoundExpr.Base.MultiOut
import CsoundExpr.Base.SideEffect
import CsoundExpr.Base.UserDefined



-- | * opcode : aftouch
--  
--  
-- * syntax : 
--  
--  >   kaft aftouch [imin] [, imax]
--  
--  
-- * description : 
--  
--  Get the current after-touch value for this channel.
--  
--  
-- * url : <http://www.csounds.com/manual/html/aftouch.html>
 
aftouch :: [Irate] -> Krate
aftouch i0init = opcode "aftouch" args
  where args = map to i0init


-- | * opcode : chanctrl
--  
--  
-- * syntax : 
--  
--  >   ival chanctrl ichnl, ictlno [, ilow] [, ihigh]
--  >   kval chanctrl ichnl, ictlno [, ilow] [, ihigh]
--  
--  
-- * description : 
--  
--  Get the current value of a controller and optionally map it onto
-- specified range.
--  
--  
-- * url : <http://www.csounds.com/manual/html/chanctrl.html>
 
chanctrlI :: [Irate] -> Irate -> Irate -> Irate
chanctrlI i0init i1chnl i2ctlno = opcode "chanctrl" args
  where args = [to i1chnl, to i2ctlno] ++ map to i0init


-- | * opcode : chanctrl
--  
--  
-- * syntax : 
--  
--  >   ival chanctrl ichnl, ictlno [, ilow] [, ihigh]
--  >   kval chanctrl ichnl, ictlno [, ilow] [, ihigh]
--  
--  
-- * description : 
--  
--  Get the current value of a controller and optionally map it onto
-- specified range.
--  
--  
-- * url : <http://www.csounds.com/manual/html/chanctrl.html>
 
chanctrlK :: [Irate] -> Irate -> Irate -> Krate
chanctrlK i0init i1chnl i2ctlno = opcode "chanctrl" args
  where args = [to i1chnl, to i2ctlno] ++ map to i0init


-- | * opcode : polyaft
--  
--  
-- * syntax : 
--  
--  >   ires polyaft inote [, ilow] [, ihigh]
--  >   kres polyaft inote [, ilow] [, ihigh]
--  
--  
-- * description : 
--  
--  polyaft returns the polyphonic pressure of the selected note
-- number, optionally mapped to an user-specified range.
--  
--  
-- * url : <http://www.csounds.com/manual/html/polyaft.html>
 
polyaftI :: [Irate] -> Irate -> Irate
polyaftI i0init i1note = opcode "polyaft" args
  where args = [to i1note] ++ map to i0init


-- | * opcode : polyaft
--  
--  
-- * syntax : 
--  
--  >   ires polyaft inote [, ilow] [, ihigh]
--  >   kres polyaft inote [, ilow] [, ihigh]
--  
--  
-- * description : 
--  
--  polyaft returns the polyphonic pressure of the selected note
-- number, optionally mapped to an user-specified range.
--  
--  
-- * url : <http://www.csounds.com/manual/html/polyaft.html>
 
polyaftK :: [Irate] -> Irate -> Krate
polyaftK i0init i1note = opcode "polyaft" args
  where args = [to i1note] ++ map to i0init


-- | * opcode : pchbend
--  
--  
-- * syntax : 
--  
--  >   ibend pchbend [imin] [, imax]
--  >   kbend pchbend [imin] [, imax]
--  
--  
-- * description : 
--  
--  Get the current pitch-bend value for this channel.
--  
--  
-- * url : <http://www.csounds.com/manual/html/pchbend.html>
 
pchbendI :: [Irate] -> Irate
pchbendI i0init = opcode "pchbend" args
  where args = map to i0init


-- | * opcode : pchbend
--  
--  
-- * syntax : 
--  
--  >   ibend pchbend [imin] [, imax]
--  >   kbend pchbend [imin] [, imax]
--  
--  
-- * description : 
--  
--  Get the current pitch-bend value for this channel.
--  
--  
-- * url : <http://www.csounds.com/manual/html/pchbend.html>
 
pchbendK :: [Irate] -> Krate
pchbendK i0init = opcode "pchbend" args
  where args = map to i0init


-- | * opcode : veloc
--  
--  
-- * syntax : 
--  
--  >   ival veloc [ilow] [, ihigh]
--  
--  
-- * description : 
--  
--  Get the velocity from a MIDI event.
--  
--  
-- * url : <http://www.csounds.com/manual/html/veloc.html>
 
veloc :: [Irate] -> Irate
veloc i0init = opcode "veloc" args
  where args = map to i0init


-- | * opcode : midictrl
--  
--  
-- * syntax : 
--  
--  >   ival midictrl inum [, imin] [, imax]
--  >   kval midictrl inum [, imin] [, imax]
--  
--  
-- * description : 
--  
--  Get the current value (0-127) of a specified MIDI controller.
--  
--  
-- * url : <http://www.csounds.com/manual/html/midictrl.html>
 
midictrlI :: [Irate] -> Irate -> Irate
midictrlI i0init i1num = opcode "midictrl" args
  where args = [to i1num] ++ map to i0init


-- | * opcode : midictrl
--  
--  
-- * syntax : 
--  
--  >   ival midictrl inum [, imin] [, imax]
--  >   kval midictrl inum [, imin] [, imax]
--  
--  
-- * description : 
--  
--  Get the current value (0-127) of a specified MIDI controller.
--  
--  
-- * url : <http://www.csounds.com/manual/html/midictrl.html>
 
midictrlK :: [Irate] -> Irate -> Krate
midictrlK i0init i1num = opcode "midictrl" args
  where args = [to i1num] ++ map to i0init


-- | * opcode : notnum
--  
--  
-- * syntax : 
--  
--  >   ival notnum
--  
--  
-- * description : 
--  
--  Get a note number from a MIDI event.
--  
--  
-- * url : <http://www.csounds.com/manual/html/notnum.html>
 
notnum :: Irate
notnum = opcode "notnum" args
  where args = []


-- | * opcode : ctrl7
--  
--  
-- * syntax : 
--  
--  >   idest ctrl7 ichan, ictlno, imin, imax [, ifn]
--  >   kdest ctrl7 ichan, ictlno, kmin, kmax [, ifn]
--  >   adest ctrl7 ichan, ictlno, kmin, kmax [, ifn] [, icutoff]
--  
--  
-- * description : 
--  
--  Allows a floating-point 7-bit MIDI signal scaled with a minimum
-- and a maximum range.
--  
--  
-- * url : <http://www.csounds.com/manual/html/ctrl7.html>
 
ctrl7A ::
         (K k0, K k1) => [Irate] -> Irate -> Irate -> k0 -> k1 -> Arate
ctrl7A i0init i1chan i2ctlno k3min k4max = opcode "ctrl7" args
  where args
          = [to i1chan, to i2ctlno, to k3min, to k4max] ++ map to i0init


-- | * opcode : ctrl7
--  
--  
-- * syntax : 
--  
--  >   idest ctrl7 ichan, ictlno, imin, imax [, ifn]
--  >   kdest ctrl7 ichan, ictlno, kmin, kmax [, ifn]
--  >   adest ctrl7 ichan, ictlno, kmin, kmax [, ifn] [, icutoff]
--  
--  
-- * description : 
--  
--  Allows a floating-point 7-bit MIDI signal scaled with a minimum
-- and a maximum range.
--  
--  
-- * url : <http://www.csounds.com/manual/html/ctrl7.html>
 
ctrl7I :: [Irate] -> Irate -> Irate -> Irate -> Irate -> Irate
ctrl7I i0init i1chan i2ctlno i3min i4max = opcode "ctrl7" args
  where args
          = [to i1chan, to i2ctlno, to i3min, to i4max] ++ map to i0init


-- | * opcode : ctrl7
--  
--  
-- * syntax : 
--  
--  >   idest ctrl7 ichan, ictlno, imin, imax [, ifn]
--  >   kdest ctrl7 ichan, ictlno, kmin, kmax [, ifn]
--  >   adest ctrl7 ichan, ictlno, kmin, kmax [, ifn] [, icutoff]
--  
--  
-- * description : 
--  
--  Allows a floating-point 7-bit MIDI signal scaled with a minimum
-- and a maximum range.
--  
--  
-- * url : <http://www.csounds.com/manual/html/ctrl7.html>
 
ctrl7K ::
         (K k0, K k1) => [Irate] -> Irate -> Irate -> k0 -> k1 -> Krate
ctrl7K i0init i1chan i2ctlno k3min k4max = opcode "ctrl7" args
  where args
          = [to i1chan, to i2ctlno, to k3min, to k4max] ++ map to i0init


-- | * opcode : ctrl14
--  
--  
-- * syntax : 
--  
--  >   idest ctrl14 ichan, ictlno1, ictlno2, imin, imax [, ifn]
--  >   kdest ctrl14 ichan, ictlno1, ictlno2, kmin, kmax [, ifn]
--  
--  
-- * description : 
--  
--  Allows a floating-point 14-bit MIDI signal scaled with a minimum
-- and a maximum range.
--  
--  
-- * url : <http://www.csounds.com/manual/html/ctrl14.html>
 
ctrl14I ::
          [Irate] -> Irate -> Irate -> Irate -> Irate -> Irate -> Irate
ctrl14I i0init i1chan i2ctlno1 i3ctlno2 i4min i5max
  = opcode "ctrl14" args
  where args
          = [to i1chan, to i2ctlno1, to i3ctlno2, to i4min, to i5max] ++
              map to i0init


-- | * opcode : ctrl14
--  
--  
-- * syntax : 
--  
--  >   idest ctrl14 ichan, ictlno1, ictlno2, imin, imax [, ifn]
--  >   kdest ctrl14 ichan, ictlno1, ictlno2, kmin, kmax [, ifn]
--  
--  
-- * description : 
--  
--  Allows a floating-point 14-bit MIDI signal scaled with a minimum
-- and a maximum range.
--  
--  
-- * url : <http://www.csounds.com/manual/html/ctrl14.html>
 
ctrl14K ::
          (K k0, K k1) =>
          [Irate] -> Irate -> Irate -> Irate -> k0 -> k1 -> Krate
ctrl14K i0init i1chan i2ctlno1 i3ctlno2 k4min k5max
  = opcode "ctrl14" args
  where args
          = [to i1chan, to i2ctlno1, to i3ctlno2, to k4min, to k5max] ++
              map to i0init


-- | * opcode : ctrl21
--  
--  
-- * syntax : 
--  
--  >   idest ctrl21 ichan, ictlno1, ictlno2, ictlno3, imin, imax [, ifn]
--  >   kdest ctrl21 ichan, ictlno1, ictlno2, ictlno3, kmin, kmax [, ifn]
--  
--  
-- * description : 
--  
--  Allows a floating-point 21-bit MIDI signal scaled with a minimum
-- and a maximum range.
--  
--  
-- * url : <http://www.csounds.com/manual/html/ctrl21.html>
 
ctrl21I ::
          [Irate] ->
            Irate -> Irate -> Irate -> Irate -> Irate -> Irate -> Irate
ctrl21I i0init i1chan i2ctlno1 i3ctlno2 i4ctlno3 i5min i6max
  = opcode "ctrl21" args
  where args
          = [to i1chan, to i2ctlno1, to i3ctlno2, to i4ctlno3, to i5min,
             to i6max]
              ++ map to i0init


-- | * opcode : ctrl21
--  
--  
-- * syntax : 
--  
--  >   idest ctrl21 ichan, ictlno1, ictlno2, ictlno3, imin, imax [, ifn]
--  >   kdest ctrl21 ichan, ictlno1, ictlno2, ictlno3, kmin, kmax [, ifn]
--  
--  
-- * description : 
--  
--  Allows a floating-point 21-bit MIDI signal scaled with a minimum
-- and a maximum range.
--  
--  
-- * url : <http://www.csounds.com/manual/html/ctrl21.html>
 
ctrl21K ::
          (K k0, K k1) =>
          [Irate] -> Irate -> Irate -> Irate -> Irate -> k0 -> k1 -> Krate
ctrl21K i0init i1chan i2ctlno1 i3ctlno2 i4ctlno3 k5min k6max
  = opcode "ctrl21" args
  where args
          = [to i1chan, to i2ctlno1, to i3ctlno2, to i4ctlno3, to k5min,
             to k6max]
              ++ map to i0init


-- | * opcode : midic7
--  
--  
-- * syntax : 
--  
--  >   idest midic7 ictlno, imin, imax [, ifn]
--  >   kdest midic7 ictlno, kmin, kmax [, ifn]
--  
--  
-- * description : 
--  
--  Allows a floating-point 7-bit MIDI signal scaled with a minimum
-- and a maximum range.
--  
--  
-- * url : <http://www.csounds.com/manual/html/midic7.html>
 
midic7I :: [Irate] -> Irate -> Irate -> Irate -> Irate
midic7I i0init i1ctlno i2min i3max = opcode "midic7" args
  where args = [to i1ctlno, to i2min, to i3max] ++ map to i0init


-- | * opcode : midic7
--  
--  
-- * syntax : 
--  
--  >   idest midic7 ictlno, imin, imax [, ifn]
--  >   kdest midic7 ictlno, kmin, kmax [, ifn]
--  
--  
-- * description : 
--  
--  Allows a floating-point 7-bit MIDI signal scaled with a minimum
-- and a maximum range.
--  
--  
-- * url : <http://www.csounds.com/manual/html/midic7.html>
 
midic7K :: (K k0, K k1) => [Irate] -> Irate -> k0 -> k1 -> Krate
midic7K i0init i1ctlno k2min k3max = opcode "midic7" args
  where args = [to i1ctlno, to k2min, to k3max] ++ map to i0init


-- | * opcode : midic14
--  
--  
-- * syntax : 
--  
--  >   idest midic14 ictlno1, ictlno2, imin, imax [, ifn]
--  >   kdest midic14 ictlno1, ictlno2, kmin, kmax [, ifn]
--  
--  
-- * description : 
--  
--  Allows a floating-point 14-bit MIDI signal scaled with a minimum
-- and a maximum range.
--  
--  
-- * url : <http://www.csounds.com/manual/html/midic14.html>
 
midic14I :: [Irate] -> Irate -> Irate -> Irate -> Irate -> Irate
midic14I i0init i1ctlno1 i2ctlno2 i3min i4max
  = opcode "midic14" args
  where args
          = [to i1ctlno1, to i2ctlno2, to i3min, to i4max] ++ map to i0init


-- | * opcode : midic14
--  
--  
-- * syntax : 
--  
--  >   idest midic14 ictlno1, ictlno2, imin, imax [, ifn]
--  >   kdest midic14 ictlno1, ictlno2, kmin, kmax [, ifn]
--  
--  
-- * description : 
--  
--  Allows a floating-point 14-bit MIDI signal scaled with a minimum
-- and a maximum range.
--  
--  
-- * url : <http://www.csounds.com/manual/html/midic14.html>
 
midic14K ::
           (K k0, K k1) => [Irate] -> Irate -> Irate -> k0 -> k1 -> Krate
midic14K i0init i1ctlno1 i2ctlno2 k3min k4max
  = opcode "midic14" args
  where args
          = [to i1ctlno1, to i2ctlno2, to k3min, to k4max] ++ map to i0init


-- | * opcode : midic21
--  
--  
-- * syntax : 
--  
--  >   idest midic21 ictlno1, ictlno2, ictlno3, imin, imax [, ifn]
--  >   kdest midic21 ictlno1, ictlno2, ictlno3, kmin, kmax [, ifn]
--  
--  
-- * description : 
--  
--  Allows a floating-point 21-bit MIDI signal scaled with a minimum
-- and a maximum range.
--  
--  
-- * url : <http://www.csounds.com/manual/html/midic21.html>
 
midic21I ::
           [Irate] -> Irate -> Irate -> Irate -> Irate -> Irate -> Irate
midic21I i0init i1ctlno1 i2ctlno2 i3ctlno3 i4min i5max
  = opcode "midic21" args
  where args
          = [to i1ctlno1, to i2ctlno2, to i3ctlno3, to i4min, to i5max] ++
              map to i0init


-- | * opcode : midic21
--  
--  
-- * syntax : 
--  
--  >   idest midic21 ictlno1, ictlno2, ictlno3, imin, imax [, ifn]
--  >   kdest midic21 ictlno1, ictlno2, ictlno3, kmin, kmax [, ifn]
--  
--  
-- * description : 
--  
--  Allows a floating-point 21-bit MIDI signal scaled with a minimum
-- and a maximum range.
--  
--  
-- * url : <http://www.csounds.com/manual/html/midic21.html>
 
midic21K ::
           (K k0, K k1) =>
           [Irate] -> Irate -> Irate -> Irate -> k0 -> k1 -> Krate
midic21K i0init i1ctlno1 i2ctlno2 i3ctlno3 k4min k5max
  = opcode "midic21" args
  where args
          = [to i1ctlno1, to i2ctlno2, to i3ctlno3, to k4min, to k5max] ++
              map to i0init


-- | * opcode : initc7
--  
--  
-- * syntax : 
--  
--  >   initc7 ichan, ictlno, ivalue
--  
--  
-- * description : 
--  
--  Initializes MIDI controller ictlno with ivalue
--  
--  
-- * url : <http://www.csounds.com/manual/html/initc7.html>
 
initc7 :: Irate -> Irate -> Irate -> SignalOut
initc7 i0chan i1ctlno i2value = outOpcode "initc7" args
  where args = [to i0chan, to i1ctlno, to i2value]


-- | * opcode : initc14
--  
--  
-- * syntax : 
--  
--  >   initc14 ichan, ictlno1, ictlno2, ivalue
--  
--  
-- * description : 
--  
--  Initializes the controllers used to create a 14-bit MIDI value.
--  
--  
-- * url : <http://www.csounds.com/manual/html/initc14.html>
 
initc14 :: Irate -> Irate -> Irate -> Irate -> SignalOut
initc14 i0chan i1ctlno1 i2ctlno2 i3value = outOpcode "initc14" args
  where args = [to i0chan, to i1ctlno1, to i2ctlno2, to i3value]


-- | * opcode : initc21
--  
--  
-- * syntax : 
--  
--  >   initc21 ichan, ictlno1, ictlno2, ictlno3, ivalue
--  
--  
-- * description : 
--  
--  Initializes the controllers used to create a 21-bit MIDI value.
--  
--  
-- * url : <http://www.csounds.com/manual/html/initc21.html>
 
initc21 :: Irate -> Irate -> Irate -> Irate -> Irate -> SignalOut
initc21 i0chan i1ctlno1 i2ctlno2 i3ctlno3 i4value
  = outOpcode "initc21" args
  where args
          = [to i0chan, to i1ctlno1, to i2ctlno2, to i3ctlno3, to i4value]