-- | -- 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 #-} {-# LANGUAGE BangPatterns #-} 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.Ukrainian.ArrInt8 (Sound8,FlowSound,convertToProperUkrainianI8) import Languages.Phonetic.Ukrainian.Syllable.ArrInt8 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 . convertToProperUkrainianI8 -- | The default way to get 'Intervals' from a converted Ukrainian text. vStrToVInt :: FlowSound -> 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 :: Sound8 -> 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 . convertToProperUkrainianI8 $ xs) y | otherwise = error "Composition.Sound.DIS5G6G.str2Durations: Not defined for such arguments. " -- | A conversion to the 'Float' that is used inside 'str2Durations'. str2Durat1 :: Sound8 -> Float str2Durat1 = getBFstLSorted' 0.051020 [(1,0.138231),(2,9.3605e-2),(3,0.116463),(4,0.10907),(5,9.9955e-2),(6,9.415e-2),(7,2.0227e-2),(8,5.5601e-2),(9,5.5601e-2),(10,7.0658e-2),(11,7.0658e-2),(15,5.7143e-2),(16,5.7143e-2),(17,7.2063e-2),(18,7.2063e-2),(19,6.2948e-2),(20,6.2948e-2),(21,7.6825e-2),(22,7.6825e-2),(23,4.8934e-2),(24,4.8934e-2),(25,5.6054e-2),(26,5.6054e-2),(27,5.7143e-2),(28,6.4036e-2),(29,6.4036e-2),(30,7.737e-2),(31,7.737e-2),(32,7.424e-2),(33,7.424e-2),(34,4.9206e-2),(35,4.9206e-2),(36,8.2268e-2),(37,8.2268e-2),(38,5.3061e-2),(39,5.7596e-2),(40,5.7596e-2),(41,6.6077e-2),(42,6.6077e-2),(43,6.2268e-2),(44,6.2268e-2),(45,4.5351e-2),(46,4.5351e-2),(47,0.13483),(48,0.13483),(49,7.4603e-2),(50,0.110658),(51,0.110658),(52,7.7188e-2),(53,7.7188e-2),(54,7.4558e-2),(66,8.9342e-2)] -- | A full conversion to the 'Strengths' from a Ukrainian text. str2Volume :: String -> Strengths str2Volume = (\rs -> listArray (0,length rs - 1) rs) . map (getBFstLSorted' 0.06408817 [(1,0.27161466),(2,0.27192511),(3,0.28539351),(4,0.25250039),(5,0.2050935),(6,0.20026538),(7,2.218624e-2),(8,7.729654e-2),(9,7.729654e-2),(10,8.048113e-2),(11,8.048113e-2),(15,0.10977617),(16,0.10977617),(17,6.58655e-2),(18,6.58655e-2),(19,7.751571e-2),(20,7.751571e-2),(21,5.392745e-2),(22,5.392745e-2),(23,8.900757e-2),(24,8.900757e-2),(25,6.099951e-2),(26,6.099951e-2),(27,8.226452e-2),(28,0.11159399),(29,0.11159399),(30,0.14303837),(31,0.14303837),(32,5.639178e-2),(33,5.639178e-2),(34,6.354637e-2),(35,6.354637e-2),(36,8.404524e-2),(37,8.404524e-2),(38,5.616409e-2),(39,0.12541547),(40,0.12541547),(41,0.12838476),(42,0.12838476),(43,0.15776219),(44,0.15776219),(45,4.91782e-2),(46,4.91782e-2),(47,9.603085e-2),(48,9.603085e-2),(49,5.294375e-2),(50,5.047358e-2),(51,5.047358e-2),(52,7.905155e-2),(53,7.905155e-2),(54,7.512999e-2),(66,7.835033e-2)]) . convertToProperUkrainianI8 -- | A conversion to the 'Float' that is used inside 'str2Volume'. str2Vol1 :: String -> Float str2Vol1 = getBFstLSorted' 0.06408817 [(1,0.27161466),(2,0.27192511),(3,0.28539351),(4,0.25250039),(5,0.2050935),(6,0.20026538),(7,2.218624e-2),(8,7.729654e-2),(9,7.729654e-2),(10,8.048113e-2),(11,8.048113e-2),(15,0.10977617),(16,0.10977617),(17,6.58655e-2),(18,6.58655e-2),(19,7.751571e-2),(20,7.751571e-2),(21,5.392745e-2),(22,5.392745e-2),(23,8.900757e-2),(24,8.900757e-2),(25,6.099951e-2),(26,6.099951e-2),(27,8.226452e-2),(28,0.11159399),(29,0.11159399),(30,0.14303837),(31,0.14303837),(32,5.639178e-2),(33,5.639178e-2),(34,6.354637e-2),(35,6.354637e-2),(36,8.404524e-2),(37,8.404524e-2),(38,5.616409e-2),(39,0.12541547),(40,0.12541547),(41,0.12838476),(42,0.12838476),(43,0.15776219),(44,0.15776219),(45,4.91782e-2),(46,4.91782e-2),(47,9.603085e-2),(48,9.603085e-2),(49,5.294375e-2),(50,5.047358e-2),(51,5.047358e-2),(52,7.905155e-2),(53,7.905155e-2),(54,7.512999e-2),(66,7.835033e-2)] . head . convertToProperUkrainianI8 -- | 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)