-- |
-- Module      :  Main
-- Copyright   :  (c) OleksandrZhabenko 2019
-- License     :  MIT
--
-- Maintainer  :  olexandr543@yahoo.com
--
-- A program and a library that can be used as a musical instrument synthesizer or for Ukrainian speech synthesis 
-- especially for poets, translators and writers. 
--

module Main (
  main,
  -- * Control the program
  genControl,
  -- * Security and Limits
  nSymbols
) where

import Data.Char (isSpace, isControl,isDigit)
import Data.Maybe (isJust,fromJust)
import System.IO
import System.IO.Unsafe (unsafePerformIO)
import System.Environment (getArgs)
import System.Process (callProcess)
import System.Directory (removeFile,findExecutable)
import qualified Data.Vector as V
import Control.Exception (bracketOnError)
import CaseBi (getBFst')
import EndOfExe (showE)
import Melodics.Ukrainian (appendS16LEFile, convertToProperUkrainian)

{-
-- Inspired by: https://mail.haskell.org/pipermail/beginners/2011-October/008649.html
-}

-- | The function creates a raw PCM sound file with bitrate 22050 Hz 1 mono channel 16-bit signed-integer encoding 
-- and tries to automatically convert it to the .wav, .ogg, or .flac file with the same parameters specified by the first command line argument
-- (for more details see: 'genControl' function) using the system binary SoX. 
-- If it is not installed properly, the program makes ending informational message for the user. 
-- 
-- Command line argument is described in more details in the documentation for the 'Melodics.Ukrainian.nSymbols' function. 
-- 
-- * Notification.
-- 
-- Please, notice that successful usage of the SoX installed in the system prior to the @mmsyn6ukr@ leads to approximately doubling 
-- the size of used space in the storage for the resulting files because it adds a header to the .raw file and writes down additionally 
-- the raw data to form a .wav file. Also notice that the size of the largest data file representing a symbol or their combination is 6792 bytes (with 44-byte 
-- header included). So, if you expect to create sounding for @n@ symbols of the Ukrainian text, provide at least @2 * (6792 - 44) * n + 44 = 13496 * n + 44@ (bytes) 
-- of the additional space in the storage (in reality it can occupy much less because other data files are less in size). Afterwards, the program deletes 
-- the .raw file (this will approximately halve the occupied space by the resulting file) and you can manually compress the .wav file 
-- (e. g. FLAC compression with the best ratio gives approximately halving the size. Therefore, the resulting file 
-- for the @mmsyn6ukr@ executable run prior to such operations without command line arguments is expected to be less than about @10^7@ bytes that is about 100 MB 
-- (for 31416 symbols Ukrainian text)). The best comression is with the .ogg files, but they can lose some quality so be careful if you need it.
main :: IO ()
main = bracketOnError (do
  args <- getArgs
  putStrLn "Please, specify the name of the resulting sound file! Please, do NOT use '}' character and space or control characters!"
  nameOfSoundFile <- getLine
  let nameSF = filter (\x -> not (isSpace x) && not (isControl x) && x /= '}') nameOfSoundFile
  return (args, nameSF)) (\(args, nameSF) -> do
    putStr $ "Exception: please, specify the command line argument (if needed) in the form \"ABC\""
    putStrLn $ " where A is either a letter \'f\', \'o\', \'w\' or a digit and B and C are both digits! "
      ++ show args ++ " for the file: " ++ show nameSF) (\(args, nameSF) -> do
         xs <- getContents
         let ys = take (nSymbols (let zs = take 1 args in if null zs then [] else fst . genControl . head $ zs)) xs in
             withBinaryFile (nameSF ++ ".raw") AppendMode (appendS16LEFile (convertToProperUkrainian ys))
         putStrLn "The .raw file was created by the program. If there is SoX installed then it will run further. "
         let ts = showE "sox" in if isJust ts
                      then do
                             if null args
                               then do
                                  callProcess (fromJust . unsafePerformIO . findExecutable . fromJust $ ts) ["-r22050","-c1","-L","-esigned-integer","-b16", nameSF ++ ".raw", nameSF ++ ".wav"]
                                  removeFile $ nameSF ++ ".raw"
                               else do
                                  let ws = snd . genControl . head . take 1 $ args in callProcess (fromJust . unsafePerformIO . findExecutable . fromJust $ ts)
                                    ["-r22050","-c1","-L","-esigned-integer","-b16", nameSF ++ ".raw", fst ws, nameSF ++ snd ws]
                                  removeFile $ nameSF ++ ".raw"
                      else do
                         putStr "You have a resulting file in a raw PCM format with bitrate 22050 Hz and 1 channel (mono) in the .raw format. "
                         putStr "You can further process it by yourself manually, otherwise, please, install FFMpeg or LibAV executables in the directory mentioned in the variable PATH"
                         putStrLn " and then run: "
                         putStrLn "\"name_of_FFMpeg_or_LibAV_executable\" -f s16le -acodec pcm_s16le -ac 1 -ar 22050 -i \"name_Of_the_sound_file\" \"the_same_name_without_.raw_ending_and_with_.wav_ending\""
                         putStrLn ""
                         putStrLn "OR you can install SoX executable in the directory mentioned in the variable PATH and then run: "
                         putStrLn "\"Path_to_the_SoX_executable\" -b16 -r22050 -c1 -e signed-integer -L \"name_of_the_file_in_raw_format_with_new._prefix\" \"name_of_the_file_in_raw_format_with_new._prefix\" in the terminal.")

-- | Function that converts the first command line argument given, which is a digit in the range @[0..9]@ 
-- (providing an ascending approximately exponential scale with a basis of 10 starting from 2 and ending at 1000000001), 
-- to the upper bound of number of symbols that the 'Main.main' function of the @mmsyn6ukr@ executable reads from the 'System.IO.stdin' for sounding.
-- The default value (no input) is 31416. If there is another first command line argument then the program 
-- terminates with the error and informational message. Using the command line argument is done for the security reasons: 
-- because of performative writing to the resulting file(s) there is a need to limit the used memory. For most cases it is
-- enough to use the default value. If you have enough resources and a large Ukrainian text amount then specify the higher values 
-- (5 or a greater one). 
nSymbols :: String -> Int
nSymbols xs | null xs = 31416::Int
            | otherwise = getBFst' (31416::Int, V.generate 10 (\n -> (n, (10^n + 1)::Int))) (let temp = read xs::Int in if temp <= 9 && temp >= 0
                            then temp
                            else error "Please, specify a digit as a command line argument for the program!")

-- | Function that prepares arguments for the controlling functions for the executable @mmsyn6ukr@. It takes a first command line argument and makes 
-- an analysis to produce a set of String. The first resulting String is an argument to 'nSymbols' function, the first in the inner tuple is an argument
-- to the compression level for the comressed formats and the last one is the resulting file extension. The default value (no command line arguments) is
-- @("", ("", ".wav"))@. Please, specify the command line argument (if needed) in the form \"ABC\""
-- where A is either a letter \'f\', \'o\', \'w\' or a digit and B and C are both digits (or something equivalent, see below). 
-- 
-- Their meaning:
-- 
-- A:
-- 
-- \'f\' -> native FLAC format with compression from 0 (least) to 8 (best compression ratio) specified by the third characters; \'9\' is equivalent to \'8\'.
-- \'o\' -> Ogg Vorbis format with compression from -1 (best) to 10 (least) specified by the characters after the first two characters;
-- \'w\' -> WAV format with two options for bitrate - 11025 if the third character is less than 5 and otherwise 22050 (the default one also for no command line arguments).
-- If A is a digit, then it is used accordingly to 'nSymbols' function and SoX (if properly installed) converts the .raw file to the default .wav with 22050 Hz bitrate.
-- 
-- For more information, please, see the sox manuals (e. g. for @soxformat@).
genControl :: String -> (String, (String, String))
genControl (x:xs) | x == 'f' = ([head xs], ("-C" ++ (if tail xs < "9" then tail xs else "8"), ".flac"))
                  | x == 'o' = ([head xs], ("-C" ++ (if (compare (tail xs) "10" /= GT) && (compare (tail xs) "-1" == GT) then tail xs else "-1"), ".ogg"))
                  | x == 'w' = ([head xs], ("-r" ++ (if (compare (tail xs) "4" /= GT) then "11025" else "22050"), ".wav"))
                  | isDigit x = ([x], ("", ".wav"))
                  | otherwise = ("", ("", ".wav"))
genControl [] = ("", ("", ".wav"))