module Sound.SoXBasics1 (
moveSnd2Fst
, getULFromExt
, twoExceptions2Files
, threeFiles1Exception
, norm
, normL
, gainL
, quarterSinFade
, silenceBoth
, resampleA
, noiseReduceB
, noiseReduceE
, noiseReduceBU
, noiseReduceEU
, sincA
, volS
, volS2
) where
import System.Directory
import Data.Maybe (isJust, fromJust)
import Numeric
import System.Process
import EndOfExe2
import System.Exit
import qualified Sound.SoXBasics as SB (ULencode(..), SoundFileExts(..), soxOpG, soxOpG1,
ulAccessParameters, ulResultParameters, doubleCleanCheck, presenseCheck, secondFileClean,
twoIntermediateFs, twoExceptions1File, applyExts2, beforeExtStr, extremeS1,upperBndG,selMAG,maxAbs,normG)
import Sound.Control.Exception.FinalException
moveSnd2Fst :: FilePath -> FilePath -> FinalException -> IO ()
moveSnd2Fst :: FilePath -> FilePath -> FinalException -> IO ()
moveSnd2Fst FilePath
file1 FilePath
file2 FinalException
exception = do
Bool
e2 <- FilePath -> IO Bool
doesFileExist FilePath
file2
if Bool
e2
then do
FilePath -> IO ()
removeFile FilePath
file1
FilePath -> FilePath -> IO ()
renameFile FilePath
file2 FilePath
file1
else FinalException -> IO ()
catchEnd FinalException
exception
getULFromExt :: FilePath -> SB.ULencode
getULFromExt :: FilePath -> ULencode
getULFromExt FilePath
file =
case FilePath
end of
FilePath
".wav" -> ULencode
SB.W
(Char
z:FilePath
".ul") -> ULencode
SB.UL
FilePath
_ -> FilePath -> ULencode
forall a. HasCallStack => FilePath -> a
error FilePath
"Sound.SoXBasics1.getULFromExt: The file has neither .wav, nor .ul extension."
where l :: Int
l = FilePath -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length FilePath
file Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
4
(FilePath
begin,FilePath
end) = Int -> FilePath -> (FilePath, FilePath)
forall a. Int -> [a] -> ([a], [a])
splitAt Int
l FilePath
file
norm :: FilePath -> IO ()
norm :: FilePath -> IO ()
norm FilePath
file = if Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust (FilePath -> Maybe FilePath
showE FilePath
"sox")
then do
(ExitCode
code, FilePath
_, FilePath
_) <- ULencode
-> [FilePath]
-> FilePath
-> [FilePath]
-> FilePath
-> [FilePath]
-> IO (ExitCode, FilePath, FilePath)
SB.soxOpG (FilePath -> ULencode
getULFromExt FilePath
file) [] FilePath
file [] (FilePath
"8" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) [FilePath
"norm"]
if ExitCode
code ExitCode -> ExitCode -> Bool
forall a. Eq a => a -> a -> Bool
/= ExitCode
ExitSuccess
then FilePath -> FinalException -> IO ()
SB.doubleCleanCheck (FilePath
"8" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) (FilePath -> FinalException
NotCreatedWithEffect FilePath
"norm")
else FilePath -> FilePath -> FinalException -> IO ()
moveSnd2Fst (FilePath
"8" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) FilePath
file (FilePath -> FinalException
InitialFileNotChanged FilePath
file)
else FinalException -> IO ()
catchEnd FinalException
ExecutableNotProperlyInstalled
twoExceptions2Files :: ExitCode -> FilePath -> FilePath -> FinalException -> FinalException -> IO ()
twoExceptions2Files :: ExitCode
-> FilePath
-> FilePath
-> FinalException
-> FinalException
-> IO ()
twoExceptions2Files ExitCode
code FilePath
file1 FilePath
file2 FinalException
exc1 FinalException
exc2 =
if ExitCode
code ExitCode -> ExitCode -> Bool
forall a. Eq a => a -> a -> Bool
/= ExitCode
ExitSuccess then FilePath -> FinalException -> IO ()
SB.doubleCleanCheck FilePath
file2 FinalException
exc1 else FilePath -> FilePath -> FinalException -> IO ()
moveSnd2Fst FilePath
file1 FilePath
file2 FinalException
exc2
normL :: FilePath -> Int -> IO ()
normL :: FilePath -> Int -> IO ()
normL FilePath
file Int
level = if Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust (FilePath -> Maybe FilePath
showE FilePath
"sox")
then do
(ExitCode
code, FilePath
_, FilePath
_) <- ULencode
-> [FilePath]
-> FilePath
-> [FilePath]
-> FilePath
-> [FilePath]
-> IO (ExitCode, FilePath, FilePath)
SB.soxOpG (FilePath -> ULencode
getULFromExt FilePath
file) [] FilePath
file [] (FilePath
"9" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) [FilePath
"gain", FilePath
"-n", Int -> FilePath
forall a. Show a => a -> FilePath
show Int
level]
ExitCode
-> FilePath
-> FilePath
-> FinalException
-> FinalException
-> IO ()
twoExceptions2Files ExitCode
code FilePath
file (FilePath
"9" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) (FilePath -> FinalException
NotCreatedWithEffect FilePath
"gain -n") (FilePath -> FinalException
InitialFileNotChanged FilePath
file)
else FinalException -> IO ()
catchEnd FinalException
ExecutableNotProperlyInstalled
gainL :: FilePath -> Float -> IO ()
gainL :: FilePath -> Float -> IO ()
gainL FilePath
file Float
level = if Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust (FilePath -> Maybe FilePath
showE FilePath
"sox")
then do
(ExitCode
code, FilePath
_, FilePath
_) <- ULencode
-> [FilePath]
-> FilePath
-> [FilePath]
-> FilePath
-> [FilePath]
-> IO (ExitCode, FilePath, FilePath)
SB.soxOpG (FilePath -> ULencode
getULFromExt FilePath
file) [] FilePath
file [] (FilePath
"9" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) [FilePath
"gain", FilePath
"-b", Maybe Int -> Float -> FilePath -> FilePath
forall a. RealFloat a => Maybe Int -> a -> FilePath -> FilePath
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
6) Float
level (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ Integer -> FilePath
forall a. Show a => a -> FilePath
show Integer
0]
ExitCode
-> FilePath
-> FilePath
-> FinalException
-> FinalException
-> IO ()
twoExceptions2Files ExitCode
code FilePath
file (FilePath
"9" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) (FilePath -> FinalException
NotCreatedWithEffect FilePath
"gain -b") (FilePath -> FinalException
InitialFileNotChanged FilePath
file)
else FinalException -> IO ()
catchEnd FinalException
ExecutableNotProperlyInstalled
quarterSinFade :: FilePath -> IO ()
quarterSinFade :: FilePath -> IO ()
quarterSinFade FilePath
file = if Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust (FilePath -> Maybe FilePath
showE FilePath
"sox")
then do
Int
pos <- FilePath -> IO Int
SB.extremeS1 FilePath
file
Int
upp <- ULencode -> FilePath -> IO Int
SB.upperBndG (FilePath -> ULencode
getULFromExt FilePath
file) FilePath
file
(ExitCode
code, FilePath
_, FilePath
_) <- ULencode
-> [FilePath]
-> FilePath
-> [FilePath]
-> FilePath
-> [FilePath]
-> IO (ExitCode, FilePath, FilePath)
SB.soxOpG (FilePath -> ULencode
getULFromExt FilePath
file) [] FilePath
file [] (FilePath
"4" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) [FilePath
"fade", FilePath
"q", Int -> FilePath
forall a. Show a => a -> FilePath
show Int
pos FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"s", FilePath
"=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> FilePath
forall a. Show a => a -> FilePath
show Int
upp FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"s", Int -> FilePath
forall a. Show a => a -> FilePath
show (Int
upp Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
pos) FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"s"]
ExitCode
-> FilePath
-> FilePath
-> FinalException
-> FinalException
-> IO ()
twoExceptions2Files ExitCode
code FilePath
file (FilePath
"4" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) (FilePath -> FinalException
NotCreatedWithEffect FilePath
"fade q") (FilePath -> FinalException
InitialFileNotChanged FilePath
file)
else FinalException -> IO ()
catchEnd FinalException
ExecutableNotProperlyInstalled
threeFiles1Exception :: ExitCode -> FilePath -> FilePath -> FilePath -> FinalException -> IO ()
threeFiles1Exception :: ExitCode
-> FilePath -> FilePath -> FilePath -> FinalException -> IO ()
threeFiles1Exception ExitCode
code FilePath
file1 FilePath
file2 FilePath
file3 FinalException
exception
| ExitCode
code ExitCode -> ExitCode -> Bool
forall a. Eq a => a -> a -> Bool
/= ExitCode
ExitSuccess = do
Bool
e2 <- FilePath -> IO Bool
doesFileExist FilePath
file3
if Bool
e2 then FilePath -> IO ()
removeFile FilePath
file3 else FilePath -> IO ()
putStr FilePath
""
FilePath -> IO ()
removeFile FilePath
file2
FinalException -> IO ()
catchEnd FinalException
exception
| Bool
otherwise = do
Bool
e3 <- FilePath -> IO Bool
doesFileExist FilePath
file3
FilePath -> IO ()
removeFile FilePath
file2
if Bool
e3
then do
FilePath -> IO ()
removeFile FilePath
file1
FilePath -> FilePath -> IO ()
renameFile FilePath
file3 FilePath
file1
else FinalException -> IO ()
catchEnd FinalException
exception
silenceBoth :: FilePath -> Int -> Int -> IO ()
silenceBoth :: FilePath -> Int -> Int -> IO ()
silenceBoth FilePath
file Int
beginning Int
end = if Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust (FilePath -> Maybe FilePath
showE FilePath
"sox")
then do
(ExitCode
code, FilePath
_, FilePath
_) <- ULencode
-> [FilePath]
-> FilePath
-> [FilePath]
-> FilePath
-> [FilePath]
-> IO (ExitCode, FilePath, FilePath)
SB.soxOpG (FilePath -> ULencode
getULFromExt FilePath
file) [] FilePath
file [] (FilePath
"3" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) [FilePath
"delay", Int -> FilePath
forall a. Show a => a -> FilePath
show Int
beginning FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"s", FilePath
"reverse"]
if ExitCode
code ExitCode -> ExitCode -> Bool
forall a. Eq a => a -> a -> Bool
/= ExitCode
ExitSuccess
then FilePath -> FinalException -> IO ()
SB.doubleCleanCheck (FilePath
"3" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) (FilePath -> FinalException
NotCreatedWithEffects FilePath
"delay reverse")
else do
Bool
e2 <- FilePath -> IO Bool
doesFileExist (FilePath -> IO Bool) -> FilePath -> IO Bool
forall a b. (a -> b) -> a -> b
$ FilePath
"3" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file
if Bool
e2
then do
(ExitCode
code1, FilePath
_, FilePath
_) <- ULencode
-> [FilePath]
-> FilePath
-> [FilePath]
-> FilePath
-> [FilePath]
-> IO (ExitCode, FilePath, FilePath)
SB.soxOpG (FilePath -> ULencode
getULFromExt FilePath
file) [] (FilePath
"3" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) [] (FilePath
"2" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) [FilePath
"delay", Int -> FilePath
forall a. Show a => a -> FilePath
show Int
end FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"s", FilePath
"reverse"]
ExitCode
-> FilePath -> FilePath -> FilePath -> FinalException -> IO ()
threeFiles1Exception ExitCode
code1 FilePath
file (FilePath
"3" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) (FilePath
"2" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) (FilePath -> FinalException
NotCreated FilePath
file)
else FinalException -> IO ()
catchEnd (FilePath -> FinalException
InitialFileNotChanged FilePath
file)
else FinalException -> IO ()
catchEnd FinalException
ExecutableNotProperlyInstalled
resampleA :: FilePath -> Int -> IO ()
resampleA :: FilePath -> Int -> IO ()
resampleA FilePath
file Int
frequency = if Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust (FilePath -> Maybe FilePath
showE FilePath
"sox")
then do
(ExitCode
code, FilePath
_, FilePath
_) <- ULencode
-> [FilePath]
-> FilePath
-> [FilePath]
-> FilePath
-> [FilePath]
-> IO (ExitCode, FilePath, FilePath)
SB.soxOpG (FilePath -> ULencode
getULFromExt FilePath
file) [] FilePath
file [] (FilePath
"3" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) [FilePath
"rate", FilePath
"-s", FilePath
"-I", Int -> FilePath
forall a. Show a => a -> FilePath
show Int
frequency]
ExitCode
-> FilePath
-> FilePath
-> FinalException
-> FinalException
-> IO ()
twoExceptions2Files ExitCode
code FilePath
file (FilePath
"3" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) (FilePath -> FinalException
NotCreatedWithEffect FilePath
"rate") (FilePath -> FinalException
InitialFileNotChanged FilePath
file)
else FinalException -> IO ()
catchEnd FinalException
ExecutableNotProperlyInstalled
noiseReduceB :: FilePath -> IO ()
noiseReduceB :: FilePath -> IO ()
noiseReduceB FilePath
file = if Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust (FilePath -> Maybe FilePath
showE FilePath
"sox")
then do
(ExitCode
code, FilePath
_, FilePath
_) <- ULencode
-> [FilePath]
-> FilePath
-> [FilePath]
-> FilePath
-> [FilePath]
-> IO (ExitCode, FilePath, FilePath)
SB.soxOpG (FilePath -> ULencode
getULFromExt FilePath
file) [] FilePath
file [] (FilePath
"_" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) [FilePath
"noisered", FilePath
file FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
".b.prof"]
ExitCode
-> FilePath
-> FilePath
-> FinalException
-> FinalException
-> IO ()
twoExceptions2Files ExitCode
code FilePath
file (FilePath
"_" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) (FilePath -> FinalException
NotCreatedWithEffect FilePath
"noisered") (FilePath -> FinalException
InitialFileNotChanged FilePath
file)
else FinalException -> IO ()
catchEnd FinalException
ExecutableNotProperlyInstalled
noiseReduceE :: FilePath -> IO ()
noiseReduceE :: FilePath -> IO ()
noiseReduceE FilePath
file = if Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust (FilePath -> Maybe FilePath
showE FilePath
"sox")
then do
(ExitCode
code, FilePath
_, FilePath
_) <- ULencode
-> [FilePath]
-> FilePath
-> [FilePath]
-> FilePath
-> [FilePath]
-> IO (ExitCode, FilePath, FilePath)
SB.soxOpG (FilePath -> ULencode
getULFromExt FilePath
file) [] FilePath
file [] (FilePath
"_." FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) [FilePath
"noisered", FilePath
file FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
".e.prof"]
ExitCode
-> FilePath
-> FilePath
-> FinalException
-> FinalException
-> IO ()
twoExceptions2Files ExitCode
code FilePath
file (FilePath
"_." FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) (FilePath -> FinalException
NotCreatedWithEffect FilePath
"noisered") (FilePath -> FinalException
InitialFileNotChanged FilePath
file)
else FinalException -> IO ()
catchEnd FinalException
ExecutableNotProperlyInstalled
noiseReduceBU :: FilePath -> Float -> IO ()
noiseReduceBU :: FilePath -> Float -> IO ()
noiseReduceBU FilePath
file Float
amount = if Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust (FilePath -> Maybe FilePath
showE FilePath
"sox")
then do
(ExitCode
code, FilePath
_, FilePath
_) <- ULencode
-> [FilePath]
-> FilePath
-> [FilePath]
-> FilePath
-> [FilePath]
-> IO (ExitCode, FilePath, FilePath)
SB.soxOpG (FilePath -> ULencode
getULFromExt FilePath
file) [] FilePath
file [] (FilePath
"_" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) [FilePath
"noisered", FilePath
file FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
".b.prof", Maybe Int -> Float -> FilePath -> FilePath
forall a. RealFloat a => Maybe Int -> a -> FilePath -> FilePath
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) Float
amount (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ Integer -> FilePath
forall a. Show a => a -> FilePath
show Integer
0]
ExitCode
-> FilePath
-> FilePath
-> FinalException
-> FinalException
-> IO ()
twoExceptions2Files ExitCode
code FilePath
file (FilePath
"_" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) (FilePath -> FinalException
NotCreatedWithEffect FilePath
"noisered") (FilePath -> FinalException
InitialFileNotChanged FilePath
file)
else FinalException -> IO ()
catchEnd FinalException
ExecutableNotProperlyInstalled
noiseReduceEU :: FilePath -> Float -> IO ()
noiseReduceEU :: FilePath -> Float -> IO ()
noiseReduceEU FilePath
file Float
amount = if Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust (FilePath -> Maybe FilePath
showE FilePath
"sox")
then do
(ExitCode
code, FilePath
_, FilePath
_) <- ULencode
-> [FilePath]
-> FilePath
-> [FilePath]
-> FilePath
-> [FilePath]
-> IO (ExitCode, FilePath, FilePath)
SB.soxOpG (FilePath -> ULencode
getULFromExt FilePath
file) [] FilePath
file [] (FilePath
"_." FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) [FilePath
"noisered", FilePath
file FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
".e.prof", Maybe Int -> Float -> FilePath -> FilePath
forall a. RealFloat a => Maybe Int -> a -> FilePath -> FilePath
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) Float
amount (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ Integer -> FilePath
forall a. Show a => a -> FilePath
show Integer
0]
ExitCode
-> FilePath
-> FilePath
-> FinalException
-> FinalException
-> IO ()
twoExceptions2Files ExitCode
code FilePath
file (FilePath
"_." FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) (FilePath -> FinalException
NotCreatedWithEffect FilePath
"noisered") (FilePath -> FinalException
InitialFileNotChanged FilePath
file)
else FinalException -> IO ()
catchEnd FinalException
ExecutableNotProperlyInstalled
volS :: FilePath -> Float -> IO ()
volS :: FilePath -> Float -> IO ()
volS FilePath
file Float
amplitude = if Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust (FilePath -> Maybe FilePath
showE FilePath
"sox")
then do
ULencode -> FilePath -> IO ()
SB.normG (FilePath -> ULencode
getULFromExt FilePath
file) FilePath
file
Bool
e0 <- FilePath -> IO Bool
doesFileExist (FilePath -> IO Bool) -> FilePath -> IO Bool
forall a b. (a -> b) -> a -> b
$ FilePath
"8" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file
if Bool
e0
then do
(ExitCode
code, FilePath
_, FilePath
_) <- ULencode
-> [FilePath]
-> FilePath
-> [FilePath]
-> FilePath
-> [FilePath]
-> IO (ExitCode, FilePath, FilePath)
SB.soxOpG (FilePath -> ULencode
getULFromExt FilePath
file) [] (FilePath
"8" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) [] (FilePath
"8." FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) [FilePath
"vol", Maybe Int -> Float -> FilePath -> FilePath
forall a. RealFloat a => Maybe Int -> a -> FilePath -> FilePath
showFFloat Maybe Int
forall a. Maybe a
Nothing Float
amplitude (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ Integer -> FilePath
forall a. Show a => a -> FilePath
show Integer
0, FilePath
"amplitude"]
if ExitCode
code ExitCode -> ExitCode -> Bool
forall a. Eq a => a -> a -> Bool
/= ExitCode
ExitSuccess
then do
Bool
e1 <- FilePath -> IO Bool
doesFileExist (FilePath -> IO Bool) -> FilePath -> IO Bool
forall a b. (a -> b) -> a -> b
$ FilePath
"8." FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file
if Bool
e1
then do
FilePath -> IO ()
removeFile (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"8." FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file
FilePath -> IO ()
removeFile (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"8" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file
FinalException -> IO ()
catchEnd (FilePath -> FinalException
NotCreatedWithEffect FilePath
"vol")
else do
FilePath -> IO ()
removeFile (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"8" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file
FinalException -> IO ()
catchEnd (FilePath -> FinalException
NotCreatedWithEffect FilePath
"vol")
else do
Bool
e2 <- FilePath -> IO Bool
doesFileExist (FilePath -> IO Bool) -> FilePath -> IO Bool
forall a b. (a -> b) -> a -> b
$ FilePath
"8." FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file
if Bool
e2
then do
FilePath -> IO ()
removeFile FilePath
file
FilePath -> IO ()
removeFile (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"8" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file
FilePath -> FilePath -> IO ()
renameFile (FilePath
"8." FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) FilePath
file
else do
FilePath -> IO ()
removeFile (FilePath -> IO ()) -> FilePath -> IO ()
forall a b. (a -> b) -> a -> b
$ FilePath
"8" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file
FinalException -> IO ()
catchEnd (FilePath -> FinalException
InitialFileNotChanged FilePath
file)
else FinalException -> IO ()
catchEnd (FilePath -> FinalException
InitialFileNotChanged FilePath
file)
else FinalException -> IO ()
catchEnd FinalException
ExecutableNotProperlyInstalled
volS2 :: FilePath -> FilePath -> IO ()
volS2 :: FilePath -> FilePath -> IO ()
volS2 FilePath
fileA FilePath
fileB = if Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust (FilePath -> Maybe FilePath
showE FilePath
"sox")
then do
Int
upp <- ULencode -> FilePath -> IO Int
SB.upperBndG (FilePath -> ULencode
getULFromExt FilePath
fileB) FilePath
fileB
FilePath
amplMax <- ULencode -> FilePath -> (Int, Int) -> Bool -> IO FilePath
SB.selMAG (FilePath -> ULencode
getULFromExt FilePath
fileB) FilePath
fileB (Int
0, Int
upp) Bool
True
FilePath
amplMin <- ULencode -> FilePath -> (Int, Int) -> Bool -> IO FilePath
SB.selMAG (FilePath -> ULencode
getULFromExt FilePath
fileB) FilePath
fileB (Int
0, Int
upp) Bool
False
let ampl :: Float
ampl = FilePath -> Float
forall a. Read a => FilePath -> a
read ((FilePath, Bool) -> FilePath
forall a b. (a, b) -> a
fst ((FilePath, Bool) -> FilePath)
-> ((FilePath, FilePath) -> (FilePath, Bool))
-> (FilePath, FilePath)
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath, FilePath) -> (FilePath, Bool)
SB.maxAbs ((FilePath, FilePath) -> FilePath)
-> (FilePath, FilePath) -> FilePath
forall a b. (a -> b) -> a -> b
$ (FilePath
amplMax, FilePath
amplMin))::Float
(ExitCode
code, FilePath
_, FilePath
_) <- ULencode
-> [FilePath]
-> FilePath
-> [FilePath]
-> FilePath
-> [FilePath]
-> IO (ExitCode, FilePath, FilePath)
SB.soxOpG (FilePath -> ULencode
getULFromExt FilePath
fileA) [] FilePath
fileA [] (FilePath
"8." FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> FilePath -> FilePath
forall a. Int -> [a] -> [a]
drop Int
1 FilePath
fileA) [FilePath
"vol", Maybe Int -> Float -> FilePath -> FilePath
forall a. RealFloat a => Maybe Int -> a -> FilePath -> FilePath
showFFloat Maybe Int
forall a. Maybe a
Nothing Float
ampl (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$ Integer -> FilePath
forall a. Show a => a -> FilePath
show Integer
0, FilePath
"amplitude"]
ExitCode
-> FilePath
-> FilePath
-> FinalException
-> FinalException
-> IO ()
twoExceptions2Files ExitCode
code FilePath
fileA (FilePath
"8." FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> FilePath -> FilePath
forall a. Int -> [a] -> [a]
drop Int
1 FilePath
fileA) (FilePath -> FinalException
NotCreatedWithEffect FilePath
"vol") (FilePath -> FinalException
InitialFileNotChanged FilePath
fileA)
else FinalException -> IO ()
catchEnd FinalException
ExecutableNotProperlyInstalled
sincA :: FilePath -> IO ()
sincA :: FilePath -> IO ()
sincA FilePath
file = if Maybe FilePath -> Bool
forall a. Maybe a -> Bool
isJust (FilePath -> Maybe FilePath
showE FilePath
"sox")
then do
(ExitCode
code, FilePath
_, FilePath
_) <- ULencode
-> [FilePath]
-> FilePath
-> [FilePath]
-> FilePath
-> [FilePath]
-> IO (ExitCode, FilePath, FilePath)
SB.soxOpG (FilePath -> ULencode
getULFromExt FilePath
file) [] FilePath
file [] (FilePath
"4." FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) [FilePath
"sinc", FilePath
"-a", FilePath
"50", FilePath
"-I", FilePath
"0.07k-11k"]
ExitCode
-> FilePath
-> FilePath
-> FinalException
-> FinalException
-> IO ()
twoExceptions2Files ExitCode
code FilePath
file (FilePath
"4." FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
file) (FilePath -> FinalException
NotCreatedWithEffect FilePath
"sinc") (FilePath -> FinalException
InitialFileNotChanged FilePath
file)
else FinalException -> IO ()
catchEnd FinalException
ExecutableNotProperlyInstalled