-- |
-- Module      :  DobutokO.Sound.Executable
-- 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.

{-# OPTIONS_GHC -threaded #-}

module DobutokO.Sound.Executable (
  -- * Basic functions for the executable
  dobutokO2
  , recAndProcess
  , dobutokO2H7
  , dobutokO2H9
) where

import System.Exit (ExitCode (ExitSuccess))
import qualified Data.List as L (groupBy,sort)
import CaseBi (getBFst')
import Numeric (showFFloat)
import Control.Exception (onException)
import System.Environment (getArgs)
import Data.List (isPrefixOf)
import Data.Maybe (fromJust)
import Data.Char (isDigit,isSpace)
import System.Process
import EndOfExe (showE)
import qualified Data.Vector as V (Vector (..),generate,fromList,length,imapM_,snoc,toList,unsafeSlice)
import System.Directory
import SoXBasics
import Processing_mmsyn7ukr
import DobutokO.Sound hiding (dobutokO2, recAndProcess)
import DobutokO.Sound.IntermediateF (pAnR_)

-- | Function that actually makes processing in the @dobutokO2@ executable. 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.
dobutokO2 :: IO ()
dobutokO2 = do
  arggs <- getArgs
  let arg1 = concat . take 1 $ arggs
      file = concat . drop 1 . take 2 $ arggs
      args = unwords . drop 2 $ arggs
  exist2 <- doesFileExist file
  getBFst' (dobutokO2H exist2 args file, V.fromList . fmap (\(xs, f) -> (xs,f exist2 args file)) $ [("0",o2help),("1",dobutokO2H1),("11",dobutokO2H11),
    ("2",dobutokO2H2),("21",dobutokO2H21),("3",dobutokO2H3),("31",dobutokO2H31),("4",dobutokO2H4),("41",dobutokO2H41),("5",dobutokO2H5),
      ("51",dobutokO2H51),("61",dobutokO2H61),("7",dobutokO2H7),("8",dobutokO2H8),("80",dobutokO2H80),("9",dobutokO2H9)]) arg1

dobutokO2H1 :: Bool -> String -> FilePath -> IO ()
dobutokO2H1 exist2 args file = do
  [_,_,octave,ampLS,time2] <- mapM (recAndProcess file) (if exist2 then [0,2,3,4,5] else [1..5])
  let octave1 = read octave::Int
      ampL = read ampLS::Double
      time3 = read time2::Double
  oberSoXSynthNGen file octave1 ampL time3 args
{-# INLINE dobutokO2H1 #-}

dobutokO2H2 :: Bool -> String -> FilePath -> IO ()
dobutokO2H2 exist2 args file = do
  [_,_,octave,ampLS,time2,wws] <- mapM (recAndProcess file) (if exist2 then [0,2,3,4,5,6] else [1..6])
  let octave1 = read octave::Int
      ampL = read ampLS::Double
      time3 = read time2::Double
  uniqOberSoXSynthNGen file octave1 ampL time3 args wws
{-# INLINE dobutokO2H2 #-}

dobutokO2H3 :: Bool -> String -> FilePath -> IO ()
dobutokO2H3 exist2 args file = do
  [_,_,octave,ampLS,time2,tts] <- mapM (recAndProcess file) (if exist2 then [0,2,3,4,5,7] else [1,2,3,4,5,7])
  let octave1 = read octave::Int
      ampL = read ampLS::Double
      time3 = read time2::Double
  oberSoXSynthNGen2 file octave1 ampL time3 args tts
{-# INLINE dobutokO2H3 #-}

dobutokO2H4 :: Bool -> String -> FilePath -> IO ()
dobutokO2H4 exist2 args file = do
  [_,_,octave,ampLS,time2,wws,tts] <- mapM (recAndProcess file) (if exist2 then [0,2,3,4,5,6,7] else [1..7])
  let octave1 = read octave::Int
      ampL = read ampLS::Double
      time3 = read time2::Double
  uniqOberSoXSynthNGen3 file octave1 ampL time3 args wws tts
{-# INLINE dobutokO2H4 #-}

dobutokO2H5 :: Bool -> String -> FilePath -> IO ()
dobutokO2H5 exist2 args file = do
  [_,_,octave,ampLS,time2,tts,dAmpl0,vs] <- mapM (recAndProcess file) (if exist2 then [0,2,3,4,5,7,8,9] else [1,2,3,4,5,7,8,9])
  let octave1 = read octave::Int
      ampL = read ampLS::Double
      time3 = read time2::Double
      dAmpl = read dAmpl0::Double
  oberSoXSynthNGen3 file octave1 ampL time3 dAmpl args tts vs
{-# INLINE dobutokO2H5 #-}

dobutokO2H :: Bool -> String -> FilePath -> IO ()
dobutokO2H exist2 args file = do
  [_,_,octave,ampLS,time2,wws,tts,dAmpl0,vs] <- mapM (recAndProcess file) (if exist2 then [0,2,3,4,5,6,7,8,9] else [1..9])
  let octave1 = read octave::Int
      ampL = read ampLS::Double
      time3 = read time2::Double
      dAmpl = read dAmpl0::Double
  uniqOberSoXSynthNGen4 file octave1 ampL time3 dAmpl args wws tts vs
{-# INLINE dobutokO2H #-}

dobutokO2H61 :: Bool -> String -> FilePath -> IO ()
dobutokO2H61 exist2 args file = do
  [_,_,complexNky,ampLS,time2,wws,tts,dAmpl0,vs] <- mapM (recAndProcess file) (if exist2 then [0,2,11,4,5,6,7,8,9] else [1,2,11,4,5,6,7,8,9])
  let [enkA,nTh] = map (\z -> read z::Int) . words $ complexNky
      ampL = read ampLS::Double
      time3 = read time2::Double
      dAmpl = read dAmpl0::Double
  uniqOberSoXSynthNGen4E file nTh enkA ampL time3 dAmpl args wws tts vs
{-# INLINE dobutokO2H61 #-}

dobutokO2H8 :: Bool -> String -> FilePath -> IO ()
dobutokO2H8 _ _ _ = do
  path8s0 <- listDirectory "."
  let path8v = V.fromList . L.sort . filter (isPrefixOf "result") $ path8s0
      path8v1 = V.generate (V.length path8v `quot` 800) (\i0 -> V.unsafeSlice (i0 * 800) 800 path8v ) `V.snoc` V.unsafeSlice (800 *
         (V.length path8v `quot` 800)) (V.length path8v `rem` 800) path8v
  V.imapM_ dO2H8 path8v1
  epath0s <- listDirectory "."
  let epaths = L.sort . filter (isPrefixOf "end0") $ epath0s
  (code1,_,_) <- readProcessWithExitCode (fromJust (showE "sox")) (epaths ++ ["end.wav"]) ""
  case code1 of
    ExitSuccess -> mapM_ removeFile epaths
    _           -> do
      exi1 <- doesFileExist "end.wav"
      if exi1
        then do
          removeFile "end.wav"
          error $ "The end file \"end.wav\" was not created. "
        else error "The end file \"end.wav\" was not created. "
{-# INLINE dobutokO2H8 #-}

dobutokO2H11 :: Bool -> String -> FilePath -> IO ()
dobutokO2H11 exist2 args file = do
  [_,_,complexNky,ampLS,time2] <- mapM (recAndProcess file) (if exist2 then [0,2,11,4,5] else [1,2,11,4,5])
  let [enkA,nTh] = map (\z -> read z::Int) . words $ complexNky
      ampL = read ampLS::Double
      time3 = read time2::Double
  oberSoXSynthNGenE file nTh enkA ampL time3 args
{-# INLINE dobutokO2H11 #-}

dobutokO2H21 :: Bool -> String -> FilePath -> IO ()
dobutokO2H21 exist2 args file = do
  [_,_,complexNky,ampLS,time2,wws] <- mapM (recAndProcess file) (if exist2 then [0,2,11,4,5,6] else [1,2,11,4,5,6])
  let [enkA,nTh] = map (\z -> read z::Int) . words $ complexNky
      ampL = read ampLS::Double
      time3 = read time2::Double
  uniqOberSoXSynthNGenE file nTh enkA ampL time3 args wws
{-# INLINE dobutokO2H21 #-}

dobutokO2H31 :: Bool -> String -> FilePath -> IO ()
dobutokO2H31 exist2 args file = do
  [_,_,complexNky,ampLS,time2,tts] <- mapM (recAndProcess file) (if exist2 then [0,2,11,4,5,7] else [1,2,11,4,5,7])
  let [enkA,nTh] = map (\z -> read z::Int) . words $ complexNky
      ampL = read ampLS::Double
      time3 = read time2::Double
  oberSoXSynthNGen2E file nTh enkA ampL time3 args tts
{-# INLINE dobutokO2H31 #-}

dobutokO2H41 :: Bool -> String -> FilePath -> IO ()
dobutokO2H41 exist2 args file = do
  [_,_,complexNky,ampLS,time2,wws,tts] <- mapM (recAndProcess file) (if exist2 then [0,2,11,4,5,6,7] else [1,2,11,4,5,6,7])
  let [enkA,nTh] = map (\z -> read z::Int) . words $ complexNky
      ampL = read ampLS::Double
      time3 = read time2::Double
  uniqOberSoXSynthNGen3E file nTh enkA ampL time3 args wws tts
{-# INLINE dobutokO2H41 #-}

dobutokO2H51 :: Bool -> String -> FilePath -> IO ()
dobutokO2H51 exist2 args file = do
  [_,_,complexNky,ampLS,time2,tts,dAmpl0,vs] <- mapM (recAndProcess file) (if exist2 then [0,2,11,4,5,7,8,9] else [1,2,11,4,5,7,8,9])
  let [enkA,nTh] = map (\z -> read z::Int) . words $ complexNky
      ampL = read ampLS::Double
      time3 = read time2::Double
      dAmpl = read dAmpl0::Double
  oberSoXSynthNGen3E file nTh enkA ampL time3 dAmpl args tts vs
{-# INLINE dobutokO2H51 #-}

dO2H8 :: Int -> V.Vector String -> IO ()
dO2H8 i v = do
  (code,_,_) <- readProcessWithExitCode (fromJust (showE "sox")) (V.toList v ++ ["end0" ++ show i ++ ".wav"]) ""
  case code of
    ExitSuccess -> putStr ""
    _           -> do
      exi0 <- doesFileExist $ "end0" ++ show i ++ ".wav"
      if exi0
        then do
          removeFile $ "end0" ++ show i ++ ".wav"
          error $ "The intermediate file " ++ "\"end0" ++ show i ++ ".wav\" was not created. "
        else error $ "The intermediate file " ++ "\"end0" ++ show i ++ ".wav\" was not created. "
{-# INLINE dO2H8 #-}

dobutokO2H80 :: Bool -> String -> FilePath -> IO ()
dobutokO2H80 _ _ _ = do
  path8s0 <- listDirectory "."
  let path8v = V.fromList . L.sort . filter (isPrefixOf "result") $ path8s0
      path8v1 = V.generate (V.length path8v `quot` 800) (\i0 -> V.unsafeSlice (i0 * 800) 800 path8v ) `V.snoc` V.unsafeSlice (800 *
         (V.length path8v `quot` 800)) (V.length path8v `rem` 800) path8v
  V.imapM_ dO2H8 path8v1
  epath0s <- listDirectory "."
  let epaths = L.sort . filter (isPrefixOf "end0") $ epath0s
  (code1,_,_) <- readProcessWithExitCode (fromJust (showE "sox")) (epaths ++ ["end.wav"]) ""
  case code1 of
    ExitSuccess -> do
      mapM_ removeFile epaths
      mapM_ removeFile $ V.toList path8v
    _           -> do
      exi1 <- doesFileExist "end.wav"
      if exi1
        then do
          removeFile "end.wav"
          error $ "The end file \"end.wav\" was not created. "
        else error "The end file \"end.wav\" was not created. "
{-# INLINE dobutokO2H80 #-}

-- | Actually works as 'pAnR_' function.
dobutokO2H9 :: Bool -> String -> FilePath -> IO ()
dobutokO2H9 _ _ _ = pAnR_
{-# INLINE dobutokO2H9 #-}

dobutokO2H99 :: Bool -> String -> FilePath -> IO ()
dobutokO2H99 exist2 args file = do
  undefined
{-# INLINE dobutokO2H99 #-}



isDataStr :: String -> Bool
isDataStr = null . filter (== '@')

isTextPair :: String -> String -> Bool
isTextPair xs ys = isDataStr xs && isDataStr ys

-- | Used to obtain one multiline specially formatted textual input and do the full processment for the sound. 
-- The function generates obertones using additional 'String' and allows maximum control over the parameters.
-- Besides, all the needed information it obtains from the singular formatted input, which can be ended
-- with a keyboard keys combination that means an end of input (e. g. for Unices, that is probably Ctrl + D).
-- \'@\' are separators for the input parts for their respective parts. For more information about the
-- format of the single input, see:
--
-- 'https://drive.google.com/open?id=10Z_GRZR4TKoL5KXfqPm-t-4humuHN0O4'
--
-- The file is also provided with the package as text.dat.txt. 
-- The last two or three inputs (an input just here means a textual input between two \'@\') can be omitted,
-- the program will work also but with less control for the user possible. 
-- 
dobutokO2H7 :: Bool -> String -> FilePath -> IO ()
dobutokO2H7 True args file = do
  putStrLn "Please, specify a prepared textual input. To end the input press a keyboard keys combination that means an end of the input (e. g. for Unices, possibly Ctrl + D). "
  input <- getContents
  let text0   = lines input
      listTxt = filter isDataStr . map (unwords . words . unlines) . L.groupBy isTextPair $ text0
      l       = length listTxt
  case l of
    4 -> onException (do
      let [octave0,ampLS0,time20,wws] = listTxt
          octave1 = read (d3H octave0)::Int
          ampL = read (d4H ampLS0)::Double
          time3 = read (d5H time20)::Double
      uniqOberSoXSynthNGen file octave1 ampL time3 args wws) (do
        putStrLn "--------------------------------------------------------------------------------------------------------------------"
        putStrLn ""
        putStrLn "The operation was not successful because of the not valid textual input. Please, specify a valid textual input. "
        dobutokO2H7 True args file)
    5 -> onException (do
      let [octave0,ampLS0,time20,wws,tts0] = listTxt
          octave1 = read (d3H octave0)::Int
          ampL = read (d4H ampLS0)::Double
          time3 = read (d5H time20)::Double
      uniqOberSoXSynthNGen3 file octave1 ampL time3 args wws (d7H tts0)) (do
        putStrLn "--------------------------------------------------------------------------------------------------------------------"
        putStrLn ""
        putStrLn "The operation was not successful because of the not valid textual input. Please, specify a valid textual input. "
        dobutokO2H7 True args file)
    7 -> onException (do
      let [octave0,ampLS0,time20,wws,tts0,dAmpl0,vs0] = listTxt
          octave1 = read (d3H octave0)::Int
          ampL = read (d4H ampLS0)::Double
          time3 = read (d5H time20)::Double
          dAmpl = read (d8H dAmpl0)::Double
      uniqOberSoXSynthNGen4 file octave1 ampL time3 dAmpl args wws (d7H tts0) (d9H vs0)) (do
        putStrLn "--------------------------------------------------------------------------------------------------------------------"
        putStrLn ""
        putStrLn "The operation was not successful because of the not valid textual input. Please, specify a valid textual input. "
        dobutokO2H7 True args file)
    _ -> do
        putStrLn "--------------------------------------------------------------------------------------------------------------------"
        putStrLn ""
        putStrLn "The operation was not successful because of the not valid textual input. Please, specify a valid textual input. "
        dobutokO2H7 True args file
dobutokO2H7 _ args file = onException (do
  _ <- processD1
  _ <- processD2 file
  dobutokO2H7 True args file) (do
    putStrLn "--------------------------------------------------------------------------------------------------------------------"
    putStrLn ""
    putStr "The operation was not successful because the file with such a name does not exist or was not created by a program. "
    putStrLn "Please, interrupt a program and start again with a better data. "
    dobutokO2H7 False args file)
{-# INLINE dobutokO2H7 #-}

-- | Takes textual input from the stdin and prints it as one 'String' to the stdout.
o2help :: Bool -> String -> FilePath -> IO ()
o2help _ _ _ = do
  xs <- getContents
  let ys = unwords . lines $ xs in do
    putStrLn ""
    putStrLn "-------------------------------------------------------------------------------------------------------------"
    putStrLn ys

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

-- | Function records and processes the sound data needed to generate the \"end.wav\" file in the 'dobutokO2' function. Please, check before executing
-- whether there is no \"x.wav\" file in the current directory, because it can be overwritten.
recAndProcess :: FilePath -> Int -> IO String
recAndProcess file x =
  getBFst' (processD, V.fromList [(0,processD0 file),(1,processD1),(2,processD2 file),(3,processD3),(4,processD4),(5,processD5),(7,processD7),
    (8,processD8),(9,processD9),(11,processD_1)]) x

processD_1 :: IO String
processD_1 = onException (do
  putStr "Please, specify two \'Int\' numbers (with intermediate space character between them): the first one is a number of different notes there will be "
  putStr "in the result, and the second one is a number of enky, to which you would like all the main components (not taking into account their "
  putStr "respective lower pure quints) should belong. "
  putStrLn "If you specify as the first one 2 (possibly the simplest case), then to the second one you can define a number in the range [3..53]. "
  putStrLn "If you specify as the first one 3, then to the second one you can define a number in the range [2..35]. "
  putStrLn "If you specify as the first one 4, then to the second one you can define a number in the range [2..26]. "
  putStrLn "If you specify as the first one 6, then to the second one you can define a number in the range [1..17]. "
  putStrLn "If you specify as the first one 9, then to the second one you can define a number in the range [1..11]. "
  enka0 <- getLine
  let enka1 = take 2 . words . filter (\x -> isDigit x || isSpace x) $ enka0
      enka2 = read (head . take 1 $ enka1)::Int
      enka3
        | enka2 == 2 = if compare ((read (take 2 . head . tail $ enka1)::Int) `rem` 53) 3 == LT then 28 else (read (take 2 . head . tail $ enka1)::Int)
           `rem` 53
        | enka2 == 3 = if compare ((read (take 2 . head . tail $ enka1)::Int) `rem` 35) 2 == LT then 19 else (read (take 2 . head . tail $ enka1)::Int)
           `rem` 35
        | enka2 == 4 = if compare ((read (take 2 . head . tail $ enka1)::Int) `rem` 26) 2 == LT then 14 else (read (take 2 . head . tail $ enka1)::Int)
           `rem` 26
        | enka2 == 6 = if compare ((read (take 2 . head . tail $ enka1)::Int) `rem` 17) 1 == LT then 9 else (read (take 2 . head . tail $ enka1)::Int)
           `rem` 17
        | enka2 == 9 = if compare ((read (take 2 . head . tail $ enka1)::Int) `rem` 11) 1 == LT then 6 else (read (take 2 . head . tail $ enka1)::Int)
           `rem` 11
        | otherwise  = error "Not valid number in the second place. "
  return $ show enka2 ++ " " ++ show enka3 ) (do
    putStrLn "The process was not successful may be because of the not valid data. Please, specify the valid data as requested."
    putStrLn "_______________________________________________________________________"
    processD3)
{-# INLINE processD_1 #-}

processD0 :: FilePath -> IO String
processD0 file = onException (readProcessWithExitCode (fromJust (showE "sox")) [file, "x.wav", "-r22050", "channels", "1"] "" >> putStrLn "" >> return "") (do
  exist <- doesFileExist "x.wav"
  if exist then removeFile "x.wav"
  else putStr ""
  putStrLn ""
  putStr "The process was not successful may be because of the not valid data OR SoX cannot convert the given file to the .wav format. "
  putStrLn "Interrupt the program and start again with the valid file. "
  putStrLn "_______________________________________________________________________"
  processD0 file)
{-# INLINE processD0 #-}

processD1 :: IO String
processD1 = onException (do
  tempeRa 0
  putStrLn "Please, specify, how many seconds long sound data you would like to record."
  time <- getLine
  let time0 = read (filter (\t -> isDigit t || t == '.') $ time)::Double
  putStrLn "Please, wait for 0.5 second and produce the needed sound now."
  recA "x.wav" time0
  putStrLn ""
  return "") (do
    dir0 <- listDirectory "."
    let paths5 = filter (isPrefixOf "nx.") dir0
        paths6 = filter (== "x.wav") dir0
        paths  = paths5 ++ paths6
    mapM_ removeFile paths
    putStrLn ""
    putStrLn "The process was not successful may be because of the not valid data. Please, specify the valid data as requested."
    putStrLn "_______________________________________________________________________"
    processD1)
{-# INLINE processD1 #-}

processD2 :: FilePath -> IO String
processD2 file = onException (do
  exist3 <- doesFileExist file
  if exist3 then return ""
  else do
    putStr "Please, specify the control parameter for the SoX \"noisered\" effect in the range from 0.0 to 1.0. "
    putStrLn "The greater value causes more reduction with possibly removing some important sound data. The default value is 0.5 "
    putStrLn "To use the default value, you can simply press Enter."
    ctrlN <- getLine
    let addit = dropWhile (/= '.') . filter (\t -> isDigit t || t == '.') $ ctrlN
        noiseP = if null ctrlN then ""
                 else tail addit
    controlNoiseReduction $ '0':noiseP
    norm "_x.wav"
    if isPrefixOf "nx." file
      then putStr ""
      else renameFile "8_x.wav" file
    removeFile "x.wav"
    removeFile "_x.wav"
    dir <- listDirectory "."
    let paths4 = filter (isPrefixOf "nx.") dir
    mapM_ removeFile paths4
    putStrLn ""
    return "") (do
      putStrLn "The process was not successful may be because of the not valid data. Please, specify the valid data as requested."
      putStrLn "_______________________________________________________________________"
      processD2 file)
{-# INLINE processD2 #-}

processD3 :: IO String
processD3 = onException (do
  putStr "Please, specify the octave number, to which you would like all the main components (not taking into account their respective lower pure quints) "
  putStrLn "should belong. The number should be better in the range [1..8]"
  octave0 <- getLine
  return $ d3H octave0 ) (do
    putStrLn "The process was not successful may be because of the not valid data. Please, specify the valid data as requested."
    putStrLn "_______________________________________________________________________"
    processD3)
{-# INLINE processD3 #-}

d3H :: String -> String
d3H xs = show $ (read (take 1 xs)::Int) `rem` 9
{-# INLINE d3H #-}

processD4 :: IO String
processD4 = onException (do
  putStr "Please, specify the amplitude for the generated obertones as an Int number in the range [0..99]. "
  putStrLn "The default one is 99"
  putStrLn "To use the default value, you can simply press Enter."
  amplOb0 <- getLine
  return $ d4H amplOb0) (do
             putStrLn "The process was not successful may be because of the not valid data. Please, specify the valid data as requested."
             putStrLn "_______________________________________________________________________"
             processD4)
{-# INLINE processD4 #-}

d4H :: String -> String
d4H xs
 | null xs = "1.0"
 | otherwise = let amplOb = (read (take 2 . filter isDigit $ xs)::Int) `rem` 100 in
    case amplOb of
      99 -> "1.0"
      _ -> if compare (amplOb `quot` 9) 1 == LT then "0.0" ++ show (amplOb + 1)
           else "0." ++ show (amplOb + 1)
{-# INLINE d4H #-}

processD5 :: IO String
processD5 = onException (do
  putStr "Please, specify the basic duration for the generated sounds as a Double number in the range [0.1..4.0]. "
  putStrLn "The default one is 0.5"
  putStrLn "To use the default value, you can simply press Enter."
  time0 <- getLine
  return $ d5H time0) (do
             putStrLn "The process was not successful may be because of the not valid data. Please, specify the valid data as requested."
             putStrLn "_______________________________________________________________________"
             processD5)
{-# INLINE processD5 #-}

d5H :: String -> String
d5H xs
  | null xs = "0.5"
  | otherwise = let time1 = (read (filter (\z -> isDigit z || z == '.') $ xs)::Double) in
      if compare time1 0.1 /= LT && compare time1 4.0 /= GT then showFFloat (Just 4) time1 $ show 0
      else let mantissa = time1 - (fromIntegral . truncate $ time1)
               ceilP    = (truncate time1::Int) `rem` 4 in
             if ceilP == 0 then "0." ++ (showFFloat (Just 4) mantissa $ show 0)
             else show ceilP ++ "." ++ (showFFloat (Just 4) mantissa $ show 0)
{-# INLINE d5H #-}

processD7 :: IO String
processD7 = onException (do
  putStrLn "Please, input the Ukrainian text that will be used to define signs for the harmonics coefficients to produce a special timbre for the notes: "
  tts <- getLine
  return $ d7H tts) (do
    putStrLn "The process was not successful may be because of the not valid data. Please, specify the valid data as requested."
    putStrLn "_______________________________________________________________________"
    processD7)
{-# INLINE processD7 #-}

d7H :: String -> String
d7H xs
  | null xs = "або"
  | otherwise = xs
{-# INLINE d7H #-}

processD8 :: IO String
processD8 = onException (do
  putStr "Please, specify in how many times the amplitude for the second lower note (if any) is greater than the amplitude for the main note. "
  putStrLn "The number is in the range [0.1..2.0]. The default one is 1.0"
  putStrLn "To use the default value, you can simply press Enter."
  dAmpl0 <- getLine
  return $ d8H dAmpl0) (do
             putStrLn "The process was not successful may be because of the not valid data. Please, specify the valid data as requested."
             putStrLn "_______________________________________________________________________"
             processD8)
{-# INLINE processD8 #-}

d8H :: String -> String
d8H xs
  | null xs = "1.0"
  | otherwise = let dAmpl1 = (read (filter (\z -> isDigit z || z == '.') $ xs)::Double) in
    if compare dAmpl1 0.1 /= LT && compare dAmpl1 2.0 /= GT then showFFloat (Just 4) dAmpl1 $ show 0
    else let mantissa = dAmpl1 - (fromIntegral . truncate $ dAmpl1)
             ceilP    = (truncate dAmpl1::Int) `rem` 2 in
           if ceilP == 0 then "0." ++ (showFFloat (Just 4) mantissa $ show 0)
           else show ceilP ++ "." ++ (showFFloat (Just 4) mantissa $ show 0)
{-# INLINE d8H #-}

processD9 :: IO String
processD9 = onException (do
  putStrLn "Please, input the Ukrainian text that will be used to define intervals to be used to produce the lower note for the given main one. "
  putStrLn "The default one is \"й\". "
  putStrLn "To use the default value, you can simply press Enter."
  vs <- getLine
  return $ d9H vs) (do
    putStrLn "The process was not successful may be because of the not valid data. Please, specify the valid data as requested."
    putStrLn "_______________________________________________________________________"
    processD9)
{-# INLINE processD9 #-}

d9H :: String -> String
d9H xs
  | null xs = "й"
  | otherwise = xs
{-# INLINE d9H #-}

processD :: IO String
processD = onException (do
  putStrLn "Please, input the Ukrainian text that will be used to create a special timbre for the notes: "
  wws <- getLine
  return wws) (do
    putStrLn "The process was not successful may be because of the not valid data. Please, specify the valid data as requested."
    putStrLn "_______________________________________________________________________"
    processD)
{-# INLINE processD #-}