module Melodics.Executable (
  circle
  , workWithInput
  , rawToSoundFile
  , printInfoF
  , recFileName
)
where
import Data.Char (isSpace, isControl)
import Data.Maybe (isJust,fromJust,fromMaybe)
import System.IO
import System.IO.Unsafe (unsafePerformIO)
import System.Process (callProcess)
import System.Directory (removeFile,findExecutable)
import Control.Exception (onException)
import EndOfExe (showE)
import Melodics.Ukrainian (appendS16LEFile, convertToProperUkrainian)
import UkrainianLControl
circle :: String -> IO ()
circle zs = onException (mapM_ (workWithInput zs) [1..]) (do
    putStr "Notice, there was (may be) CmdLineArgument exception. To avoid it, please, specify the command line argument (if needed) in the form \"ABC\""
    putStr " where A is either a letter \'f\', \'o\', \'w\' or a digit and B and C are both digits! The exception (may be) arose from "
    putStrLn $ "the command line arguments " ++ show zs ++ ". Please, check also whether the SoX was installed with the support for needed codec.")
workWithInput :: String -> Int -> IO ()
workWithInput zs j = do
  [nameSF,ys] <- nameAndControl zs [1,2]
  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"
  if isJust ts
    then rawToSoundFile zs nameSF (fromJust ts)
    else printInfoF
recFileName :: IO String
recFileName = do
  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 nameSF
getCtrl :: String -> IO String
getCtrl zs = do
  xs <- getLine
  let ys = take (nSymbols . fst . genControl $ zs) xs
  return ys
recFNAndCtrl :: String -> Int -> IO String
recFNAndCtrl zs n
  | odd n = recFileName
  | otherwise = getCtrl zs
nameAndControl :: String -> [Int] -> IO [String]
nameAndControl zs = mapM (recFNAndCtrl zs)
rawToSoundFile :: String -> String -> FilePath -> IO ()
rawToSoundFile zs nameSF executablePath
  | null zs = do
     callProcess executablePath ["-r22050","-c1","-L","-esigned-integer","-b16", nameSF ++ ".raw", nameSF ++ ".wav"]
     removeFile $ nameSF ++ ".raw"
  | otherwise = do
     let ws = snd . genControl $ zs
     callProcess executablePath ["-r22050","-c1","-L","-esigned-integer","-b16", nameSF ++ ".raw", fst ws, nameSF ++ snd ws]
     removeFile $ nameSF ++ ".raw"
printInfoF :: IO ()
printInfoF = 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."