module Exercise06 where import Data.List import Effects import Types sinPeriod :: Signal sinPeriod = sin . (*(2*pi)) sqwPeriod :: Signal sqwPeriod x | x < 0.5 = -1 | x == 0.5 = 0 | otherwise = 1 sawPeriod :: Signal sawPeriod x = -1 + 2*x triPeriod :: Signal triPeriod x | x <= 0.5 = 4*x - 1 | otherwise = -4*x + 3 silence :: Signal silence = undefined -- NOTE: the formula is taken from https://pages.mtu.edu/~suits/NoteFreqCalcs.html f :: Semitone -> Hz f n = 440.0 * (2 ** (fromInteger n / 12.0)) osc :: Signal -> ADSR -> Oscillator osc signal at_de_su_re semitone duration = adsr at_de_su_re duration (signal . norm) where frequency = f semitone norm x = (x*frequency) - fromIntegral (floor (x*frequency)) adsr :: ADSR -> Seconds -> Signal -> Signal adsr (attack, decay, sustain, release) duration signal x | x <= attack = (1/attack) * x * signal x | x <= attack + decay = ((sustain - 1) / decay * x + 1 - attack * (sustain - 1)/decay) * signal x | x <= duration - release = sustain * signal x | otherwise = (-sustain / release * x + duration * sustain / release) * signal x mix :: [SampledSignal] -> SampledSignal mix xss = foldr (mAdd . (\xs -> [x/fromIntegral len | x<-xs])) [] xss where len = length xss mAdd :: Fractional a => [a] -> [a] -> [a] mAdd [] ys = ys mAdd xs [] = xs mAdd (x:xs) (y:ys) = (x+y) : mAdd xs ys {-WETT-} -- you can add new oscillators here piano :: Oscillator piano = osc sawPeriod (0.01, 0.1, 0.7, 0.2) lead :: Oscillator lead = osc sqwPeriod (0.01, 0.2, 0.3, 0.1) bass :: Oscillator bass = osc sinPeriod (0.001, 0.2, 0.9, 0.1) -- you can add more effects here lowCut :: Double -> DSPEffect lowCut d = map (\sample -> if abs sample < d then 0 else sample) echo :: Int -> DSPEffect echo d xs = [x+y | (x,y)<-zip xs (drop d (xs++[0.0 | x<-[1..d]]))] smooth :: DSPEffect smooth xs = [(a+b+c+d)/4 | ((a,b),(c,d))<-zip (zip xs (drop 1 (xs++[0.0]))) (zip (drop 2 (xs++[0.0,0.0])) (drop 3 (xs++[0.0,0.0,0.0])))] -- mix the signals with some volume mixTracks :: [SampledSignal] -> [Double] -> SampledSignal mixTracks trks vols = mix $ zipWith (\trk vol -> map (* vol) trk) trks vols {-MCCOMMENT run: stack run synth mid/wwyamc.mid wwyamc.wav-} -- here we mix it all together and apply the effects notesToSignal :: (Oscillator -> [Note] -> SampledSignal) -> [[Note]] -> SampledSignal notesToSignal playNotes tracks = audio where -- specify the instruments of each track -- try the following instruments with the mario.mid file instrs = cycle [piano, bass, lead, piano, bass] audioTracks = zipWith playNotes instrs tracks audioNoEffects = mixTracks audioTracks [0.8, 0.7] -- audio = audioNoEffects -- To add effects, replace the line above by the line at the end of this comment and change the list off effects to your own effects. -- Note that the effects are applied from right to left, ie. the rightmost effect is applied first. audio = addEffects [smooth, smooth, smooth, smooth, smooth, addGain 1.8, clip 0.8, echo 69200] audioNoEffects -- If you want to apply an effect only to parts of the signal, you can use the function applyEffectToInterval, as shown below. -- Thereby the first argument specifies the interval to which the effect should be applied in seconds. --audio = applyEffectToInterval (2, 6) audioNoEffects distortion {-TTEW-}