-- | Reverberation
module CsoundExpr.Opcodes.Sigmod.Reverbtn
    (alpass,
     babo,
     comb,
     freeverb,
     nestedap,
     nreverb,
     reverb2,
     reverb,
     reverbsc,
     valpass,
     vcomb)
where



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



-- | * opcode : alpass
--  
--  
-- * syntax : 
--  
--  >   ares alpass asig, krvt, ilpt [, iskip] [, insmps]
--  
--  
-- * description : 
--  
--  Reverberates an input signal with a flat frequency response.
--  
--  
-- * url : <http://www.csounds.com/manual/html/alpass.html>
 
alpass :: (K k0) => [Irate] -> Arate -> k0 -> Irate -> Arate
alpass i0init a1sig k2rvt i3lpt = opcode "alpass" args
  where args = [to a1sig, to k2rvt, to i3lpt] ++ map to i0init


-- | * opcode : babo
--  
--  
-- * syntax : 
--  
--  >   a1, a2 babo asig, ksrcx, ksrcy, ksrcz, irx, iry, irz [, idiff] [, ifno]
--  
--  
-- * description : 
--  
--  babo stands for ball-within-the-box. It is a physical model
-- reverberator based on the paper by Davide Rocchesso "The Ball
-- within the Box: a sound-processing metaphor", Computer Music
-- Journal, Vol 19, N.4, pp.45-47, Winter 1995.
--  
--  
-- * url : <http://www.csounds.com/manual/html/babo.html>
 
babo ::
       (K k0, K k1, K k2) =>
       [Irate] ->
         Arate -> k0 -> k1 -> k2 -> Irate -> Irate -> Irate -> MultiOut
babo i0init a1sig k2srcx k3srcy k4srcz i5rx i6ry i7rz
  = opcode "babo" args
  where args
          = [to a1sig, to k2srcx, to k3srcy, to k4srcz, to i5rx, to i6ry,
             to i7rz]
              ++ map to i0init


-- | * opcode : comb
--  
--  
-- * syntax : 
--  
--  >   ares comb asig, krvt, ilpt [, iskip] [, insmps]
--  
--  
-- * description : 
--  
--  Reverberates an input signal with a colored frequency response.
--  
--  
-- * url : <http://www.csounds.com/manual/html/comb.html>
 
comb :: (K k0) => [Irate] -> Arate -> k0 -> Irate -> Arate
comb i0init a1sig k2rvt i3lpt = opcode "comb" args
  where args = [to a1sig, to k2rvt, to i3lpt] ++ map to i0init


-- | * opcode : freeverb
--  
--  
-- * syntax : 
--  
--  >   aoutL, aoutR freeverb ainL, ainR, kRoomSize, kHFDamp[, iSRate[, iSkip]]
--  
--  
-- * description : 
--  
--  freeverb is a stereo reverb unit based on Jezar's public domain
-- C++ sources, composed of eight parallel comb filters on both
-- channels, followed by four allpass units in series. The filters
-- on the right channel are slightly detuned compared to the left
-- channel in order to create a stereo effect.
--  
--  
-- * url : <http://www.csounds.com/manual/html/freeverb.html>
 
freeverb ::
           (K k0, K k1) => [Irate] -> Arate -> Arate -> k0 -> k1 -> MultiOut
freeverb i0init a1inL a2inR k3RoomSize k4HFDamp
  = opcode "freeverb" args
  where args
          = [to a1inL, to a2inR, to k3RoomSize, to k4HFDamp] ++ map to i0init


-- | * opcode : nestedap
--  
--  
-- * syntax : 
--  
--  >   ares nestedap asig, imode, imaxdel, idel1, igain1 [, idel2] [, igain2] 
--  >       [, idel3] [, igain3] [, istor]
--  
--  
-- * description : 
--  
--  Three different nested all-pass filters, useful for implementing
-- reverbs.
--  
--  
-- * url : <http://www.csounds.com/manual/html/nestedap.html>
 
nestedap ::
           [Irate] -> Arate -> Irate -> Irate -> Irate -> Irate -> Arate
nestedap i0init a1sig i2mode i3maxdel i4del1 i5gain1
  = opcode "nestedap" args
  where args
          = [to a1sig, to i2mode, to i3maxdel, to i4del1, to i5gain1] ++
              map to i0init


-- | * opcode : nreverb
--  
--  
-- * syntax : 
--  
--  >   ares nreverb asig, ktime, khdif [, iskip] [,inumCombs] [, ifnCombs] 
--  >       [, inumAlpas] [, ifnAlpas]
--  
--  
-- * description : 
--  
--  This is a reverberator consisting of 6 parallel comb-lowpass
-- filters being fed into a series of 5 allpass filters. nreverb
-- replaces reverb2 (version 3.48) and so both opcodes are
-- identical.
--  
--  
-- * url : <http://www.csounds.com/manual/html/nreverb.html>
 
nreverb :: (K k0, K k1) => [Irate] -> Arate -> k0 -> k1 -> Arate
nreverb i0init a1sig k2time k3hdif = opcode "nreverb" args
  where args = [to a1sig, to k2time, to k3hdif] ++ map to i0init


-- | * opcode : reverb2
--  
--  
-- * syntax : 
--  
--  >   ares reverb2 asig, ktime, khdif [, iskip] [,inumCombs] 
--  >       [, ifnCombs] [, inumAlpas] [, ifnAlpas]
--  
--  
-- * description : 
--  
--  Same as the nreverb opcode.
--  
--  
-- * url : <http://www.csounds.com/manual/html/reverb2.html>
 
reverb2 :: (K k0, K k1) => [Irate] -> Arate -> k0 -> k1 -> Arate
reverb2 i0init a1sig k2time k3hdif = opcode "reverb2" args
  where args = [to a1sig, to k2time, to k3hdif] ++ map to i0init


-- | * opcode : reverb
--  
--  
-- * syntax : 
--  
--  >   ares reverb asig, krvt [, iskip]
--  
--  
-- * description : 
--  
--  Reverberates an input signal with a natural room frequency
-- response.
--  
--  
-- * url : <http://www.csounds.com/manual/html/reverb.html>
 
reverb :: (K k0) => [Irate] -> Arate -> k0 -> Arate
reverb i0init a1sig k2rvt = opcode "reverb" args
  where args = [to a1sig, to k2rvt] ++ map to i0init


-- | * opcode : reverbsc
--  
--  
-- * syntax : 
--  
--  >   aoutL, aoutR reverbsc ainL, ainR, kfblvl, kfco[, israte[, ipitchm[, iskip]]]
--  
--  
-- * description : 
--  
--  8 delay line stereo FDN reverb, with feedback matrix based upon
-- physical modeling scattering junction of 8 lossless waveguides of
-- equal characteristic impedance. Based on Csound orchestra version
-- by Sean Costello.
--  
--  
-- * url : <http://www.csounds.com/manual/html/reverbsc.html>
 
reverbsc ::
           (K k0, K k1) => [Irate] -> Arate -> Arate -> k0 -> k1 -> MultiOut
reverbsc i0init a1inL a2inR k3fblvl k4fco = opcode "reverbsc" args
  where args
          = [to a1inL, to a2inR, to k3fblvl, to k4fco] ++ map to i0init


-- | * opcode : valpass
--  
--  
-- * syntax : 
--  
--  >   ares valpass asig, krvt, xlpt, imaxlpt [, iskip] [, insmps]
--  
--  
-- * description : 
--  
--  Variably reverberates an input signal with a flat frequency
-- response.
--  
--  
-- * url : <http://www.csounds.com/manual/html/valpass.html>
 
valpass ::
          (K k0, X x0) => [Irate] -> Arate -> k0 -> x0 -> Irate -> Arate
valpass i0init a1sig k2rvt x3lpt i4maxlpt = opcode "valpass" args
  where args
          = [to a1sig, to k2rvt, to x3lpt, to i4maxlpt] ++ map to i0init


-- | * opcode : vcomb
--  
--  
-- * syntax : 
--  
--  >   ares vcomb asig, krvt, xlpt, imaxlpt [, iskip] [, insmps]
--  
--  
-- * description : 
--  
--  Variably reverberates an input signal with a colored frequency
-- response.
--  
--  
-- * url : <http://www.csounds.com/manual/html/vcomb.html>
 
vcomb ::
        (K k0, X x0) => [Irate] -> Arate -> k0 -> x0 -> Irate -> Arate
vcomb i0init a1sig k2rvt x3lpt i4maxlpt = opcode "vcomb" args
  where args
          = [to a1sig, to k2rvt, to x3lpt, to i4maxlpt] ++ map to i0init