-- |
-- Module      :  Main
-- Copyright   :  (c) OleksandrZhabenko 2020
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  olexandr543@yahoo.com
--
-- Helps to order the 7 or less Ukrainian words (or their concatenations) 
-- to obtain somewhat suitable for poetry or music text.

module Main where

import System.IO
import DobutokO.Poetry (uniq10Poetical4,uniq10Poetical5)
import System.Environment (getArgs)
import Melodics.Executable (recFileName, printInfoF, rawToSoundFile)
import Melodics.Ukrainian (appendS16LEFile, convertToProperUkrainian)
import EndOfExe (showE)
import Data.Maybe (fromJust,isJust)

-- | The first command line argument specifies which function to run. If given \"4\" it runs 'uniq10Poetical4', otherwise 'uniq10Poetical5'. The next 7 
-- are treated as the Ukrainian words to be ordered accordingly to the norm. For more information, please, refer to the documentation for the abovementioned 
-- functions. 
-- 
-- Afterwards, you can generate a sounding using 'workWithInput' in the \".wav\" format.
main :: IO ()
main = do
  args <- getArgs
  let arg0 = concat . take 1 $ args
      word1s = unwords . drop 1 $ args
  if arg0 == "4" then uniq10Poetical4 word1s else uniq10Poetical5 word1s
  putStrLn "What string would you like to record as a Ukrainian text sounding by mmsyn6ukr package? "
  str <- getLine
  nameAndRec str

-- | Is used to specify a name for the recorded sounding for the selected text and to record it.
nameAndRec :: String -> IO ()
nameAndRec str = do
  name <- recFileName
  withBinaryFile (name ++ ".raw") AppendMode (appendS16LEFile (convertToProperUkrainian str))
  putStrLn "The .raw file was created by the program. If there is SoX installed then it will run further. "
  let ts = showE "sox"
  if isJust ts
    then rawToSoundFile "" name (fromJust ts)
    else printInfoF