-- | Slider Banks
module CsoundExpr.Opcodes.Midi.Slidrbk
    (slider16,
     slider16f,
     slider32,
     slider32f,
     slider64,
     slider64f,
     s16b14,
     s32b14,
     sliderKawai,
     slider8table,
     slider8tablef,
     slider16table,
     slider16tablef,
     slider32table,
     slider32tablef,
     slider64table,
     slider64tablef)
where



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



-- | * opcode : slider16
--  
--  
-- * syntax : 
--  
--  >   i1,...,i16 slider16 ichan, ictlnum1, imin1, imax1, init1, ifn1,..., 
--  >       ictlnum16, imin16, imax16, init16, ifn16
--  >   k1,...,k16 slider16 ichan, ictlnum1, imin1, imax1, init1, ifn1,..., 
--  >       ictlnum16, imin16, imax16, init16, ifn16
--  
--  
-- * description : 
--  
--  Creates a bank of 16 different MIDI control message numbers.
--  
--  
-- * url : <http://www.csounds.com/manual/html/slider16.html>
 
slider16 :: Irate -> [Irate] -> MultiOut
slider16 i0chan i1vals = opcode "slider16" args
  where args = [to i0chan] ++ map to i1vals


-- | * opcode : slider16f
--  
--  
-- * syntax : 
--  
--  >   k1,...,k16 slider16f ichan, ictlnum1, imin1, imax1, init1, ifn1, 
--  >       icutoff1,..., ictlnum16, imin16, imax16, init16, ifn16, icutoff16
--  
--  
-- * description : 
--  
--  Creates a bank of 16 different MIDI control message numbers,
-- filtered before output.
--  
--  
-- * url : <http://www.csounds.com/manual/html/slider16f.html>
 
slider16f :: Irate -> [Irate] -> MultiOut
slider16f i0chan i1vals = opcode "slider16f" args
  where args = [to i0chan] ++ map to i1vals


-- | * opcode : slider32
--  
--  
-- * syntax : 
--  
--  >   i1,...,i32 slider32 ichan, ictlnum1, imin1, imax1, init1, ifn1,..., 
--  >       ictlnum32, imin32, imax32, init32, ifn32
--  >   k1,...,k32 slider32 ichan, ictlnum1, imin1, imax1, init1, ifn1,..., 
--  >       ictlnum32, imin32, imax32, init32, ifn32
--  
--  
-- * description : 
--  
--  Creates a bank of 32 different MIDI control message numbers.
--  
--  
-- * url : <http://www.csounds.com/manual/html/slider32.html>
 
slider32 :: Irate -> [Irate] -> MultiOut
slider32 i0chan i1vals = opcode "slider32" args
  where args = [to i0chan] ++ map to i1vals


-- | * opcode : slider32f
--  
--  
-- * syntax : 
--  
--  >   k1,...,k32 slider32f ichan, ictlnum1, imin1, imax1, init1, ifn1, icutoff1, 
--  >      ..., ictlnum32, imin32, imax32, init32, ifn32, icutoff32
--  
--  
-- * description : 
--  
--  Creates a bank of 32 different MIDI control message numbers,
-- filtered before output.
--  
--  
-- * url : <http://www.csounds.com/manual/html/slider32f.html>
 
slider32f :: Irate -> [Irate] -> MultiOut
slider32f i0chan i1vals = opcode "slider32f" args
  where args = [to i0chan] ++ map to i1vals


-- | * opcode : slider64
--  
--  
-- * syntax : 
--  
--  >   i1,...,i64 slider64 ichan, ictlnum1, imin1, imax1, init1, ifn1,..., 
--  >       ictlnum64, imin64, imax64, init64, ifn64
--  >   k1,...,k64 slider64 ichan, ictlnum1, imin1, imax1, init1, ifn1,..., 
--  >       ictlnum64, imin64, imax64, init64, ifn64
--  
--  
-- * description : 
--  
--  Creates a bank of 64 different MIDI control message numbers.
--  
--  
-- * url : <http://www.csounds.com/manual/html/slider64.html>
 
slider64 :: Irate -> [Irate] -> MultiOut
slider64 i0chan i1vals = opcode "slider64" args
  where args = [to i0chan] ++ map to i1vals


-- | * opcode : slider64f
--  
--  
-- * syntax : 
--  
--  >   k1,...,k64 slider64f ichan, ictlnum1, imin1, imax1, init1, ifn1, 
--  >       icutoff1,..., ictlnum64, imin64, imax64, init64, ifn64, icutoff64
--  
--  
-- * description : 
--  
--  Creates a bank of 64 different MIDI control message numbers,
-- filtered before output.
--  
--  
-- * url : <http://www.csounds.com/manual/html/slider64f.html>
 
slider64f :: Irate -> [Irate] -> MultiOut
slider64f i0chan i1vals = opcode "slider64f" args
  where args = [to i0chan] ++ map to i1vals


-- | * opcode : s16b14
--  
--  
-- * syntax : 
--  
--  >   i1,...,i16 s16b14 ichan, ictlno_msb1, ictlno_lsb1, imin1, imax1, 
--  >       initvalue1, ifn1,..., ictlno_msb16, ictlno_lsb16, imin16, imax16, initvalue16, ifn16
--  >   k1,...,k16 s16b14 ichan, ictlno_msb1, ictlno_lsb1, imin1, imax1, 
--  >       initvalue1, ifn1,..., ictlno_msb16, ictlno_lsb16, imin16, imax16, initvalue16, ifn16
--  
--  
-- * description : 
--  
--  Creates a bank of 16 different 14-bit MIDI control message
-- numbers.
--  
--  
-- * url : <http://www.csounds.com/manual/html/s16b14.html>
 
s16b14 :: Irate -> [Irate] -> MultiOut
s16b14 i0chan i1vals = opcode "s16b14" args
  where args = [to i0chan] ++ map to i1vals


-- | * opcode : s32b14
--  
--  
-- * syntax : 
--  
--  >   i1,...,i32 s32b14 ichan, ictlno_msb1, ictlno_lsb1, imin1, imax1, 
--  >       initvalue1, ifn1,..., ictlno_msb32, ictlno_lsb32, imin32, imax32, initvalue32, ifn32
--  >   k1,...,k32 s32b14 ichan, ictlno_msb1, ictlno_lsb1, imin1, imax1, 
--  >       initvalue1, ifn1,..., ictlno_msb32, ictlno_lsb32, imin32, imax32, initvalue32, ifn32
--  
--  
-- * description : 
--  
--  Creates a bank of 32 different 14-bit MIDI control message
-- numbers.
--  
--  
-- * url : <http://www.csounds.com/manual/html/s32b14.html>
 
s32b14 :: Irate -> [Irate] -> MultiOut
s32b14 i0chan i1vals = opcode "s32b14" args
  where args = [to i0chan] ++ map to i1vals


-- | * opcode : sliderKawai
--  
--  
-- * syntax : 
--  
--  >   k1, k2,...., k16 sliderKawai imin1, imax1, init1, ifn1, 
--  >       imin2, imax2, init2, ifn2,..., imin16, imax16, init16, ifn16
--  
--  
-- * description : 
--  
--  Creates a bank of 16 different MIDI control message numbers from
-- a KAWAI MM-16 midi mixer.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sliderKawai.html>
 
sliderKawai :: [Irate] -> MultiOut
sliderKawai i0vals = opcode "sliderKawai" args
  where args = map to i0vals


-- | * opcode : slider8table
--  
--  
-- * syntax : 
--  
--  >   kflag slider8table ichan, ioutTable, ioffset, ictlnum1, imin1, imax1, 
--  >       init1, ifn1,..., ictlnum8, imin8, imax8, init8, ifn8
--  
--  
-- * description : 
--  
--  Stores a bank of 8 different MIDI control messages to a table.
--  
--  
-- * url : <http://www.csounds.com/manual/html/slider8table.html>
 
slider8table :: Irate -> Irate -> Irate -> [Irate] -> Krate
slider8table i0chan i1outTable i2offset i3vals
  = opcode "slider8table" args
  where args
          = [to i0chan, to i1outTable, to i2offset] ++ map to i3vals


-- | * opcode : slider8tablef
--  
--  
-- * syntax : 
--  
--  >   kflag slider8tablef ichan, ioutTable, ioffset, ictlnum1, imin1, imax1, 
--  >       init1, ifn1, icutoff1,...., ictlnum8, imin8, imax8, init8, ifn8, icutoff8
--  
--  
-- * description : 
--  
--  Stores a bank of 8 different MIDI control messages to a table,
-- filtered before output.
--  
--  
-- * url : <http://www.csounds.com/manual/html/slider8tablef.html>
 
slider8tablef :: Irate -> Irate -> Irate -> [Irate] -> Krate
slider8tablef i0chan i1outTable i2offset i3vals
  = opcode "slider8tablef" args
  where args
          = [to i0chan, to i1outTable, to i2offset] ++ map to i3vals


-- | * opcode : slider16table
--  
--  
-- * syntax : 
--  
--  >   kflag slider16table ichan, ioutTable, ioffset, ictlnum1, imin1, imax1, 
--  >       init1, ifn1,...., ictlnum16, imin16, imax16, init16, ifn16
--  
--  
-- * description : 
--  
--  Stores a bank of 16 different MIDI control messages to a table.
--  
--  
-- * url : <http://www.csounds.com/manual/html/slider16table.html>
 
slider16table :: Irate -> Irate -> Irate -> [Irate] -> Krate
slider16table i0chan i1outTable i2offset i3vals
  = opcode "slider16table" args
  where args
          = [to i0chan, to i1outTable, to i2offset] ++ map to i3vals


-- | * opcode : slider16tablef
--  
--  
-- * syntax : 
--  
--  >   kflag slider16tablef ichan, ioutTable, ioffset, ictlnum1, imin1, imax1, 
--  >       init1, ifn1, icutoff1,...., ictlnum16, imin16, imax16, init16, ifn16, icutoff16
--  
--  
-- * description : 
--  
--  Stores a bank of 16 different MIDI control messages to a table,
-- filtered before output.
--  
--  
-- * url : <http://www.csounds.com/manual/html/slider16tablef.html>
 
slider16tablef :: Irate -> Irate -> Irate -> [Irate] -> Krate
slider16tablef i0chan i1outTable i2offset i3vals
  = opcode "slider16tablef" args
  where args
          = [to i0chan, to i1outTable, to i2offset] ++ map to i3vals


-- | * opcode : slider32table
--  
--  
-- * syntax : 
--  
--  >   kflag slider32table ichan, ioutTable, ioffset, ictlnum1, imin1, 
--  >       imax1, init1, ifn1,...., ictlnum32, imin32, imax32, init32, ifn32
--  
--  
-- * description : 
--  
--  Creates a bank of 32 different MIDI control messages to a table.
--  
--  
-- * url : <http://www.csounds.com/manual/html/slider32table.html>
 
slider32table :: Irate -> Irate -> Irate -> [Irate] -> Krate
slider32table i0chan i1outTable i2offset i3vals
  = opcode "slider32table" args
  where args
          = [to i0chan, to i1outTable, to i2offset] ++ map to i3vals


-- | * opcode : slider32tablef
--  
--  
-- * syntax : 
--  
--  >   kflag slider32tablef ichan, ioutTable, ioffset, ictlnum1, imin1, imax1, 
--  >       init1, ifn1, icutoff1,...., ictlnum32, imin32, imax32, init32, ifn32, icutoff32
--  
--  
-- * description : 
--  
--  Creates a bank of 32 different MIDI control message numbers,
-- filtered before output.
--  
--  
-- * url : <http://www.csounds.com/manual/html/slider32tablef.html>
 
slider32tablef :: Irate -> Irate -> Irate -> [Irate] -> Krate
slider32tablef i0chan i1outTable i2offset i3vals
  = opcode "slider32tablef" args
  where args
          = [to i0chan, to i1outTable, to i2offset] ++ map to i3vals


-- | * opcode : slider64table
--  
--  
-- * syntax : 
--  
--  >   kflag slider64table ichan, ioutTable, ioffset, ictlnum1, imin1, 
--  >       imax1, init1, ifn1,...., ictlnum64, imin64, imax64, init64, ifn64
--  
--  
-- * description : 
--  
--  Creates a bank of 64 different MIDI control messages to a table.
--  
--  
-- * url : <http://www.csounds.com/manual/html/slider64table.html>
 
slider64table :: Irate -> Irate -> Irate -> [Irate] -> Krate
slider64table i0chan i1outTable i2offset i3vals
  = opcode "slider64table" args
  where args
          = [to i0chan, to i1outTable, to i2offset] ++ map to i3vals


-- | * opcode : slider64tablef
--  
--  
-- * syntax : 
--  
--  >   kflag slider64tablef ichan, ioutTable, ioffset, ictlnum1, imin1, imax1, 
--  >       init1, ifn1, icutoff1,...., ictlnum64, imin64, imax64, init64, ifn64, icutoff64
--  
--  
-- * description : 
--  
--  Stores a bank of 64 different MIDI MIDI control messages to a
-- table, filtered before output.
--  
--  
-- * url : <http://www.csounds.com/manual/html/slider64tablef.html>
 
slider64tablef :: Irate -> Irate -> Irate -> [Irate] -> Krate
slider64tablef i0chan i1outTable i2offset i3vals
  = opcode "slider64tablef" args
  where args
          = [to i0chan, to i1outTable, to i2offset] ++ map to i3vals