-- | -- Module : Composition.Sound.DIS5G6G -- 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.DIS5G6G ( -- ** Auxiliary functions syllableStr -- *** Working with Intervals, Durations, Strengths and StrengthDb , intervalsFromString , vStrToVInt , strToInt , durationsAver , str2Durat1 , str2Durations , str2Vol1 , str2Volume , doublesAveragedA , doublesAveragedG , equalize2Vec , intervalsFromStringG , silentSound2G , strengthsAver , strengthsDbAver -- * New generalized 6G functions that works with Strengths , apply6G , apply6G2 , apply6GS , apply6GS2 ) where import CaseBi.Arr (getBFstLSorted') import Numeric import Data.Maybe (fromJust) import GHC.Arr import qualified Data.Foldable as F import System.Process import EndOfExe import Melodics.ByteString.Ukrainian.Arr (convertToProperUkrainianS) import Languages.Phonetic.Ukrainian.Syllable.Arr hiding (str2Durat1) import MMSyn7l import Composition.Sound.IntermediateF import Composition.Sound.Functional.Params import Composition.Sound.Decibel -- | Generatlized version of the 'intervalsFromString' with a possibility to specify your own 'Intervals'. intervalsFromStringG :: Intervals -> String -> Intervals intervalsFromStringG v = vStrToVIntG v . convertToProperUkrainianS -- | The default way to get 'Intervals' from a converted Ukrainian text. vStrToVInt :: String -> Intervals vStrToVInt = (\rs -> listArray (0,length rs - 1) rs) . map (strToIntG defInt) -- | The default way to get number of semi-tones between notes in a single element of 'Intervals'. strToInt :: Char -> Int strToInt = strToIntG defInt {-# INLINE strToInt #-} --------------------------------------------------------------------------------------------------------------------- -- | Arithmetic average for the 'Array' 'Int' is used as a weight for a duration. doublesAveragedA :: Array Int Float -> Float -> Array Int Float doublesAveragedA v4 y3 | F.null v4 || y3 == 0 || sum v4 == 0 = error "Composition.Sound.DIS5G6G.doublesAveragedA: Not defined for such arguments. " | otherwise = let !aver = sum v4 / fromIntegral (numElements v4) in amap (*(y3 / aver)) v4 -- | Geometric average for the 'Array' 'Int' is used as a weight for a strength. doublesAveragedG :: Array Int Float -> Float -> Array Int Float doublesAveragedG v4 y3 | F.null v4 || y3 == 0 || any (== 0) v4 = error "Composition.Sound.DIS5G6G.doublesAveragedG: Not defined for such arguments. " | otherwise = let !aver = product v4 ** (1.0 / (fromIntegral (numElements v4))) in amap (*(y3 / aver)) v4 -- | 'Durations' accounting the desired average duration. durationsAver :: Durations -> Float -> Durations durationsAver = doublesAveragedA -- | 'Strengths' accounting the desired average strength. strengthsAver :: Strengths -> Float -> Strengths strengthsAver = doublesAveragedG -- | 'StrengthsDb' accounting the desired average strength in dB. strengthsDbAver :: StrengthsDb -> Float -> StrengthsDb strengthsDbAver = doublesAveragedG -- | Auxiliary function to make all lists in an 'Array' 'Int' equal by length (the minimum one). equalize2Vec :: Array Int [a] -> Array Int [a] equalize2Vec v = let min = minimum . amap length $ v in amap (take min) $ v -- | A full conversion to the 'Durations' from a Ukrainian text. The 'String' must be not empty Ukrainian text and -- the 'Float' must be greater than 0.0. str2Durations :: String -> Float -> Durations str2Durations xs y | y > 0.0 && not (null xs) = durationsAver ((\rs -> listArray (0,length rs -1) rs) . map str2Durat1 . convertToProperUkrainianS $ xs) y | otherwise = error "Composition.Sound.DIS5G6G.str2Durations: Not defined for such arguments. " -- | A conversion to the 'Float' that is used inside 'str2Durations'. str2Durat1 :: Char -> Float str2Durat1 = getBFstLSorted' (-0.153016) [('-', (-0.101995)), ('0', (-0.051020)), ('1', (-0.153016)), ('a', 0.138231), ('b', 0.057143), ('v', 0.082268), ('h', 0.076825), ('d', 0.072063), ('j', 0.048934), ('A', 0.055601), ('e', 0.093605), ('B', 0.070658), ('z', 0.056054), ('y', 0.099955), ('C', 0.057143), ('k', 0.045351), ('l', 0.064036), ('m', 0.077370), ('n', 0.074240), ('o', 0.116463), ('p', 0.134830), ('r', 0.049206), ('s', 0.074603), ('D', 0.074558), ('t', 0.110658), ('u', 0.109070), ('f', 0.062268), ('x', 0.077188), ('c', 0.053061), ('w', 0.089342), ('E', 0.057596), ('F', 0.066077), ('q', 0.020227), ('i', 0.094150), ('g', 0.062948)] -- | A full conversion to the 'Strengths' from a Ukrainian text. str2Volume :: String -> Strengths str2Volume = (\rs -> listArray (0,length rs - 1) rs) . map (getBFstLSorted' 0.0 [('a', 0.890533), ('b', 0.211334), ('v', (-0.630859)), ('h', (-0.757599)), ('d', 0.884613), ('j', 0.768127), ('A', (-0.731262)), ('e', (-0.742523)), ('B', (-0.588959)), ('z', (-0.528870)), ('y', 0.770935), ('C', (-0.708008)), ('k', (-0.443085)), ('l', 0.572632), ('m', (-0.782349)), ('n', (-0.797607)), ('o', (-0.579559)), ('p', 0.124908), ('r', 0.647369), ('s', 0.155640), ('D', (-0.207764)), ('t', -0.304443), ('u', 0.718262), ('f', (-0.374359)), ('x', (-0.251160)), ('c', (-0.392365)), ('w', 0.381348), ('E', (-0.189240)), ('F', 0.251221), ('q', 0.495483), ('i', (-0.682709)), ('g', 0.557098)]) . convertToProperUkrainianS -- | A conversion to the 'Float' that is used inside 'str2Volume'. str2Vol1 :: String -> Float str2Vol1 = getBFstLSorted' 0.0 [('a', 0.890533), ('b', 0.211334), ('v', (-0.630859)), ('h', (-0.757599)), ('d', 0.884613), ('j', 0.768127), ('A', (-0.731262)), ('e', (-0.742523)), ('B', (-0.588959)), ('z', (-0.528870)), ('y', 0.770935), ('C', (-0.708008)), ('k', (-0.443085)), ('l', 0.572632), ('m', (-0.782349)), ('n', (-0.797607)), ('o', (-0.579559)), ('p', 0.124908), ('r', 0.647369), ('s', 0.155640), ('D', (-0.207764)), ('t', -0.304443), ('u', 0.718262), ('f', (-0.374359)), ('x', (-0.251160)), ('c', (-0.392365)), ('w', 0.381348), ('E', (-0.189240)), ('F', 0.251221), ('q', 0.495483), ('i', (-0.682709)), ('g', 0.557098)] . head . convertToProperUkrainianS -- | For the given non-existing 'FilePath' for a sound file supported by SoX generates a silence of the specified -- duration and quality (see, 'soxBasicParams'). silentSound2G :: FilePath -> Float -> String -> IO () silentSound2G file y4 ys = do _ <- readProcessWithExitCode (fromJust (showE "sox")) ((if null ys then id else soxBasicParams ys) ["-r22040","-n",file,"synth", showFFloat (Just 1) y4 "","sine","440.0","vol","0"]) "" putStr "" -- | After producing sounds as WAV or FLAC files you can apply to them volume adjustments using 'Strengths'. The first 'String' is used accordingly to -- 'soxBasicParams' and the second one -- as a prefix of the filenames for the files that the function is applied to. The files must not be silent ones. -- Otherwise, it leads to likely noise sounding or errors. apply6G :: Strengths -> String -> String -> IO () apply6G v6 ys zs | F.null v6 = putStrLn "Composition.Sound.DIS5G6G.apply6G: Nothing has changed, because the array of volume adjustments is empty! " | otherwise = do dir0v <- fmap elems . listVDirectory3G ys $ zs let !l6 = numElements v6 mapM_ (\(i, file) -> soxE file ["norm","vol", showFFloat (Just 4) (unsafeAt v6 (i `rem` l6)) ""]) . zip [0..] $ dir0v -- | Variant of the 'apply6G' where you use as a 'Strengths' parameter that one obtained from a Ukrainian text provided as a first 'String' argument. -- It uses 'str2Volume' inside. The files must not be the silent ones. Otherwise, it leads to likely noise sounding or errors. apply6GS :: String -> String -> String -> IO () apply6GS xs = apply6G (str2Volume xs) -- | Variant of the 'apply6G' function which can be applied also to the silent files. Whether a file is silent is defined using the 'Float' argument -- so that if the maximum by absolute value amplitude is less by absolute value than the 'Float' argument then the file is not changed. apply6G2 :: Strengths -> String -> String -> Float -> IO () apply6G2 v6 ys zs limV | F.null v6 = putStrLn "Composition.Sound.DIS5G6G.apply6G2: Nothing has changed, because the array of volume adjustments is empty! " | otherwise = do dir0v <- fmap elems . listVDirectory3G ys $ zs let !l6 = numElements v6 mapM_ (\(i, file) -> apply6GSilentFile file limV (unsafeAt v6 (i `rem` l6))) . zip [0..] $ dir0v -- | Variant of the 'apply6G2' where you use as a 'Strengths' parameter that one obtained from a Ukrainian text provided as the first 'String' argument. -- It uses 'str2Volume' inside. apply6GS2 :: String -> String -> String -> Float -> IO () apply6GS2 xs = apply6G2 (str2Volume xs)