{-# LANGUAGE BangPatterns #-}
{-# OPTIONS_GHC -threaded #-}
module DobutokO.Sound.Uniq (
  
  
  uniqOvertonesV
  , uniqOverSoXSynth
  , uniqOverSoXSynthN
  
  , uniqOvertonesV2
  , uniqOverSoXSynth2
  , uniqOverSoXSynthN3
  , uniqOverSoXSynthN4
  
  , uniqOverSoXSynthNGen
  , uniqOverSoXSynthNGen3
  , uniqOverSoXSynthNGen4
  
 
  , uniqOverSoXSynthNGenE
  , uniqOverSoXSynthNGen3E
  , uniqOverSoXSynthNGen4E
  
  , uniqOverSoXSynthN4G
  , uniqOverSoXSynthN34G
  , uniqOverSoXSynthN44G
  , uniqOverSoXSynthNGenE4G
  , uniqOverSoXSynthNGen3E4G
  , uniqOverSoXSynthNGen4E4G
  
  , uniqOverSoXSynthN4GS
  , uniqOverSoXSynthN34GS
  , uniqOverSoXSynthN44GS
  , uniqOverSoXSynthNGenE4GS
  , uniqOverSoXSynthNGen3E4GS
  , uniqOverSoXSynthNGen4E4GS
  
  , uniqOverSoXSynthN45G
  , uniqOverSoXSynthNGen4E5G
  
  , uniqOverSoXSynthN45GS
  , uniqOverSoXSynthNGen4E5GS
  
  , uniqOverSoXSynthNGen4E6G
  
  , uniqOverSoXSynthN46GS
  , uniqOverSoXSynthN46GSu
  , uniqOverSoXSynthNGen4E6GS
  , uniqOverSoXSynthNGen4E6GSu
  
  , uniqOverSoXSynthNGenEPar
  , uniqOverSoXSynthNGenE4GSPar
  , uniqOverSoXSynthNGenE4GPar
  , uniqOverSoXSynthNGen3EPar
  , uniqOverSoXSynthNGen3E4GSPar
  , uniqOverSoXSynthNGen3E4GPar
  , uniqOverSoXSynthNGen4EPar
  , uniqOverSoXSynthNGen4E4GSPar
  , uniqOverSoXSynthNGen4E4GPar
  , uniqOverSoXSynthNGen4E5GPar
  , uniqOverSoXSynthNGen4E5GSPar
  , uniqOverSoXSynthNGen4E6GPar
  , uniqOverSoXSynthNGen4E6GSPar
  , uniqOverSoXSynthNGen4E6GSuPar
) where
import Numeric (showFFloat)
import Data.Maybe (isNothing,fromJust)
import qualified Data.Vector as V
import System.Process
import EndOfExe (showE)
import String.Ukrainian.UniquenessPeriods
import DobutokO.Sound.Functional.Basics
import DobutokO.Sound.Functional.Params
import DobutokO.Sound.DIS5G6G
uniqOvertonesV :: Float -> String -> OvertonesO
uniqOvertonesV note xs =
  let ys = uniquenessPeriods xs
      z  = sum ys
      v  = V.fromList . fmap (\y -> fromIntegral y / fromIntegral z) $ ys
      z2 = V.length v
      v2 = V.generate z2 (\i -> V.unsafeIndex v i / fromIntegral (i + 1)) in
        V.takeWhile (\(!u,!z) -> compare u (V.unsafeIndex notes 107) /= GT && compare (abs z) 0.001 == GT) . V.unsafeSlice 1 (z2 - 1) .
          V.zip (V.generate z2 (\i -> note * fromIntegral (i + 1))) $ v2
uniqOvertonesV2 :: Float -> String -> String -> OvertonesO
uniqOvertonesV2 note xs ts =
  let ys = uniquenessPeriods xs
      z  = sum ys
      v  = V.fromList . fmap (\y -> fromIntegral y / fromIntegral z) $ ys
      z2 = V.length v
      v2 = V.generate z2 (\i -> (V.unsafeIndex (V.map fromIntegral . signsFromString z2 $ ts) i) * V.unsafeIndex v i / fromIntegral (i + 1)) in
        V.takeWhile (\(!u,!z) -> compare u (V.unsafeIndex notes 107) /= GT && compare (abs z) 0.001 == GT) . V.filter (\(_, t4) -> t4 /= 0.0) .
          V.unsafeSlice 1 (z2 - 1) . V.zip (V.generate z2 (\i -> note * fromIntegral (i + 1))) $ v2
uniqOverSoXSynth :: Float -> String -> IO ()
uniqOverSoXSynth x wws = do
  let note0 = closestNote x
      note1 = pureQuintNote note0
      v0    = uniqOvertonesV note0 wws
      v1    = uniqOvertonesV note1 wws
  _ <- readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "test-.wav", "synth", "0.5","sine", showFFloat (Just 4) note0 "",
     "synth", "0.5","sine", "mix", showFFloat (Just 4) note1 "", "vol","0.5"] ""
  uniqOverSoXSynthHelp v0
  uniqOverSoXSynthHelp2 v1
  mixTest
uniqOverSoXSynthHelp1 :: String -> OvertonesO -> IO ()
uniqOverSoXSynthHelp1 xs = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
 ["-r22050", "-n", xs ++ show (i + 2) ++ ".wav", "synth", "0.5","sine", showFFloat (Just 4) noteN "", "vol", showFFloat (Just 4) amplN ""] "")
uniqOverSoXSynthHelp :: OvertonesO -> IO ()
uniqOverSoXSynthHelp = uniqOverSoXSynthHelp1 "test0"
uniqOverSoXSynthHelp2 :: OvertonesO -> IO ()
uniqOverSoXSynthHelp2 = uniqOverSoXSynthHelp1 "test1"
uniqOverSoXSynth2 :: Float -> String -> String -> IO ()
uniqOverSoXSynth2 x wws tts = do
  let note0 = closestNote x
      note1 = pureQuintNote note0
      v0    = uniqOvertonesV2 note0 wws tts
      v1    = uniqOvertonesV2 note1 wws tts
  _ <- readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "test-.wav", "synth", "0.5","sine", showFFloat (Just 4) note0 "", "synth",
     "0.5","sine", "mix", showFFloat (Just 4) note1 "", "vol","0.5"] ""
  uniqOverSoXSynthHelp v0
  uniqOverSoXSynthHelp2 v1
  mixTest
uniqOverSoXSynthN :: Int -> Float -> Float -> String -> String -> V.Vector Float -> IO ()
uniqOverSoXSynthN n ampL time3 zs = uniqOverSoXSynthN4G n ampL (str2DurationsDef n zs time3)
uniqOverSoXSynthN4GS :: Int -> Float -> Float -> String -> String -> V.Vector Float -> IO ()
uniqOverSoXSynthN4GS n ampL time3 zs = uniqOverSoXSynthN4G n ampL (str2Durations zs time3)
uniqOverSoXSynthN4G :: Int -> Float -> Durations -> String -> V.Vector Float -> IO ()
uniqOverSoXSynthN4G n ampL v2 wws vec0
 | V.all (== 0.0) v2 = putStrLn "You provided no valid durations data! "
 | compare (abs ampL) 0.01 /= LT && compare (abs ampL) 1.0 /= GT =
    let v21 = V.filter (/= 0.0) v2
        m     = V.length v21
        zeroN = numVZeroesPre vec0 in V.imapM_ (\j x -> do
          let note0 = closestNote x
              note1 = pureQuintNote note0
              v0    = uniqOvertonesV note0 wws
              v1    = uniqOvertonesV note1 wws
              uniqOverSoXSynthHelpN = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
                ["-r22050", "-n", "test" ++ prependZeroes zeroN (show (i + 2)) ++ ".wav", "synth", showFFloat (Just 4) (abs (V.unsafeIndex v21 (j `rem` m))) "",
                   "sine", showFFloat (Just 4) noteN "", "vol", if compare (V.unsafeIndex v21 (j `rem` m)) 0.0 == GT
                      then showFFloat (Just 4) (amplN * ampL) "" else "0"] "")
              uniqOverSoXSynthHelpN2 = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
                ["-r22050", "-n", "testQ" ++ prependZeroes zeroN (show (i + 2)) ++ ".wav", "synth", showFFloat (Just 4) (abs (V.unsafeIndex v21 (j `rem` m))) "",
                   "sine", showFFloat (Just 4) noteN "", "vol", if compare (V.unsafeIndex v21 (j `rem` m)) 0.0 == GT
                      then showFFloat (Just 4) (amplN * ampL) "" else "0"] "")
              soxSynthHelpMain note01 note02 = readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testA" ++
                 prependZeroes zeroN "1" ++  ".wav", "synth", showFFloat (Just 4) (abs (V.unsafeIndex v21 (j `rem` m))) "","sine", showFFloat (Just 4) note01 "", "synth", showFFloat (Just 4) (V.unsafeIndex v2 (j `rem` m)) "","sine", "mix", showFFloat (Just 4) note02 "", "vol",
                    if compare (V.unsafeIndex v21 (j `rem` m)) 0.0 == GT then "0.5" else "0"]  ""
          _ <- soxSynthHelpMain note0 note1
          uniqOverSoXSynthHelpN v0
          uniqOverSoXSynthHelpN2 v1
          mixTest2 zeroN j) vec0
 | otherwise = let ampL1 = ampL - (fromIntegral . truncate $ ampL) in
    if abs ampL1 < 0.01 then uniqOverSoXSynthN4G n 0.01 v2 wws vec0
    else uniqOverSoXSynthN4G n ampL1 v2 wws vec0
uniqOverSoXSynthN3 :: Int -> Float -> Float -> String -> String -> String -> V.Vector Float -> IO ()
uniqOverSoXSynthN3 n ampL time3 zs = uniqOverSoXSynthN34G n ampL (str2DurationsDef n zs time3)
uniqOverSoXSynthN34GS :: Int -> Float -> Float -> String -> String -> String -> V.Vector Float -> IO ()
uniqOverSoXSynthN34GS n ampL time3 zs = uniqOverSoXSynthN34G n ampL (str2Durations zs time3)
uniqOverSoXSynthN34G :: Int -> Float -> Durations -> String -> String -> V.Vector Float -> IO ()
uniqOverSoXSynthN34G n ampL v2 wws tts vec0
 | V.all (== 0.0) v2 = putStrLn "You provided no valid durations data! "
 | compare (abs ampL) 0.01 /= LT && compare (abs ampL) 1.0 /= GT =
    let v21 = V.filter (/=0.0) v2
        m     = V.length v2
        zeroN = numVZeroesPre vec0 in V.imapM_ (\j x -> do
          let note0 = closestNote x                         
              note1 = pureQuintNote note0
              v0    = uniqOvertonesV2 note0 wws tts
              v1    = uniqOvertonesV2 note1 wws tts
              uniqOverSoXSynthHelpN vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
                ["-r22050", "-n", "test" ++ prependZeroes zeroN (show (i + 2)) ++ ".wav", "synth", showFFloat (Just 4) (abs (V.unsafeIndex v21 (j `rem` m))) "",
                   "sine", showFFloat (Just 4) noteN "", "vol", if compare (V.unsafeIndex v21 (j `rem` m)) 0.0 == GT then showFFloat (Just 4) (amplN * ampL) "" else "0"] "") vec
              uniqOverSoXSynthHelpN2 vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
                ["-r22050", "-n", "testQ" ++ prependZeroes zeroN (show (i + 2)) ++ ".wav", "synth", showFFloat (Just 4) (abs (V.unsafeIndex v21 (j `rem` m))) "",
                   "sine", showFFloat (Just 4) noteN "", "vol", if compare (V.unsafeIndex v21 (j `rem` m)) 0.0 == GT then showFFloat (Just 4) (amplN * ampL) "" else "0"] "") vec
              soxSynthHelpMain note01 note02 = readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testA" ++
                prependZeroes zeroN "1" ++  ".wav", "synth", showFFloat (Just 4) (abs (V.unsafeIndex v21 (j `rem` m))) "","sine", showFFloat (Just 4) note01 "",
                  "synth", showFFloat (Just 4) (abs (V.unsafeIndex v21 (j `rem` m))) "","sine", "mix", showFFloat (Just 4) note02 "", "vol",
                    if compare (V.unsafeIndex v21 (j `rem` m)) 0.0 == GT then "0.5" else "0"] ""
          _ <- soxSynthHelpMain note0 note1
          uniqOverSoXSynthHelpN v0
          uniqOverSoXSynthHelpN2 v1
          mixTest2 zeroN j) vec0
 | otherwise = let ampL1 = ampL - (fromIntegral . truncate $ ampL) in
    if abs ampL1 < 0.01 then uniqOverSoXSynthN34G n 0.01 v2 wws tts vec0
    else uniqOverSoXSynthN34G n ampL1 v2 wws tts vec0
uniqOverSoXSynthN4 :: Int -> Float -> Float -> Float -> String -> String -> String -> String -> V.Vector Float -> IO ()
uniqOverSoXSynthN4 n ampL time3 dAmpl zs = uniqOverSoXSynthN44G n ampL dAmpl (str2DurationsDef n zs time3)
uniqOverSoXSynthN44GS :: Int -> Float -> Float -> Float -> String -> String -> String -> String -> V.Vector Float -> IO ()
uniqOverSoXSynthN44GS n ampL time3 dAmpl zs = uniqOverSoXSynthN44G n ampL dAmpl (str2Durations zs time3)
uniqOverSoXSynthN44G :: Int -> Float -> Float -> Durations -> String -> String -> String -> V.Vector Float -> IO ()
uniqOverSoXSynthN44G n ampL dAmpl v2 wws tts vs = uniqOverSoXSynthN45G n ampL dAmpl v2 wws tts (intervalsFromString vs)
uniqOverSoXSynthN45G :: Int -> Float -> Float -> Durations -> String -> String -> Intervals -> V.Vector Float -> IO ()
uniqOverSoXSynthN45G n ampL dAmpl v2 wws tts v3 vec0
 | V.all (== 0.0) v2 = putStrLn "You provided no valid durations data! "
 | compare (abs ampL) 0.01 /= LT && compare (abs ampL) 1.0 /= GT =
    let v21 = V.filter (/=0.0) v2
        m     = V.length v2
        zeroN = numVZeroesPre vec0
        l     = V.length v3 in V.imapM_ (\j x -> do
          let note0 = closestNote x
              note1 = dNote (V.unsafeIndex v3 (j `rem` l)) note0
              v0    = uniqOvertonesV2 note0 wws tts
              v1    = if isNothing note1 then V.empty
                      else uniqOvertonesV2 (fromJust note1) wws tts
              uniqOverSoXSynthHelpN = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
                ["-r22050", "-n", "test" ++ prependZeroes zeroN (show (i + 2)) ++ ".wav", "synth", showFFloat (Just 4) (abs (V.unsafeIndex v21 (j `rem` m))) "",
                  "sine",showFFloat (Just 4) noteN "", "vol", if compare (V.unsafeIndex v21 (j `rem` m)) 0.0 == GT then showFFloat (Just 4) (amplN * ampL) "" else "0"] "")
              uniqOverSoXSynthHelpN2 = V.imapM_ (\i (noteN, amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
                ["-r22050", "-n", "testQ" ++ prependZeroes zeroN (show (i + 2)) ++ ".wav", "synth", showFFloat (Just 4) (abs (V.unsafeIndex v21 (j `rem` m))) "",
                   "sine", showFFloat (Just 4) noteN "", "vol", if compare (V.unsafeIndex v21 (j `rem` m)) 0.0 == GT then showFFloat (Just 4) (if dAmpl * amplN * ampL > 1.0 then 1.0
                      else dAmpl * amplN * ampL) "" else "0"] "")
              soxSynthHelpMain0 note01 = readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testA" ++
                 prependZeroes zeroN "1" ++  ".wav", "synth", showFFloat (Just 4) (abs (V.unsafeIndex v21 (j `rem` m))) "","sine", showFFloat (Just 4) note01 "",
                   "vol",if compare (V.unsafeIndex v21 (j `rem` m)) 0.0 == GT then "0.5" else "0"] ""
              soxSynthHelpMain1 note02 = readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testB" ++
                 prependZeroes zeroN "1" ++  ".wav", "synth", showFFloat (Just 4) (abs (V.unsafeIndex v21 (j `rem` m))) "","sine", showFFloat (Just 4) note02 "",
                    "vol", if compare (V.unsafeIndex v21 (j `rem` m)) 0.0 == GT then showFFloat (Just 4) (if dAmpl > 0.5 then 0.5 else dAmpl / 2) "" else "0"] ""
          if isNothing note1 then do { _ <- soxSynthHelpMain0 note0
                                     ; uniqOverSoXSynthHelpN v0 }
          else do { _ <- soxSynthHelpMain0 note0
                  ; _ <- soxSynthHelpMain1 (fromJust note1)
                  ; uniqOverSoXSynthHelpN v0
                  ; uniqOverSoXSynthHelpN2 v1}
          mixTest2 zeroN j) vec0
 | otherwise = let ampL1 = ampL - (fromIntegral . truncate $ ampL) in
    if abs ampL1 < 0.01 then uniqOverSoXSynthN45G n 0.01 dAmpl v2 wws tts v3 vec0
    else uniqOverSoXSynthN45G n ampL1 dAmpl v2 wws tts v3 vec0
uniqOverSoXSynthN46G :: Int -> Float -> Float -> Durations -> String -> String -> Intervals -> V.Vector Float -> Strengths -> Float -> IO ()
uniqOverSoXSynthN46G n ampL dAmpl v2 wws tts v3 vec0 v6 limV
 | V.all (== 0.0) v2 = putStrLn "You provided no valid durations data! "
 | V.null v6 = putStrLn "You did not provide a volume adjustments vector! "
 | compare (abs ampL) 0.01 /= LT && compare (abs ampL) 1.0 /= GT =
    let v21 = V.filter (/=0.0) v2
        m     = V.length v2
        zeroN = numVZeroesPre vec0
        l     = V.length v3 in V.imapM_ (\j x -> do
          let note0 = closestNote x
              note1 = dNote (V.unsafeIndex v3 (j `rem` l)) note0
              v0    = uniqOvertonesV2 note0 wws tts
              v1    = if isNothing note1 then V.empty
                      else uniqOvertonesV2 (fromJust note1) wws tts
              uniqOverSoXSynthHelpN = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
                ["-r22050", "-n", "test" ++ prependZeroes zeroN (show (i + 2)) ++ ".wav", "synth", showFFloat (Just 4) (abs (V.unsafeIndex v21 (j `rem` m))) "",
                  "sine",showFFloat (Just 4) noteN "", "vol", if compare (V.unsafeIndex v21 (j `rem` m)) 0.0 == GT then showFFloat (Just 4) (amplN * ampL) "" else "0"] "")
              uniqOverSoXSynthHelpN2 = V.imapM_ (\i (noteN, amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
                ["-r22050", "-n", "testQ" ++ prependZeroes zeroN (show (i + 2)) ++ ".wav", "synth", showFFloat (Just 4) (abs (V.unsafeIndex v21 (j `rem` m))) "",
                   "sine", showFFloat (Just 4) noteN "", "vol", if compare (V.unsafeIndex v21 (j `rem` m)) 0.0 == GT then showFFloat (Just 4) (if dAmpl * amplN * ampL > 1.0 then 1.0
                      else dAmpl * amplN * ampL) "" else "0"] "")
              soxSynthHelpMain0 note01 = readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testA" ++
                 prependZeroes zeroN "1" ++  ".wav", "synth", showFFloat (Just 4) (abs (V.unsafeIndex v21 (j `rem` m))) "","sine", showFFloat (Just 4) note01 "",
                   "vol",if compare (V.unsafeIndex v21 (j `rem` m)) 0.0 == GT then "0.5" else "0"] ""
              soxSynthHelpMain1 note02 = readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testB" ++
                 prependZeroes zeroN "1" ++  ".wav", "synth", showFFloat (Just 4) (abs (V.unsafeIndex v21 (j `rem` m))) "","sine", showFFloat (Just 4) note02 "",
                    "vol", if compare (V.unsafeIndex v21 (j `rem` m)) 0.0 == GT then showFFloat (Just 4) (if dAmpl > 0.5 then 0.5 else dAmpl / 2) "" else "0"] ""
          if isNothing note1 then do { _ <- soxSynthHelpMain0 note0
                                     ; uniqOverSoXSynthHelpN v0 }
          else do { _ <- soxSynthHelpMain0 note0
                  ; _ <- soxSynthHelpMain1 (fromJust note1)
                  ; uniqOverSoXSynthHelpN v0
                  ; uniqOverSoXSynthHelpN2 v1}
          mixTest2 zeroN j
          apply6GSilentFile ("result" ++ prependZeroes zeroN (show j) ++ ".wav") limV (V.unsafeIndex v6 (j `rem` V.length v6))) vec0
 | otherwise = let ampL1 = ampL - (fromIntegral . truncate $ ampL) in
    if abs ampL1 < 0.01 then uniqOverSoXSynthN46G n 0.01 dAmpl v2 wws tts v3 vec0 v6 limV
    else uniqOverSoXSynthN46G n ampL1 dAmpl v2 wws tts v3 vec0 v6 limV
uniqOverSoXSynthN45GS :: Int -> Float -> Float -> Float -> String -> String -> String -> Intervals -> String -> V.Vector Float -> IO ()
uniqOverSoXSynthN45GS n ampL time3 dAmpl zs wws tts v3 vs = uniqOverSoXSynthN45G n ampL dAmpl (str2Durations zs time3) wws tts (intervalsFromStringG v3 vs)
uniqOverSoXSynthN46GS :: Int -> Float -> Float -> Float -> String -> String -> String -> Intervals -> String -> V.Vector Float -> String ->
  Float -> IO ()
uniqOverSoXSynthN46GS n ampL time3 dAmpl zs wws tts v3 vs vec0 xxs limV = uniqOverSoXSynthN46G n ampL dAmpl (str2Durations zs time3) wws tts
  (intervalsFromStringG v3 vs) vec0 (str2Volume xxs) limV
uniqOverSoXSynthN46GSu :: Int -> Float -> Float -> Float -> String -> String -> Intervals -> String -> V.Vector Float -> String -> Float -> IO ()
uniqOverSoXSynthN46GSu n ampL time3 dAmpl wws tts v5 vs vec0 xxs limV =
 uniqOverSoXSynthN46G n ampL dAmpl (str2Durations xxs time3) wws tts (intervalsFromStringG v5 vs) vec0 (str2Volume xxs) limV
uniqOverSoXSynthNGen :: FilePath -> Int -> Float -> Float -> String -> String -> IO ()
uniqOverSoXSynthNGen file m = uniqOverSoXSynthNGenE file m 12
uniqOverSoXSynthNGenE :: FilePath -> Int -> Int -> Float -> Float -> String -> String -> IO ()
uniqOverSoXSynthNGenE file m ku ampL time3 zs wws = do
  n <- duration1000 file
  unGenNE4Gi n file m ku ampL (str2DurationsDef n zs time3) wws
uniqOverSoXSynthNGenEPar :: FilePath -> Params -> Float -> Float -> String -> String -> IO ()
uniqOverSoXSynthNGenEPar file params ampL time3 zs wws = do
  n <- duration1000 file
  unGenNE4GiPar n file params ampL (str2DurationsDef n zs time3) wws
uniqOverSoXSynthNGenE4GS :: FilePath -> Int -> Int -> Float -> Float -> String -> String -> IO ()
uniqOverSoXSynthNGenE4GS file m ku ampL time3 zs wws = do
  n <- duration1000 file
  unGenNE4Gi n file m ku ampL (str2Durations zs time3) wws
uniqOverSoXSynthNGenE4GSPar :: FilePath -> Params -> Float -> Float -> String -> String -> IO ()
uniqOverSoXSynthNGenE4GSPar file params ampL time3 zs wws = do
  n <- duration1000 file
  unGenNE4GiPar n file params ampL (str2Durations zs time3) wws
unGenNE4Gi :: Int -> FilePath -> Int -> Int -> Float -> Durations -> String -> IO ()
unGenNE4Gi n file m ku ampL v2 wws = do
  vecA <- freqsFromFile file n
  let vecB = liftInEnkuV m ku . V.map fromIntegral . V.filter (/= (11440::Int)) $ vecA
  uniqOverSoXSynthN4G n ampL v2 wws vecB
  endFromResult
unGenNE4GiPar :: Int -> FilePath -> Params -> Float -> Durations -> String -> IO ()
unGenNE4GiPar n file params ampL v2 wws = do
  vecA <- freqsFromFile file n
  let vecB = liftInParamsV params . V.map fromIntegral $ vecA
  uniqOverSoXSynthN4G n ampL v2 wws vecB
  endFromResult
uniqOverSoXSynthNGenE4G :: FilePath -> Int -> Int -> Float -> Durations -> String -> IO ()
uniqOverSoXSynthNGenE4G file m ku ampL v2 wws = do
  n <- duration1000 file
  unGenNE4Gi n file m ku ampL v2 wws
uniqOverSoXSynthNGenE4GPar :: FilePath -> Params -> Float -> Durations -> String -> IO ()
uniqOverSoXSynthNGenE4GPar file params ampL v2 wws = do
  n <- duration1000 file
  unGenNE4GiPar n file params ampL v2 wws
uniqOverSoXSynthNGen3 :: FilePath -> Int -> Float -> Float -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen3 file m = uniqOverSoXSynthNGen3E file m 12
uniqOverSoXSynthNGen3E :: FilePath -> Int -> Int -> Float -> Float -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen3E file m ku ampL time3 zs wws tts = do
  n <- duration1000 file
  unGenN3E4Gi n file m ku ampL (str2DurationsDef n zs time3) wws tts
uniqOverSoXSynthNGen3EPar :: FilePath -> Params -> Float -> Float -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen3EPar file params ampL time3 zs wws tts = do
  n <- duration1000 file
  unGenN3E4GiPar n file params ampL (str2DurationsDef n zs time3) wws tts
uniqOverSoXSynthNGen3E4GS :: FilePath -> Int -> Int -> Float -> Float -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen3E4GS file m ku ampL time3 zs wws tts = do
  n <- duration1000 file
  unGenN3E4Gi n file m ku ampL (str2Durations zs time3) wws tts
uniqOverSoXSynthNGen3E4GSPar :: FilePath -> Params -> Float -> Float -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen3E4GSPar file params ampL time3 zs wws tts = do
  n <- duration1000 file
  unGenN3E4GiPar n file params ampL (str2Durations zs time3) wws tts
unGenN3E4Gi :: Int -> FilePath -> Int -> Int -> Float -> Durations -> String -> String -> IO ()
unGenN3E4Gi n file m ku ampL v2 wws tts = do
  vecA <- freqsFromFile file n
  let vecB = liftInEnkuV m ku . V.map fromIntegral . V.filter (/= (11440::Int)) $ vecA
  uniqOverSoXSynthN34G n ampL v2 wws tts vecB
  endFromResult
unGenN3E4GiPar :: Int -> FilePath -> Params -> Float -> Durations -> String -> String -> IO ()
unGenN3E4GiPar n file params ampL v2 wws tts = do
  vecA <- freqsFromFile file n
  let vecB = liftInParamsV params . V.map fromIntegral $ vecA
  uniqOverSoXSynthN34G n ampL v2 wws tts vecB
  endFromResult
uniqOverSoXSynthNGen3E4G :: FilePath -> Int -> Int -> Float -> Durations -> String -> String -> IO ()
uniqOverSoXSynthNGen3E4G file m ku ampL v2 wws tts = do
  n <- duration1000 file
  unGenN3E4Gi n file m ku ampL v2 wws tts
uniqOverSoXSynthNGen3E4GPar :: FilePath -> Params -> Float -> Durations -> String -> String -> IO ()
uniqOverSoXSynthNGen3E4GPar file params ampL v2 wws tts = do
  n <- duration1000 file
  unGenN3E4GiPar n file params ampL v2 wws tts
uniqOverSoXSynthNGen4 :: FilePath -> Int -> Float -> Float -> Float -> String -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen4 file m = uniqOverSoXSynthNGen4E file m 12
uniqOverSoXSynthNGen4E :: FilePath -> Int -> Int -> Float -> Float -> Float -> String -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen4E file m ku ampL time3 dAmpl zs wws tts vs = do
  n <- duration1000 file
  unGenN4E4Gi n file m ku ampL dAmpl (str2DurationsDef n zs time3) wws tts vs
uniqOverSoXSynthNGen4EPar :: FilePath -> Params -> Float -> Float -> Float -> String -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen4EPar file params ampL time3 dAmpl zs wws tts vs = do
  n <- duration1000 file
  unGenN4E4GiPar n file params ampL dAmpl (str2DurationsDef n zs time3) wws tts vs
uniqOverSoXSynthNGen4E4GS :: FilePath -> Int -> Int -> Float -> Float -> Float -> String -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen4E4GS file m ku ampL time3 dAmpl zs wws tts vs = do
  n <- duration1000 file
  unGenN4E4Gi n file m ku ampL dAmpl (str2Durations zs time3) wws tts vs
uniqOverSoXSynthNGen4E4GSPar :: FilePath -> Params -> Float -> Float -> Float -> String -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen4E4GSPar file params ampL time3 dAmpl zs wws tts vs = do
  n <- duration1000 file
  unGenN4E4GiPar n file params ampL dAmpl (str2Durations zs time3) wws tts vs
unGenN4E4Gi :: Int -> FilePath -> Int -> Int -> Float -> Float -> Durations -> String -> String -> String -> IO ()
unGenN4E4Gi n file m ku ampL dAmpl v2 wws tts vs = do
  vecA <- freqsFromFile file n
  let vecB = liftInEnkuV m ku . V.map fromIntegral . V.filter (/= (11440::Int)) $ vecA
  uniqOverSoXSynthN44G n ampL dAmpl v2 wws tts vs vecB
  endFromResult
unGenN4E4GiPar :: Int -> FilePath -> Params -> Float -> Float -> Durations -> String -> String -> String -> IO ()
unGenN4E4GiPar n file params ampL dAmpl v2 wws tts vs = do
  vecA <- freqsFromFile file n
  let vecB = liftInParamsV params . V.map fromIntegral $ vecA
  uniqOverSoXSynthN44G n ampL dAmpl v2 wws tts vs vecB
  endFromResult
unGenN4E5Gi :: Int -> FilePath -> Int -> Int -> Float -> Float -> Durations -> String -> String -> Intervals -> IO ()
unGenN4E5Gi n file m ku ampL dAmpl v2 wws tts v3 = do
  vecA <- freqsFromFile file n
  let vecB = liftInEnkuV m ku . V.map fromIntegral . V.filter (/= (11440::Int)) $ vecA
  uniqOverSoXSynthN45G n ampL dAmpl v2 wws tts v3 vecB
  endFromResult
unGenN4E5GiPar :: Int -> FilePath -> Params -> Float -> Float -> Durations -> String -> String -> Intervals -> IO ()
unGenN4E5GiPar n file params ampL dAmpl v2 wws tts v3 = do
  vecA <- freqsFromFile file n
  let vecB = liftInParamsV params . V.map fromIntegral $ vecA
  uniqOverSoXSynthN45G n ampL dAmpl v2 wws tts v3 vecB
  endFromResult
uniqOverSoXSynthNGen4E4G :: FilePath -> Int -> Int -> Float -> Float -> Durations -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen4E4G file m ku ampL dAmpl v2 wws tts vs = do
  n <- duration1000 file
  unGenN4E4Gi n file m ku ampL dAmpl v2 wws tts vs
uniqOverSoXSynthNGen4E4GPar :: FilePath -> Params -> Float -> Float -> Durations -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen4E4GPar file params ampL dAmpl v2 wws tts vs = do
  n <- duration1000 file
  unGenN4E4GiPar n file params ampL dAmpl v2 wws tts vs
uniqOverSoXSynthNGen4E5G :: FilePath -> Int -> Int -> Float -> Float -> Durations -> String -> String -> Intervals -> IO ()
uniqOverSoXSynthNGen4E5G file m ku ampL dAmpl v2 wws tts v3 = do
  n <- duration1000 file
  unGenN4E5Gi n file m ku ampL dAmpl v2 wws tts v3
uniqOverSoXSynthNGen4E5GPar :: FilePath -> Params -> Float -> Float -> Durations -> String -> String -> Intervals -> IO ()
uniqOverSoXSynthNGen4E5GPar file params ampL dAmpl v2 wws tts v3 = do
  n <- duration1000 file
  unGenN4E5GiPar n file params ampL dAmpl v2 wws tts v3
uniqOverSoXSynthNGen4E5GS :: FilePath -> Int -> Int -> Float -> Float -> Float -> String -> String -> String -> Intervals -> String -> IO ()
uniqOverSoXSynthNGen4E5GS file m ku ampL time3 dAmpl zs wws tts v3 vs = do
  n <- duration1000 file
  unGenN4E5Gi n file m ku ampL dAmpl (str2Durations zs time3) wws tts (intervalsFromStringG v3 vs)
uniqOverSoXSynthNGen4E5GSPar :: FilePath -> Params -> Float -> Float -> Float -> String -> String -> String -> Intervals -> String -> IO ()
uniqOverSoXSynthNGen4E5GSPar file params ampL time3 dAmpl zs wws tts v3 vs = do
  n <- duration1000 file
  unGenN4E5GiPar n file params ampL dAmpl (str2Durations zs time3) wws tts (intervalsFromStringG v3 vs)
uniqOverSoXSynthNGen4E6G :: FilePath -> Int -> Int -> Float -> Float -> Durations -> String -> String -> Intervals -> Strengths -> Float -> IO ()
uniqOverSoXSynthNGen4E6G file m ku ampL dAmpl v2 wws tts v3 v6 limV =
 uniqOverSoXSynthNGen4E5G file m ku ampL dAmpl v2 wws tts v3 >> apply6G2 v6 "221w" "result" limV >> endFromResult
uniqOverSoXSynthNGen4E6GPar :: FilePath -> Params -> Float -> Float -> Durations -> String -> String -> Intervals -> Strengths -> Float -> IO ()
uniqOverSoXSynthNGen4E6GPar file params ampL dAmpl v2 wws tts v3 v6 limV =
 uniqOverSoXSynthNGen4E5GPar file params ampL dAmpl v2 wws tts v3 >> apply6G2 v6 "221w" "result" limV >> endFromResult
uniqOverSoXSynthNGen4E6GS :: FilePath -> Int -> Int -> Float -> Float -> Float -> String -> String -> String -> Intervals -> String ->
  String -> Float -> IO ()
uniqOverSoXSynthNGen4E6GS file m ku ampL time3 dAmpl zs wws tts v5 vs xxs limV =
 uniqOverSoXSynthNGen4E6G file m ku ampL dAmpl (str2Durations zs time3) wws tts (intervalsFromStringG v5 vs) (str2Volume xxs) limV
uniqOverSoXSynthNGen4E6GSPar :: FilePath -> Params -> Float -> Float -> Float -> String -> String -> String -> Intervals -> String ->
  String -> Float -> IO ()
uniqOverSoXSynthNGen4E6GSPar file params ampL time3 dAmpl zs wws tts v5 vs xxs limV =
 uniqOverSoXSynthNGen4E6GPar file params ampL dAmpl (str2Durations zs time3) wws tts (intervalsFromStringG v5 vs) (str2Volume xxs) limV
uniqOverSoXSynthNGen4E6GSu :: FilePath -> Int -> Int -> Float -> Float -> Float -> String -> String -> Intervals -> String -> String -> Float -> IO ()
uniqOverSoXSynthNGen4E6GSu file m ku ampL time3 dAmpl wws tts v5 vs xxs limV =
 uniqOverSoXSynthNGen4E6G file m ku ampL dAmpl (str2Durations xxs time3) wws tts (intervalsFromStringG v5 vs) (str2Volume xxs) limV
uniqOverSoXSynthNGen4E6GSuPar :: FilePath -> Params -> Float -> Float -> Float -> String -> String -> Intervals -> String -> String -> Float -> IO ()
uniqOverSoXSynthNGen4E6GSuPar file params ampL time3 dAmpl wws tts v5 vs xxs limV =
 uniqOverSoXSynthNGen4E6GPar file params ampL dAmpl (str2Durations xxs time3) wws tts (intervalsFromStringG v5 vs) (str2Volume xxs) limV