-- | -- Module : Composition.Sound.Functional.OvertonesO -- Copyright : (c) OleksandrZhabenko 2021 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Some variants of the f :: 'Float' -> 'OvertonesO' function that can be used for overtones -- (and a timbre respectively) generation. {-# LANGUAGE BangPatterns #-} {-# OPTIONS_HADDOCK show-extensions #-} {-# OPTIONS_GHC -threaded #-} module Composition.Sound.Functional.OvertonesO where import GHC.Arr import Composition.Sound.Functional.Basics {-| For the given frequency of the note it generates a list of the tuples, each one of which contains the harmonics' frequency and amplitude. Is taken from the Composition.Sound.Functional.Basics module, so it must be imported qualified to be used with the last one. -} overTones :: Float -> OvertonesO overTones = overTonesKNPG 1 1 2 1.0 {-# INLINE overTones #-} {-| A generalized variant of the 'overTones' function with just two additional control parameters (so represents a two-parameters additionally parameterized family of 'overTones' functions). -} overTonesKN2 :: Int -> Int -> Float -> OvertonesO overTonesKN2 k n = overTonesKNPG k n 2 1.0 {-# INLINE overTonesKN2 #-} {-| A generalized variant of the 'overTones' and 'overTonesKN2' with the possibility to specify the additional parameters for them. -} overTonesKNPG :: Int -> Int -> Int -> Float -> Float -> OvertonesO overTonesKNPG k n p amplK note = takeWhile (\(!w,!z) -> w <= unsafeAt notes 107 && abs z > 0.001) . filter (\(_,z) -> abs z <= 1.0) . map (\i -> (note * abs (fromIntegral (i + k)), amplK / fromIntegral (product . replicate p $ (i + n)))) $ [1 - n..40000 * abs n] {-| A generalized variant of the 'overTones' and 'overTonesKN2' with the possibility to specify the additional parameters for them. Otherwise than the similar 'overTonesKNPG', it can generate the higher overtones than the B8 to the 20000 Hz. -} overTonesKNPG20k :: Int -> Int -> Int -> Float -> Float -> OvertonesO overTonesKNPG20k = overTonesKNPG20kF id {-# INLINE overTonesKNPG20k #-} {-| A generalized variant of the 'overTonesKNPG20k' with the possibility to specify the additional function to control the overtones amplitudes. Otherwise than the similar 'overTonesKNPG', it can generate the higher overtones than the B8 to the 20000 Hz. The first argument, the function @f@ is intended to be a monotonic growing one though it can be not necessary. -} overTonesKNPG20kF :: (Float -> Float) -> Int -> Int -> Int -> Float -> Float -> OvertonesO overTonesKNPG20kF f = overTonesKNPG20kFALaClarinet f id {-# INLINE overTonesKNPG20kF #-} {-| Is taken from the Composition.Sound.Functional.Basics module, so it must be imported qualified to be used with the last one. -} overTonesALaClarinet :: Float -> OvertonesO overTonesALaClarinet note = takeWhile (\(!w,!z) -> w <= unsafeAt notes 107 && abs z > 0.001) . map (\i -> (note * fromIntegral (2 * i + 1), 1 / fromIntegral ((i + 1) * (i + 1)))) $ [0..512] {-| A generalized variant of the 'overTonesKNPG20k' with the possibility to specify the additional function to control the overtones amplitudes. Otherwise than the similar 'overTonesKNPG', it can generate the higher overtones than the B8 to the 20000 Hz. The first argument, the function @f@ is intended to be a monotonic growing one though it can be not necessary. The second one parameter -- the @g@ function can be simply (*2), (*4) or something else and also is intended to be monotonic. -} overTonesKNPG20kFALaClarinet :: (Float -> Float) -> (Int -> Int) -> Int -> Int -> Int -> Float -> Float -> OvertonesO overTonesKNPG20kFALaClarinet f g k n p amplK note = takeWhile (\(!w,!z) -> w <= 20000.0 && abs z > 0.001) . filter (\(_,!z) -> abs z <= 1.0) . map (\i -> (note * abs (fromIntegral (g i + k)), f (amplK / fromIntegral (product . replicate p $ (i + n))))) $ [1 - n..]