-- | Sample Playback
module CsoundExpr.Opcodes.Siggen.Sample
    (bbcutm,
     bbcuts,
     flooper,
     flooper2,
     loscil,
     loscil3,
     loscilx,
     lphasor,
     lposcil,
     lposcil3,
     lposcila,
     lposcilsa,
     lposcilsa2,
     sndloop,
     waveset,
     fluidAllOut,
     fluidCCi,
     fluidCCk,
     fluidControl,
     fluidEngine,
     fluidLoad,
     fluidNote,
     fluidOut,
     fluidProgramSelect,
     fluidSetInterpMethod,
     sfilist,
     sfinstr,
     sfinstr3,
     sfinstr3m,
     sfinstrm,
     sfload,
     sfpassign,
     sfplay,
     sfplay3,
     sfplay3m,
     sfplaym,
     sflooper,
     sfplist,
     sfpreset)
where



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



-- | * opcode : bbcutm
--  
--  
-- * syntax : 
--  
--  >   a1 bbcutm asource, ibps, isubdiv, ibarlength, iphrasebars, inumrepeats 
--  >       [, istutterspeed] [, istutterchance] [, ienvchoice ]
--  
--  
-- * description : 
--  
--  The BreakBeat Cutter automatically generates cut-ups of a source
-- audio stream in the style of drum and bass/jungle breakbeat
-- manipulations. There are two versions, for mono (bbcutm) or
-- stereo (bbcuts) sources. Whilst originally based on breakbeat
-- cutting, the opcode can be applied to any type of source audio.
--  
--  
-- * url : <http://www.csounds.com/manual/html/bbcutm.html>
 
bbcutm ::
         [Irate] ->
           Arate -> Irate -> Irate -> Irate -> Irate -> Irate -> Arate
bbcutm i0init a1source i2bps i3subdiv i4barlength i5phrasebars
  i6numrepeats = opcode "bbcutm" args
  where args
          = [to a1source, to i2bps, to i3subdiv, to i4barlength,
             to i5phrasebars, to i6numrepeats]
              ++ map to i0init


-- | * opcode : bbcuts
--  
--  
-- * syntax : 
--  
--  >   a1,a2 bbcuts asource1, asource2, ibps, isubdiv, ibarlength, iphrasebars, 
--  >       inumrepeats [, istutterspeed] [, istutterchance] [, ienvchoice]
--  
--  
-- * description : 
--  
--  The BreakBeat Cutter automatically generates cut-ups of a source
-- audio stream in the style of drum and bass/jungle breakbeat
-- manipulations. There are two versions, for mono (bbcutm) or
-- stereo (bbcuts) sources. Whilst originally based on breakbeat
-- cutting, the opcode can be applied to any type of source audio.
--  
--  
-- * url : <http://www.csounds.com/manual/html/bbcuts.html>
 
bbcuts ::
         [Irate] ->
           Arate ->
             Arate -> Irate -> Irate -> Irate -> Irate -> Irate -> MultiOut
bbcuts i0init a1source1 a2source2 i3bps i4subdiv i5barlength
  i6phrasebars i7numrepeats = opcode "bbcuts" args
  where args
          = [to a1source1, to a2source2, to i3bps, to i4subdiv,
             to i5barlength, to i6phrasebars, to i7numrepeats]
              ++ map to i0init


-- | * opcode : flooper
--  
--  
-- * syntax : 
--  
--  >   asig flooper kamp, kpitch, istart, idur, ifad, ifn
--  
--  
-- * description : 
--  
--  This opcode reads audio from a function table and plays it back
-- in a loop with user-defined start time, duration and crossfade
-- time. It also allows the pitch of the loop to be controlled,
-- including reversed playback. It accepts non-power-of-two tables,
-- such as deferred-allocation GEN01 tables.
--  
--  
-- * url : <http://www.csounds.com/manual/html/flooper.html>
 
flooper ::
          (K k0, K k1) =>
          k0 -> k1 -> Irate -> Irate -> Irate -> Irate -> Arate
flooper k0amp k1pitch i2start i3dur i4fad i5fn
  = opcode "flooper" args
  where args
          = [to k0amp, to k1pitch, to i2start, to i3dur, to i4fad, to i5fn]


-- | * opcode : flooper2
--  
--  
-- * syntax : 
--  
--  >   asig flooper2 kamp, kpitch, kloopstart, kloopend, kcrossfade, ifn 
--  >       [, istart, imode, ifenv, iskip]
--  
--  
-- * description : 
--  
--  This opcode implements a crossfading looper with variable loop
-- parameters and three looping modes, optionally using a table for
-- its crossfade shape. It accepts non-power-of-two tables for its
-- source sounds, such as deferred-allocation GEN01 tables.
--  
--  
-- * url : <http://www.csounds.com/manual/html/flooper2.html>
 
flooper2 ::
           (K k0, K k1, K k2, K k3, K k4) =>
           [Irate] -> k0 -> k1 -> k2 -> k3 -> k4 -> Irate -> Arate
flooper2 i0init k1amp k2pitch k3loopstart k4loopend k5crossfade
  i6fn = opcode "flooper2" args
  where args
          = [to k1amp, to k2pitch, to k3loopstart, to k4loopend,
             to k5crossfade, to i6fn]
              ++ map to i0init


-- | * opcode : loscil
--  
--  
-- * syntax : 
--  
--  >   ar1 [,ar2] loscil xamp, kcps, ifn [, ibas] [, imod1] [, ibeg1] [, iend1] 
--  >       [, imod2] [, ibeg2] [, iend2]
--  
--  
-- * description : 
--  
--  Read sampled sound (mono or stereo) from a table, with optional
-- sustain and release looping.
--  
--  
-- * url : <http://www.csounds.com/manual/html/loscil.html>
 
loscil :: (X x0, K k0) => [Irate] -> x0 -> k0 -> Irate -> MultiOut
loscil i0init x1amp k2cps i3fn = opcode "loscil" args
  where args = [to x1amp, to k2cps, to i3fn] ++ map to i0init


-- | * opcode : loscil3
--  
--  
-- * syntax : 
--  
--  >   ar1 [,ar2] loscil3 xamp, kcps, ifn [, ibas] [, imod1] [, ibeg1] [, iend1] 
--  >       [, imod2] [, ibeg2] [, iend2]
--  
--  
-- * description : 
--  
--  Read sampled sound (mono or stereo) from a table, with optional
-- sustain and release looping, using cubic interpolation.
--  
--  
-- * url : <http://www.csounds.com/manual/html/loscil3.html>
 
loscil3 :: (X x0, K k0) => [Irate] -> x0 -> k0 -> Irate -> MultiOut
loscil3 i0init x1amp k2cps i3fn = opcode "loscil3" args
  where args = [to x1amp, to k2cps, to i3fn] ++ map to i0init


-- | * opcode : loscilx
--  
--  
-- * syntax : 
--  
--  >   ar1 [, ar2, ar3, ar4, ar5, ar6, ar7, ar8, ar9, ar10, ar11, ar12, ar13, ar14, 
--  >       ar15, ar16] loscilx xamp, kcps, ifn 
--  >       [, iwsize, ibas, istrt, imod1, ibeg1, iend1]
--  
--  
-- * description : 
--  
--  This file is currently a stub, but the syntax should be correct.
--  
--  
-- * url : <http://www.csounds.com/manual/html/loscilx.html>
 
loscilx :: (X x0, K k0) => [Irate] -> x0 -> k0 -> Irate -> MultiOut
loscilx i0init x1amp k2cps i3fn = opcode "loscilx" args
  where args = [to x1amp, to k2cps, to i3fn] ++ map to i0init


-- | * opcode : lphasor
--  
--  
-- * syntax : 
--  
--  >   ares lphasor xtrns [, ilps] [, ilpe] [, imode] [, istrt] [, istor]
--  
--  
-- * description : 
--  
--  This opcode can be used to generate table index for sample
-- playback (e.g. tablexkt).
--  
--  
-- * url : <http://www.csounds.com/manual/html/lphasor.html>
 
lphasor :: (X x0) => [Irate] -> x0 -> Arate
lphasor i0init x1trns = opcode "lphasor" args
  where args = [to x1trns] ++ map to i0init


-- | * opcode : lposcil
--  
--  
-- * syntax : 
--  
--  >   ares lposcil kamp, kfreqratio, kloop, kend, ifn [, iphs]
--  
--  
-- * description : 
--  
--  Read sampled sound (mono or stereo) from a table, with optional
-- sustain and release looping, and high precision.
--  
--  
-- * url : <http://www.csounds.com/manual/html/lposcil.html>
 
lposcil ::
          (K k0, K k1, K k2, K k3) =>
          [Irate] -> k0 -> k1 -> k2 -> k3 -> Irate -> Arate
lposcil i0init k1amp k2freqratio k3loop k4end i5fn
  = opcode "lposcil" args
  where args
          = [to k1amp, to k2freqratio, to k3loop, to k4end, to i5fn] ++
              map to i0init


-- | * opcode : lposcil3
--  
--  
-- * syntax : 
--  
--  >   ares lposcil3 kamp, kfreqratio, kloop, kend, ifn [, iphs]
--  
--  
-- * description : 
--  
--  Read sampled sound (mono or stereo) from a table, with optional
-- sustain and release looping, and high precision. lposcil3 uses
-- cubic interpolation.
--  
--  
-- * url : <http://www.csounds.com/manual/html/lposcil3.html>
 
lposcil3 ::
           (K k0, K k1, K k2, K k3) =>
           [Irate] -> k0 -> k1 -> k2 -> k3 -> Irate -> Arate
lposcil3 i0init k1amp k2freqratio k3loop k4end i5fn
  = opcode "lposcil3" args
  where args
          = [to k1amp, to k2freqratio, to k3loop, to k4end, to i5fn] ++
              map to i0init


-- | * opcode : lposcila
--  
--  
-- * syntax : 
--  
--  >   ar lposcila aamp, kfreqratio, kloop, kend, ift [,iphs]
--  
--  
-- * description : 
--  
--  lposcila reads sampled sound from a table with optional looping
-- and high precision.
--  
--  
-- * url : <http://www.csounds.com/manual/html/lposcila.html>
 
lposcila ::
           (K k0, K k1, K k2) =>
           [Irate] -> Arate -> k0 -> k1 -> k2 -> Irate -> Arate
lposcila i0init a1amp k2freqratio k3loop k4end i5ft
  = opcode "lposcila" args
  where args
          = [to a1amp, to k2freqratio, to k3loop, to k4end, to i5ft] ++
              map to i0init


-- | * opcode : lposcilsa
--  
--  
-- * syntax : 
--  
--  >   ar1, ar2 lposcilsa aamp, kfreqratio, kloop, kend, ift [,iphs]
--  
--  
-- * description : 
--  
--  lposcilsa reads stereo sampled sound from a table with optional
-- looping and high precision.
--  
--  
-- * url : <http://www.csounds.com/manual/html/lposcilsa.html>
 
lposcilsa ::
            (K k0, K k1, K k2) =>
            [Irate] -> Arate -> k0 -> k1 -> k2 -> Irate -> MultiOut
lposcilsa i0init a1amp k2freqratio k3loop k4end i5ft
  = opcode "lposcilsa" args
  where args
          = [to a1amp, to k2freqratio, to k3loop, to k4end, to i5ft] ++
              map to i0init


-- | * opcode : lposcilsa2
--  
--  
-- * syntax : 
--  
--  >   ar1, ar2 lposcilsa2 aamp, kfreqratio, kloop, kend, ift [,iphs]
--  
--  
-- * description : 
--  
--  lposcilsa2 reads stereo sampled sound from a table with optional
-- looping and high precision.
--  
--  
-- * url : <http://www.csounds.com/manual/html/lposcilsa2.html>
 
lposcilsa2 ::
             (K k0, K k1, K k2) =>
             [Irate] -> Arate -> k0 -> k1 -> k2 -> Irate -> MultiOut
lposcilsa2 i0init a1amp k2freqratio k3loop k4end i5ft
  = opcode "lposcilsa2" args
  where args
          = [to a1amp, to k2freqratio, to k3loop, to k4end, to i5ft] ++
              map to i0init


-- | * opcode : sndloop
--  
--  
-- * syntax : 
--  
--  >   asig, krec sndloop ain, kpitch, ktrig, idur, ifad
--  
--  
-- * description : 
--  
--  This opcode records input audio and plays it back in a loop with
-- user-defined duration and crossfade time. It also allows the
-- pitch of the loop to be controlled, including reversed playback.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sndloop.html>
 
sndloop ::
          (K k0, K k1) =>
          Arate -> k0 -> k1 -> Irate -> Irate -> (Arate, Krate)
sndloop a0in k1pitch k2trig i3dur i4fad
  = mo2 $ opcode "sndloop" args
  where args = [to a0in, to k1pitch, to k2trig, to i3dur, to i4fad]


-- | * opcode : waveset
--  
--  
-- * syntax : 
--  
--  >   ares waveset ain, krep [, ilen]
--  
--  
-- * description : 
--  
--  A simple time stretch by repeating cycles.
--  
--  
-- * url : <http://www.csounds.com/manual/html/waveset.html>
 
waveset :: (K k0) => [Irate] -> Arate -> k0 -> Arate
waveset i0init a1in k2rep = opcode "waveset" args
  where args = [to a1in, to k2rep] ++ map to i0init


-- | * opcode : fluidAllOut
--  
--  
-- * syntax : 
--  
--  >   aleft, aright fluidAllOut
--  
--  
-- * description : 
--  
--  Collects all audio from all Fluidsynth engines in a performance
--  
--  
-- * url : <http://www.csounds.com/manual/html/fluidAllOut.html>
 
fluidAllOut :: MultiOut
fluidAllOut = opcode "fluidAllOut" args
  where args = []


-- | * opcode : fluidCCi
--  
--  
-- * syntax : 
--  
--  >   fluidCCi iEngineNumber, iChannelNumber, iControllerNumber, iValue
--  
--  
-- * description : 
--  
--  Sends a MIDI controller data (MIDI controller number and value
-- to use) message to a fluid engine by number on the user specified
-- MIDI channel number.
--  
--  
-- * url : <http://www.csounds.com/manual/html/fluidCCi.html>
 
fluidCCi :: Irate -> Irate -> Irate -> Irate -> SignalOut
fluidCCi i0EngineNumber i1ChannelNumber i2ControllerNumber i3Value
  = outOpcode "fluidCCi" args
  where args
          = [to i0EngineNumber, to i1ChannelNumber, to i2ControllerNumber,
             to i3Value]


-- | * opcode : fluidCCk
--  
--  
-- * syntax : 
--  
--  >   fluidCCk iEngineNumber, iChannelNumber, iControllerNumber, kValue
--  
--  
-- * description : 
--  
--  Sends a MIDI controller data (MIDI controller number and value
-- to use) message to a fluid engine by number on the user specified
-- MIDI channel number.
--  
--  
-- * url : <http://www.csounds.com/manual/html/fluidCCk.html>
 
fluidCCk :: (K k0) => Irate -> Irate -> Irate -> k0 -> SignalOut
fluidCCk i0EngineNumber i1ChannelNumber i2ControllerNumber k3Value
  = outOpcode "fluidCCk" args
  where args
          = [to i0EngineNumber, to i1ChannelNumber, to i2ControllerNumber,
             to k3Value]


-- | * opcode : fluidControl
--  
--  
-- * syntax : 
--  
--  >   fluidControl ienginenum, kstatus, kchannel, kdata1, kdata2
--  
--  
-- * description : 
--  
--  The fluid opcodes provide a simple Csound opcode wrapper around
-- Peter Hanappe's Fluidsynth SoundFont2 synthesizer. This
-- implementation accepts any MIDI note on, note off, controller,
-- pitch bend, or program change message at k-rate. Maximum
-- polyphony is 4096 simultaneously sounding voices. Any number of
-- SoundFonts may be loaded and played simultaneously.
--  
--  
-- * url : <http://www.csounds.com/manual/html/fluidControl.html>
 
fluidControl ::
               (K k0, K k1, K k2, K k3) =>
               Irate -> k0 -> k1 -> k2 -> k3 -> SignalOut
fluidControl i0enginenum k1status k2channel k3data1 k4data2
  = outOpcode "fluidControl" args
  where args
          = [to i0enginenum, to k1status, to k2channel, to k3data1,
             to k4data2]


-- | * opcode : fluidEngine
--  
--  
-- * syntax : 
--  
--  >   ienginenum fluidEngine [iReverbEnabled] [, iChorusEnabled] [,iNumChannels] [, iPolyphony]
--  
--  
-- * description : 
--  
--  Instantiates a fluidsynth engine, and returns ienginenum to
-- identify the engine. ienginenum is passed to other other opcodes
-- for loading and playing SoundFonts and gathering the generated
-- sound.
--  
--  
-- * url : <http://www.csounds.com/manual/html/fluidEngine.html>
 
fluidEngine :: [Irate] -> Irate
fluidEngine i0init = opcode "fluidEngine" args
  where args = map to i0init


-- | * opcode : fluidLoad
--  
--  
-- * syntax : 
--  
--  >   isfnum fluidLoad soundfont, ienginenum[, ilistpresets]
--  
--  
-- * description : 
--  
--  Loads a SoundFont into an instance of a fluidEngine, optionally
-- listing banks and presets for SoundFont.
--  
--  
-- * url : <http://www.csounds.com/manual/html/fluidLoad.html>
 
fluidLoad :: [Irate] -> String -> Irate -> Irate
fluidLoad i0init s1soundfont i2enginenum = opcode "fluidLoad" args
  where args = [to s1soundfont, to i2enginenum] ++ map to i0init


-- | * opcode : fluidNote
--  
--  
-- * syntax : 
--  
--  >   fluidNote ienginenum, ichannelnum, imidikey, imidivel
--  
--  
-- * description : 
--  
--  Plays a note at imidikey pitch and imidivel velocity on
-- ichannelnum channel of number ienginenum fluidEngine.
--  
--  
-- * url : <http://www.csounds.com/manual/html/fluidNote.html>
 
fluidNote :: Irate -> Irate -> Irate -> Irate -> SignalOut
fluidNote i0enginenum i1channelnum i2midikey i3midivel
  = outOpcode "fluidNote" args
  where args
          = [to i0enginenum, to i1channelnum, to i2midikey, to i3midivel]


-- | * opcode : fluidOut
--  
--  
-- * syntax : 
--  
--  >   aleft, aright fluidOut ienginenum
--  
--  
-- * description : 
--  
--  Outputs the sound from a fluidEngine.
--  
--  
-- * url : <http://www.csounds.com/manual/html/fluidOut.html>
 
fluidOut :: Irate -> MultiOut
fluidOut i0enginenum = opcode "fluidOut" args
  where args = [to i0enginenum]


-- | * opcode : fluidProgramSelect
--  
--  
-- * syntax : 
--  
--  >   fluidProgramSelect ienginenum, ichannelnum, isfnum, ibanknum, ipresetnum
--  
--  
-- * description : 
--  
--  Assigns a preset from a SoundFont to a channel on a fluidEngine.
--  
--  
-- * url : <http://www.csounds.com/manual/html/fluidProgramSelect.html>
 
fluidProgramSelect ::
                     Irate -> Irate -> Irate -> Irate -> Irate -> SignalOut
fluidProgramSelect i0enginenum i1channelnum i2sfnum i3banknum
  i4presetnum = outOpcode "fluidProgramSelect" args
  where args
          = [to i0enginenum, to i1channelnum, to i2sfnum, to i3banknum,
             to i4presetnum]


-- | * opcode : fluidSetInterpMethod
--  
--  
-- * syntax : 
--  
--  >   fluidSetInterpMethod ienginenum, ichannelnum, iInterpMethod
--  
--  
-- * description : 
--  
--  Set interpolation method for channel in Fluid Engine. Lower
-- order interpolation methods will render faster at lower fidelity
-- while higher order interpolation methods will render slower at
-- higher fidelity. Default interpolation for a channel is 4th order
-- interpolation.
--  
--  
-- * url : <http://www.csounds.com/manual/html/fluidSetInterpMethod.html>
 
fluidSetInterpMethod :: Irate -> Irate -> Irate -> SignalOut
fluidSetInterpMethod i0enginenum i1channelnum i2InterpMethod
  = outOpcode "fluidSetInterpMethod" args
  where args = [to i0enginenum, to i1channelnum, to i2InterpMethod]


-- | * opcode : sfilist
--  
--  
-- * syntax : 
--  
--  >   sfilist ifilhandle
--  
--  
-- * description : 
--  
--  Prints a list of all instruments of a previously loaded
-- SoundFont2 (SF2) sample file. These opcodes allow management the
-- sample-structure of SF2 files. In order to understand the usage
-- of these opcodes, the user must have some knowledge of the SF2
-- format, so a brief description of this format can be found in the
-- SoundFont2 File Format Appendix.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sfilist.html>
 
sfilist :: Irate -> SignalOut
sfilist i0filhandle = outOpcode "sfilist" args
  where args = [to i0filhandle]


-- | * opcode : sfinstr
--  
--  
-- * syntax : 
--  
--  >   ar1, ar2 sfinstr ivel, inotenum, xamp, xfreq, instrnum, ifilhandle 
--  >       [, iflag] [, ioffset]
--  
--  
-- * description : 
--  
--  Plays a SoundFont2 (SF2) sample instrument, generating a stereo
-- sound. These opcodes allow management the sample-structure of SF2
-- files. In order to understand the usage of these opcodes, the
-- user must have some knowledge of the SF2 format, so a brief
-- description of this format can be found in the SoundFont2 File
-- Format Appendix.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sfinstr.html>
 
sfinstr ::
          (X x0, X x1) =>
          [Irate] -> Irate -> Irate -> x0 -> x1 -> Irate -> Irate -> MultiOut
sfinstr i0init i1vel i2notenum x3amp x4freq i5nstrnum i6filhandle
  = opcode "sfinstr" args
  where args
          = [to i1vel, to i2notenum, to x3amp, to x4freq, to i5nstrnum,
             to i6filhandle]
              ++ map to i0init


-- | * opcode : sfinstr3
--  
--  
-- * syntax : 
--  
--  >   ar1, ar2 sfinstr3 ivel, inotenum, xamp, xfreq, instrnum, ifilhandle 
--  >       [, iflag] [, ioffset]
--  
--  
-- * description : 
--  
--  Plays a SoundFont2 (SF2) sample instrument, generating a stereo
-- sound with cubic interpolation. These opcodes allow management
-- the sample-structure of SF2 files. In order to understand the
-- usage of these opcodes, the user must have some knowledge of the
-- SF2 format, so a brief description of this format can be found in
-- the SoundFont2 File Format Appendix.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sfinstr3.html>
 
sfinstr3 ::
           (X x0, X x1) =>
           [Irate] -> Irate -> Irate -> x0 -> x1 -> Irate -> Irate -> MultiOut
sfinstr3 i0init i1vel i2notenum x3amp x4freq i5nstrnum i6filhandle
  = opcode "sfinstr3" args
  where args
          = [to i1vel, to i2notenum, to x3amp, to x4freq, to i5nstrnum,
             to i6filhandle]
              ++ map to i0init


-- | * opcode : sfinstr3m
--  
--  
-- * syntax : 
--  
--  >   ares sfinstr3m ivel, inotenum, xamp, xfreq, instrnum, ifilhandle 
--  >       [, iflag] [, ioffset]
--  
--  
-- * description : 
--  
--  Plays a SoundFont2 (SF2) sample instrument, generating a mono
-- sound with cubic interpolation. These opcodes allow management
-- the sample-structure of SF2 files. In order to understand the
-- usage of these opcodes, the user must have some knowledge of the
-- SF2 format, so a brief description of this format can be found in
-- the SoundFont2 File Format Appendix.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sfinstr3m.html>
 
sfinstr3m ::
            (X x0, X x1) =>
            [Irate] -> Irate -> Irate -> x0 -> x1 -> Irate -> Irate -> Arate
sfinstr3m i0init i1vel i2notenum x3amp x4freq i5nstrnum i6filhandle
  = opcode "sfinstr3m" args
  where args
          = [to i1vel, to i2notenum, to x3amp, to x4freq, to i5nstrnum,
             to i6filhandle]
              ++ map to i0init


-- | * opcode : sfinstrm
--  
--  
-- * syntax : 
--  
--  >   ares sfinstrm ivel, inotenum, xamp, xfreq, instrnum, ifilhandle 
--  >       [, iflag] [, ioffset]
--  
--  
-- * description : 
--  
--  Plays a SoundFont2 (SF2) sample instrument, generating a mono
-- sound. These opcodes allow management the sample-structure of SF2
-- files. In order to understand the usage of these opcodes, the
-- user must have some knowledge of the SF2 format, so a brief
-- description of this format can be found in the SoundFont2 File
-- Format Appendix.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sfinstrm.html>
 
sfinstrm ::
           (X x0, X x1) =>
           [Irate] -> Irate -> Irate -> x0 -> x1 -> Irate -> Irate -> Arate
sfinstrm i0init i1vel i2notenum x3amp x4freq i5nstrnum i6filhandle
  = opcode "sfinstrm" args
  where args
          = [to i1vel, to i2notenum, to x3amp, to x4freq, to i5nstrnum,
             to i6filhandle]
              ++ map to i0init


-- | * opcode : sfload
--  
--  
-- * syntax : 
--  
--  >   ir sfload "filename"
--  
--  
-- * description : 
--  
--  Loads an entire SoundFont2 (SF2) sample file into memory. These
-- opcodes allow management the sample-structure of SF2 files. In
-- order to understand the usage of these opcodes, the user must
-- have some knowledge of the SF2 format, so a brief description of
-- this format can be found in the SoundFont2 File Format Appendix.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sfload.html>
 
sfload :: String -> Irate
sfload s0filename = opcode "sfload" args
  where args = [to s0filename]


-- | * opcode : sfpassign
--  
--  
-- * syntax : 
--  
--  >   sfpassign istartindex, ifilhandle[, imsgs]
--  
--  
-- * description : 
--  
--  Assigns all presets of a previously loaded SoundFont2 (SF2)
-- sample file to a sequence of progressive index numbers. These
-- opcodes allow management the sample-structure of SF2 files. In
-- order to understand the usage of these opcodes, the user must
-- have some knowledge of the SF2 format, so a brief description of
-- this format can be found in the SoundFont2 File Format Appendix.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sfpassign.html>
 
sfpassign :: [Irate] -> Irate -> Irate -> SignalOut
sfpassign i0init i1startindex i2filhandle
  = outOpcode "sfpassign" args
  where args = [to i1startindex, to i2filhandle] ++ map to i0init


-- | * opcode : sfplay
--  
--  
-- * syntax : 
--  
--  >   ar1, ar2 sfplay ivel, inotenum, xamp, xfreq, ipreindex [, iflag] [, ioffset] [, ienv]
--  
--  
-- * description : 
--  
--  Plays a SoundFont2 (SF2) sample preset, generating a stereo
-- sound. These opcodes allow management the sample-structure of SF2
-- files. In order to understand the usage of these opcodes, the
-- user must have some knowledge of the SF2 format, so a brief
-- description of this format can be found in the SoundFont2 File
-- Format Appendix.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sfplay.html>
 
sfplay ::
         (X x0, X x1) =>
         [Irate] -> Irate -> Irate -> x0 -> x1 -> Irate -> MultiOut
sfplay i0init i1vel i2notenum x3amp x4freq i5preindex
  = opcode "sfplay" args
  where args
          = [to i1vel, to i2notenum, to x3amp, to x4freq, to i5preindex] ++
              map to i0init


-- | * opcode : sfplay3
--  
--  
-- * syntax : 
--  
--  >   ar1, ar2 sfplay3 ivel, inotenum, xamp, xfreq, ipreindex [, iflag] [, ioffset] [, ienv]
--  
--  
-- * description : 
--  
--  Plays a SoundFont2 (SF2) sample preset, generating a stereo
-- sound with cubic interpolation. These opcodes allow management
-- the sample-structure of SF2 files. In order to understand the
-- usage of these opcodes, the user must have some knowledge of the
-- SF2 format, so a brief description of this format can be found in
-- the SoundFont2 File Format Appendix.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sfplay3.html>
 
sfplay3 ::
          (X x0, X x1) =>
          [Irate] -> Irate -> Irate -> x0 -> x1 -> Irate -> MultiOut
sfplay3 i0init i1vel i2notenum x3amp x4freq i5preindex
  = opcode "sfplay3" args
  where args
          = [to i1vel, to i2notenum, to x3amp, to x4freq, to i5preindex] ++
              map to i0init


-- | * opcode : sfplay3m
--  
--  
-- * syntax : 
--  
--  >   ares sfplay3m ivel, inotenum, xamp, xfreq, ipreindex [, iflag] [, ioffset] [, ienv]
--  
--  
-- * description : 
--  
--  Plays a SoundFont2 (SF2) sample preset, generating a mono sound
-- with cubic interpolation. These opcodes allow management the
-- sample-structure of SF2 files. In order to understand the usage
-- of these opcodes, the user must have some knowledge of the SF2
-- format, so a brief description of this format can be found in the
-- SoundFont2 File Format Appendix.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sfplay3m.html>
 
sfplay3m ::
           (X x0, X x1) =>
           [Irate] -> Irate -> Irate -> x0 -> x1 -> Irate -> Arate
sfplay3m i0init i1vel i2notenum x3amp x4freq i5preindex
  = opcode "sfplay3m" args
  where args
          = [to i1vel, to i2notenum, to x3amp, to x4freq, to i5preindex] ++
              map to i0init


-- | * opcode : sfplaym
--  
--  
-- * syntax : 
--  
--  >   ares sfplaym ivel, inotenum, xamp, xfreq, ipreindex [, iflag] [, ioffset] [, ienv]
--  
--  
-- * description : 
--  
--  Plays a SoundFont2 (SF2) sample preset, generating a mono sound.
-- These opcodes allow management the sample-structure of SF2 files.
-- In order to understand the usage of these opcodes, the user must
-- have some knowledge of the SF2 format, so a brief description of
-- this format can be found in the SoundFont2 File Format Appendix.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sfplaym.html>
 
sfplaym ::
          (X x0, X x1) =>
          [Irate] -> Irate -> Irate -> x0 -> x1 -> Irate -> Arate
sfplaym i0init i1vel i2notenum x3amp x4freq i5preindex
  = opcode "sfplaym" args
  where args
          = [to i1vel, to i2notenum, to x3amp, to x4freq, to i5preindex] ++
              map to i0init


-- | * opcode : sflooper
--  
--  
-- * syntax : 
--  
--  >   ar1, ar2 sflooper ivel, inotenum, kamp, kpitch, ipreindex, kloopstart, kloopend, kcrossfade, ifn 
--  >       [, istart, imode, ifenv, iskip]
--  
--  
-- * description : 
--  
--  Plays a SoundFont2 (SF2) sample preset, generating a stereo
-- sound, similarly to sfplay. Unlike that opcode, though, it
-- ignores the looping points set in the SF2 file and substitutes
-- them for a user-defined crossfade loop. It is a cross between
-- sfplay and flooper2.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sflooper.html>
 
sflooper ::
           (K k0, K k1, K k2, K k3, K k4) =>
           [Irate] ->
             Irate ->
               Irate -> k0 -> k1 -> Irate -> k2 -> k3 -> k4 -> Irate -> MultiOut
sflooper i0init i1vel i2notenum k3amp k4pitch i5preindex
  k6loopstart k7loopend k8crossfade i9fn = opcode "sflooper" args
  where args
          = [to i1vel, to i2notenum, to k3amp, to k4pitch, to i5preindex,
             to k6loopstart, to k7loopend, to k8crossfade, to i9fn]
              ++ map to i0init


-- | * opcode : sfplist
--  
--  
-- * syntax : 
--  
--  >   sfplist ifilhandle
--  
--  
-- * description : 
--  
--  Prints a list of all presets of a previously loaded SoundFont2
-- (SF2) sample file. These opcodes allow management the
-- sample-structure of SF2 files. In order to understand the usage
-- of these opcodes, the user must have some knowledge of the SF2
-- format, so a brief description of this format can be found in the
-- SoundFont2 File Format Appendix.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sfplist.html>
 
sfplist :: Irate -> SignalOut
sfplist i0filhandle = outOpcode "sfplist" args
  where args = [to i0filhandle]


-- | * opcode : sfpreset
--  
--  
-- * syntax : 
--  
--  >   ir sfpreset iprog, ibank, ifilhandle, ipreindex
--  
--  
-- * description : 
--  
--  Assigns an existing preset of a previously loaded SoundFont2
-- (SF2) sample file to an index number. These opcodes allow
-- management the sample-structure of SF2 files. In order to
-- understand the usage of these opcodes, the user must have some
-- knowledge of the SF2 format, so a brief description of this
-- format can be found in the SoundFont2 File Format Appendix.
--  
--  
-- * url : <http://www.csounds.com/manual/html/sfpreset.html>
 
sfpreset :: Irate -> Irate -> Irate -> Irate -> Irate
sfpreset i0prog i1bank i2filhandle i3preindex
  = opcode "sfpreset" args
  where args = [to i0prog, to i1bank, to i2filhandle, to i3preindex]