-- |
-- Module      :  DobutokO.Sound
-- Copyright   :  (c) OleksandrZhabenko 2020
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  olexandr543@yahoo.com
--
-- A program and a library to create experimental music
-- from a mono audio and a Ukrainian text.
{-# LANGUAGE BangPatterns, LambdaCase #-}
{-# OPTIONS_GHC -threaded #-}

module DobutokO.Sound (
  -- * Library and executable functions
  -- ** For the fixed timbre
  overSoXSynthN
  -- *** For the fixed timbre with different signs for harmonics coefficients
  , overTones2
  , overSoXSynth2
  , overSoXSynthN2
  , overSoXSynthN3
  -- *** Use additional parameters
  , overSoXSynthDN
  , overSoXSynth2DN
  -- *** Use a file for information
  , overSoXSynthNGen
  , overSoXSynthNGen2
  , overSoXSynthNGen3
  -- ** For the unique for the String structure timbre
  , uniqOvertonesV
  , uniqOverSoXSynth
  , uniqOverSoXSynthN
  -- *** For the unique for the String structure timbre with different signs for harmonics coefficients
  , uniqOvertonesV2
  , uniqOverSoXSynth2
  , uniqOverSoXSynthN3
  , uniqOverSoXSynthN4
  -- *** Use a file for information
  , uniqOverSoXSynthNGen
  , uniqOverSoXSynthNGen3
  , uniqOverSoXSynthNGen4
  -- ** Work with octaves
  , octaveUp
  , octaveDown
  , whichOctave
  , liftInOctave
  , liftInOctaveV
  -- ** Even more extended
  , dviykyTA
  , triykyTA
  , chetvirkyTA
  , p'yatirkyTA
  , shistkyTA
  , simkyTA
  , visimkyTA
  , dev'yatkyTA
  , desyatkyTA
  , odynadtsyatkyTA
  , octavesTA
  -- * Extended generation using enky functionality
  -- ** With somewhat fixed timbre
  , overSoXSynthNGenE
  , overSoXSynthNGen2E
  , overSoXSynthNGen3E
  -- ** With usage of additional information in the Ukrainian text
  , uniqOverSoXSynthNGenE
  , uniqOverSoXSynthNGen3E
  , uniqOverSoXSynthNGen4E
  -- * Auxiliary functions
  , signsFromString
) where

import CaseBi (getBFst')
import System.Exit (ExitCode(ExitSuccess))
import Numeric (showFFloat)
import Control.Exception (onException)
import System.Environment (getArgs)
import Data.List (isPrefixOf,sort,sortBy,nubBy)
import Data.Maybe (isJust,isNothing,fromJust,maybe)
import Data.Char (isDigit)
import qualified Data.Vector as V
import System.Process
import EndOfExe (showE)
import MMSyn7.Syllable
import MMSyn7s
import System.Directory
import SoXBasics
import Processing_mmsyn7ukr
import Melodics.Ukrainian (convertToProperUkrainian)
import DobutokO.Sound.Functional

dviykyTA :: NotePairs
dviykyTA = V.generate 107 (\i -> (V.unsafeIndex notes i, V.unsafeIndex notes (i + 1)))

triykyTA :: NotePairs
triykyTA = V.generate 106 (\i -> (V.unsafeIndex notes i, V.unsafeIndex notes (i + 2)))

chetvirkyTA :: NotePairs
chetvirkyTA = V.generate 105 (\i -> (V.unsafeIndex notes i, V.unsafeIndex notes (i + 3)))

p'yatirkyTA :: NotePairs
p'yatirkyTA = V.generate 104 (\i -> (V.unsafeIndex notes i, V.unsafeIndex notes (i + 4)))

shistkyTA :: NotePairs
shistkyTA = V.generate 103 (\i -> (V.unsafeIndex notes i, V.unsafeIndex notes (i + 5)))

simkyTA :: NotePairs
simkyTA = V.generate 102 (\i -> (V.unsafeIndex notes i, V.unsafeIndex notes (i + 6)))

visimkyTA :: NotePairs
visimkyTA = V.generate 101 (\i -> (V.unsafeIndex notes i, V.unsafeIndex notes (i + 7)))

dev'yatkyTA :: NotePairs
dev'yatkyTA = V.generate 100 (\i -> (V.unsafeIndex notes i, V.unsafeIndex notes (i + 8)))

desyatkyTA :: NotePairs
desyatkyTA = V.generate 99 (\i -> (V.unsafeIndex notes i, V.unsafeIndex notes (i + 9)))

odynadtsyatkyTA  :: NotePairs
odynadtsyatkyTA = V.generate 98 (\i -> (V.unsafeIndex notes i, V.unsafeIndex notes (i + 10)))

octavesTA :: NotePairs
octavesTA = V.generate 97 (\i -> (V.unsafeIndex notes i, V.unsafeIndex notes (i + 11)))

--------------------------------------------------------------------------------------------------------------------------

-- | Returns an analogous note in the higher octave (its frequency in Hz).
octaveUp :: Double -> Double
octaveUp x = 2 * x
{-# INLINE octaveUp #-}


-- | Returns an analogous note in the lower octave (its frequency in Hz).
octaveDown :: Double -> Double
octaveDown x = x / 2
{-# INLINE octaveDown #-}

-----------------------------------------------------------------------------------------------------------------------------

-- | Function can be used to determine to which octave (in the American notation for the notes, this is a number in the note written form,
-- e. g. for C4 this is 4) the frequency belongs (to be more exact, the closest note for the given frequency -- see 'closestNote' taking into account
-- its lower pure quint, which can lay in the lower by 1 octave). If it is not practical to determine the number, then the function returns 'Nothing'.
whichOctave :: Double -> Maybe Int
whichOctave x
  | compare (closestNote x) 24.4996 == GT = (\t ->
     case isJust t of
       True -> fmap (\z ->
         case z of
           0 -> z
           _ -> z - 1) t
       _    -> Just 8) . V.findIndex (\(t1, t2) -> compare (closestNote x) t1 == LT) $ octavesT
  | otherwise = Nothing

-- | Function lifts the given frequency to the given number of the octave (in American notation, from 0 to 8). This number is an 'Int' parameter.
-- The function also takes into account the lower pure quint for the closest note.
-- If it is not practical to determine the number, then the function returns 'Nothing'.
liftInOctave :: Int -> Double -> Maybe Double
liftInOctave n x
  | compare n 0 == LT || compare n 8 == GT = Nothing
  | compare (closestNote x) 24.4996 == GT =
      case compare (fromJust . whichOctave $ x) n of
        EQ -> Just (closestNote x)
        LT -> let z  = logBase 2.0 (V.unsafeIndex notes (n * 12) / closestNote x)
                  z1 = truncate z in
                   if abs (z - fromIntegral z1) > 0.999 || abs (z - fromIntegral z1) < 0.001
                     then Just (V.unsafeLast . V.iterateN (fromIntegral z1 + 1) octaveUp $ closestNote x)
                     else Just (V.unsafeLast . V.iterateN (fromIntegral z1 + 2) octaveUp $ closestNote x)
        _  -> let z  = logBase 2.0 (closestNote x / V.unsafeIndex notes (n * 12))
                  z1 = truncate z in
                   if abs (z - fromIntegral z1) > 0.999 || abs (z - fromIntegral z1) < 0.001
                     then Just (V.unsafeLast . V.iterateN (fromIntegral z1 + 2) octaveDown $ closestNote x)
                     else Just (V.unsafeLast . V.iterateN (fromIntegral z1 + 1) octaveDown $ closestNote x)
  | otherwise = Nothing

-- | Function lifts the 'V.Vector' of 'Double' representing frequencies to the given octave with the 'Int' number. Better to use numbers in the range [1..8].
-- The function also takes into account the lower pure quint for the obtained note behaviour. If it is not practical to determine the octave, the resulting
-- frequency is omitted from the resulting 'V.Vector'.
liftInOctaveV :: Int -> V.Vector Double -> V.Vector Double
liftInOctaveV n = V.mapMaybe (liftInOctave n)

--------------------------------------------------------------------------------------------------------------------------------

-- | For the given frequency of the note it generates a 'V.Vector' of the tuples, each one of which contains the harmonics' frequency and amplitude. For every given
-- 'String' structure of the uniqueness (see the documentation for @mmsyn7s@ package and its 'MMSyn7.Syllable' module) it produces the unique timbre.
uniqOvertonesV :: Double -> 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

-- | Additional function to produce signs from the given 'String' of the Ukrainian text. Ukrainian vowels and voiced consonants gives \"+\" sign (+1), voiceless
-- and sonorous consonants gives \"-\" sign (-1). Voiceless2 gives "0". Other symbols are not taken into account.
signsFromString :: Int -> String -> V.Vector Int
signsFromString n1 =
  V.take n1 . V.fromList . concatMap (fmap (\case
      Vowel _ -> 1
      Voiced _ -> 1
      VoicedP _ -> 1
      Voiceless _ -> (-1)
      VoicelessP _ -> (-1)
      Sonorous _ -> (-1)
      SonorousP _ -> (-1)
      _ -> 0) . concatMap representProlonged) . syllablesUkrP . take (3 * n1) . cycle

-- | For the given frequency of the note and a Ukrainian text it generates a 'V.Vector' of the tuples, each one of which contains
-- the harmonics' frequency and amplitude. The 'String' is used to produce the signs for harmonics coefficients.
overTones2 :: Double -> String -> OvertonesO
overTones2 note ts =
  V.takeWhile (\(!w,!z) -> compare w (V.unsafeIndex notes 107) /= GT && compare (abs z) 0.001 == GT) . V.filter (\(_, t4) -> t4 /= 0.0) .
    V.zip (V.generate 1024 (\i -> note * fromIntegral (i + 2))) $ (V.generate 1024 (\i -> fromIntegral (V.unsafeIndex (signsFromString 1024 ts)
      (i + 1)) / fromIntegral ((i + 1) * (i + 1))))

-- | For the given frequency of the note it generates a 'V.Vector' of the tuples, each one of which contains the harmonics' frequency and amplitude. For every given
-- first 'String' argument structure of the uniqueness (see the documentation for @mmsyn7s@ package and its 'MMSyn7.Syllable' module) it produces the unique timbre.
-- The second 'String' is used to produce the signs for harmonics coefficients.
uniqOvertonesV2 :: Double -> 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

-- | Similar to 'overSoXSynth' except that takes not necessarily pure lower quint note as the second one, but the one specified by the 'String' parameter
-- as an argument to 'dNote'. If you begin the 'String' with space characters, or \"сь\", or \"ць\", or dash, or apostrophe, or soft sign, than there will
-- be no interval and the sound will be solely one with its Overtones.
overSoXSynthDN :: Double -> String -> IO ()
overSoXSynthDN x zs
 | V.null . convertToProperUkrainian $ zs = overSoXSynth x
 | otherwise = do
  let note0 = closestNote x
      note1 = dNote (V.unsafeIndex (intervalsFromString zs) 0) note0
      v0    = overTones note0
      v1    = maybe V.empty overTones note1
      overSoXSynthHelp vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
        ["-r22050", "-n", "test0" ++ show (i + 2) ++ ".wav", "synth", "0.5","sine", showFFloat (Just 4) noteN "", "vol",
          showFFloat (Just 4) amplN ""] "") vec
      overSoXSynthHelp2 vec = let l = V.length vec in V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
        ["-r22050", "-n", "test1" ++ show (i + 2) ++ ".wav", "synth", "0.5","sine", showFFloat (Just 4) noteN "", "vol",
           showFFloat (Just 4) amplN ""] "") vec
  _ <- readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testA.wav", "synth", "0.5","sine", showFFloat (Just 4) note0 "", "vol","0.5"] ""
  if isNothing note1 then overSoXSynthHelp v0
  else do
    _ <- readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testB.wav", "synth", "0.5","sine", showFFloat (Just 4) (fromJust note1) "",   "vol","0.5"]   ""
    overSoXSynthHelp v0
    overSoXSynthHelp2 v1
  mixTest

-- | Similar to 'overSoXSynthDN' except that the resulting duration is specified by the second 'Double' parameter in seconds. For 'overSoXSynthDN'
-- it is equal to 0.5.
overSoXSynth2DN :: Double -> Double -> String -> IO ()
overSoXSynth2DN x y zs
 | V.null . convertToProperUkrainian $ zs = overSoXSynth x
 | otherwise = do
    let note0 = closestNote x
        note1 = dNote (V.unsafeIndex (intervalsFromString zs) 0) note0
        v0    = overTones note0
        v1    = maybe V.empty overTones note1
        overSoXSynthHelp vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
          ["-r22050", "-n", "test0" ++ show (i + 2) ++ ".wav", "synth", showFFloat (Just 4) y "","sine", showFFloat (Just 4) noteN "",
            "vol", showFFloat (Just 4) amplN ""] "") vec
        overSoXSynthHelp2 vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
          ["-r22050", "-n", "test1" ++ show (i + 2) ++ ".wav", "synth", showFFloat (Just 4) y "","sine", showFFloat (Just 4) noteN "",
            "vol", showFFloat (Just 4) amplN ""] "") vec
    _ <- readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testA.wav", "synth", showFFloat (Just 4) y "","sine",
       showFFloat (Just 4) note0 "", "vol","0.5"] ""
    if isNothing note1 then overSoXSynthHelp v0
    else do
      _ <- readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testB.wav", "synth", showFFloat (Just 4) y "","sine",
         showFFloat (Just 4) (fromJust note1) "", "vol","0.5"] ""
      overSoXSynthHelp v0
      overSoXSynthHelp2 v1
    mixTest

-- | For the given frequency it generates a musical sound with a timbre. The main component of the sound includes the lower pure quint,
-- which can be in the same octave or in the one with the number lower by one. Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" files in the current directory, because they can be overwritten.
-- The 'String' argument is used to define signs of the harmonics coefficients for Overtones.
overSoXSynth2 :: Double -> String -> IO ()
overSoXSynth2 x tts = do
  let note0 = closestNote x
      note1 = pureQuintNote note0
      v0    = overTones2 note0 tts
      v1    = overTones2 note1 tts
      overSoXSynthHelp vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
        ["-r22050", "-n", "test0" ++ show (i + 2) ++ ".wav", "synth", "0.5","sine", showFFloat (Just 4) noteN "",
           "vol", showFFloat (Just 4) amplN ""] "") vec
      overSoXSynthHelp2 vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
        ["-r22050", "-n", "test1" ++ show (i + 2) ++ ".wav", "synth", "0.5","sine", showFFloat (Just 4) noteN "",
           "vol", showFFloat (Just 4) amplN ""] "") vec
  _ <- readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "test01.wav", "synth", "0.5","sine", showFFloat (Just 4) note0 "",
     "synth", "0.5","sine", "mix", showFFloat (Just 4) note1 "", "vol","0.5"] ""
  overSoXSynthHelp v0
  overSoXSynthHelp2 v1
  mixTest

-- | Function to create a melody for the given arguments. 'String' is used to provide a rhythm. The main component of the sound includes the lower pure quint, which
-- can be in the same octave or in the one with the number lower by one. The first 'Double' argument from the range [0.01..1.0] is used as a maximum amplitude
-- for Overtones. If it is set to 1.0 the overTones amplitudes are just the maximum ones, otherwise they are multiplied by the parameter and this results
-- in their becoming more silent ones. The second 'Double' argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" files in the current directory, because they can be overwritten.
overSoXSynthN :: Int -> Double -> Double -> String -> V.Vector Double -> IO ()
overSoXSynthN n ampL time3 zs vec0
 | compare (abs ampL) 0.01 /= LT && compare (abs ampL) 1.0 /= GT =
    let (t, ws) = splitAt 1 . syllableStr n $ zs
        m     = length ws
        zeroN = numVZeroesPre vec0
        v2    = V.map (\yy -> time3 * fromIntegral (yy * m) / fromIntegral (head t)) . V.fromList $ ws in V.imapM_ (\j x -> do
          let note0 = closestNote x                     -- zs is obtained from the command line arguments
              note1 = pureQuintNote note0
              v0    = overTones note0
              v1    = overTones note1
              overSoXSynthHelpN vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
                ["-r22050", "-n", "test" ++ prependZeroes zeroN (show (i + 2)) ++ ".wav", "synth", showFFloat (Just 4) (V.unsafeIndex v2 (j `rem` m)) "",
                   "sine", showFFloat (Just 4) noteN "", "vol", showFFloat (Just 4) (amplN * ampL) ""] "") vec
              overSoXSynthHelpN2 vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
                ["-r22050", "-n", "testQ" ++ prependZeroes zeroN (show (i + 2)) ++ ".wav", "synth", showFFloat (Just 4) (V.unsafeIndex v2 (j `rem` m)) "",
                   "sine", showFFloat (Just 4) noteN "", "vol", showFFloat (Just 4) (amplN * ampL) ""] "") vec
              soxSynthHelpMain note01 note02 = readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testA" ++ prependZeroes zeroN "1" ++
                ".wav", "synth", showFFloat (Just 4) (V.unsafeIndex v2 (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","0.5"] ""
          soxSynthHelpMain note0 note1
          overSoXSynthHelpN v0
          overSoXSynthHelpN2 v1
          mixTest2 zeroN j) vec0
 | otherwise = let ampL1 = ampL - (fromIntegral . truncate $ ampL) in
    if abs ampL1 < 0.01 then overSoXSynthN n 0.01 time3 zs vec0
    else overSoXSynthN n ampL1 time3 zs vec0

-- | Function to create a melody for the given arguments. 'String' is used to provide a rhythm. The main component of the sound includes the lower pure quint, which
-- can be in the same octave or in the one with the number lower by one. The first 'Double' argument from the range [0.01..1.0] is used as a maximum amplitude
-- for Overtones. If it is set to 1.0 the overTones amplitudes are just the maximum ones, otherwise they are multiplied by the parameter and this results
-- in their becoming more silent ones. The second 'Double' argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" files in the current directory, because they can be overwritten.
overSoXSynthN2 :: Int -> Double -> Double -> String -> String -> V.Vector Double -> IO ()
overSoXSynthN2 n ampL time3 zs tts vec0
 | compare (abs ampL) 0.01 /= LT && compare (abs ampL) 1.0 /= GT =
    let (t, ws) = splitAt 1 . syllableStr n $ zs
        m     = length ws
        zeroN = numVZeroesPre vec0
        v2    = V.map (\yy -> time3 * fromIntegral (yy * m) / fromIntegral (head t)) . V.fromList $ ws in V.imapM_ (\j x -> do
          let note0 = closestNote x                     -- zs is obtained from the command line arguments
              note1 = pureQuintNote note0
              v0    = overTones2 note0 tts
              v1    = overTones2 note1 tts
              overSoXSynthHelpN vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
                ["-r22050", "-n", "test" ++ prependZeroes zeroN (show (i + 2)) ++ ".wav", "synth", showFFloat (Just 4) (V.unsafeIndex v2 (j `rem` m)) "",
                  "sine",showFFloat (Just 4) noteN "", "vol", showFFloat (Just 4) (amplN * ampL) ""] "") vec
              overSoXSynthHelpN2 vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
                ["-r22050", "-n", "testQ" ++ prependZeroes zeroN (show (i + 2)) ++ ".wav", "synth", showFFloat (Just 4) (V.unsafeIndex v2 (j `rem` m)) "",
                   "sine", showFFloat (Just 4) noteN "", "vol", showFFloat (Just 4) (amplN * ampL) ""] "") vec
              soxSynthHelpMain note01 note02 = readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testA" ++ prependZeroes zeroN "1" ++
                ".wav", "synth", showFFloat (Just 4) (V.unsafeIndex v2 (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","0.5"] ""
          soxSynthHelpMain note0 note1
          overSoXSynthHelpN v0
          overSoXSynthHelpN2 v1
          mixTest2 zeroN j) vec0
 | otherwise = let ampL1 = ampL - (fromIntegral . truncate $ ampL) in
    if abs ampL1 < 0.01 then overSoXSynthN2 n 0.01 time3 zs tts vec0
    else overSoXSynthN2 n ampL1 time3 zs tts vec0

-- | Function to create a melody for the given arguments. 'String' is used to provide a rhythm. The main component of the sound includes the lower pure quint, which
-- can be in the same octave or in the one with the number lower by one. The first 'Double' argument from the range [0.01..1.0] is used as a maximum amplitude
-- for Overtones. If it is set to 1.0 the overTones amplitudes are just the maximum ones, otherwise they are multiplied by the parameter and this results
-- in their becoming more silent ones. The second 'Double' argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" files in the current directory, because they can be overwritten.
-- The third 'String' argument is used to define the intervals for the notes if any.
-- The third 'Double' parameter basically is used to define in how many times the volume for the second lower note is less than the volume of
-- the main note. If it is rather great, it can signal that the volume for the second note overTones are greater than for the main note obetones.
-- The last one is experimental feature.
overSoXSynthN3 :: Int -> Double -> Double -> Double -> String -> String -> String -> V.Vector Double -> IO ()
overSoXSynthN3 n ampL time3 dAmpl zs tts vs vec0
 | compare (abs ampL) 0.01 /= LT && compare (abs ampL) 1.0 /= GT =
    let (t, ws) = splitAt 1 . syllableStr n $ zs
        m     = length ws
        zeroN = numVZeroesPre vec0
        v3    = intervalsFromString vs
        l     = length vs
        v2    = V.map (\yy -> time3 * fromIntegral (yy * m) / fromIntegral (head t)) . V.fromList $ ws in V.imapM_ (\j x -> do
          let note0 = closestNote x                     -- zs is obtained from the command line arguments
              note1 = dNote (V.unsafeIndex v3 (j `rem` l)) note0
              v0    = overTones2 note0 tts
              v1    = if isNothing note1 then V.empty
                      else overTones2 (fromJust note1) tts
              overSoXSynthHelpN vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
                ["-r22050", "-n", "test" ++ prependZeroes zeroN (show (i + 2)) ++ ".wav", "synth", showFFloat (Just 4) (V.unsafeIndex v2 (j `rem` m)) "",
                  "sine",showFFloat (Just 4) noteN "", "vol", showFFloat (Just 4) (amplN * ampL) ""] "") vec
              overSoXSynthHelpN2 vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
                ["-r22050", "-n", "testQ" ++ prependZeroes zeroN (show (i + 2)) ++ ".wav", "synth", showFFloat (Just 4) (V.unsafeIndex v2 (j `rem` m)) "",
                   "sine", showFFloat (Just 4) noteN "", "vol", showFFloat (Just 4) (if dAmpl * amplN * ampL > 1.0 then 1.0
                     else dAmpl * amplN * ampL) ""] "") vec
              soxSynthHelpMain0 note01 = readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testA" ++ prependZeroes zeroN "1" ++  ".wav",
                "synth", showFFloat (Just 4) (V.unsafeIndex v2 (j `rem` m)) "","sine", showFFloat (Just 4) note01 "", "vol","0.5"] ""
              soxSynthHelpMain1 note02 = readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testB" ++
                 prependZeroes zeroN "1" ++  ".wav", "synth", showFFloat (Just 4) (V.unsafeIndex v2 (j `rem` m)) "","sine", showFFloat (Just 4) note02 "",
                   "vol", showFFloat (Just 4) (if dAmpl > 0.5 then 0.5 else dAmpl / 2) ""] ""
          if isNothing note1 then do { soxSynthHelpMain0 note0
                                     ; overSoXSynthHelpN v0 }
          else do { soxSynthHelpMain0 note0
                  ; soxSynthHelpMain1 (fromJust note1)
                  ; overSoXSynthHelpN v0
                  ; overSoXSynthHelpN2 v1}
          paths0 <- listDirectory "."
          let paths = sort . filter (isPrefixOf "test") $ paths0
          _ <- readProcessWithExitCode (fromJust (showE "sox")) (["--combine", "mix"] ++ paths ++ ["result0" ++ prependZeroes zeroN (show j) ++ ".wav","vol","0.3"]) ""
          mapM_ removeFile paths) vec0
 | otherwise = let ampL1 = ampL - (fromIntegral . truncate $ ampL) in
    if abs ampL1 < 0.01 then overSoXSynthN3 n 0.01 time3 dAmpl zs tts vs vec0
    else overSoXSynthN3 n ampL1 time3 dAmpl zs tts vs vec0

-- | Similar to 'overSoXSynthN', but uses a sound file to obtain the information analogous to 'V.Vector' in the latter one. Besides, the function lifts
-- the frequencies to the octave with the given by 'Int' parameter number (better to use from the range [1..8]). The first 'Double' argument from
-- the range [0.01..1.0] is used as a maximum amplitude for Overtones. If it is set to 1.0 the overTones amplitudes are just maximum ones,
-- otherwise they are multiplied by the parameter and this results in their becoming more silent ones.
-- The second 'Double' argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" and \"end.wav\" files in the current directory, because they can be overwritten.
--
-- For better usage the 'FilePath' should be a filepath for the .wav file.
overSoXSynthNGen :: FilePath -> Int -> Double -> Double -> String -> IO ()
overSoXSynthNGen file m = overSoXSynthNGenE file m 12

-- | Similar to 'overSoXSynthNGen', but uses additional second 'Int' parameter. It defines, to which n-th elements set (see 'nkyT') belongs the obtained
-- higher notes in the intervals. If that parameter equals to 12, then the function is practically equivalent to 'overSoXSynthNGen'. To obtain
-- its modifications, please, use 2, 3, 4, 6, or 9.
overSoXSynthNGenE :: FilePath -> Int -> Int -> Double -> Double -> String -> IO ()
overSoXSynthNGenE file m ku ampL time3 zs = do
  duration0 <- durationA file
  let n = truncate (duration0 / 0.001)
  vecA <- freqsFromFile file n
  let vecB = liftInEnkuV m ku . V.map fromIntegral . V.filter (/= (11440::Int)) $ vecA
  overSoXSynthN n ampL time3 zs vecB
  endFromResult

-- | Similar to 'overSoXSynthN2', but uses a sound file to obtain the information analogous to 'V.Vector' in the latter one. Besides, the function lifts
-- the frequencies to the octave with the given by 'Int' parameter number (better to use from the range [1..8]). The first 'Double' argument from
-- the range [0.01..1.0] is used as a maximum amplitude for Overtones. If it is set to 1.0 the overTones amplitudes are just maximum ones,
-- otherwise they are multiplied by the parameter and this results in their becoming more silent ones.
-- The second 'Double' argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" and \"end.wav\" files in the current directory, because they can be overwritten.
-- 
-- For better usage the 'FilePath' should be a filepath for the .wav file.
-- The second 'String' argument is used to define signs of the harmonics coefficients in the generated sounds.
overSoXSynthNGen2 :: FilePath -> Int -> Double -> Double -> String -> String -> IO ()
overSoXSynthNGen2 file m = overSoXSynthNGen2E file m 12

-- | Similar to 'overSoXSynthNGen2', but uses additional second 'Int' parameter. It defines, to which n-th elements set (see 'nkyT') belongs the obtained
-- higher notes in the intervals. If that parameter equals to 12, then the function is practically equivalent to 'overSoXSynthNGen2'. To obtain
-- its modifications, please, use 2, 3, 4, 6, or 9.
overSoXSynthNGen2E :: FilePath -> Int -> Int -> Double -> Double -> String -> String -> IO ()
overSoXSynthNGen2E file m ku ampL time3 zs tts = do
  duration0 <- durationA file
  let n = truncate (duration0 / 0.001)
  vecA <- freqsFromFile file n
  let vecB = liftInEnkuV m ku. V.map fromIntegral . V.filter (/= (11440::Int)) $ vecA
  overSoXSynthN2 n ampL time3 zs tts vecB
  endFromResult

-- | Similar to 'overSoXSynthN2', but uses a sound file to obtain the information analogous to 'V.Vector' in the latter one. Besides, the function lifts
-- the frequencies to the octave with the given by 'Int' parameter number (better to use from the range [1..8]). The first 'Double' argument from
-- the range [0.01..1.0] is used as a maximum amplitude for Overtones. If it is set to 1.0 the overTones amplitudes are just maximum ones,
-- otherwise they are multiplied by the parameter and this results in their becoming more silent ones.
-- The second 'Double' argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" and \"end.wav\" files in the current directory, because they can be overwritten.
-- 
-- For better usage the 'FilePath' should be a filepath for the .wav file.
-- The second 'String' argument is used to define signs of the harmonics coefficients in the generated sounds.
-- The third 'String' argument is used to define the intervals for the notes if any.
-- The third 'Double' parameter basically is used to define in how many times the volume for the second lower note is less than the volume of
-- the main note. If it is rather great, it can signal that the volume for the second note overTones are greater than for the main note obetones.
-- The last one is experimental feature.
overSoXSynthNGen3 :: FilePath -> Int -> Double -> Double -> Double -> String -> String -> String -> IO ()
overSoXSynthNGen3 file m = overSoXSynthNGen3E file m 12

-- | Similar to 'overSoXSynthNGen3', but uses additional second 'Int' parameter. It defines, to which n-th elements set (see 'nkyT') belongs the obtained
-- higher notes in the intervals. If that parameter equals to 12, then the function is practically equivalent to 'overSoXSynthNGen3'. To obtain
-- its modifications, please, use 2, 3, 4, 6, or 9.
overSoXSynthNGen3E :: FilePath -> Int -> Int -> Double -> Double -> Double -> String -> String -> String -> IO ()
overSoXSynthNGen3E file m ku ampL time3 dAmpl zs tts vs = do
  duration0 <- durationA file
  let n = truncate (duration0 / 0.001)
  vecA <- freqsFromFile file n
  let vecB = liftInEnkuV m ku . V.map fromIntegral . V.filter (/= (11440::Int)) $ vecA
  overSoXSynthN3 n ampL time3 dAmpl zs tts vs vecB
  endFromResult

-- | For the given frequency and a Ukrainian text it generates a musical sound with the timbre obtained from the Ukrainian text (see the
-- documentation for @mmsyn7s@ package). The timbre for another given text usually differs, but can be the same. The last one is only
-- if the uniqueness structure and length are the same for both 'String'. Otherwise, they differs. This gives an opportunity to practically
-- and quickly synthesize differently sounding intervals. The main component of the sound includes the lower pure quint, which can be in
-- the same octave or in the one with the number lower by one. Please, check before executing 
-- whether there is no \"x.wav\", \"test*\", \"result*\" files in the current directory, because they can be overwritten.
uniqOverSoXSynth :: Double -> String -> IO ()
uniqOverSoXSynth x wws = do
  let note0 = closestNote x
      note1 = pureQuintNote note0
      v0    = uniqOvertonesV note0 wws
      v1    = uniqOvertonesV note1 wws
      uniqOverSoXSynthHelp vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
        ["-r22050", "-n", "test0" ++ show (i + 2) ++ ".wav", "synth", "0.5","sine", showFFloat (Just 4) noteN "", "vol", showFFloat (Just 4) amplN ""] "") vec
      uniqOverSoXSynthHelp2 vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
        ["-r22050", "-n", "test1" ++ show (i + 2) ++ ".wav", "synth", "0.5","sine", showFFloat (Just 4) noteN "",
           "vol", showFFloat (Just 4) amplN ""] "") vec
  _ <- 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

-- | For the given frequency and a Ukrainian text it generates a musical sound with the timbre obtained from the Ukrainian text (see the
-- documentation for @mmsyn7s@ package). The timbre for another given text usually differs, but can be the same. The last one is only
-- if the uniqueness structure and length are the same for both 'String'. Otherwise, they differs. This gives an opportunity to practically
-- and quickly synthesize differently sounding intervals. The main component of the sound includes the lower pure quint, which can be in
-- the same octave or in the one with the number lower by one. Please, check before executing 
-- whether there is no \"x.wav\", \"test*\", \"result*\" files in the current directory, because they can be overwritten.
-- The second 'String' argument is used to define signs for the harmonics coefficients for Overtones.
uniqOverSoXSynth2 :: Double -> 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
      uniqOverSoXSynthHelp vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
        ["-r22050", "-n", "test0" ++ show (i + 2) ++ ".wav", "synth", "0.5","sine", showFFloat (Just 4) noteN "",
           "vol", showFFloat (Just 4) amplN ""] "") vec
      uniqOverSoXSynthHelp2 vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
        ["-r22050", "-n", "test1" ++ show (i + 2) ++ ".wav", "synth", "0.5","sine", showFFloat (Just 4) noteN "",
           "vol", showFFloat (Just 4) amplN ""] "") vec
  _ <- 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

-- | Function to create a melody for the given arguments. The first 'String' is used to provide a rhythm. The second one -- to provide a timbre.
-- The timbre for another given text usually differs, but can be the same. This gives an opportunity to practically and quickly
-- synthesize differently sounding intervals. The first 'Double' argument from the range [0.01..1.0] is used as a maximum amplitude for Overtones.
-- If it is set to 1.0 the overTones amplitudes are just maximum ones, otherwise they are multiplied by the parameter and this results in
-- their becoming more silent ones. The main component of the sound is in the given octave with a number given
-- by 'Int' parameter. Besides, another main component of the sound includes the lower pure quint, which can be in the same octave or in the one with
-- the number lower by one. The second 'Double' argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" files in the current directory, because they can be overwritten.
uniqOverSoXSynthN :: Int -> Double -> Double -> String -> String -> V.Vector Double -> IO ()
uniqOverSoXSynthN n ampL time3 zs wws vec0
 | compare (abs ampL) 0.01 /= LT && compare (abs ampL) 1.0 /= GT =
    let (t, ws) = splitAt 1 . syllableStr n $ zs
        m     = length ws
        zeroN = numVZeroesPre vec0
        v2    = V.map (\yy -> time3 * fromIntegral (yy * m) / fromIntegral (head t)) . V.fromList $ ws in V.imapM_ (\j x -> do
          let note0 = closestNote x                         -- zs ? vec0 -- are they related to the one object? No, they are obtained from different sources.
              note1 = pureQuintNote note0
              v0    = uniqOvertonesV note0 wws
              v1    = uniqOvertonesV note1 wws
              uniqOverSoXSynthHelpN vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
                ["-r22050", "-n", "test" ++ prependZeroes zeroN (show (i + 2)) ++ ".wav", "synth", showFFloat (Just 4) (V.unsafeIndex v2 (j `rem` m)) "",
                   "sine", showFFloat (Just 4) noteN "", "vol", showFFloat (Just 4) (amplN * ampL) ""] "") 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) (V.unsafeIndex v2 (j `rem` m)) "",
                   "sine", showFFloat (Just 4) noteN "", "vol", showFFloat (Just 4) (amplN * ampL) ""] "") vec
              soxSynthHelpMain note01 note02 = readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testA" ++
                 prependZeroes zeroN "1" ++  ".wav", "synth", showFFloat (Just 4) (V.unsafeIndex v2 (j `rem` m)) "","sine", showFFloat (Just 4) note01 $
                  show 0, "synth", showFFloat (Just 4) (V.unsafeIndex v2 (j `rem` m)) "","sine", "mix", showFFloat (Just 4) note02 "", "vol","0.5"]  ""
          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 uniqOverSoXSynthN n 0.01 time3 zs wws vec0
    else uniqOverSoXSynthN n ampL1 time3 zs wws vec0

-- | Function to create a melody for the given arguments. The first 'String' is used to provide a rhythm. The second one -- to provide a timbre.
-- The timbre for another given text usually differs, but can be the same. This gives an opportunity to practically and quickly
-- synthesize differently sounding intervals. The first 'Double' argument from the range [0.01..1.0] is used as a maximum amplitude for Overtones.
-- If it is set to 1.0 the overTones amplitudes are just maximum ones, otherwise they are multiplied by the parameter and this results in
-- their becoming more silent ones. The main component of the sound is in the given octave with a number given
-- by 'Int' parameter. Besides, another main component of the sound includes the lower pure quint, which can be in the same octave or in the one with
-- the number lower by one. The second 'Double' argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" files in the current directory, because they can be overwritten.
-- The third 'String' argument is used to define signs of the harmonics coefficients in the generated sounds.
uniqOverSoXSynthN3 :: Int -> Double -> Double -> String -> String -> String -> V.Vector Double -> IO ()
uniqOverSoXSynthN3 n ampL time3 zs wws tts vec0
 | compare (abs ampL) 0.01 /= LT && compare (abs ampL) 1.0 /= GT =
    let (t, ws) = splitAt 1 . syllableStr n $ zs
        m     = length ws
        zeroN = numVZeroesPre vec0
        v2    = V.map (\yy -> time3 * fromIntegral (yy * m) / fromIntegral (head t)) . V.fromList $ ws in V.imapM_ (\j x -> do
          let note0 = closestNote x                         -- zs ? vec0 -- are they related to the one object? No, they are obtained from different sources.
              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) (V.unsafeIndex v2 (j `rem` m)) "",
                   "sine", showFFloat (Just 4) noteN "", "vol", showFFloat (Just 4) (amplN * ampL) ""] "") 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) (V.unsafeIndex v2 (j `rem` m)) "",
                   "sine", showFFloat (Just 4) noteN "", "vol", showFFloat (Just 4) (amplN * ampL) ""] "") vec
              soxSynthHelpMain note01 note02 = readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testA" ++
                prependZeroes zeroN "1" ++  ".wav", "synth", showFFloat (Just 4) (V.unsafeIndex v2 (j `rem` m)) "","sine", showFFloat (Just 4) note01 $
                  show 0,"synth", showFFloat (Just 4) (V.unsafeIndex v2 (j `rem` m)) "","sine", "mix", showFFloat (Just 4) note02 "", "vol","0.5"] ""
          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 uniqOverSoXSynthN3 n 0.01 time3 zs wws tts vec0
    else uniqOverSoXSynthN3 n ampL1 time3 zs wws tts vec0

-- | Function to create a melody for the given arguments. The first 'String' is used to provide a rhythm. The second one -- to provide a timbre.
-- The timbre for another given text usually differs, but can be the same. This gives an opportunity to practically and quickly
-- synthesize differently sounding intervals. The first 'Double' argument from the range [0.01..1.0] is used as a maximum amplitude for Overtones.
-- If it is set to 1.0 the overTones amplitudes are just maximum ones, otherwise they are multiplied by the parameter and this results in
-- their becoming more silent ones. The main component of the sound is in the given octave with a number given
-- by 'Int' parameter. Besides, another main component of the sound includes the lower pure quint, which can be in the same octave or in the one with
-- the number lower by one. The second 'Double' argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" files in the current directory, because they can be overwritten.
-- The third 'String' argument is used to define signs of the harmonics coefficients in the generated sounds.
-- The fourth 'String' argument is used to define the intervals for the notes if any.
-- The third 'Double' parameter basically is used to define in how many times the volume for the second lower note is less than the volume of
-- the main note. If it is rather great, it can signal that the volume for the second note overTones are greater than for the main note obetones.
-- The last one is experimental feature.
uniqOverSoXSynthN4 :: Int -> Double -> Double -> Double -> String -> String -> String -> String -> V.Vector Double -> IO ()
uniqOverSoXSynthN4 n ampL time3 dAmpl zs wws tts vs vec0
 | compare (abs ampL) 0.01 /= LT && compare (abs ampL) 1.0 /= GT =
    let (t, ws) = splitAt 1 . syllableStr n $ zs
        m     = length ws
        zeroN = numVZeroesPre vec0
        v3    = intervalsFromString vs
        l     = length vs
        v2    = V.map (\yy -> time3 * fromIntegral (yy * m) / fromIntegral (head t)) . V.fromList $ ws in V.imapM_ (\j x -> do
          let note0 = closestNote x                         -- zs ? vec0 -- are they related to the one object? No, they are obtained from different sources.
              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 vec = V.imapM_ (\i (noteN, !amplN) -> readProcessWithExitCode (fromJust (showE "sox"))
                ["-r22050", "-n", "test" ++ prependZeroes zeroN (show (i + 2)) ++ ".wav", "synth", showFFloat (Just 4) (V.unsafeIndex v2 (j `rem` m)) "",
                  "sine",showFFloat (Just 4) noteN "", "vol", showFFloat (Just 4) (amplN * ampL) ""] "") 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) (V.unsafeIndex v2 (j `rem` m)) "",
                   "sine", showFFloat (Just 4) noteN "", "vol", showFFloat (Just 4) (if dAmpl * amplN * ampL > 1.0 then 1.0
                      else dAmpl * amplN * ampL) ""] "") vec
              soxSynthHelpMain0 note01 = readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testA" ++
                 prependZeroes zeroN "1" ++  ".wav", "synth", showFFloat (Just 4) (V.unsafeIndex v2 (j `rem` m)) "","sine", showFFloat (Just 4) note01 "",
                   "vol","0.5"] ""
              soxSynthHelpMain1 note02 = readProcessWithExitCode (fromJust (showE "sox")) ["-r22050", "-n", "testB" ++
                 prependZeroes zeroN "1" ++  ".wav", "synth", showFFloat (Just 4) (V.unsafeIndex v2 (j `rem` m)) "","sine", showFFloat (Just 4) note02 "",
                    "vol", showFFloat (Just 4) (if dAmpl > 0.5 then 0.5 else dAmpl / 2) ""] ""
          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 uniqOverSoXSynthN4 n 0.01 time3 dAmpl zs wws tts vs vec0
    else uniqOverSoXSynthN4 n ampL1 time3 dAmpl zs wws tts vs vec0

-- | Similar to 'uniqOverSoXSynthN', but uses a sound file to obtain the information analogous to 'V.Vector' in the latter one. 
-- Besides, the function lifts the frequencies to the octave with the given by 'Int' parameter number (better to use from the range [1..8]).
-- The first 'Double' argument from the range [0.01..1.0] is used as a maximum amplitude for Overtones. If it is set to 1.0 the
-- overTones amplitudes are just the maximum ones, otherwise they are multiplied by the parameter and this results in their becoming more silent ones.
-- The second 'Double' argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" and \"end.wav\" files in the current directory, because they can be overwritten.
--
-- For better usage the 'FilePath' should be a filepath for the .wav file.
uniqOverSoXSynthNGen :: FilePath -> Int -> Double -> Double -> String -> String -> IO ()
uniqOverSoXSynthNGen file m = uniqOverSoXSynthNGenE file m 12

-- | Similar to 'uniqOverSoXSynthNGen', but uses additional second 'Int' parameter. It defines, to which n-th elements set (see 'nkyT') belongs the obtained
-- higher notes in the intervals. If that parameter equals to 12, then the function is practically equivalent to 'uniqOverSoXSynthNGen'. To obtain
-- its modifications, please, use 2, 3, 4, 6, or 9.
uniqOverSoXSynthNGenE :: FilePath -> Int -> Int -> Double -> Double -> String -> String -> IO ()
uniqOverSoXSynthNGenE file m ku ampL time3 zs wws = do
  duration0 <- durationA file
  let n = truncate (duration0 / 0.001)
  vecA <- freqsFromFile file n
  let vecB = liftInEnkuV m ku . V.map fromIntegral . V.filter (/= (11440::Int)) $ vecA
  uniqOverSoXSynthN n ampL time3 zs wws vecB
  endFromResult

-- | Similar to 'uniqOverSoXSynthN', but uses a sound file to obtain the information analogous to 'V.Vector' in the latter one. 
-- Besides, the function lifts the frequencies to the octave with the given by 'Int' parameter number (better to use from the range [1..8]).
-- The first 'Double' argument from the range [0.01..1.0] is used as a maximum amplitude for Overtones. If it is set to 1.0 the
-- overTones amplitudes are just the maximum ones, otherwise they are multiplied by the parameter and this results in their becoming more silent ones.
-- The second 'Double' argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" and \"end.wav\" files in the current directory, because they can be overwritten.
--
-- For better usage the 'FilePath' should be a filepath for the .wav file.
-- The third 'String' argument is used to define signs of the harmonics coefficients in the generated sounds.
uniqOverSoXSynthNGen3 :: FilePath -> Int -> Double -> Double -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen3 file m = uniqOverSoXSynthNGen3E file m 12

-- | Similar to 'uniqOverSoXSynthNGen3', but uses additional second 'Int' parameter. It defines, to which n-th elements set (see 'nkyT') belongs the obtained
-- higher notes in the intervals. If that parameter equals to 12, then the function is practically equivalent to 'uniqOverSoXSynthNGen3'. To obtain
-- its modifications, please, use 2, 3, 4, 6, or 9.
uniqOverSoXSynthNGen3E :: FilePath -> Int -> Int -> Double -> Double -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen3E file m ku ampL time3 zs wws tts = do
  duration0 <- durationA file
  let n = truncate (duration0 / 0.001)
  vecA <- freqsFromFile file n
  let vecB = liftInEnkuV m ku . V.map fromIntegral . V.filter (/= (11440::Int)) $ vecA
  uniqOverSoXSynthN3 n ampL time3 zs wws tts vecB
  endFromResult

-- | Similar to 'uniqOverSoXSynthN', but uses a sound file to obtain the information analogous to 'V.Vector' in the latter one. 
-- Besides, the function lifts the frequencies to the octave with the given by 'Int' parameter number (better to use from the range [1..8]).
-- The first 'Double' argument from the range [0.01..1.0] is used as a maximum amplitude for Overtones. If it is set to 1.0 the
-- overTones amplitudes are just the maximum ones, otherwise they are multiplied by the parameter and this results in their becoming more silent ones.
-- The second 'Double' argument is a basic sound duration. The default one is 0.5 (second). Please, check before executing
-- whether there is no \"x.wav\", \"test*\", \"result*\" and \"end.wav\" files in the current directory, because they can be overwritten.
--
-- For better usage the 'FilePath' should be a filepath for the .wav file.
-- The third 'String' argument is used to define signs of the harmonics coefficients in the generated sounds.
-- The fourth 'String' argument is used to define the intervals for the notes if any.
-- The third 'Double' parameter basically is used to define in how many times the volume for the second lower note is less than the volume of
-- the main note. If it is rather great, it can signal that the volume for the second note overTones are greater than for the main note obetones.
-- The last one is an experimental feature.
uniqOverSoXSynthNGen4 :: FilePath -> Int -> Double -> Double -> Double -> String -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen4 file m = uniqOverSoXSynthNGen4E file m 12

-- | Similar to 'uniqOverSoXSynthNGen4', but uses additional second 'Int' parameter. It defines, to which n-th elements set (see 'nkyT') belongs the obtained
-- higher notes in the intervals. If that parameter equals to 12, then the function is practically equivalent to 'uniqOverSoXSynthNGen4'. To obtain
-- its modifications, please, use 2, 3, 4, 6, or 9.
uniqOverSoXSynthNGen4E :: FilePath -> Int -> Int -> Double -> Double -> Double -> String -> String -> String -> String -> IO ()
uniqOverSoXSynthNGen4E file m ku ampL time3 dAmpl zs wws tts vs = do
  duration0 <- durationA file
  let n = truncate (duration0 / 0.001)
  vecA <- freqsFromFile file n
  let vecB = liftInEnkuV m ku . V.map fromIntegral . V.filter (/= (11440::Int)) $ vecA
  uniqOverSoXSynthN4 n ampL time3 dAmpl zs wws tts vs vecB
  endFromResult