{-# OPTIONS_GHC -threaded #-}
{-# LANGUAGE CPP #-}
module DobutokO.Sound.Faded (
overChangeVolGNC
, overChangeVolGN
, overChangeVolG
, overChangeVolGC
, overChangeVolGF
, overChangeVol
, overChangeVolC
, overChangeVolF
, overChangeVolGCN
, overChangeVolGFN
, overChangeVolN
, overChangeVolCN
, overChangeVolFN
, mixGTest
, mixGTestN
, basicFN
, basicF
, basicFC
, basicF2
, basicF2C
, basicFCN
, basicF2N
, basicF2CN
, moreFNC
, moreFN
, moreFCN
, reverbFix
, endingWF
, charFadeType
, argString
, freqChange
, sameConst
) where
#ifdef __GLASGOW_HASKELL__
#if __GLASGOW_HASKELL__>=710
/* code that applies only to GHC 7.10.* and higher versions */
import GHC.Base (mconcat)
#endif
#endif
import System.Exit (ExitCode (ExitSuccess))
import Data.List (isPrefixOf,isSuffixOf)
import Data.Maybe (fromJust)
import System.Process
import EndOfExe (showE)
import MMSyn7l (fadeEndsTMB,fadeEndsTMN)
import Numeric (showFFloat)
import qualified Data.Vector as V
import System.Directory
import DobutokO.Sound.Functional.Basics
import DobutokO.Sound.IntermediateF (soxBasicParams)
import Data.Vector.DoubleZip (evalSndFV)
#ifdef __GLASGOW_HASKELL__
#if __GLASGOW_HASKELL__==708
/* code that applies only to GHC 7.8.* */
mconcat = concat
#endif
#endif
overChangeVolG :: String -> String -> Int -> Float -> Float -> Float -> Float -> ((Float,Float), (Float,Float)) -> IO ()
overChangeVolG = overChangeVolGN "test"
overChangeVolGN :: FilePath -> String -> String -> Int -> Float -> Float -> Float -> Float -> ((Float,Float), (Float,Float)) -> IO ()
overChangeVolGN filestart ys cs j freq1 freq2 x0 xdelta ((t0,v0), (t1,v1))
| x0 /= 0 && compare (abs x0) 1.0 /= GT && compare freq1 16 == GT && compare freq1 20000 == LT =
case compare (v1 * v0) 0 of
GT -> do
(code1,_,herr1) <- readProcessWithExitCode (fromJust (showE "sox")) (soxBasicParams ys ["","-n","test1.wav","synth",
showFFloat Nothing (if t1 == t0 then abs x0 else abs (t1 - t0)) "", "sine", showFFloat (Just 4) freq1 (freqChange (drop 1 cs) freq2 freq1), "fade",
charFadeType (if null cs then 'l' else head cs)] ++
if compare ((v1 - v0) * (t1 - t0)) 0 /= LT then [showFFloat Nothing (if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) ""]
else ["0", "-0.0", showFFloat Nothing (if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) "", "vol",
showFFloat (Just 4) (signum v1 * abs (v1 - v0)) ""]) ""
if code1 /= ExitSuccess then error $ "DobutokO.Sound.Faded.overChangeVolGN: " ++ herr1
else do
(code2,_,herr2) <- readProcessWithExitCode (fromJust (showE "sox")) (soxBasicParams ys ["","-n","test0.wav","synth",
showFFloat Nothing (if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) "", "sine",
showFFloat (Just 4) freq1 (freqChange (drop 1 cs) freq2 freq1), "vol", showFFloat (Just 4) (min v0 v1) ""]) ""
if code2 == ExitSuccess
then do
(code3,_,herr3) <- readProcessWithExitCode (fromJust (showE "sox")) ["-m","test0" ++ endingWF ys,"test1" ++ endingWF ys, (filestart ++ "G") ++
prependZeroes 6 (show j) ++ endingWF ys, "vol", "2"] ""
if code3 == ExitSuccess
then removeFile ("test0" ++ endingWF ys) >> removeFile ("test1" ++ endingWF ys)
else error $ "DobutokO.Sound.Faded.overChangeVolGN: " ++ herr3
else print herr2 >> error "DobutokO.Sound.Faded.overChangeVolGN: Operation not successful. "
LT -> do
overChangeVolGN filestart ys cs j freq1 ((v0 * freq2 - v1 * freq1) / (v0 - v1)) x0 xdelta ((t0,v0), ((v0 * t1 - v1 * t0) / (v0 - v1),0)) >>
renameFile ((filestart ++ "G") ++ prependZeroes 6 (show j) ++ endingWF ys) ("temp00" ++ endingWF ys)
(code0,_,herr) <- readProcessWithExitCode (fromJust (showE "sox")) ["temp00" ++ endingWF ys,"temp0" ++ endingWF ys, "fade", "h", "0", "-0.0",
showFFloat (Just 6) ((max freq1 freq2) ** (-1.0)) ""] ""
if code0 /= ExitSuccess then error (show herr)
else do
overChangeVolGN filestart ys cs j ((v0 * freq2 - v1 * freq1) / (v0 - v1)) freq2 x0 xdelta (((v0 * t1 - v1 * t0) / (v0 - v1),0), (t1,v1)) >>
renameFile ((filestart ++ "G") ++ prependZeroes 6 (show j) ++ endingWF ys) ("temp1" ++ endingWF ys)
(code1,_,herr1) <- readProcessWithExitCode (fromJust (showE "sox")) ["temp0" ++ endingWF ys,"temp1" ++ endingWF ys, (filestart ++ "G") ++
prependZeroes 6 (show j) ++ endingWF ys] ""
if code1 == ExitSuccess then removeFile ("temp0" ++ endingWF ys) >> removeFile ("temp1" ++ endingWF ys) >> removeFile ("temp00" ++ endingWF ys)
else error $ "DobutokO.Sound.Faded.overChangeVolGN: " ++ herr1
_ ->
case v1 of
0 ->
if v0 == 0
then do
(code1,_,herr1) <- readProcessWithExitCode (fromJust (showE "sox")) (soxBasicParams ys ["","-n",(filestart ++ "G") ++ prependZeroes 6 (show j) ++
".wav","delay", showFFloat Nothing (if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) "", "trim", showFFloat Nothing
(if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) ""]) ""
if code1 /= ExitSuccess then error $ "DobutokO.Sound.Faded.overChangeVolGN: " ++ herr1
else return ()
else do
(code1,_,herr1) <- readProcessWithExitCode (fromJust (showE "sox")) (soxBasicParams ys ["","-n",(filestart ++ "G") ++ prependZeroes 6 (show j) ++
".wav","synth", showFFloat Nothing (if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) "", "sine",
showFFloat (Just 4) freq1 (freqChange (drop 1 cs) freq2 freq1), "fade", charFadeType (if null cs then 'l' else head cs)] ++
if compare t0 t1 == GT then [showFFloat Nothing
(if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) ""] else ["0", "-0.0", showFFloat Nothing
(if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) "", "vol", showFFloat (Just 4) v0 ""]) ""
if code1 /= ExitSuccess then error $ "DobutokO.Sound.Faded.overChangeVolGN: " ++ herr1
else return ()
_ -> do
(code1,_,herr1) <- readProcessWithExitCode (fromJust (showE "sox")) (soxBasicParams ys ["","-n",(filestart ++ "G") ++ prependZeroes 6 (show j) ++ ".wav",
"synth", showFFloat Nothing (if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) "", "sine",
showFFloat (Just 4) freq1 (freqChange (drop 1 cs) freq2 freq1), "fade", charFadeType (if null cs then 'l' else head cs)] ++
if compare t1 t0 == GT
then [showFFloat Nothing (if compare (abs (t1 - t0)) xdelta /= GT then abs x0
else abs (t1 - t0)) ""] else ["0", "-0.0", showFFloat Nothing (if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) "",
"vol", showFFloat (Just 4) v1 ""]) ""
if code1 /= ExitSuccess then error $ "DobutokO.Sound.Faded.overChangeVolGN: " ++ herr1
else return ()
| otherwise = error "DobutokO.Sound.Faded.overChangeVolGN: sound for these conditions is not defined. "
freqChange :: String -> Float -> Float -> String
freqChange xs freq freq1
| compare freq 16 /= LT && compare freq 20000 /= GT = if freq /= freq1 then
case xs of
"l" -> ':':showFFloat (Just 4) freq ""
"s" -> '+':showFFloat (Just 4) freq ""
"e" -> '/':showFFloat (Just 4) freq ""
_ -> '-':showFFloat (Just 4) freq ""
else ""
| otherwise = error "DobutokO.Sound.Faded.freqChange: undefined for this value of the frequency (the first Float argument). "
overChangeVol :: String -> Char -> Int -> Float -> Float -> Float -> ((Float,Float), (Float,Float)) -> IO ()
overChangeVol ys c j freq1 = overChangeVolGN "test" ys [c] j freq1 freq1
overChangeVolN :: FilePath -> String -> Char -> Int -> Float -> Float -> Float -> ((Float,Float), (Float,Float)) -> IO ()
overChangeVolN filestart ys c j freq1 = overChangeVolGN filestart ys [c] j freq1 freq1
overChangeVolC :: String -> Char -> Int -> Float -> Float -> Float -> (Float,Float) -> (Float,Float) -> IO ()
overChangeVolC ys c j freq x0 xdelta w1 = overChangeVol ys c j freq x0 xdelta . (,) w1
overChangeVolCN :: FilePath -> String -> Char -> Int -> Float -> Float -> Float -> (Float,Float) -> (Float,Float) -> IO ()
overChangeVolCN filestart ys c j freq x0 xdelta w1 = overChangeVolN filestart ys c j freq x0 xdelta . (,) w1
overChangeVolGC :: String -> String -> Int -> Float -> Float -> Float -> Float -> (Float,Float) -> (Float,Float) -> IO ()
overChangeVolGC ys cs j freq1 freq2 x0 xdelta w1 = overChangeVolG ys cs j freq1 freq2 x0 xdelta . (,) w1
overChangeVolGCN :: FilePath -> String -> String -> Int -> Float -> Float -> Float -> Float -> (Float,Float) -> (Float,Float) -> IO ()
overChangeVolGCN filestart ys cs j freq1 freq2 x0 xdelta w1 = overChangeVolGN filestart ys cs j freq1 freq2 x0 xdelta . (,) w1
overChangeVolF :: String -> Char -> Int -> Float -> Float -> (Float,Float) -> (Float,Float) -> Float -> IO ()
overChangeVolF ys c j x0 xdelta w1 w2 freq = overChangeVol ys c j freq x0 xdelta (w1,w2)
overChangeVolFN :: FilePath -> String -> Char -> Int -> Float -> Float -> (Float,Float) -> (Float,Float) -> Float -> IO ()
overChangeVolFN filestart ys c j x0 xdelta w1 w2 freq = overChangeVolN filestart ys c j freq x0 xdelta (w1,w2)
overChangeVolGF :: String -> String -> Int -> Float -> Float -> (Float,Float) -> (Float,Float) -> Float -> Float -> IO ()
overChangeVolGF ys cs j x0 xdelta w1 w2 freq1 freq2 = overChangeVolG ys cs j freq1 freq2 x0 xdelta (w1,w2)
overChangeVolGFN :: FilePath -> String -> String -> Int -> Float -> Float -> (Float,Float) -> (Float,Float) -> Float -> Float -> IO ()
overChangeVolGFN filestart ys cs j x0 xdelta w1 w2 freq1 freq2 = overChangeVolGN filestart ys cs j freq1 freq2 x0 xdelta (w1,w2)
endingWF :: String -> String
endingWF ys
| not (null ys) = if last ys == 'f' then ".flac" else ".wav"
| otherwise = ".wav"
charFadeType :: Char -> String
charFadeType c =
case c of
'h' -> "h"
'p' -> "p"
't' -> "t"
_ -> "l"
mixGTest :: String -> IO ()
mixGTest ys = do
dir <- listDirectory "."
(code1,_,herr1) <- readProcessWithExitCode (fromJust (showE "sox")) (mconcat [["-m"], filter (\xs -> "testG" `isPrefixOf` xs &&
endingWF ys `isSuffixOf` xs) dir, ["resultG" ++ endingWF ys]]) ""
if code1 /= ExitSuccess then error $ "DobutokO.Sound.Times.mixGTest: " ++ herr1
else mapM_ removeFile . filter (\xs -> "testG" `isPrefixOf` xs && endingWF ys `isSuffixOf` xs) $ dir
mixGTestN :: FilePath -> String -> IO ()
mixGTestN filestart ys = do
dir <- listDirectory "."
(code1,_,herr1) <- readProcessWithExitCode (fromJust (showE "sox")) (mconcat [["-m"], filter (\xs -> (filestart ++ "G") `isPrefixOf` xs &&
endingWF ys `isSuffixOf` xs) dir, ["resultG" ++ endingWF ys]]) ""
if code1 /= ExitSuccess then error $ "DobutokO.Sound.Times.mixGTestN: " ++ herr1
else mapM_ removeFile . filter (\xs -> (filestart ++ "G") `isPrefixOf` xs && endingWF ys `isSuffixOf` xs) $ dir
basicF :: String -> String -> Float -> Float -> Float -> Float -> (Float -> Float) -> V.Vector Float -> IO ()
basicF ys x2s freq x0 xdelta per f v = do
let (xs1,xs2) = splitAt 1 x2s
c1 = if null xs1 then 'l' else head xs1
c2 = if null xs2 then 'l' else head xs2
v1 <- evalSndFV f v
V.imapM_ (\i x -> do
overChangeVol ys c1 i freq x0 xdelta x
fadeEndsTMB c2 per $ "testG" ++ prependZeroes 6 (show i) ++ endingWF ys) v1
basicFN :: FilePath -> String -> String -> Float -> Float -> Float -> Float -> (Float -> Float) -> V.Vector Float -> IO ()
basicFN filestart ys x2s freq x0 xdelta per f v = do
let (xs1,xs2) = splitAt 1 x2s
c1 = if null xs1 then 'l' else head xs1
c2 = if null xs2 then 'l' else head xs2
v1 <- evalSndFV f v
V.imapM_ (\i x -> do
overChangeVolGN filestart ys [c1] i freq freq x0 xdelta x
fadeEndsTMB c2 per $ (filestart ++ "G") ++ prependZeroes 6 (show i) ++ endingWF ys) v1
argString :: String -> (String,String)
argString xs = (take 4 xs,take 2 . drop 4 $ xs)
basicFC :: String -> Float -> Float -> Float -> Float -> (Float -> Float) -> V.Vector Float -> IO ()
basicFC = basicFCN "test"
basicFCN :: FilePath -> String -> Float -> Float -> Float -> Float -> (Float -> Float) -> V.Vector Float -> IO ()
basicFCN filestart xs freq x0 xdelta per f v = let (ys,x2s) = argString xs in basicFN filestart ys x2s freq x0 xdelta per f v
basicF2 :: String -> String -> Float -> Float -> Float -> Float -> Float -> (Float -> Float) -> V.Vector Float -> IO ()
basicF2 = basicF2N "test"
basicF2N :: FilePath -> String -> String -> Float -> Float -> Float -> Float -> Float -> (Float -> Float) -> V.Vector Float -> IO ()
basicF2N filestart ys x2s freq x0 xdelta per1 per2 f v = do
let (xs1,xs2) = splitAt 1 x2s
c1 = if null xs1 then 'l' else head xs1
c2 = if null xs2 then 'l' else head xs2
v1 <- evalSndFV f v
V.imapM_ (\i x -> do
overChangeVolN filestart ys c1 i freq x0 xdelta x
fadeEndsTMN c2 per1 per2 $ (filestart ++ "G") ++ prependZeroes 6 (show i) ++ endingWF ys) v1
basicF2C :: String -> Float -> Float -> Float -> Float -> Float -> (Float -> Float) -> V.Vector Float -> IO ()
basicF2C = basicF2CN "test"
basicF2CN :: FilePath -> String -> Float -> Float -> Float -> Float -> Float -> (Float -> Float) -> V.Vector Float -> IO ()
basicF2CN filestart xs freq x0 xdelta per1 per2 f v = let (ys,x2s) = argString xs in basicF2N filestart ys x2s freq x0 xdelta per1 per2 f v
moreFN :: FilePath -> String -> String -> Float -> Float -> Float -> Float -> Float -> (Float -> Float) -> V.Vector Float -> IO ()
moreFN filestart ys x2s freq1 freq2 x0 xdelta per f v = do
let (xs1,xs2) = splitAt 1 x2s
c1 = if null xs1 then 'l' else head xs1
c2 = if null xs2 then 'l' else head xs2
v1 <- evalSndFV f v
V.imapM_ (\i x -> do
overChangeVolGN filestart ys [c1] i freq1 freq2 x0 xdelta x
fadeEndsTMB c2 per $ (filestart ++ "G") ++ prependZeroes 6 (show i) ++ endingWF ys) v1
moreFCN :: FilePath -> String -> Float -> Float -> Float -> Float -> Float -> (Float -> Float) -> V.Vector Float -> IO ()
moreFCN filestart xs freq1 freq2 x0 xdelta per f v = let (ys,x2s) = argString xs in moreFN filestart ys x2s freq1 freq2 x0 xdelta per f v
sameConst :: Int -> Float
sameConst i
| i == 0 = 0.1 * (7.0 + pi)
| otherwise = 10.0 / (7.0 + pi)
overChangeVolGNC :: String -> FilePath -> String -> String -> Int -> Float -> Float -> Float -> Float -> ((Float,Float), (Float,Float)) -> IO ()
overChangeVolGNC check filestart ys cs j freq1 freq2 x0 xdelta ((t0,v0), (t1,v1))
| x0 /= 0 && compare (abs x0) 1.0 /= GT && compare freq1 16 == GT && compare freq1 20000 == LT =
case compare (v1 * v0) 0 of
GT -> do
(code1,_,herr1) <- readProcessWithExitCode (fromJust (showE "sox")) (soxBasicParams ys ["","-n","test1.wav","synth",
showFFloat Nothing (if t1 == t0 then abs x0 else abs (t1 - t0)) "", "sine", showFFloat (Just 4) freq1 (freqChange (drop 1 cs) freq2 freq1), "fade",
charFadeType (if null cs then 'l' else head cs)] ++
if compare ((v1 - v0) * (t1 - t0)) 0 /= LT then [showFFloat Nothing (if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) ""]
else ["0", "-0.0", showFFloat Nothing (if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) "", "vol",
showFFloat (Just 4) (signum v1 * abs (v1 - v0)) ""]) ""
if code1 /= ExitSuccess then error $ "DobutokO.Sound.Faded.overChangeVolGNC: " ++ herr1
else do
(code2,_,herr2) <- readProcessWithExitCode (fromJust (showE "sox")) (soxBasicParams ys ["","-n","test0.wav","synth",
showFFloat Nothing (if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) "", "sine",
showFFloat (Just 4) freq1 (freqChange (drop 1 cs) freq2 freq1), "vol", showFFloat (Just 4) (min v0 v1) ""]) ""
if code2 == ExitSuccess
then do
(code3,_,herr3) <- readProcessWithExitCode (fromJust (showE "sox")) ["-m","test0" ++ endingWF ys,"test1" ++ endingWF ys, (filestart ++ "G") ++
prependZeroes 6 (show j) ++ endingWF ys, "vol", "2"] ""
if code3 == ExitSuccess
then removeFile ("test0" ++ endingWF ys) >> removeFile ("test1" ++ endingWF ys)
else error $ "DobutokO.Sound.Faded.overChangeVolGNC: " ++ herr3
else print herr2 >> error "DobutokO.Sound.Faded.overChangeVolGNC: Operation not successful. "
LT ->
case check of
"simple" -> do
overChangeVolGNC check filestart ys cs j freq1 ((v0 * freq2 - v1 * freq1) / (v0 - v1)) x0 xdelta ((t0,v0), ((v0 * t1 - v1 * t0) / (v0 - v1),0)) >>
renameFile ((filestart ++ "G") ++ prependZeroes 6 (show j) ++ endingWF ys) ("temp00" ++ endingWF ys)
(code0,_,herr) <- readProcessWithExitCode (fromJust (showE "sox")) ["temp00" ++ endingWF ys,"temp0" ++ endingWF ys, "fade", "h", "0", "-0.0",
showFFloat (Just 6) ((max freq1 freq2) ** (-1.0)) ""] ""
if code0 /= ExitSuccess then error (show herr)
else do
overChangeVolGNC check filestart ys cs j ((v0 * freq2 - v1 * freq1) / (v0 - v1)) freq2 x0 xdelta (((v0 * t1 - v1 * t0) / (v0 - v1),0), (t1,v1)) >>
renameFile ((filestart ++ "G") ++ prependZeroes 6 (show j) ++ endingWF ys) ("temp1" ++ endingWF ys)
(code1,_,herr1) <- readProcessWithExitCode (fromJust (showE "sox")) ["temp0" ++ endingWF ys,"temp1" ++ endingWF ys, (filestart ++ "G") ++
prependZeroes 6 (show j) ++ endingWF ys] ""
if code1 == ExitSuccess then removeFile ("temp0" ++ endingWF ys) >> removeFile ("temp1" ++ endingWF ys) >> removeFile ("temp00" ++ endingWF ys)
else error $ "DobutokO.Sound.Faded.overChangeVolGNC: " ++ herr1
"silent" -> do
(code0,_,herr) <- readProcessWithExitCode (fromJust (showE "sox")) (soxBasicParams ys ["","-n","temp0" ++ endingWF ys,"trim", "0",
showFFloat (Just 6) (abs (v0 * (t0 - t1) / (v0 - v1))) "","vol","0"]) ""
if code0 /= ExitSuccess then error (show herr)
else do
overChangeVolGNC check filestart ys cs j ((v0 * freq2 - v1 * freq1) / (v0 - v1)) freq2 x0 xdelta (((v0 * t1 - v1 * t0) / (v0 - v1),0), (t1,v1)) >>
renameFile ((filestart ++ "G") ++ prependZeroes 6 (show j) ++ endingWF ys) ("temp1" ++ endingWF ys)
(code1,_,herr1) <- readProcessWithExitCode (fromJust (showE "sox")) ["temp0" ++ endingWF ys,"temp1" ++ endingWF ys, (filestart ++ "G") ++
prependZeroes 6 (show j) ++ endingWF ys] ""
if code1 == ExitSuccess then removeFile ("temp0" ++ endingWF ys) >> removeFile ("temp1" ++ endingWF ys)
else error $ "DobutokO.Sound.Faded.overChangeVolGNC: " ++ herr1
_ -> do
(code0,_,herr) <- readProcessWithExitCode (fromJust (showE "sox")) (soxBasicParams ys ["","-n","temp0" ++ endingWF ys,"trim", "0",
showFFloat (Just 6) (abs (v0 * (t0 - t1) / (v0 - v1))) "","vol","0"]) ""
if code0 /= ExitSuccess then error (show herr)
else do
overChangeVolGNC check filestart ys cs j ((v0 * freq2 - v1 * freq1) / (v0 - v1)) freq2 x0 xdelta (((v0 * t1 - v1 * t0) / (v0 - v1),0), (t1,v1)) >>
renameFile ((filestart ++ "G") ++ prependZeroes 6 (show j) ++ endingWF ys) ("temp1" ++ endingWF ys)
(code1,_,herr1) <- readProcessWithExitCode (fromJust (showE "sox")) ["temp0" ++ endingWF ys,"temp1" ++ endingWF ys, (filestart ++ "G") ++
prependZeroes 6 (show j) ++ endingWF ys,"reverb","-w","1","1","10","gain","-n","gain","-9"] ""
if code1 == ExitSuccess then removeFile ("temp0" ++ endingWF ys) >> removeFile ("temp1" ++ endingWF ys)
else error $ "DobutokO.Sound.Faded.overChangeVolGNC: " ++ herr1
_ ->
case v1 of
0 ->
if v0 == 0
then do
(code1,_,herr1) <- readProcessWithExitCode (fromJust (showE "sox")) (soxBasicParams ys ["","-n",(filestart ++ "G") ++ prependZeroes 6 (show j) ++
".wav","delay", showFFloat Nothing (if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) "", "trim", showFFloat Nothing
(if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) ""]) ""
if code1 /= ExitSuccess then error $ "DobutokO.Sound.Faded.overChangeVolGNC: " ++ herr1
else return ()
else do
(code1,_,herr1) <- readProcessWithExitCode (fromJust (showE "sox")) (soxBasicParams ys ["","-n",(filestart ++ "G") ++ prependZeroes 6 (show j) ++
".wav","synth", showFFloat Nothing (if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) "", "sine",
showFFloat (Just 4) freq1 (freqChange (drop 1 cs) freq2 freq1), "fade", charFadeType (if null cs then 'l' else head cs)] ++
if compare t0 t1 == GT then [showFFloat Nothing
(if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) ""] else ["0", "-0.0", showFFloat Nothing
(if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) "", "vol", showFFloat (Just 4) v0 ""]) ""
if code1 /= ExitSuccess then error $ "DobutokO.Sound.Faded.overChangeVolGNC: " ++ herr1
else return ()
_ -> do
(code1,_,herr1) <- readProcessWithExitCode (fromJust (showE "sox")) (soxBasicParams ys ["","-n",(filestart ++ "G") ++ prependZeroes 6 (show j) ++ ".wav",
"synth", showFFloat Nothing (if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) "", "sine",
showFFloat (Just 4) freq1 (freqChange (drop 1 cs) freq2 freq1), "fade", charFadeType (if null cs then 'l' else head cs)] ++
if compare t1 t0 == GT
then [showFFloat Nothing (if compare (abs (t1 - t0)) xdelta /= GT then abs x0
else abs (t1 - t0)) ""] else ["0", "-0.0", showFFloat Nothing (if compare (abs (t1 - t0)) xdelta /= GT then abs x0 else abs (t1 - t0)) "",
"vol", showFFloat (Just 4) v1 ""]) ""
if code1 /= ExitSuccess then error $ "DobutokO.Sound.Faded.overChangeVolGNC: " ++ herr1
else return ()
| otherwise = error "DobutokO.Sound.Faded.overChangeVolGNC: sound for these conditions is not defined. "
moreFNC :: String -> FilePath -> String -> String -> Float -> Float -> Float -> Float -> Float -> (Float -> Float) -> V.Vector Float -> IO ()
moreFNC check filestart ys x2s freq1 freq2 x0 xdelta per f v = do
let (xs1,xs2) = splitAt 1 x2s
c1 = if null xs1 then 'l' else head xs1
c2 = if null xs2 then 'l' else head xs2
v1 <- evalSndFV f v
V.imapM_ (\i x -> do
overChangeVolGNC check filestart ys [c1] i freq1 freq2 x0 xdelta x
fadeEndsTMB c2 per $ (filestart ++ "G") ++ prependZeroes 6 (show i) ++ endingWF ys
reverbFix $ (filestart ++ "G") ++ prependZeroes 6 (show i) ++ endingWF ys) v1
reverbFix :: FilePath -> IO ()
reverbFix file = do
(code,_,herr) <- readProcessWithExitCode (fromJust (showE "sox")) [file,"temp" ++ file,"reverb","-w","10", "1", "100"] ""
if code /= ExitSuccess then do
exi <- doesFileExist $ "temp" ++ file
if exi then removeFile ("temp" ++ file) >> error ("DobutokO.Sound.Faded.reverbFix: Operation on the file" ++ show file ++ " was unsucessful " ++ herr)
else error $ "DobutokO.Sound.Faded.reverbFix: Operation on the file" ++ show file ++ " was unsucessful " ++ herr
else renameFile ("temp" ++ file) file