module Exercise06 where import Data.List import Effects import Types --Signal = Seconds -> Sample sinPeriod :: Signal sinPeriod x = sin (x * 2 * pi) sqwPeriod :: Signal sqwPeriod x = if x < 0.5 then -1 else 1 sawPeriod :: Signal sawPeriod x = 2 * x - 1 triPeriod :: Signal triPeriod x = if x < 0.5 then 4 * x - 1 else -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)) --type Oscillator = Semitone -> Seconds -> Signal. osc :: Signal -> ADSR -> Oscillator osc sig vector semi duration x = adsr vector duration (help sig (f semi)) x help:: Signal -> Hz -> Signal help sig freq z = sig ((freq * z) - fromIntegral (floor (freq * z))) adsr :: ADSR -> Seconds -> Signal -> Signal adsr (a,d,s,r) duration sig x | x < a = sig x * (x / a) --attac | x < d + a = let m = (s - 1.0) / d; t = 1.0 - m * a in sig x * (m * x + t) -- decay | x < (duration - r) = sig x * s -- sustain: m = 0, t = s | otherwise = let m = - s / r; t = s - (m * ( duration - r)) in sig x * (m * x + t) --release mix :: [SampledSignal] -> SampledSignal mix xss = hilp [[ x / fromIntegral(length xss) | x <- xs]| xs <- xss] hilp:: [SampledSignal] -> SampledSignal hilp = foldr bincomrec [] bincomrec:: SampledSignal -> SampledSignal -> SampledSignal bincomrec [] [] = [] bincomrec [] ys = ys bincomrec xs [] = xs bincomrec (x:xs) (y:ys) = [x+y] ++ bincomrec xs ys bincom:: SampledSignal -> SampledSignal -> SampledSignal bincom xs ys = [(xs `safeget` i) + (ys `safeget` i )| i <- [0.. (max(length xs) (length ys)) - 1]] safeget:: SampledSignal -> Int -> Sample safeget xs i = if i < (length xs) then (xs !! i) else 0.0 --this would be nice, but we did not learn how to "unwrap" Maybes yet, so not useful (!!!)::[a] -> Int -> Maybe a (!!!) xs i = if i < length xs then Just (xs !! i) else Nothing {-WETT-} -- you can add new oscillators here piano :: Oscillator piano = osc sawPeriod (0.01, 0.01, 0.7, 0.2) lead :: Oscillator lead = osc sqwPeriod (0.01, 0.01, 0.2, 0.1) bass :: Oscillator bass = osc sinPeriod (0.001, 0.8, 0.1, 0.01) -- you can add more effects here -- mix the signals with some volume mixTracks :: [SampledSignal] -> [Double] -> SampledSignal mixTracks trks vols = mix $ zipWith (\trk vol -> map (* vol) trk) trks vols -- 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] audioTracks = zipWith playNotes instrs tracks audioNoEffects = mixTracks audioTracks [0.5, 0.9, 0.2] {-MCCOMMENT the source MIDI is called "frosty.mid". run like specified in the exercise I got my source MIDI from http://www.telewerkstatt.at/midis_xmas.htm#.X95UrS335QI There is a surprise change in about the middle, at 41 sec. -} --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 = applyEffectToInterval(41, 154) (addEffects [echo 0.25, clip 0.15] audioNoEffects) bitcrusher -- 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 (10, 20) audioNoEffects echo {-TTEW-}