-- | -- Module : Composition.Sound.Octaves -- Copyright : (c) OleksandrZhabenko 2020-2021 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Helps to create experimental music from a file (or its part) and a Ukrainian text. -- It can also generate a timbre for the notes. Uses SoX inside. {-# OPTIONS_GHC -threaded #-} module Composition.Sound.Octaves ( -- * Work with octaves octaveUp , octaveDown , liftInOctave , liftInOctaveV ) where import Data.Maybe (fromJust, mapMaybe) --import qualified Data.Vector as V import GHC.Arr import GHC.List (iterate') import Data.List hiding (iterate') import Composition.Sound.Functional.Basics -- | Returns an analogous note in the higher octave (its frequency in Hz). octaveUp :: Float -> Float octaveUp x = 2 * x {-# INLINE octaveUp #-} -- | Returns an analogous note in the lower octave (its frequency in Hz). octaveDown :: Float -> Float octaveDown x = x / 2 {-# INLINE octaveDown #-} -- | Function lifts the given frequency to the given number of the octave (in American notation, from 0 to 8). This number is an 'Int' parameter. -- The function also takes into account the lower pure quint for the closest note. -- If it is not practical to determine the number, then the function returns 'Nothing'. liftInOctave :: Int -> Float -> Maybe Float liftInOctave n x | n < 0 || n > 8 = Nothing | closestNote x > 24.4996 = case compare (fromJust . whichOctave $ x) n of EQ -> Just (closestNote x) LT -> let z = logBase 2.0 (unsafeAt notes (n * 12) / closestNote x) z1 = truncate z in if abs (z - fromIntegral z1) > 0.999 || abs (z - fromIntegral z1) < 0.001 then Just (last . take (fromIntegral z1 + 1) . iterate' octaveUp $ closestNote x) else Just (last . take (fromIntegral z1 + 2) . iterate' octaveUp $ closestNote x) _ -> let z = logBase 2.0 (closestNote x / unsafeAt notes (n * 12)) z1 = truncate z in if abs (z - fromIntegral z1) > 0.999 || abs (z - fromIntegral z1) < 0.001 then Just (last . take (fromIntegral z1 + 2) . iterate' octaveDown $ closestNote x) else Just (last . take (fromIntegral z1 + 1) . iterate' octaveDown $ closestNote x) | otherwise = Nothing -- | Function lifts the list of 'Float' representing frequencies to the given octave with the 'Int' number. Better to use numbers in the range [1..8]. -- The function also takes into account the lower pure quint for the obtained note behaviour. If it is not practical to determine the octave, the resulting -- frequency is omitted from the resulting list. liftInOctaveV :: Int -> [Float] -> [Float] liftInOctaveV n = mapMaybe (liftInOctave n) --------------------------------------------------------------------------------------------------------------------------------