Contact: david.ogborn@utoronto.ca
Project hosted by: sourceForge.net
module Generators

The module Generators is a large (and growing) collection of functions, useful for electronic music, based on the modules Allegory, Sndfile and Csound. It can be used as an example of what to do with these more general libraries, or as a collection of useful tools in their own right.

It is, however, largely undocumented...


{- Csound-based generators for Allegory
     by David Ogborn
-}

module Generators where
import Allegory
import Csound
import Hugs.Quote
import System
import IO
import Sndfile
import List
      
ampScale :: Double -> FilePath -> Sound
ampScale scale inputTarget = csound csdStr
 where durationS = show (sfDuration inputTarget)
       scaleS = show scale
       nchnls = sfChannels inputTarget
       diskin
        | nchnls == 1 = "a1"
        | nchnls == 2 = "a1,a2"
        | nchnls == 4 = "a1,a2,a3,a4"
       out
        | nchnls == 1 = "out a1*iscale"
        | nchnls == 2 = "outs a1*iscale,a2*iscale"
        | nchnls == 4 = "outq a1*iscale,a2*iscale,a3*iscale,a4*iscale"
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=$(nchnls)
instr 1
iscale = $(scaleS)
           $(diskin) diskin "$(inputTarget)", 1
           $(out)
endin
</CsInstruments>
<CsScore>
i1 0 $(durationS)
</CsScore>
</CsoundSynthesizer>''

ampScaleLinear :: Double -> Double -> FilePath -> Sound
ampScaleLinear a1 a2 inputTarget = csound csdStr
 where durationS = show (sfDuration inputTarget)
       nchnls = sfChannels inputTarget
       diskin
        | nchnls == 1 = "a1"
        | nchnls == 2 = "a1,a2"
        | nchnls == 4 = "a1,a2,a3,a4"
       out
        | nchnls == 1 = "out a1*aenv"
        | nchnls == 2 = "outs a1*aenv,a2*aenv"
        | nchnls == 4 = "outq a1*aenv,a2*aenv,a3*aenv,a4*aenv"
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=$(nchnls)
instr 1
           aenv linseg $(a1),p3,$(a2)
           $(diskin) diskin "$(inputTarget)", 1
           $(out)
endin
</CsInstruments>
<CsScore>
i1 0 $(durationS)
</CsScore>
</CsoundSynthesizer>''

ampScaleExponential :: Double -> Double -> FilePath -> Sound
ampScaleExponential a1 a2 inputTarget = csound csdStr
 where durationS = show (sfDuration inputTarget)
       nchnls = sfChannels inputTarget
       diskin
        | nchnls == 1 = "a1"
        | nchnls == 2 = "a1,a2"
        | nchnls == 4 = "a1,a2,a3,a4"
       out
        | nchnls == 1 = "out a1*aenv"
        | nchnls == 2 = "outs a1*aenv,a2*aenv"
        | nchnls == 4 = "outq a1*aenv,a2*aenv,a3*aenv,a4*aenv"
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=$(nchnls)
instr 1
           aenv expseg $(a1),p3,$(a2)
           $(diskin) diskin "$(inputTarget)", 1
           $(out)
endin
</CsInstruments>
<CsScore>
i1 0 $(durationS)
</CsScore>
</CsoundSynthesizer>''


fadeInExponential :: Double -> Double -> Double -> FilePath -> Sound
fadeInExponential a1 a2 t inputTarget = csound csdStr
 where durationS = show (sfDuration inputTarget)
       nchnls = sfChannels inputTarget
       diskin
        | nchnls == 1 = "a1"
        | nchnls == 2 = "a1,a2"
        | nchnls == 4 = "a1,a2,a3,a4"
       out
        | nchnls == 1 = "out a1*aenv"
        | nchnls == 2 = "outs a1*aenv,a2*aenv"
        | nchnls == 4 = "outq a1*aenv,a2*aenv,a3*aenv,a4*aenv"
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=$(nchnls)
instr 1
           aenv expseg $(a1),$(t),$(a2),p3-$(t),$(a2)
           $(diskin) diskin "$(inputTarget)", 1
           $(out)
endin
</CsInstruments>
<CsScore>
i1 0 $(durationS)
</CsScore>
</CsoundSynthesizer>''



speedChange :: Double -> FilePath -> Sound
speedChange speed f = csound csdStr
 where
   duration = (sfDuration f)/speed
   nchnls = sfChannels f
   diskin
    | nchnls == 1 = "a1"
    | nchnls == 2 = "a1,a2"
    | nchnls == 4 = "a1,a2,a3,a4"
   out
    | nchnls == 1 = "out a1"
    | nchnls == 2 = "outs a1,a2"
    | nchnls == 4 = "outq a1,a2,a3,a4"
   csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=$(nchnls)
instr 1
     $(diskin) diskin "$(f)",$(speed)
     $(out)
endin
</CsInstruments>
<CsScore>
i1 0 $(duration)
</CsScore>
</CsoundSynthesizer>''

reverseSound :: FilePath -> Sound
reverseSound f = csound csdStr
 where nchnls = sfChannels f
       buffers
        | nchnls==1 = "a1"
        | nchnls==2 = "a1,a2"
        | nchnls==4 = "a1,a2,a3,a4"
       output
        | nchnls==1 = "out "++buffers
        | nchnls==2 = "outs "++buffers
        | nchnls==4 = "outq "++buffers
       dur = sfDuration f
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=100
ksmps=441
nchnls=$(nchnls)
instr 1
          $(buffers) diskin "$(f)", -1.0, $(dur)
          $(output)
endin
</CsInstruments>
<CsScore>
i1 0 $(dur)
</CsScore>
</CsoundSynthesizer>''


{- pScale is in semitones -}
resynthesis :: FilePath -> Double -> Double -> Double -> Double -> Double -> Sound
resynthesis f scanStart scanEnd pScale duration aScale = csound csdStr
 where scanStartS = show scanStart
       scanEndS = show scanEnd
       durationS = show duration
       pScaleS = show ((exp ((log 2.0) / 12.0)) ** pScale)
       aScaleS = show aScale
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=100
ksmps=441
nchnls=1
; i1 p2=startTime p3=duration
instr 1
ktime linseg $(scanStartS), p3, $(scanEndS)
asig pvoc ktime, $(pScaleS), "$(f)"
 out asig*$(aScaleS)
endin
</CsInstruments>
<CsScore>
i1 0 $(durationS)
</CsScore>
</CsoundSynthesizer>''


resonator :: Double -> Double -> [String] -> FilePath -> Sound
resonator bwStart bwEnd pitchList inputTarget = csound csdStr
  where duration = sfDuration inputTarget
        csdStr = (``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=1
instr 1
ifreq init cpspch(p4)
kbw line ifreq*p5,p3,ifreq*p6
a1 diskin "$(inputTarget)",1
a2 resonz a1,ifreq,kbw,2
out a2
endin
</CsInstruments>
<CsScore>'' ++ (concat [("i1 0 "++(show duration)++" "++p++" "++(show bwStart)++" "++(show bwEnd)++"\n") | p <-pitchList]) ++ ``</CsScore>
</CsoundSynthesizer>'')

ringModulate :: FilePath -> FilePath -> Sound
ringModulate i1 i2 = csound csdStr
 where nchnls = min (sfChannels i1) (sfChannels i2)
       d = min (sfDuration i1) (sfDuration i2)
       buffers1
        | nchnls==1 = "a1a"
        | nchnls==2 = "a1a,a2a"
        | nchnls==4 = "a1a,a2a,a3a,a4a"
       buffers2
        | nchnls==1 = "a1b"
        | nchnls==2 = "a1b,a2b"
        | nchnls==4 = "a1b,a2b,a3b,a4b"
       output
        | nchnls==1 = "out (a1a/32767)*(a1b/32767)*32767"
        | nchnls==2 = "outs (a1a/32767)*(a1b/32767)*32767, (a2a/32767)*(a2b/32767)*32767"
        | nchnls==4 = "outq (a1a/32767)*(a1b/32767)*32767, (a2a/32767)*(a2b/32767)*32767, (a3a/32767)*(a3b/32767)*32767, (a4a/32767)*(a4b/32767)*32767"
       csdStr = ``<CsoundSynthesizer>
<CsScore>
i1 0 $(d)
</CsScore>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=$(nchnls)
instr 1
         $(buffers1) diskin "$(i1)",1
         $(buffers2) diskin "$(i2)",1
         $(output)
endin
</CsInstruments>
</CsoundSynthesizer>''

scaledRingModulate :: Double -> FilePath -> FilePath -> Sound
scaledRingModulate s i1 i2 = csound csdStr
 where nchnls = min (sfChannels i1) (sfChannels i2)
       d = min (sfDuration i1) (sfDuration i2)
       ss = show (s*32767.0)
       buffers1
        | nchnls==1 = "a1a"
        | nchnls==2 = "a1a,a2a"
        | nchnls==4 = "a1a,a2a,a3a,a4a"
       buffers2
        | nchnls==1 = "a1b"
        | nchnls==2 = "a1b,a2b"
        | nchnls==4 = "a1b,a2b,a3b,a4b"
       output
        | nchnls==1 = "out (a1a/32767)*(a1b/32767)*"++ss
        | nchnls==2 = "outs (a1a/32767)*(a1b/32767)*"++ss++", (a2a/32767)*(a2b/32767)*"++ss
        | nchnls==4 = "outq (a1a/32767)*(a1b/32767)*"++ss++", (a2a/32767)*(a2b/32767)*"++ss++", (a3a/32767)*(a3b/32767)*"++ss++", (a4a/32767)*(a4b/32767)*"++ss
       csdStr = ``<CsoundSynthesizer>
<CsScore>
i1 0 $(d)
</CsScore>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=$(nchnls)
instr 1
         $(buffers1) diskin "$(i1)",1
         $(buffers2) diskin "$(i2)",1
         $(output)
endin
</CsInstruments>
</CsoundSynthesizer>''


loopedRingModulation :: FilePath -> FilePath -> Sound
loopedRingModulation loopedInput fixedInput = csound csdStr
  where looppoint = show ((sfSampleCount loopedInput)-1)
        fixedDuration = show (sfDuration fixedInput)
        csdStr = ``<CsoundSynthesizer>
<CsScore>
f1 0 0 1 "$(loopedInput)" 0 0 0
i1 0 $(fixedDuration)
</CsScore>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=1
instr 1
a1 loscil 1, 440, 1, 440, 1, 0, $(looppoint)
a2 diskin "$(fixedInput)",1
out a1*a2
endin
</CsInstruments>
</CsoundSynthesizer>''


stringTogetherF :: [FilePath] -> [(FilePath,Double)]
stringTogether :: [FilePath] -> Sound
stringTogetherF inputTargets = [(x,y) | (x,y) <- zip inputTargets (runningTotal 0.0 (map sfDuration inputTargets))]
stringTogether = compose . stringTogetherF

leftAlignF :: [FilePath] -> [(FilePath,Double)]
leftAlign :: [FilePath] -> Sound
leftAlignF inputTargets = [ (x,0.0) | x <- inputTargets ]
leftAlign = compose . leftAlignF

centreAlignF :: [FilePath] -> [(FilePath,Double)]
centreAlign :: [FilePath] -> Sound
centreAlignF inputTargets = [ (x,y) | (x,y) <- zip inputTargets startTimes ]
 where durations = map sfDuration inputTargets
       startTimes = [ ((maximum durations) / 2.0) - (d / 2.0) | d <- durations]
centreAlign = compose . centreAlignF

rightAlignF :: [FilePath] -> [(FilePath,Double)]
rightAlign :: [FilePath] -> Sound
rightAlignF inputTargets = [ (x,y) | (x,y) <- zip inputTargets startTimes ]
 where durations = map sfDuration inputTargets
       startTimes = [ (maximum durations)-d | d <- durations]
rightAlign = compose . rightAlignF

alignSpecificF :: [(FilePath,Double)] -> [(FilePath,Double)]
alignSpecific :: [(FilePath,Double)] -> Sound
alignSpecificF inputTargets = zip (map fst inputTargets) startTimes
 where xs = map snd inputTargets
       startTimes = [ (maximum xs) - x | x <- xs ]
alignSpecific = compose . alignSpecificF



locsig :: Double -> Double -> Double -> Double -> Double -> FilePath -> Sound
locsig degree distance reverb rvbTime rvbDiff inputTarget = csound csdStr
 where degreeS = show degree
       distanceS = show distance
       reverbS = show reverb
       rvbTimeS = show rvbTime
       rvbDiffS = show rvbDiff
       durationS = show (sfDuration inputTarget)
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=2
instr 1
a1 diskin "$(inputTarget)",1
al, ar locsig a1, $(degreeS), $(distanceS), $(reverbS)
asendl,asendr locsend
arl nreverb asendl, $(rvbTimeS), $(rvbDiffS)
arr nreverb asendr, $(rvbTimeS), $(rvbDiffS)
outs al+arl,ar+arr
endin
</CsInstruments>
<CsScore>
i1 0 $(durationS)
</CsScore>
</CsoundSynthesizer>''


stereoPan :: Double -> FilePath -> Sound
stereoPan degrees f = csound csdStr
 where d = sfDuration f
       l = 1.0 - (degrees / 90.0)
       r = degrees / 90.0
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=2
instr 1
a1 diskin "$(f)",1
al = a1 * $(l)
ar = a1 * $(r)
outs al,ar
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''

releaseReverbStereo :: Double -> Double -> Double -> Double -> Double -> Double -> FilePath -> Sound
releaseReverbStereo seconds r1 r2 rvbTime rvbDiff extender inputTarget = csound csdStr
 where secondsS = show seconds
       r1S = show r1
       r2S = show r2
       rvbTimeS = show rvbTime
       rvbDiffS = show rvbDiff
       fdur = sfDuration inputTarget
       onTime = fdur - seconds
       tdur = fdur + extender
       onTimeS = show onTime
       tdurS = show tdur
       fdurS = show fdur
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=2
gal init 0
gar init 0
instr 1
a1l,a1r diskin "$(inputTarget)",1
krvb linseg 0, $(onTimeS), 0, 0.001, $(r1S), p3-$(onTimeS)-0.001, $(r2S)
gal = gal + a1l*krvb
gar = gar + a1r*krvb
outs a1l,a1r
endin
instr 2
al nreverb gal, $(rvbTimeS), $(rvbDiffS)
ar nreverb gar, $(rvbTimeS), $(rvbDiffS)
gal = 0
gar = 0
outs al,ar
endin
</CsInstruments>
<CsScore>
i1 0 $(fdurS)
i2 0 $(tdurS)
</CsScore>
</CsoundSynthesizer>''

releaseReverbQuad :: Double -> Double -> Double -> Double -> Double -> Double -> FilePath -> Sound
releaseReverbQuad seconds r1 r2 rvbTime rvbDiff extender inputTarget = csound csdStr
 where secondsS = show seconds
       r1S = show r1
       r2S = show r2
       rvbTimeS = show rvbTime
       rvbDiffS = show rvbDiff
       fdur = sfDuration inputTarget
       onTime = fdur - seconds
       tdur = fdur + extender
       onTimeS = show onTime
       tdurS = show tdur
       fdurS = show fdur
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=4
gaw init 0
gax init 0
gay init 0
gaz init 0
instr 1
a1w,a1x,a1y,a1z diskin "$(inputTarget)",1
krvb linseg 0, $(onTimeS), 0, 0.001, $(r1S), p3-$(onTimeS)-0.001, $(r2S)
gaw = gaw + a1w*krvb
gax = gax + a1x*krvb
gay = gay + a1y*krvb
gaz = gaz + a1z*krvb
outq a1w,a1x,a1y,a1z
endin
instr 2
aw nreverb gaw, $(rvbTimeS), $(rvbDiffS)
ax nreverb gax, $(rvbTimeS), $(rvbDiffS)
ay nreverb gay, $(rvbTimeS), $(rvbDiffS)
az nreverb gaz, $(rvbTimeS), $(rvbDiffS)
gaw = 0
gax = 0
gay = 0
gaz = 0
outq aw,ax,ay,az
endin
</CsInstruments>
<CsScore>
i1 0 $(fdurS)
i2 0 $(tdurS)
</CsScore>
</CsoundSynthesizer>''

nreverb :: Double -> Double -> Double -> Double -> FilePath -> Sound
nreverb rvbTime diffusion dry wet f = csound csdStr
 where d = sfDuration f
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=1
instr 1
a1 diskin "$(f)",1
ar nreverb a1, $(rvbTime), $(diffusion)
out (a1*$(dry))+(ar*$(wet))
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''


balance :: FilePath -> FilePath -> Sound
balance mask input = csound csdStr
 where maskD = sfDuration mask
       maskS = show maskD
       inputD = sfDuration input
       inputS = show inputD
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=1
instr 1
a1 diskin "$(mask)",1
a2 diskin "$(input)",1
a3 balance a2,a1
out a3
endin
</CsInstruments>
<CsScore>
i1 0 $(maskS)
</CsScore>
</CsoundSynthesizer>''
       
accumulator :: [(FilePath,Double)] -> Double -> Double -> Double -> Double -> Sound
accumulator inputs duration delay fdbk amp = csound csdStr
 where iTargets = [ x | (x,y) <- inputs]
       durations = map sfDuration iTargets
       startTimes = [ y | (x,y) <- inputs ]
       durationS = show duration
       ampS = show amp
       delayS = show delay
       fdbkS = show fdbk
       csdStr = (``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=1
gainput init 0
instr 1
a1 diskin p4, 1
gainput = gainput+(a1*$(ampS))
endin
instr 2
a1 init 0
a1 delay gainput+(a1*$(fdbkS)), $(delayS)
out a1+gainput
gainput=0
endin
</CsInstruments>
<CsScore>
i2 0 $(durationS)'' ++ "\n" ++ (concat [("i1 " ++ (show s) ++ " " ++ (show d) ++ " \"" ++ f ++ "\"\n") | (s,d,f) <- zip3 startTimes durations iTargets]) ++ "</CsScore>\n</CsoundSynthesizer>\n")

stereoAccumulator :: [(FilePath,Double)] -> Double -> Double -> Double -> Double -> Sound
stereoAccumulator inputs duration delay fdbk amp = csound csdStr
 where iTargets = [ x | (x,y) <- inputs]
       durations = map sfDuration iTargets
       startTimes = [ y | (x,y) <- inputs ]
       durationS = show duration
       ampS = show amp
       delayS = show delay
       fdbkS = show fdbk
       csdStr = (``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=2
gainput1 init 0
gainput2 init 0
instr 1
a1,a2 diskin p4, 1
gainput1 = gainput1+(a1*$(ampS))
gainput2 = gainput2+(a2*$(ampS))
endin
instr 2
a1 init 0
a2 init 0
a1 delay gainput1+(a1*$(fdbkS)), $(delayS)
a2 delay gainput2+(a2*$(fdbkS)), $(delayS)
outs a1+gainput1,a2+gainput2
gainput1=0
gainput2=0
endin
</CsInstruments>
<CsScore>
i2 0 $(durationS)'' ++ "\n" ++ (concat [("i1 " ++ (show s) ++ " " ++ (show d) ++ " \"" ++ f ++ "\"\n") | (s,d,f) <- zip3 startTimes durations iTargets]) ++ "</CsScore>\n</CsoundSynthesizer>\n")


compose :: [(FilePath,Double)] -> Sound
composeCsdScore :: [(FilePath,Double)] -> String

composeCsdScore inputTargets = "\n<CsScore>\n" ++ (concat [("i" ++ (show (sfChannels f)) ++ " " ++ (show s) ++ " " ++ (show d) ++ " \"" ++ f ++ "\"\n") | (s,d,f) <- zip3 startTimes durations targetList]) ++ "</CsScore>\n</CsoundSynthesizer>\n"
  where targetList = [ x | (x,y) <- inputTargets ]
        startTimes = [ y | (x,y) <- inputTargets ]
        durations = map sfDuration targetList

compose x = csound (csdOrc ++ (composeCsdScore x))
  where nchnls = maximum (map (\(f,_)->sfChannels f) x)
        out1
         | nchnls ==1 = "out a1"
         | nchnls ==2 = "outs a1,a1"
         | nchnls ==4 = "outq a1,a1,a1,a1"
        out2
         | nchnls ==1 = "out (a1+a2)*0.5"
         | nchnls ==2 = "outs a1,a2"
         | nchnls ==4 = "outq a1,a2,a1,a2"
        out4
         | nchnls ==1 = "out (a1+a2+a3+a4)*0.25"
         | nchnls ==2 = "outs (a1+a2)*0.5,(a3+a4)*0.5"
         | nchnls ==4 = "outq a1,a2,a3,a4"
        csdOrc = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=$(nchnls)
instr 1
a1 diskin p4,1
          $(out1)
endin
instr 2
a1,a2 diskin p4,1
          $(out2)
endin
instr 4
a1,a2,a3,a4 diskin p4,1
          $(out4)
endin
</CsInstruments>''

composeWithSkip :: [(FilePath,Double,Double,Double)] -> Sound
composeWithSkipCsdScore :: [(FilePath,Double,Double,Double)] -> String

composeWithSkipCsdScore inputTargets = "\n<CsScore>\n" ++ (concat [("i" ++ (show (sfChannels f)) ++ " " ++ (show s) ++ " " ++ (show d) ++ " \"" ++ f ++ "\" " ++ (show skip) ++ "\n") | (s,d,f,skip) <- zip4 startTimes durations targetList skipTimes]) ++ "</CsScore>\n</CsoundSynthesizer>\n"
  where targetList = [ x | (x,_,_,_) <- inputTargets ]
        startTimes = [ x | (_,x,_,_) <- inputTargets ]
        durations = [ x | (_,_,x,_) <- inputTargets ]
        skipTimes = [ x | (_,_,_,x) <- inputTargets ]

composeWithSkip x = csound (csdOrc ++ (composeWithSkipCsdScore x))
  where nchnls = maximum (map (\(f,_,_,_)->sfChannels f) x)
        out1
         | nchnls ==1 = "out a1"
         | nchnls ==2 = "outs a1,a1"
         | nchnls ==4 = "outq a1,a1,a1,a1"
        out2
         | nchnls ==1 = "out (a1+a2)*0.5"
         | nchnls ==2 = "outs a1,a2"
         | nchnls ==4 = "outq a1,a2,a1,a2"
        out4
         | nchnls ==1 = "out (a1+a2+a3+a4)*0.25"
         | nchnls ==2 = "outs (a1+a2)*0.5,(a3+a4)*0.5"
         | nchnls ==4 = "outq a1,a2,a3,a4"
        csdOrc = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=$(nchnls)
instr 1
a1 diskin p4,1,p5
          $(out1)
endin
instr 2
a1,a2 diskin p4,1,p5
          $(out2)
endin
instr 4
a1,a2,a3,a4 diskin p4,1,p5
          $(out4)
endin
</CsInstruments>''


loop :: FilePath -> Double -> Sound
loop f d = csound csdStr
 where nchnls = sfChannels f
       diskin
        | nchnls==1 = "a1"
        | nchnls==2 = "a1,a2"
        | nchnls==4 = "a1,a2,a3,a4"
       out
        | nchnls==1 = "out a1"
        | nchnls==2 = "outs a1,a2"
        | nchnls==4 = "outq a1,a2,a3,a4"
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=$(nchnls)
instr 1
          $(diskin) diskin "$(f)",1,0,1
          $(out)
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''



fadeIn :: Double -> FilePath -> Sound
fadeIn l f = csound csdStr
 where d = sfDuration f
       a = d-l
       nchnls = sfChannels f
       diskin
        | nchnls ==1 = "a1"
        | nchnls ==2 = "a1,a2"
        | nchnls ==4 = "a1,a2,a3,a4"
       out
        | nchnls ==1 = "out a1*aenv"
        | nchnls ==2 = "outs a1*aenv,a2*aenv"
        | nchnls ==4 = "outq a1*aenv,a2*aenv,a3*aenv,a4*aenv"
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=$(nchnls)
instr 1
         $(diskin) diskin "$(f)",1
         aenv linseg 0.0,$(l),1.0,$(a),1.0
         $(out)
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''

{- deprecated. -}
fadeInStereo = fadeIn


fadeOut :: Double -> FilePath -> Sound
fadeOut l f = csound csdStr
 where d = sfDuration f
       a = d-l
       nchnls = sfChannels f
       diskin
        | nchnls ==1 = "a1"
        | nchnls ==2 = "a1,a2"
        | nchnls ==4 = "a1,a2,a3,a4"
       out
        | nchnls ==1 = "out a1*aenv"
        | nchnls ==2 = "outs a1*aenv,a2*aenv"
        | nchnls ==4 = "outq a1*aenv,a2*aenv,a3*aenv,a4*aenv"
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=$(nchnls)
instr 1
          $(diskin) diskin "$(f)",1
          aenv linseg 1.0,$(a),1.0,$(l),0.0
          $(out)
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''

asr :: Double -> Double -> Double -> FilePath -> Sound
asr a s r f = csound csdStr
 where d = a+s+r
       nchnls = sfChannels f
       diskin
        | nchnls ==1 = "a1"
        | nchnls ==2 = "a1,a2"
        | nchnls ==4 = "a1,a2,a3,a4"
       out
        | nchnls ==1 = "out a1*aenv"
        | nchnls ==2 = "outs a1*aenv,a2*aenv"
        | nchnls ==4 = "outq a1*aenv,a2*aenv,a3*aenv,a4*aenv"
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=$(nchnls)
instr 1
          aenv linseg 0.0, $(a), 1.0, $(s), 1.0, $(r), 0.0
          $(diskin) diskin "$(f)",1
          $(out)
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''


silence :: Double -> Sound
silence d = csound ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=1
instr 1
endin
</CsInstruments>
<CsScore>
i0 0 $(d)
</CsScore>
</CsoundSynthesizer>''

appendSilence :: Double -> FilePath -> Sound
appendSilence t f = csound csdStr
 where d = sfDuration f
       d2 = d + t
       nchnls = sfChannels f
       diskin
        | nchnls ==1 = "a1"
        | nchnls ==2 = "a1,a2"
        | nchnls ==4 = "a1,a2,a3,a4"
       out
        | nchnls ==1 = "out a1"
        | nchnls ==2 = "outs a1,a2"
        | nchnls ==4 = "outq a1,a2,a3,a4"
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=$(nchnls)
instr 1
         $(diskin) diskin "$(f)",1
         $(out)
endin
</CsInstruments>
<CsScore>
i0 0 $(d2)
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''


prependSilence :: Double -> FilePath -> Sound
prependSilence t f = csound csdStr
 where d = sfDuration f
       d2 = d + t
       nchnls = sfChannels f
       diskin
        | nchnls ==1 = "a1"
        | nchnls ==2 = "a1,a2"
        | nchnls ==4 = "a1,a2,a3,a4"
       out
        | nchnls ==1 = "out a1"
        | nchnls ==2 = "outs a1,a2"
        | nchnls ==4 = "outq a1,a2,a3,a4"
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=$(nchnls)
instr 1
          $(diskin) diskin "$(f)",1
          $(out)
endin
</CsInstruments>
<CsScore>
i0 0 $(d2)
i1 $(t) $(d)
</CsScore>
</CsoundSynthesizer>''


overlapF :: Double -> FilePath -> FilePath -> [(FilePath,Double)]
overlap :: Double -> FilePath -> FilePath -> Sound
overlapF t f1 f2 = [(f1,0.0) , (f2,(sfDuration f1)-t)]
overlap t f1 f2 = compose (overlapF t f1 f2)

separateByPause :: Double -> FilePath -> FilePath -> Sound
separateByPause t = overlap (0.0 - t)

crossfade :: Double -> FilePath -> FilePath -> Sound
crossfade l f1 f2 = csound csdStr
 where d1 = sfDuration f1
       t1 = d1 - l
       d2 = sfDuration f2
       t2 = d2 - l
       nchnls = sfChannels f1
       diskin
        | nchnls ==1 = "a1"
        | nchnls ==2 = "a1,a2"
        | nchnls ==4 = "a1,a2,a3,a4"
       out
        | nchnls ==1 = "out a1*aenv"
        | nchnls ==2 = "outs a1*aenv,a2*aenv"
        | nchnls ==4 = "outq a1*aenv,a2*aenv,a3*aenv,a4*aenv"
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=$(nchnls)
instr 1
         $(diskin) diskin "$(f1)",1
         aenv linseg 1.0,$(t1),1.0,$(l),0.0
         $(out)
endin
instr 2
         $(diskin) diskin "$(f2)",1
         aenv linseg 0.0,$(l),1.0,$(t2),1.0
         $(out)
endin
</CsInstruments>
<CsScore>
i1 0 $(d1)
i2 $(t1) $(d2)
</CsScore>
</CsoundSynthesizer>''

offsetCrossfade :: Double -> Double -> FilePath -> FilePath -> Sound
offsetCrossfade o l f1 f2 = csound csdStr
 where d1 = sfDuration f1
       t0 = d1 - l - o
       t1 = d1 - l
       d2 = sfDuration f2
       t2 = d2 - l
       nchnls = sfChannels f1
       diskin
        | nchnls ==1 = "a1"
        | nchnls ==2 = "a1,a2"
        | nchnls ==4 = "a1,a2,a3,a4"
       out
        | nchnls ==1 = "out a1*aenv"
        | nchnls ==2 = "outs a1*aenv,a2*aenv"
        | nchnls ==4 = "outq a1*aenv,a2*aenv,a3*aenv,a4*aenv"
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=$(nchnls)
instr 1
         $(diskin) diskin "$(f1)",1
         aenv linseg 1.0,$(t1),1.0,$(l),0.0
         $(out)
endin
instr 2
         $(diskin) diskin "$(f2)",1
         aenv linseg 0.0,$(l),1.0,$(t2),1.0
         $(out)
endin
</CsInstruments>
<CsScore>
i1 0 $(d1)
i2 $(t0) $(d2)
</CsScore>
</CsoundSynthesizer>''


speedEnvelope :: Double -> Double -> FilePath -> Sound
speedEnvelope s1 s2 f = csound csdStr
 where d1 = sfDuration f
       d2 = d1 / ((s1+s2)/2.0)
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=44100
ksmps=1
nchnls=1
instr 1
ks linseg $(s1),p3,$(s2)
a1 diskin "$(f)",ks
out a1
endin
</CsInstruments>
<CsScore>
i1 0 $(d2)
</CsScore>
</CsoundSynthesizer>''




smoothEnd :: Double -> FilePath -> Sound
smoothEnd t x = csound csdStr
 where d = sfDuration x
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=1
instr 1
a1 diskin "$(x)",1
a2 linseg 1.0,p3-$(t),1.0,$(t),0.0
out a1*a2
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''

leftToMono :: FilePath -> Sound
leftToMono f = csound csdStr
 where d = sfDuration f
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=1
instr 1
a1,a0 diskin "$(f)",1
out a1
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''

rightToMono :: FilePath -> Sound
rightToMono f = csound csdStr
 where d = sfDuration f
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=1
instr 1
a0,a1 diskin "$(f)",1
out a1
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''

monoToLeft :: FilePath -> Sound
monoToLeft f = csound csdStr
 where d = sfDuration f
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=2
instr 1
a0 init 0
a1 diskin "$(f)",1
outs a1,a0
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''

monoToRight :: FilePath -> Sound
monoToRight f = csound csdStr
 where d = sfDuration f
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=2
instr 1
a0 init 0
a1 diskin "$(f)",1
outs a0,a1
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''

monoToBoth :: FilePath -> Sound
monoToBoth f = csound csdStr
 where d = sfDuration f
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=2
instr 1
a1 diskin "$(f)",1
outs a1,a1
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''

quadToStereo :: (Double,Double,Double,Double) -> (Double,Double,Double,Double) -> FilePath -> Sound
quadToStereo (a1,a2,a3,a4) (b1,b2,b3,b4) f = csound csdStr
 where d = sfDuration f
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=2
instr 1
a1,a2,a3,a4 diskin "$(f)",1
outs (a1*$(a1))+(a2*$(a2))+(a3*$(a3))+(a4*$(a4)),(a1*$(b1))+(a2*$(b2))+(a3*$(b3))+(a4*$(b4))
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''


extract :: Double -> Double -> FilePath -> Sound
extract s d f = csound csdStr
 where nchnls = sfChannels f
       diskin
        | nchnls == 1 = "a1"
        | nchnls == 2 = "a1,a2"
        | nchnls == 4 = "a1,a2,a3,a4"
       out
        | nchnls == 1 = "out a1"
        | nchnls == 2 = "outs a1,a2"
        | nchnls == 4 = "outq a1,a2,a3,a4"
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=$(nchnls)
instr 1
        $(diskin) diskin "$(f)",1,$(s)
        $(out)
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''

extractLast :: Double -> FilePath -> Sound
extractLast t f = extract ((sfDuration f)-t) t f

{- deprecated. -}
extractStereo = extract


placeInSphere :: Double -> Double -> FilePath -> Sound
placeInSphere a b f = csound csdStr
 where d = sfDuration f
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=4
instr 1
a1 diskin "$(f)", 1
ax = a1 * cos($(a)) * cos($(b))
ay = a1 * sin($(a)) * cos($(b))
az = a1 * sin($(b))
aw = a1 * 0.707
outq ax,ay,az,aw
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''

stereoToAmbi :: Double -> Double -> FilePath -> Sound
stereoToAmbi x1 x2 f = csound csdStr
 where d = sfDuration f
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=4
instr 1
a1,a2 diskin "$(f)", 1
ax = (a1 * cos($(x1))) + (a2 * cos($(x2)))
ay = (a1 * sin($(x1))) + (a2 * sin($(x2)))
az = 0.0
aw = (a1 + a2) * 0.707
outq ax,ay,az,aw
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''

rotateInCircle :: Double -> Double -> FilePath -> Sound
rotateInCircle a b f = csound csdStr
 where d = sfDuration f
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=4
instr 1
a1 diskin "$(f)", 1
a2 linseg $(a),p3,$(b)
ax = a1 * cos(a2) * cos(0.0)
ay = a1 * sin(a2) * cos(0.0)
az = a1 * sin(0.0)
aw = a1 * 0.707
outq ax,ay,az,aw
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''

decodeAmbisonics :: FilePath -> Sound
decodeAmbisonics f = csound csdStr
 where d = sfDuration f
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=4
instr 1
ax,ay,az,aw diskin "$(f)",1
ax2 = ax * 0.707
ay2 = ay * 0.707
a1 = aw + ax2 + ay2
a2 = aw + ax2 - ay2
a3 = aw - ax2 - ay2
a4 = aw - ax2 + ay2
outq a1,a2,a3,a4
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''

quadToMono :: Double -> Double -> Double -> Double -> FilePath -> Sound
quadToMono x y z w f = csound csdStr
 where d = sfDuration f
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=1
instr 1
ax,ay,az,aw diskin "$(f)",1
a1 = ax*$(x) + ay*$(y) + az*$(z) + aw*$(w)
out a1
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''


monoToStereo :: Double -> Double -> FilePath -> Sound
monoToStereo l r f = csound csdStr
 where d = sfDuration f
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=2
instr 1
a1 diskin "$(f)",1
outs a1*($(l)),a1*($(r))
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''

monoToQuad :: Double -> Double -> Double -> Double -> FilePath -> Sound
monoToQuad x y z w f = csound csdStr
 where d = sfDuration f
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=4
instr 1
a1 diskin "$(f)",1
outq a1*($(x)),a1*($(y)),a1*($(z)),a1*($(w))
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''


redistributeStereo :: Double -> FilePath -> Sound
redistributeStereo x f = csound csdStr
 where d = sfDuration f
       y = 1.0 - x
       csdStr = ``<CsoundSynthesizer>
<CsInstruments>
sr=44100
kr=441
ksmps=100
nchnls=2
instr 1
a1,a2 diskin "$(f)",1
outs (a1*($(x)))+(a2*($(y))),(a1*($(y)))+(a2*($(x)))
endin
</CsInstruments>
<CsScore>
i1 0 $(d)
</CsScore>
</CsoundSynthesizer>''

butterlp :: Double -> FilePath -> Sound
butterlp cutoff = csoundImportFilter ("butterlp ") (","++(show cutoff))

butterhp :: Double -> FilePath -> Sound
butterhp cutoff = csoundImportFilter ("butterhp ") (","++(show cutoff))

butterbr :: Double -> Double -> FilePath -> Sound
butterbr cfreq bw = csoundImportFilter ("butterbr ") (","++(show cfreq)++","++(show bw))

butterbp :: Double -> Double -> FilePath -> Sound
butterbp cfreq bw = csoundImportFilter ("butterbp ") (","++(show cfreq)++","++(show bw))

pareq :: Double -> Double -> Double -> Int -> FilePath -> Sound
pareq kc iv iq imode = csoundImportFilter ("pareq ") ("," ++ (show kc) ++ "," ++ (show iv) ++ "," ++ (show iq) ++ "," ++ (show imode))

deleteBeginning :: Double -> FilePath -> Sound
deleteBeginning l f = extract l ((sfDuration f)-l) f