-- | -- Module : SoXBasics1 -- Copyright : (c) OleksandrZhabenko 2020 -- License : MIT -- -- Maintainer : olexandr543@yahoo.com -- -- A program and a library that can be used as a simple -- basic interface to some SoX functionality or for producing -- the approximately Ukrainian speech with your own recorded -- voice (actually it produces the needed sound representations). -- This module differs from a SoXBasics that the resulting files -- in it have possibly just the same name as the input ones. The functions -- try to replace the initial file with the processed one. -- module SoXBasics1 ( -- * Produce sound -- ** Amplitude modification norm , normL , gainL , quarterSinFade -- ** Adding silence , silenceBoth -- ** Changing sample rate , resampleA -- ** Working with noise , noiseReduceB , noiseReduceE -- ** Filtering , sincA -- ** Volume amplification , volS , volS2 ) where import System.Directory import Data.Maybe (isJust, fromJust) import Numeric import System.Process import EndOfExe import System.Exit import qualified SoXBasics as SX (extremeS1,upperBnd,selMA,maxAbs,norm) -- | Function 'norm' applies a SoX normalization effect on the audio file. -- The function must be used with the @FilePath@ parameter containing no directories in its name (that means the file of the @FilePath@ parameter must be -- in the same directory where the function is called from). While being -- executed the function tries to replace the initial file with the resulting processed one and to clean the temporary files. If it is not -- successful the function exits with error and leaves the initial file without modification. norm :: FilePath -> IO () norm file = if isJust (showE "sox") then do _ <- readProcessWithExitCode (fromJust (showE "sox")) [file, "8" ++ file, "norm"] "" exist0 <- doesFileExist $ "8" ++ file if exist0 then do removeFile file renameFile ("8" ++ file) file else error "The initial file was not changed!" else error "SoX is not properly installed in your system. Please, install it properly and then call the function again." -- | Function 'normL' applies a SoX gain effect on the audio file with the maximum absolute dB value given by the @Int@ argument. -- The function must be used with the @FilePath@ parameter containing no directories in its name (that means the file of the @FilePath@ parameter must be -- in the same directory where the function is called from). While being -- executed the function tries to replace the initial file with the resulting processed one and to clean the temporary files. If it is not -- successful the function exits with error and leaves the initial file without modification. normL :: FilePath -> Int -> IO () normL file level = if isJust (showE "sox") then do _ <- readProcessWithExitCode (fromJust (showE "sox")) [file, "9" ++ file, "gain", "-n", show level] "" exist0 <- doesFileExist $ "9" ++ file if exist0 then do removeFile file renameFile ("9" ++ file) file else error "The initial file was not changed!" else error "SoX is not properly installed in your system. Please, install it properly and then call the function again." -- | Function 'normL' applies a SoX \"gain -b [db-Value]\" effect on the audio file with dB value given by the @Double@ argument. -- The function must be used with the @FilePath@ parameter containing no directories in its name (that means the file of the @FilePath@ parameter must be -- in the same directory where the function is called from). While being -- executed the function tries to replace the initial file with the resulting processed one and to clean the temporary files. If it is not -- successful the function exits with error and leaves the initial file without modification. gainL :: FilePath -> Double -> IO () gainL file level = if isJust (showE "sox") then do _ <- readProcessWithExitCode (fromJust (showE "sox")) [file, "9" ++ file, "gain", "-b", showFFloat (Just 6) level $ show 0] "" exist0 <- doesFileExist $ "9" ++ file if exist0 then do removeFile file renameFile ("9" ++ file) file else error "The initial file was not changed!" else error "SoX is not properly installed in your system. Please, install it properly and then call the function again." -- | Function 'quarterSinFade' applies a fade effect by SoX to the audio file with \"q\" type. -- The function must be used with the @FilePath@ parameter containing no directories in its name (that means the file of the @FilePath@ parameter must be -- in the same directory where the function is called from). While being -- executed the function tries to replace the initial file with the resulting processed one and to clean the temporary files. If it is not -- successful the function exits with error and leaves the initial file without modification. quarterSinFade :: FilePath -> IO () quarterSinFade file = if isJust (showE "sox") then do pos <- SX.extremeS1 file upp <- SX.upperBnd file _ <- readProcessWithExitCode (fromJust (showE "sox")) [file, "4" ++ file, "fade", "q", show pos ++ "s", "=" ++ show upp ++ "s", show (upp - pos) ++ "s"] "" exist0 <- doesFileExist $ "4" ++ file if exist0 then do removeFile file renameFile ("4" ++ file) file else error "The initial file was not changed!" else error "SoX is not properly installed in your system. Please, install it properly and then call the function again." -- | Function 'silenceBoth' adds some silence to both ends of the audio. -- The function must be used with the @FilePath@ parameter containing no directories in its name (that means the file of the @FilePath@ parameter must be -- in the same directory where the function is called from). While being -- executed the function tries to replace the initial file with the resulting processed one and to clean the temporary files. If it is not -- successful the function exits with error and leaves the initial file without modification. silenceBoth :: FilePath -> Int -> Int -> IO () silenceBoth file beginning end = if isJust (showE "sox") then do _ <- readProcessWithExitCode (fromJust (showE "sox")) [file, "3" ++ file, "delay", show beginning ++ "s", "reverse"] "" _ <- readProcessWithExitCode (fromJust (showE "sox")) ["3" ++ file, "2" ++ file, "delay", show end ++ "s", "reverse"] "" exist0 <- doesFileExist $ "3" ++ file exist1 <- doesFileExist $ "2" ++ file if exist0 then if exist1 then do removeFile $ "3" ++ file removeFile file renameFile ("2" ++ file) file else do removeFile $ "3" ++ file error "The resulting file was not created!" else error "The initial file was not changed!" else error "SoX is not properly installed in your system. Please, install it properly and then call the function again." -- | Function 'resampleA' changes the sample rate for the recorded audio for further processing. -- The function must be used with the @FilePath@ parameter containing no directories in its name (that means the file of the @FilePath@ parameter must be -- in the same directory where the function is called from). While being -- executed the function tries to replace the initial file with the resulting processed one and to clean the temporary files. If it is not -- successful the function exits with error and leaves the initial file without modification. resampleA :: FilePath -> Int -> IO () resampleA file frequency = if isJust (showE "sox") then do _ <- readProcessWithExitCode (fromJust (showE "sox")) [file, "3" ++ file, "rate", "-s", "-I", show frequency] "" exist0 <- doesFileExist $ "3" ++ file if exist0 then do removeFile file renameFile ("3" ++ file) file else error "The initial file was not changed!" else error "SoX is not properly installed in your system. Please, install it properly and then call the function again." -- | Function 'noiseReduceB' reduces with SoX a noise in the file given with the corresponding noise profile created with 'noiseProfB' function. -- The function must be used with the @FilePath@ parameter containing no directories in its name (that means the file of the @FilePath@ parameter must be -- in the same directory where the function is called from). While being -- executed the function tries to replace the initial file with the resulting processed one and to clean the temporary files. If it is not -- successful the function exits with error and leaves the initial file without modification. noiseReduceB :: FilePath -> IO () noiseReduceB file = if isJust (showE "sox") then do _ <- readProcessWithExitCode (fromJust (showE "sox")) [file, "_" ++ file, "noisered", file ++ ".b.prof"] "" exist0 <- doesFileExist $ "_" ++ file if exist0 then do removeFile file renameFile ("_" ++ file) file else error "The initial file was not changed!" else error "SoX is not properly installed in your system. Please, install it properly and then call the function again." -- | Function 'noiseReduceE' reduces with SoX a noise in the file given with the corresponding noise profile created with 'noiseProfE' function. -- The function must be used with the @FilePath@ parameter containing no directories in its name (that means the file of the @FilePath@ parameter must be -- in the same directory where the function is called from). While being -- executed the function tries to replace the initial file with the resulting processed one and to clean the temporary files. If it is not -- successful the function exits with error and leaves the initial file without modification. noiseReduceE :: FilePath -> IO () noiseReduceE file = if isJust (showE "sox") then do _ <- readProcessWithExitCode (fromJust (showE "sox")) [file, "_." ++ file, "noisered", file ++ ".e.prof"] "" exist0 <- doesFileExist $ "_." ++ file if exist0 then do removeFile file renameFile ("_." ++ file) file else error "The initial file was not changed!" else error "SoX is not properly installed in your system. Please, install it properly and then call the function again." -- | Function 'volS' changes the given audio with the linear ratio for the amplitude so that the resulting amlitude is equal to the given @Double@ parameter. -- The function must be used with the @FilePath@ parameter containing no directories in its name (that means the file of the @FilePath@ parameter must be -- in the same directory where the function is called from). While being -- executed the function tries to replace the initial file with the resulting processed one and to clean the temporary files. If it is not -- successful the function exits with error and leaves the initial file without modification. volS :: FilePath -> Double -> IO () volS file amplitude = if isJust (showE "sox") then do SX.norm file exist0 <- doesFileExist $ "8" ++ file if exist0 then do _ <- readProcessWithExitCode (fromJust (showE "sox")) ["8" ++ file, "8." ++ file, "vol", showFFloat Nothing amplitude $ show 0, "amplitude"] "" exist1 <- doesFileExist $ "8." ++ file if exist1 then do removeFile file removeFile $ "8" ++ file renameFile ("8." ++ file) file else do removeFile $ "8" ++ file error "The initial file was not changed!" else error "The initial file was not changed at all!" else error "SoX is not properly installed in your system. Please, install it properly and then call the function again." -- | Function 'volS2' changes the given audio (the first @FilePath@ parameter, which must be normalized e. g. by the 'norm' function before) with -- the linear ratio for the amplitude so that the resulting amlitude is equal to the maximum by absolute value amplitude for the file given -- by the second @FilePath@ parameter. The function must be used with the first @FilePath@ parameter containing no directories in its name -- (that means the file of the first @FilePath@ parameter must be in the same directory where the function is called from). While being -- executed the function tries to replace the initial file with the resulting processed one and to clean the temporary files. If it is not -- successful the function exits with error and leaves the initial file without modification. volS2 :: FilePath -> FilePath -> IO () volS2 fileA fileB = if isJust (showE "sox") then do upp <- SX.upperBnd fileB amplMax <- SX.selMA fileB (0, upp) True amplMin <- SX.selMA fileB (0, upp) False let ampl = read (fst . SX.maxAbs $ (amplMax, amplMin))::Double (code, _, _) <- readProcessWithExitCode (fromJust (showE "sox")) [fileA, "8." ++ tail fileA, "vol", showFFloat Nothing ampl $ show 0, "amplitude"] "" if code /= ExitSuccess then error "File was not created with \"vol\" effect!" else do file8e <- doesFileExist $ "8." ++ tail fileA if file8e then do removeFile fileA renameFile ("8." ++ tail fileA) fileA else error "The initial file was not changed!" else error "SoX is not properly installed in your system. Please, install it properly and then call the function again." -- | Function 'sincA' uses a \"sinc\" effect with @-a 50 -I 0.07k-11k@ band-pass filter for the audio file given. While being -- executed the function tries to replace the initial file with the resulting processed one and to clean the temporary files. If it is not -- successful the function exits with error and leaves the initial file without modification. sincA :: FilePath -> IO () sincA file = if isJust (showE "sox") then do _ <- readProcessWithExitCode (fromJust (showE "sox")) [file, "4." ++ file, "sinc", "-a", "50", "-I", "0.07k-11k"] "" exist0 <- doesFileExist $ "4." ++ file if exist0 then do removeFile file renameFile ("4." ++ file) file else error "The initial file was not changed!" else error "SoX is not properly installed in your system. Please, install it properly and then call the function again."