-- |
-- Module      :  Main
-- Copyright   :  (c) OleksandrZhabenko 2020
-- License     :  MIT
--
-- 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.
--

module Main where

import MMSyn7l (changeVolume)
import qualified Data.Vector as V
import CaseBi (getBFst')
import System.Environment (getArgs)
import 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 = do
  args <- getArgs
  if null args
    then do
      putStrLn "Now you can change the amplitude of the sound representations of the Ukrainian sounds (or something similar). "
      putStrLn ""
      mapM_ changeVolume ["A.wav", "B.wav", "C.wav", "D.wav", "E.wav", "F.wav", "G.wav", "H.wav",
        "I.wav", "J.wav", "K.wav", "L.wav", "M.wav", "N.wav", "O.wav", "P.wav", "Q.wav", "R.wav",
          "S.wav", "T.wav", "U.wav", "V.wav", "W.wav", "X.wav", "Y.wav", "Z.wav", "a.wav", "b.wav", "c.wav",
            "d.wav", "e.wav", "f.wav"]
      putStrLn ""
      putStrLn "Now you have changed (or left unchanged) the amplitudes for the sound representations for Ukrainian language. "
      putStrLn "Please, remember about responsible usage especially in case of processing the real voice sound samples! "
    else do
      putStrLn "Now you can change the amplitude of the needed sound representations of the Ukrainian sounds (or something similar). "
      putStrLn ""
      let xs = take 1 $ args
          rrs = show xs
          list = read (replaceP rrs)::[String]
          zss = read (replaceP4 . show $ list)::[String]
          wws = map (getBFst' ("0.wav", V.fromList . zip ["а","б","в","г","д","дж","дз","е","ж","з","и","й","к","л","м","н","о","п","р","с",
                       "сь","т","у","ф","х","ц","ць","ч","ш","ь","і","ґ"] $ ["A.wav", "B.wav", "C.wav", "D.wav", "E.wav", "F.wav", "G.wav", "H.wav",
                         "I.wav", "J.wav", "K.wav", "L.wav", "M.wav", "N.wav", "O.wav", "P.wav", "Q.wav", "R.wav",
                           "S.wav", "T.wav", "U.wav", "V.wav", "W.wav", "X.wav", "Y.wav", "Z.wav", "a.wav", "b.wav", "c.wav",
                             "d.wav", "e.wav", "f.wav"])) zss
      mapM_ changeVolume wws
      putStrLn ""
      putStrLn "Now you have changed (or left unchanged) the amplitudes for the needed sound representations for the Ukrainian language. "
      putStrLn "Please, remember about responsible usage especially in case of processing the real voice sound samples! "