-- |
-- Module      :  Main
-- Copyright   :  (c) OleksandrZhabenko 2020-2021
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  olexandr543@yahoo.com
--
-- A program and a library to modify the amplitudes of the sound representations for 
-- the Ukrainian language created by mmsyn7ukr package or somehow otherwise. Besides
-- it can be used to adjust volume for the sequential \"result*.wav\" files.
--

module Main where

import Control.Exception (onException)
import MMSyn7l (changeVolume,adjustVolRes)
--import qualified Data.Vector as V
import CaseBi.Arr (getBFstL')
import System.Environment (getArgs)
import Parser.ReplaceP (replaceP, replaceP4)

-- | The main and the only one function in the module. If you specify a one command line argument, which can be obtained by running @mmsyn7s@ program
-- with the needed to be sounded (with sound representations) Ukrainian text (please, refer to: https://hackage.haskell.org/package/mmsyn7s).
main :: IO ()
main :: IO ()
main = do
  [String]
args <- IO [String]
getArgs
  case [String]
args of
    [] -> do
      String -> IO ()
putStrLn String
"Now you can change the amplitude of the sound representations of the Ukrainian sounds (or something similar). "
      String -> IO ()
putStrLn String
""
      (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Int -> String -> IO ()
changeVolume Int
1) [String
"A.wav", String
"B.wav", String
"C.wav", String
"D.wav", String
"E.wav", String
"F.wav", String
"G.wav", String
"H.wav", 
        String
"I.wav", String
"J.wav", String
"K.wav", String
"L.wav", String
"M.wav", String
"N.wav", String
"O.wav", String
"P.wav", String
"Q.wav", String
"R.wav", 
          String
"S.wav", String
"T.wav", String
"U.wav", String
"V.wav", String
"W.wav", String
"X.wav", String
"Y.wav", String
"Z.wav", String
"a.wav", String
"b.wav", String
"c.wav", 
            String
"d.wav", String
"e.wav", String
"f.wav"]
      String -> IO ()
putStrLn String
""
      String -> IO ()
putStrLn String
"Now you have changed (or left unchanged) the amplitudes for the sound representations for Ukrainian language. "
      String -> IO ()
putStrLn String
"Please, remember about responsible usage especially in case of processing the real voice sound samples! "
    (String
"-h":[String]
_)  -> do
      String -> IO ()
putStrLn String
"SYNOPSYS: "
      String -> IO ()
putStrLn String
"mmsyn7l -h    OR"
      String -> IO ()
putStrLn String
"mmsyn7l -v    OR"
      String -> IO ()
putStrLn String
"mmsyn7l -r [number-of-the-first-file-to-be-volume-adjusted [number-of-the-last-file-to-be-volume-adjusted]]   OR"
      String -> IO ()
putStrLn String
"mmsyn7l [list-of-needed-sounds-to-be-amplitude-modified]"
      String -> IO ()
putStrLn String
"\"-h\" prints this message."
      String -> IO ()
putStrLn String
"\"-v\" prints version number of the program."
      String -> IO ()
putStr String
"\"-r\" works with the \"result*.wav\" files in the current directory: it adjusts a volume for the sequence of them starting from the "
      String -> IO ()
putStr String
"first argument and ending with the second (if specified). If there is no first -- all such files are adjusted; if there is no second one -- "
      String -> IO ()
putStrLn String
"the files are adjusted to the last one. Count starts at 0. "
      String -> IO ()
putStr String
"[list-of-needed-sounds-to-be-amplitude-modified (if given) -- the program modifies the amplitudes in the interactive mode only for the "
      String -> IO ()
putStrLn String
"given sound representations. If not specified, the program modifies the amplitudes for all non-pause Ukrainian sounds representations."
      String -> IO ()
putStrLn String
""
    (String
"-v":[String]
_)  -> do
      String -> IO ()
putStrLn String
"mmsyn7l version: 0.9.0.0"
      String -> IO ()
putStrLn String
""
    (String
"-r":[String]
_)  -> [String] -> IO ()
adjustVolRes ([String] -> IO ()) -> ([String] -> [String]) -> [String] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop Int
1 ([String] -> IO ()) -> [String] -> IO ()
forall a b. (a -> b) -> a -> b
$ [String]
args
    [String]
_         ->  do
      String -> IO ()
putStrLn String
"Now you can change the amplitude of the needed sound representations of the Ukrainian sounds (or something similar). "
      String -> IO ()
putStrLn String
""
      let wss :: [String]
wss = String -> [String]
forall a. Read a => String -> a
read (String -> String
replaceP4 (String -> String) -> ([String] -> String) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall a. Show a => a -> String
show ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ (String -> [String]
forall a. Read a => String -> a
read  (String -> String
replaceP (String -> String) -> ([String] -> String) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall a. Show a => a -> String
show ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
1 ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
args)::[String]))::[String]
      (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (Int -> String -> IO ()
changeVolume Int
1) ([String] -> IO ()) -> ([String] -> [String]) -> [String] -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String -> [(String, String)] -> String -> String
forall a b. Ord a => b -> [(a, b)] -> a -> b
getBFstL' String
"0.wav" ([String] -> [String] -> [(String, String)]
forall a b. [a] -> [b] -> [(a, b)]
zip [String
"а",String
"б",String
"в",String
"г",String
"д",String
"дж",String
"дз",String
"е",String
"ж",String
"з",String
"и",String
"й",String
"к",String
"л",String
"м",String
"н",String
"о",String
"п",String
"р",String
"с",
        String
"сь",String
"т",String
"у",String
"ф",String
"х",String
"ц",String
"ць",String
"ч",String
"ш",String
"ь",String
"і",String
"ґ"] [String
"A.wav", String
"B.wav", String
"C.wav", String
"D.wav", String
"E.wav", String
"F.wav", String
"G.wav", String
"H.wav", String
"I.wav", String
"J.wav", 
          String
"K.wav", String
"L.wav", String
"M.wav", String
"N.wav", String
"O.wav", String
"P.wav", String
"Q.wav", String
"R.wav", String
"S.wav", String
"T.wav", String
"U.wav", String
"V.wav", String
"W.wav", String
"X.wav", String
"Y.wav", String
"Z.wav", 
            String
"a.wav", String
"b.wav", String
"c.wav", String
"d.wav", String
"e.wav", String
"f.wav"])) ([String] -> IO ()) -> [String] -> IO ()
forall a b. (a -> b) -> a -> b
$ [String]
wss
      String -> IO ()
putStrLn String
""
      String -> IO ()
putStrLn String
"Now you have changed (or left unchanged) the amplitudes for the needed sound representations for the Ukrainian language. "
      String -> IO ()
putStrLn String
"Please, remember about responsible usage especially in case of processing the real voice sound samples! "