module Processing_mmsyn7ukr where
import Numeric
import System.Directory
import Control.Exception (bracketOnError, onException)
import EndOfExe (showE)
import Data.Maybe (fromJust)
import Data.Char
import Data.List (isSuffixOf)
import qualified Data.Vector as V
import qualified Data.ByteString.Lazy as B
import System.Process
import System.IO
import SoXBasics
import Melodics.Ukrainian (convertToProperUkrainian, takeData)
import UkrainianLControl
import CaseBi (getBFst')
produceSound :: FilePath -> IO ()
produceSound file = let file1 = drop (length file - 5) file in do
let soundUkr = 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"] $ ["а", "б", "в", "г", "д", "дж", "дз", "е", "ж", "з", "и", "й", "к", "л", "м", "н", "о", "п", "р",
"с", "сь", "т", "у", "ф", "х", "ц", "ць", "ч", "ш", "ь", "і", "ґ"]) $ file1
putStr "The needed files were NOT created, because the sound was not at the moment of recording! The process will be restarted "
putStrLn "for the sound. Please, produce a sound during the first 3 seconds (after 0.5 second delay) or specify greater ratio!"
playA file
putStrLn "The sound duration is:"
duration0 <- durationA file
putStrLn $ showFFloat Nothing duration0 $ show 0
putStrLn ""
putStrLn "It means that to produce more than 3 seconds of recording, you must specify at least "
putStrLn $ " " ++ show (3.0/(7*duration0)) ++ " as a next step ratio being prompt "
putStrLn " OR "
putStrLn $ " " ++ show (1.0/(7*duration0)) ++ " per one second but not less than the previous number."
putStrLn $ "For example for 10 seconds record, please, specify " ++ show (10.0/(7*duration0)) ++ " as a next step ratio."
longerK0 <- tempS soundUkr
(_, Just hout, _, _) <- createProcess (proc (fromJust . showE $ "soxi") ["-D", file]) { std_out = CreatePipe }
x3 <- hGetContents hout
let longerK = (read x3::Double)*longerK0
putStrLn "Please, wait for 0.5 second and pronounce the sound representation for the "
putStrLn ""
putStrLn $ " \"" ++ (if soundUkr /= "ь" then map toUpper soundUkr else soundUkr) ++ "\""
putStrLn ""
putStrLn " sound or whatever you would like to be substituted instead (be sensible, please)! "
if (compare (7*longerK) 3.0 == LT)
then recA "x.wav" (7*longerK)
else recA "x.wav" 3.0
putStrLn "The file is recorded and now will be automatically processed. You will be notificated with the text message in the terminal about the creation of the needed file. Please, wait a little. "
norm "x.wav"
noiseProfB "8x.wav"
noiseReduceB "8x.wav"
lim0 <- durationA "_8x.wav"
alterVadB "_8x.wav" lim0
lim1 <- durationA "7_8x.wav"
if lim1 <= 0.0
then beginProcessing file file1 soundUkr
else do
alterVadE "7_8x.wav" lim1
sincA "67_8x.wav"
resampleA "4.67_8x.wav" (22050::Int)
quarterSinFade "34.67_8x.wav"
norm "434.67_8x.wav"
volS2 "8434.67_8x.wav" file
renameFile "8.434.67_8x.wav" file1
cleanTemp
beginProcessing :: FilePath -> FilePath -> String -> IO ()
beginProcessing file file1 soundUkr = do
cleanTemp
putStr "The needed files were NOT created, because the sound was not at the moment of recording! The process will be restarted "
putStrLn "for the sound. Please, produce a sound during the first 3 seconds (after 0.5 second delay) or specify greater ratio!"
putStrLn $ "Listen to the \"" ++ soundUkr ++ "\" sound and note first of all its duration. "
playA file
putStrLn "The sound duration is:"
duration0 <- durationA file
putStrLn $ showFFloat Nothing duration0 $ show 0
putStrLn ""
putStrLn "It means that to produce more than 3 seconds of recording, you must specify at least "
putStrLn $ " " ++ show (3.0/(7*duration0)) ++ " as a next step ratio being prompt "
putStrLn " OR "
putStrLn $ " " ++ show (1.0/(7*duration0)) ++ " per one second but not less than the previous number."
putStrLn $ "For example for 10 seconds record, please, specify " ++ show (10.0/(7*duration0)) ++ " as a next step ratio."
longerK0 <- tempS soundUkr
(_, Just hout, _, _) <- createProcess (proc (fromJust . showE $ "soxi") ["-D", file]) { std_out = CreatePipe }
x3 <- hGetContents hout
let longerK = (read x3::Double)*longerK0
putStrLn "Please, wait for 0.5 second and pronounce the sound representation for the "
putStrLn ""
putStrLn $ " \"" ++ (if soundUkr /= "ь" then map toUpper soundUkr else soundUkr) ++ "\""
putStrLn ""
putStrLn " sound or whatever you would like to be substituted instead (be sensible, please)! "
if (compare (7*longerK) 3.0 == LT)
then recA "x.wav" (7*longerK)
else recA "x.wav" 3.0
putStrLn "The file is recorded and now will be automatically processed. You will be notificated with the text message in the terminal about the creation of the needed file. Please, wait a little. "
norm "x.wav"
noiseProfB "8x.wav"
noiseReduceB "8x.wav"
lim0 <- durationA "_8x.wav"
alterVadB "_8x.wav" lim0
lim1 <- durationA "7_8x.wav"
if lim1 <= 0.0
then beginProcessing file file1 soundUkr
else do
alterVadE "7_8x.wav" lim1
sincA "67_8x.wav"
resampleA "4.67_8x.wav" (22050::Int)
quarterSinFade "34.67_8x.wav"
norm "434.67_8x.wav"
volS2 "8434.67_8x.wav" file
renameFile "8.434.67_8x.wav" file1
cleanTemp
tempS :: String -> IO Double
tempS soundUkr = onException (do
putStrLn "In how many times do you think your sound representing "
putStrLn ""
putStrLn $ " \"" ++ (if soundUkr /= "ь" then map toUpper soundUkr else soundUkr) ++ "\""
putStrLn ""
putStrLn "will sound longer than the recently played one? Specify as a Double value without \"e\" notation. "
longivityY <- getLine
let long = read longivityY::Double in return long) (do
putStrLn "Please, specify the value of the Double type!"
tempS soundUkr)
cleanTemp :: IO ()
cleanTemp = do
filenames <- getDirectoryContents =<< getCurrentDirectory
let rems = filter (\x -> head x `elem` (['2'..'9'] ++ "_" ++ "x")) filenames in mapM_ removeFile rems