module Exercise06 where import Data.List import Data.Ord import Effects import Types ( ADSR, Oscillator, Note, Semitone, Hz, SampledSignal, Signal, Seconds, DSPEffect ) sinPeriod :: Signal sinPeriod t = sin (t * 2*pi) triPeriod :: Signal triPeriod x = if x < 0.5 then 4*x - 1 else 3 - 4*x sawPeriod :: Signal sawPeriod x = 2*x - 1 sqwPeriod :: Signal sqwPeriod x | x < 0.5 = -1 | x == 0 = 1 | otherwise = 1 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)) adsr :: ADSR -> Seconds -> Signal -> Signal adsr (attack, decay, sustain, release) duration signal t | t <= attack = signal t * t / attack | t <= attack + decay = let x = t - attack in (1 - (1 - sustain) * x / decay) * signal t | t >= duration - release = let x = t - duration + release in (sustain - sustain * x / release) * signal t | otherwise = sustain * signal t osc :: Signal -> ADSR -> Oscillator osc singleSig adsrConfig semitone duration = adsr adsrConfig duration repeatedSignal where freq :: Double freq = f semitone repeatedSignal = singleSig . (\t -> freq * t - fromIntegral (floor (freq * t))) mix :: [SampledSignal] -> SampledSignal mix inputs = map (/ fromIntegral (length inputs)) $ foldl1 zipWithLongest inputs where zipWithLongest [] ys = ys zipWithLongest xs [] = xs zipWithLongest (x:xs) (y:ys) = (x + y):zipWithLongest xs ys testFromArtemis = [[0.86110591764466,-0.10923005774093553,-0.31107004263044513],[-0.1976978822892801,0.23211221803700433,0.5446743925843822,0.12320236796747897,-0.7220721475505438,0.798795652741608,9.263252911772879e-3]] testAdsr = adsr (2.0, 1.0, 0.5, 2.5) 10 (const 1) {-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 -- 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] 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 [clip 0.9, addGain 4] 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. -- DJ Hübler -- First we clip the amplitudes down to 0.8 clippedAudio = addEffects [clip 0.8] audioNoEffects audioIncrease1 = (0, 3, increaseAmplOverTime 5 0 0.2) audioIncrease2 = (3, 6, increaseAmplOverTime 3 0.2 0.8) audioEcho = (6, 10.125, echo 4 0.125) audioDecrease1 = (9, 12, increaseAmplOverTime 3 0.8 0.2) audioIncrease3 = (12, 16, increaseAmplOverTime 4 0.2 0.8) audioDecrease2 = (16, 18, increaseAmplOverTime 2 0.8 0.4) audioTriller = (12, 18, triller 0 1.2 25) audioUpDown = (17, 24, triller 0.2 1 0.5) audio = applyIntervals clippedAudio [audioUpDown, audioTriller, audioDecrease2, audioIncrease3, audioDecrease1, audioEcho, audioIncrease2, audioIncrease1] {-TTEW-} -- Apply the List from the right to the left applyIntervals :: SampledSignal -> [(Seconds, Seconds, DSPEffect)] -> SampledSignal applyIntervals audio [] = audio applyIntervals audio ((start, end, effect):es) = applyEffectToInterval (start, end) (applyIntervals audio es) effect {-MCCOMMENT -- It seems like the synthesizer losses the last note from the input midi. At least it does on my audio software. -- If my solutions have one trailing not fitting note please ignore it. Otherwise the last correct note is missing on my Laptop which sounds odd Input: ./mid/mario_wettew_withTrailingNote.mid Output: ./wettew/submission.wav Command: stack run synth "./mid/mario_wettew_withTrailingNote.mid" "./wettew/submission.wav" -}