module Exercise06 where import Data.List import Effects import Types sinPeriod :: Signal sinPeriod 0.5 = 0 sinPeriod 1 = 0 sinPeriod s = sin (s * 2 * pi) -- i hope this works sqwPeriod :: Signal sqwPeriod s | s < 0.5 = -1 | otherwise = 1 sawPeriod :: Signal sawPeriod s = -1 + 2 * s triPeriod :: Signal triPeriod s | s <= 0.5 = -1 + 4 * s | otherwise = - 1 + 4 * (-s + 1) silence :: Signal silence s = 0.0 -- 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 s adsr_values semitone duration = adsr adsr_values duration freqSig where freq = f semitone freqSig sec = repeatedSignal (freq * sec) repeatedSignal = repeatSignal s duration repeatSignal :: Signal -> Seconds -> Signal repeatSignal sig dur sec = sig (sec - fromIntegral (floor sec)) adsr :: ADSR -> Seconds -> Signal -> Signal adsr (attack, decay, sustain, release) = adsrHelper (attack, decay, sustain, release) adsrHelper :: ADSR -> Seconds -> Signal -> Seconds -> Sample adsrHelper (attack, decay, sustain, release) duration signal s | s < attack = signal s * attackFunction s | s == attack = signal s | s > attack && s < (decay+attack) = signal s * decayFunction s | s >= (decay+attack) && s <=(duration - release) = signal s * sustain | otherwise = signal s * releaseFunction s where attackFunction s = (1.0 / attack) * s decayFunction s = ((1.0 - sustain)/(-1 * decay)) * (s-(attack+decay)) + sustain releaseFunction s = (sustain/(-1*release)) * (s-duration) mix :: [SampledSignal] -> SampledSignal mix sigs = foldr addLists [] n1 where n1 = [map norm sig | sig <- sigs] count = length sigs norm s = s / fromIntegral count addLists :: Num a => [a] -> [a] -> [a] addLists [] ys = ys addLists xs [] = xs addLists (x:xs) (y:ys) = y + x : addLists 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 {- MCCOMMENT in anbetracht der Tatsache, dass ich gänzlich unmusikalisch bin, bezweifle ich dass sich irgendetwas hier "gut" anhört, sind alles eher Spielerein zum ausprobieren deshalb hab ich auch alles mit den gegebenen midi files gemacht, da es mir mehr um das ausprobieren von effekten als um musik machen ging-} --slowly deacreases the volume of the last x percent of the song fadeOut :: Int -> DSPEffect fadeOut duration input = zipWith (*) input fadeValuesComplete where fadeDuration = length input `div` duration fadeStartIndex = length input - fadeDuration fadeValues = unfoldr (\v -> if v < 0.1 then Nothing else Just (v, v - (1 / fromIntegral fadeDuration))) 1.0 fadeValuesComplete = replicate fadeStartIndex 1 ++ fadeValues -- counterpart to fadeOut fadeIn :: Int -> DSPEffect fadeIn duration input = zipWith (*) input fadeValuesComplete where fadeDuration = length input `div` duration fadeValues = unfoldr (\v -> if v >= 1.0 then Nothing else Just (v, v + (1 / fromIntegral fadeDuration))) 0.1 fadeValuesComplete = fadeValues ++ replicate (length input - fadeDuration) 1 --tremolo as described in the article you linked (doesn't sound like it tho, mostly distorts the sound. Maybe fiddling with the values a little would help) tremolo :: DSPEffect tremolo input = zipWith (*) input changing where --fullAmplitude = replicate (length input `div` 2) 1.2 --changingAmplitude = intersperse 0.2 fullAmplitude changing = intercalate shortHighAmp lowAmpFull lowAmpFull = replicate (length input `div` 700) shortLowAmp shortLowAmp = replicate 350 0.3 shortHighAmp = replicate 350 1.0 {- "the processor achieves the effect by taking an audio signal and mixing it with one or more delayed, pitch-modulated copies of itself" from https://en.wikipedia.org/wiki/Chorus_effect da ich keinerlei Ahnung von Musik(produktion) hab, bin ich mir nicht sicher was genau das bringt, oder wie es sich für unsere Songs anhören sollte, aber das sollte den von wikipedia beschriebenen effekt umsetzen edit: hört sich hauptsächlich komisch an :( -} chorusEffect :: DSPEffect chorusEffect input = mix [input, map (* 0.7) (replicate shift 0 ++ input)] --where shift = floor (0.0137 * fromIntegral (length input)) where shift = 2424 --i know magic numbers are bad, but i figured out 1 second of the sampled mario signal has around 48500 sample values, so this should shift it by ca 50 ms {- crushes the number of bits representing this signal stretches the amplitude, rounds it, and then reduces the amplitude again (for e.g. a sine wave this is like reducing the sampling rate [at least i think so]) -} bitCrusher :: Int -> DSPEffect bitCrusher bits input = map (\r -> fromIntegral r / ampVals) rounded where ampVals = 2 ** fromIntegral (bits-1) stretched = map (* ampVals) input rounded = map ceiling stretched -- 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. -- mario_final has varying levels of bitcrushing in the first 30 secs, then 10 secs of chorus, then 10 secs of tremolo, then 10 secs of all of them combined and finally a fade out crushed4 = applyEffectToInterval (0, 10) audioNoEffects (bitCrusher 4) crushed3 = applyEffectToInterval (10, 20) crushed4 (bitCrusher 3) crushed2 = applyEffectToInterval (20, 30) crushed3 (bitCrusher 2) chorus = applyEffectToInterval (30, 40) crushed2 chorusEffect trem = applyEffectToInterval (40, 50) chorus tremolo all = applyEffectToInterval (50, 60) (applyEffectToInterval (50,60) (applyEffectToInterval (50, 60) trem tremolo) chorusEffect) (bitCrusher 4) audio = addEffects [fadeOut 10] all --audio = addEffects [bitCrusher 4] audioNoEffects --audio = addEffects [tremolo] 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-}