module SoXBasics1 (
norm
, normL
, gainL
, quarterSinFade
, silenceBoth
, resampleA
, noiseReduceB
, noiseReduceE
, sincA
, 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 SB (extremeS1,upperBnd,selMA,maxAbs,norm)
import Control.Exception.FinalException
norm :: FilePath -> IO ()
norm file = if isJust (showE "sox")
then do
(code, _, _) <- readProcessWithExitCode (fromJust (showE "sox")) [file, "8" ++ file, "norm"] ""
if code /= ExitSuccess
then do
e1 <- doesFileExist $ "8" ++ file
if e1
then do
removeFile $ "8" ++ file
catchEnd (NotCreatedWithEffect "norm")
else catchEnd (NotCreatedWithEffect "norm")
else do
e2 <- doesFileExist $ "8" ++ file
if e2
then do
removeFile file
renameFile ("8" ++ file) file
else catchEnd (InitialFileNotChanged file)
else catchEnd ExecutableNotProperlyInstalled
normL :: FilePath -> Int -> IO ()
normL file level = if isJust (showE "sox")
then do
(code, _, _) <- readProcessWithExitCode (fromJust (showE "sox")) [file, "9" ++ file, "gain", "-n", show level] ""
if code /= ExitSuccess
then do
e1 <- doesFileExist $ "9" ++ file
if e1
then do
removeFile $ "9" ++ file
catchEnd (NotCreatedWithEffect "gain -n")
else catchEnd (NotCreatedWithEffect "gain -n")
else do
e2 <- doesFileExist $ "9" ++ file
if e2
then do
removeFile file
renameFile ("9" ++ file) file
else catchEnd (InitialFileNotChanged file)
else catchEnd ExecutableNotProperlyInstalled
gainL :: FilePath -> Double -> IO ()
gainL file level = if isJust (showE "sox")
then do
(code, _, _) <- readProcessWithExitCode (fromJust (showE "sox")) [file, "9" ++ file, "gain", "-b", showFFloat (Just 6) level $ show 0] ""
if code /= ExitSuccess
then do
e1 <- doesFileExist $ "9" ++ file
if e1
then do
removeFile $ "9" ++ file
catchEnd (NotCreatedWithEffect "gain -b")
else catchEnd (NotCreatedWithEffect "gain -b")
else do
e2 <- doesFileExist $ "9" ++ file
if e2
then do
removeFile file
renameFile ("9" ++ file) file
else catchEnd (InitialFileNotChanged file)
else catchEnd ExecutableNotProperlyInstalled
quarterSinFade :: FilePath -> IO ()
quarterSinFade file = if isJust (showE "sox")
then do
pos <- SB.extremeS1 file
upp <- SB.upperBnd file
(code, _, _) <- readProcessWithExitCode (fromJust (showE "sox")) [file, "4" ++ file, "fade", "q", show pos ++ "s", "=" ++ show upp ++ "s", show (upp - pos) ++ "s"] ""
if code /= ExitSuccess
then do
e1 <- doesFileExist $ "4" ++ file
if e1
then do
removeFile $ "4" ++ file
catchEnd (NotCreatedWithEffect "fade q")
else catchEnd (NotCreatedWithEffect "fade q")
else do
e2 <- doesFileExist $ "4" ++ file
if e2
then do
removeFile file
renameFile ("4" ++ file) file
else catchEnd (InitialFileNotChanged file)
else catchEnd ExecutableNotProperlyInstalled
silenceBoth :: FilePath -> Int -> Int -> IO ()
silenceBoth file beginning end = if isJust (showE "sox")
then do
(code, _, _) <- readProcessWithExitCode (fromJust (showE "sox")) [file, "3" ++ file, "delay", show beginning ++ "s", "reverse"] ""
if code /= ExitSuccess
then do
e1 <- doesFileExist $ "3" ++ file
if e1
then do
removeFile $ "3" ++ file
catchEnd (NotCreatedWithEffects "delay reverse")
else catchEnd (NotCreatedWithEffects "delay reverse")
else do
e2 <- doesFileExist $ "3" ++ file
if e2
then do
(code1, _, _) <- readProcessWithExitCode (fromJust (showE "sox")) ["3" ++ file, "2" ++ file, "delay", show end ++ "s", "reverse"] ""
if code1 /= ExitSuccess
then do
e2 <- doesFileExist $ "2" ++ file
if e2
then do
removeFile $ "3" ++ file
removeFile $ "2" ++ file
catchEnd (NotCreated file)
else do
removeFile $ "3" ++ file
catchEnd (NotCreated file)
else do
e3 <- doesFileExist $ "2" ++ file
if e3
then do
removeFile $ "3" ++ file
removeFile file
renameFile ("2" ++ file) file
else do
removeFile $ "3" ++ file
catchEnd (NotCreated file)
else catchEnd (InitialFileNotChanged file)
else catchEnd ExecutableNotProperlyInstalled
resampleA :: FilePath -> Int -> IO ()
resampleA file frequency = if isJust (showE "sox")
then do
(code, _, _) <- readProcessWithExitCode (fromJust (showE "sox")) [file, "3" ++ file, "rate", "-s", "-I", show frequency] ""
if code /= ExitSuccess
then do
e1 <- doesFileExist $ "3" ++ file
if e1
then do
removeFile $ "3" ++ file
catchEnd (NotCreatedWithEffect "rate")
else catchEnd (NotCreatedWithEffect "rate")
else do
e2 <- doesFileExist $ "3" ++ file
if e2
then do
removeFile file
renameFile ("3" ++ file) file
else catchEnd (InitialFileNotChanged file)
else catchEnd ExecutableNotProperlyInstalled
noiseReduceB :: FilePath -> IO ()
noiseReduceB file = if isJust (showE "sox")
then do
(code, _, _) <- readProcessWithExitCode (fromJust (showE "sox")) [file, "_" ++ file, "noisered", file ++ ".b.prof"] ""
if code /= ExitSuccess
then do
e1 <- doesFileExist $ "_" ++ file
if e1
then do
removeFile $ "_" ++ file
catchEnd (NotCreatedWithEffect "noisered")
else catchEnd (NotCreatedWithEffect "noisered")
else do
e2 <- doesFileExist $ "_" ++ file
if e2
then do
removeFile file
renameFile ("_" ++ file) file
else catchEnd (InitialFileNotChanged file)
else catchEnd ExecutableNotProperlyInstalled
noiseReduceE :: FilePath -> IO ()
noiseReduceE file = if isJust (showE "sox")
then do
(code, _, _) <- readProcessWithExitCode (fromJust (showE "sox")) [file, "_." ++ file, "noisered", file ++ ".e.prof"] ""
if code /= ExitSuccess
then do
e1 <- doesFileExist $ "_." ++ file
if e1
then do
removeFile $ "_." ++ file
catchEnd (NotCreatedWithEffect "noisered")
else catchEnd (NotCreatedWithEffect "noisered")
else do
e2 <- doesFileExist $ "_." ++ file
if e2
then do
removeFile file
renameFile ("_." ++ file) file
else catchEnd (InitialFileNotChanged file)
else catchEnd ExecutableNotProperlyInstalled
volS :: FilePath -> Double -> IO ()
volS file amplitude = if isJust (showE "sox")
then do
SB.norm file
e0 <- doesFileExist $ "8" ++ file
if e0
then do
(code, _, _) <- readProcessWithExitCode (fromJust (showE "sox")) ["8" ++ file, "8." ++ file, "vol", showFFloat Nothing amplitude $ show 0, "amplitude"] ""
if code /= ExitSuccess
then do
e1 <- doesFileExist $ "8." ++ file
if e1
then do
removeFile $ "8." ++ file
removeFile $ "8" ++ file
catchEnd (NotCreatedWithEffect "vol")
else do
removeFile $ "8" ++ file
catchEnd (NotCreatedWithEffect "vol")
else do
e2 <- doesFileExist $ "8." ++ file
if e2
then do
removeFile file
removeFile $ "8" ++ file
renameFile ("8." ++ file) file
else do
removeFile $ "8" ++ file
catchEnd (InitialFileNotChanged file)
else catchEnd (InitialFileNotChanged file)
else catchEnd ExecutableNotProperlyInstalled
volS2 :: FilePath -> FilePath -> IO ()
volS2 fileA fileB = if isJust (showE "sox")
then do
upp <- SB.upperBnd fileB
amplMax <- SB.selMA fileB (0, upp) True
amplMin <- SB.selMA fileB (0, upp) False
let ampl = read (fst . SB.maxAbs $ (amplMax, amplMin))::Double
(code, _, _) <- readProcessWithExitCode (fromJust (showE "sox")) [fileA, "8." ++ tail fileA, "vol", showFFloat Nothing ampl $ show 0, "amplitude"] ""
if code /= ExitSuccess
then do
e1 <- doesFileExist $ "8." ++ tail fileA
if e1
then do
removeFile $ "8." ++ tail fileA
catchEnd (NotCreatedWithEffect "vol")
else catchEnd (NotCreatedWithEffect "vol")
else do
file8e <- doesFileExist $ "8." ++ tail fileA
if file8e
then do
removeFile fileA
renameFile ("8." ++ tail fileA) fileA
else catchEnd (InitialFileNotChanged fileA)
else catchEnd ExecutableNotProperlyInstalled
sincA :: FilePath -> IO ()
sincA file = if isJust (showE "sox")
then do
(code, _, _) <- readProcessWithExitCode (fromJust (showE "sox")) [file, "4." ++ file, "sinc", "-a", "50", "-I", "0.07k-11k"] ""
if code /= ExitSuccess
then do
e1 <- doesFileExist $ "4." ++ file
if e1
then do
removeFile $ "4." ++ file
catchEnd (NotCreatedWithEffect "sinc")
else catchEnd (NotCreatedWithEffect "sinc")
else do
e0 <- doesFileExist $ "4." ++ file
if e0
then do
removeFile file
renameFile ("4." ++ file) file
else catchEnd (InitialFileNotChanged file)
else catchEnd ExecutableNotProperlyInstalled