module Exercise06 where import Data.List import Effects ( addEffects, addGain, clip ) import Types ( ADSR, Oscillator, Note, Semitone, Hz, SampledSignal, Signal, Seconds, DSPEffect, 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 = -1 + 2 * x triPeriod :: Signal triPeriod x = if x < 0.5 then -1 + 4 * x else 1 - 4 * (x - 0.5) silence :: Signal silence x = x -- 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 mod = os where os semi secs = adsr mod secs sig where hz = f semi sig x = signal ((hz * x) - fromInteger (floor (hz * x))) adsr :: ADSR -> Seconds -> Signal -> Signal adsr (attack, decay, sustain, release) duration signal = sig where lerp x0 y0 x1 y1 x = y0 + (x - x0) * (y1 - y0) / (x1 - x0) sig x | x < attack = signal x * lerp 0 0 attack 1 x | x < attack + decay = signal x * lerp attack 1 (attack+decay) sustain x | x > duration - release = signal x * lerp (duration-release) sustain duration 0 x | x > duration = 0 | otherwise = signal x * sustain mix :: [SampledSignal] -> SampledSignal mix sigs = map sum . transpose $ [ map (/amount) sig | sig <- sigs] where amount = fromIntegral (length sigs) {-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) pkk :: Oscillator pkk = osc triPeriod (0.01, 0.1, 0.7, 0.2) -- you can add more effects here {-MCCOMMENT Idk I am bad with music, so here is just a random effect without my own midi. I thought if I just add enough parameters I could tweak, I might be able to produce something acceptable... Turns out i was wrong. I used 'stack run synth ./mid/mario.mid mario.wav' to create the wav file -} smthing :: Int -> [Sample] -> [Sample] smthing _ [] = [] smthing n xs = take n xs ++ take n xs ++ smthing n (drop (2 * n) xs) onOff :: Int -> [Sample] -> [Sample] onOff _ [] = [] onOff n xs = take n xs ++ replicate n 0 ++ smthing n (drop (2 * n) xs) fancy :: SampledSignal -> SampledSignal fancy values = mix [ values, fan ] where fan = mix [ smthing 1200 $ map (/ negate (fromIntegral x**2)) (drop (2400 * x) values) | x <- [1..10] ] idkWhatIAmDoing :: SampledSignal -> SampledSignal idkWhatIAmDoing values = zipWith (*) values [ 1 + (0.8 * bass 42 420 (fromIntegral x / 4800)) | x <- cycle [4800..4800*20] ] -- 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 instrs = cycle [pkk, bass] audioTracks = zipWith playNotes instrs tracks audioNoEffects = mixTracks audioTracks [0.5, 0.8] instrs2 = repeat [osc sinPeriod (0.001, 0.2, 0.9, 0.1)] audioTracks2 = map (playNotes bass) tracks audioNoEffects2 = mixTracks audioTracks2 [1] audio = mixTracks [fancy audioNoEffects, drop 1200 $ fancy audioNoEffects2, idkWhatIAmDoing audioNoEffects2, onOff 24000 $ idkWhatIAmDoing $ fancy audioNoEffects2, idkWhatIAmDoing audioNoEffects] [0.666, 1.5, 1, 0.25, 0.5] {-TTEW-}