-- | -- Module : MMSyn7l -- Copyright : (c) OleksandrZhabenko 2020 -- License : MIT -- -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- A program and a library to modify the amplitude of the sound representations for -- the Ukrainian language created by mmsyn7ukr package or somehow otherwise. -- module MMSyn7l where import Data.Char (toUpper, isDigit) import qualified SoXBasics as SB import qualified SoXBasics1 as SB1 import qualified Data.Vector as V import Control.Exception (onException) import CaseBi (getBFst') -- | Function 'changeVolume' is used to change the amplitude of the sound. -- For the proper proceeding you specify a @String@, which consists of 4 -- digits (and it may be preceded by a symbol \"-\"). If the @String@ -- begins with the \"-\", then a sound amplitude decreases, otherwise -- the amplitude increases. The level of increase / decrease is -- determined by the magnitude of the absolute value of integer numbers. -- The greater is the number -- the greater is the amplitude change. -- The count begins with \"0000\" and ends with \"9999\" (the sign is not -- taken into consideration). If there is less than 4 digits in a @String@, -- then the @String@ is equivalent to that one with the appropriate number -- of zeroes preceding to fulfill to the 4 needed digits (for example, -- \"657\" is equivalent to \"0657\", \"-2\" is equivalent to \"-0002\" etc.) -- In such a case, for the @String@s without the -- initial sign \"-\" (the sound increases) an interval between the -- maximum by modulus value of the amlitude (which is represented by the -- parts of 1) and 1.0 is divided into 10 equal parts (starting a count -- from 0) and then that one of them is selected, which has a number -- determined by the first digit in the @String@ writing. Then (if specified -- further) the interval between this amplitude value and a value, -- which corresponds to the selection on the previous step the next -- first digit in the writing (for example, after \"4\" -- \"5\", -- after \"7\" -- \"8\" etc.), greater by 1 than the actually selected one, -- is also divided again into 10 equal parts and that one is selected, -- which corresponds to the number determined by the second digit in the -- String writing (again beginning with \"0\" and ending with \"9\") and so on -- until the 4th level. The greater exactness is not needed because our -- hearing ability hardly distinguish such a subtle sound changes. If -- the @String@ has as a first element the \'-\' @Char@ (the sound decreases), -- then everything is analogously the same, but an interval between the -- maximum by modulus amplitude value and 0.0 is divided into 10 equal parts -- and so on. changeVolume :: FilePath -> IO () changeVolume file = do SB.playA file let sound = getBFst' ("е", V.fromList . zip ["A.wav", "B.wav", "C.wav", "D.wav", "E.wav", "F.wav", "G.wav", "H.wav", "I.wav", "J.wav", "K.wav", "L.wav", "M.wav", "N.wav", "O.wav", "P.wav", "Q.wav", "R.wav", "S.wav", "T.wav", "U.wav", "V.wav", "W.wav", "X.wav", "Y.wav", "Z.wav", "a.wav", "b.wav", "c.wav", "d.wav", "e.wav", "f.wav"] $ ["а","б","в","г","д","дж","дз", "е","ж","з","и","й","к","л","м","н","о","п","р", "с","сь","т","у","ф","х","ц","ць","ч","ш","ь","і","ґ"]) file putStrLn $ "You can now change the volume for the played sound representation for the Ukrainian sound " ++ show (map toUpper sound) putStrLn "" putStr "Please, specify the change by passing a String of digits (with may be a preceding symbol \'-\'). " putStr "" putStr "For the proper proceeding you specify a String, which consists of 4 " putStr "digits (and it may be preceded by a symbol \"-\"). If the String " putStr "begins with the \"-\", then a sound amplitude decreases, otherwise " putStr "the amplitude increases. The level of increase / decrease is " putStr "determined by the magnitude of the absolute value of integer numbers. " putStr "The greater is the number -- the greater is the amplitude change. " putStr "The count begins with \"0000\" and ends with \"9999\" (the sign is not " putStr "taken into consideration). If there is less than 4 digits in a String, " putStr "then the String is equivalent to that one with the appropriate number " putStr "of zeroes preceding to fulfill to the 4 needed digits (for example, " putStr "\"657\" is equivalent to \"0657\", \"-2\" is equivalent to \"-0002\" etc.). " putStr "In such a case, for the Strings without the " putStr "initial sign \"-\" (the sound increases) an interval between the " putStr "maximum by modulus value of the amlitude (which is represented by the " putStr "parts of 1) and 1.0 is divided into 10 equal parts (starting a count " putStr "from 0) and then that one of them is selected, which has a number " putStr "determined by the first digit in the String writing. Then (if specified " putStr "further) the interval between this amplitude value and a value, " putStr "which corresponds to the selection on the previous step the next " putStr "first digit in the writing (for example, after \"4\" -- \"5\", " putStr "after \"7\" -- \"8\" etc.), greater by 1 than the actually selected one, " putStr "is also divided again into 10 equal parts and that one is selected, " putStr "which corresponds to the number determined by the second digit in the " putStr "String writing (again beginning with \"0\" and ending with \"9\") and so on " putStr "until the 4th level. The greater exactness is not needed because our " putStr "hearing ability hardly distinguish such a subtle sound changes. If " putStr "the String has as a first element the \'-\' Char (the sound decreases), " putStr "then everything is analogously the same, but an interval between the " putStr "maximum by modulus amplitude value and 0.0 is divided into 10 equal parts " putStrLn "and so on. " onException (specifyVol file) (do putStrLn "" putStrLn "Something went wrong for the sound representation, please, check the input value and repeat once more! " specifyVol file) -- | Function 'specifyVol' is used internally in the 'changeVolume' to get the @String@ and to apply the needed change. specifyVol :: FilePath -> IO () specifyVol file = do change0 <- getLine upperbound <- SB.upperBnd file (originalStr, bool) <- SB.selMaxAbs file (0::Int, upperbound) if bool then changeVol3 file (change0, originalStr) else changeVol4 file (change0, originalStr) -- | Function 'changeVol2' is used internally in the 'specifyVol' in case of decreasing of the sound. changeVol2 :: FilePath -> String -> Double -> IO () changeVol2 file xs ampl = do let ys = take 4 . filter isDigit $ xs coefA = 0.0001 * fromIntegral (read ys::Int) ratio = 1.0 - coefA SB1.volS file (ratio * ampl) -- | Function 'changeVol3' is used internally in the 'specifyVol' in case of working with the maximum amplitude. changeVol3 :: FilePath -> (String, String) -> IO () changeVol3 file (change0, originalStr) = do let ampl = read originalStr::Double if ampl > 0.0 then do let delta = 1.0 - ampl xs = filter (\x -> isDigit x || x == '-') change0 if take 1 xs == "-" then changeVol2 file xs ampl else do let ys = take 4 . takeWhile (isDigit) $ xs coefA = 0.0001 * fromIntegral (read ys::Int) ratio = 1.0 + (delta / ampl) * coefA SB1.volS file (ratio * ampl) else error "SoXBasics1: the volS function gave a strange result!" -- | Function 'changeVol4' is used internally in the 'specifyVol' in case of working with the minimum amplitude. changeVol4 :: FilePath -> (String, String) -> IO () changeVol4 file (change0, originalStr) = do let ampl = read originalStr::Double if ampl < 0.0 then do let delta = (-1.0) - ampl xs = filter (\x -> isDigit x || x == '-') change0 if take 1 xs == "-" then changeVol2 file xs ampl else do let ys = take 4 . filter isDigit $ xs coefA = 0.0001 * fromIntegral (read ys::Int) ratio = 1.0 + (delta / ampl) * coefA SB1.volS file (ratio * ampl) else error "SoXBasics1: the volS function gave a strange result!"