-- |
-- Module      :  Sound.SoXBasics1
-- Copyright   :  (c) OleksandrZhabenko 2020
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  olexandr543@yahoo.com
--
-- A program and a library that can be used as a simple basic interface to some SoX functionality.
-- This module differs from the "Sound.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. There is no possibility using these
-- functions to change the file extension. If you use this module and "Sound.SoXBasics" functionalities together,
-- please, use qualified import to avoid misusage.


module Sound.SoXBasics1 (
  -- * Produce sound
  -- ** General processment functions
  moveSnd2Fst
  , getULFromExt
  , twoExceptions2Files
  , threeFiles1Exception
  -- ** Amplitude modification
  , norm
  , normL
  , gainL
  , quarterSinFade
  -- ** Adding silence
  , silenceBoth
  -- ** Changing sample rate
  , resampleA
  -- ** Working with noise
  , noiseReduceB
  , noiseReduceE
  , noiseReduceBU
  , noiseReduceEU
  -- ** 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 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 (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

-- | 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 exception of the type 'FinalException' and leaves the initial file without modification.
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

-- | 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 exception of the type 'FinalException' and leaves the initial file without modification.
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

-- | Function 'normL' applies a SoX \"gain -b [db-Value]\" effect on the audio file with dB value given by the @Float@ 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 exception of the type 'FinalException' and leaves the initial file without modification.
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

-- | 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 exception of the type 'FinalException' and leaves the initial file without modification.
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

-- | 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 exception of the type 'FinalException' and leaves the initial file without modification.
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

-- | 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 exception of the type 'FinalException' and leaves the initial file without modification.
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

-- | 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 exception of the type 'FinalException' and leaves the initial file without modification.
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

-- | 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 exception of the type 'FinalException' and leaves the initial file without modification.
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

-- | Function 'noiseReduceBU' reduces with SoX a noise in the file given with the corresponding noise profile created with 'noiseProfBU' 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). The @Float@ parameter is a number between 0 and 1 showing the level of
-- reducing the noise (the greater number means that the function will reduce more intensively may be even aggressively so that for greater
-- numbers it can remove some sensitive and important sound data as a noise). Internally this parameter is passed unchanged to the \"sox\"
-- so that it uses it as an amount parameter for the \"noisered\" effect. Therefore, please, (as being stated in the SoX manual) experiment
-- with the amount to get suitable results. 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 exception of the type 'FinalException' and leaves the initial file without modification.
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

-- | Function 'noiseReduceEU' 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). The @Float@ parameter is a number between 0 and 1 showing the level of
-- reducing the noise (the greater number means that the function will reduce more intensively may be even aggressively so that for greater
-- numbers it can remove some sensitive and important sound data as a noise). Internally this parameter is passed unchanged to the \"sox\"
-- so that it uses it as an amount parameter for the \"noisered\" effect. Therefore, please, (as being stated in the SoX manual) experiment
-- with the amount to get suitable results. 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 exception of the type 'FinalException' and leaves the initial file without modification.
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

-- | Function 'volS' changes the given audio with the linear ratio for the amplitude so that the resulting amlitude is equal to the given @Float@ 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 exception of the type 'FinalException' and leaves the initial file without modification.
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

-- | 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 exception of the type 'FinalException' and leaves the initial file without modification.
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]
++ FilePath -> FilePath
forall a. [a] -> [a]
tail 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]
++ FilePath -> FilePath
forall a. [a] -> [a]
tail FilePath
fileA) (FilePath -> FinalException
NotCreatedWithEffect FilePath
"vol") (FilePath -> FinalException
InitialFileNotChanged FilePath
fileA)
  else FinalException -> IO ()
catchEnd FinalException
ExecutableNotProperlyInstalled

-- | 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 exception of the type 'FinalException' and leaves the initial file without modification.
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