-- |
-- Module      :  MMSyn7s
-- Copyright   :  (c) OleksandrZhabenko 2020
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  olexandr543@yahoo.com
--
-- A program and a library that show a sorted list of the Ukrainian sounds 
-- representations that can be used by mmsyn7 series of programs.
--

module MMSyn7s (
  -- * Used in the program
  main7s
  -- * Library functions
  -- ** For the text as a whole object
  , show7s
  , show7s2
  -- ** For the text being treated as partial one
  , show7s'
  , show7s''
  , show7s'''
  , show7s3
  , show7s4
  , show7s5
  -- *** Inner predicate (auxiliary)
  , eqSnds
  -- *** Inner backward conversion function
  , listToString
) where

import qualified Data.Vector as V
import Data.List (sort, nub,(\\),nubBy)
import Melodics.Ukrainian (convertToProperUkrainian)
import System.Environment (getArgs)

-- | Function takes the first command line argument and (may be) a Ukrainian text being written without quotes as the next command line arguments
-- and prints the sorted list of the Ukrainian sounds representations that can be used further in mmsyn7 series of programs.
--
-- Depending on the first command line argument the program behaves as follows:
-- \"-h\" -- prints help and exits;
-- \"-v\" -- prints version number and exits;
-- \"1\"  -- prints the list of String being unique (without silence) and then the rest of the text with whitespaces and some phonetical conversions;
-- \"0\"  -- prints the list of String for the whole text.
-- All other variants of the beginning for the command line arguments are the same as \"0\" (the arguments are treated as a Ukrainian text
-- and processed as a whole one object).
main7s :: IO ()
main7s = do
  texts <- getArgs
  putStrLn ""
  let arg1 = concat . take 1 $ texts in
    case arg1 of
      "-h" -> do { putStrLn "mmsyn7s: "
                 ; putStrLn "SYNOPSYS: "
                 ; putStrLn "mmsyn7s -h      OR: "
                 ; putStrLn "mmsyn7s -v      OR: "
                 ; putStrLn "mmsyn7s 1 {Ukrainian text}     OR: "
                 ; putStrLn "mmsyn7s 0 {Ukrainian text}     OR: "
                 ; putStrLn "mmsyn7s {Ukrainian text}"
                 ; putStrLn "where the first one prints this help message; "
                 ; putStrLn "      the second one prints a version number; "
                 ; putStrLn "      the \"1\" option prints the list of String being unique (without silence) and then the rest of the text with whitespaces and some phonetical conversions; "
                 ; putStrLn "      the \"0\" option prints the list of String for the whole text"
                 ; putStrLn "      the other beginning is equivalent to the previous one behaviour."
                  }
      "-v" -> putStrLn "mmsyn7s: version 0.3.0.0"
      "1"  -> do { putStrLn . show . fst . show7s5 . unwords . drop 1 $ texts
                 ; putStrLn . snd . show7s5 . unwords . drop 1 $ texts }
      "0"  -> putStrLn . show7s2 . unwords . drop 1 $ texts
      _    -> putStrLn . show7s2 . unwords $ texts


-- | Function takes Ukrainian text being a @String@ and returns a sorted list of the Ukrainian sounds representations that can be used further in mmsyn7 series of
-- programs.
show7s :: String -> [String]
show7s xs = sort . nub . V.toList . V.filter (\x -> x /= "-" && x /= "1" && x /= "0") . convertToProperUkrainian $ xs

-- | Function takes Ukrainian text being a @String@ and returns a @String@ that shows a sorted list of the Ukrainian sounds representations that can be used further
-- in mmsyn7 series of programs.
show7s2 :: String -> String
show7s2 xs = show . sort . nub . V.toList . V.filter (\x -> x /= "-" && x /= "1" && x /= "0") . convertToProperUkrainian $ xs

-- | Function 'show7s3' takes Ukrainian text being a @String@ and returns a tuple, the first element of which is a list of Strings that correspond to the Ukrainian 
-- sounds representations that (except pauses) are unique and are not repeated starting from the beginning of the given text, and the second one is a remainder
-- list of Strings starting from the first duplicated non-silent Ukrainian sound representation.
show7s3 :: String -> ([String], [String])
show7s3 xs = show7s' . V.toList . convertToProperUkrainian $ xs

-- | Function 'eqSnds' compares two non-silent Strings representations for Ukrainian sounds by equality. If one of them is a representation for silence (e. g. pause),
-- then the predicate is @False@.
eqSnds :: String -> String -> Bool
eqSnds xs ys | xs `elem` ["-","0","1"] || ys `elem` ["-","0","1"] = False
             | otherwise = xs == ys

-- | Function @show7s'@ is auxiliary to the 'show7s3' and is used internally in the latter one.
show7s' :: [String] -> ([String],[String])
show7s' zss =
  let (xss, yss) = splitAt 68 zss
      uss = xss \\ (nubBy eqSnds xss)
      (wss, vss) = if null uss then (xss,[]) else (takeWhile (/= head uss) xss ++ head uss:(takeWhile (/= head uss) . tail . dropWhile (/= head uss) $ xss),
        dropWhile (/= head uss) . tail . dropWhile (/= head uss) $ xss) in
          (wss, vss ++ yss)

-- | The same as @show7s'@, but the first list in the tuple is filtered from the silent representations and is sorted not in the order of appearance in the text,
-- but in the ascending order.
show7s'' :: [String] -> ([String],[String])
show7s'' zss =
  let (xss, yss) = splitAt 68 zss
      uss = xss \\ (nubBy eqSnds xss)
      (wss,vss) = if null uss then (xss,[]) else (takeWhile (/= head uss) xss ++ head uss:(takeWhile (/= head uss) . tail . dropWhile (/= head uss) $ xss),
        dropWhile (/= head uss) . tail . dropWhile (/= head uss) $ xss) in
          (sort . filter (\x -> x /= "-" && x /= "1" && x /= "0") $ wss,vss ++ yss)

-- | Function 'show7s4' takes Ukrainian text being a @String@ and returns a tuple, the first element of which is a list of Strings that correspond to the Ukrainian 
-- sounds representations that (except pauses) are unique and are not repeated starting from the beginning of the given text (this list is filtered from 
-- the representations for the silence and then sorted in the ascending order), and the second one is a remainder
-- list of Strings starting from the first duplicated non-silent Ukrainian sound representation.
show7s4 :: String -> ([String], [String])
show7s4 xs = show7s'' . V.toList . convertToProperUkrainian $ xs

-- | Function 'listToString' converts the list of Strings being the sequential Ukrainian sounds representations into the Ukrainian text with whitespaces
-- (whitespaces are substituted instead of punctiuation symbols, too) and some phonetical conversions.
listToString :: [String] -> String
listToString xss =
  concatMap (\t ->
    case t of
      "0" -> " "
      "1" -> " "
      "-" -> " "
      x   -> x) xss

-- | The same as @show7s''@, but the second element in the resulting tuple is again the Ukrainian text with whitespaces (whitespaces are substituted
-- instead of punctiuation symbols, too) and some phonetical conversions.
show7s''' :: [String] -> ([String],String)
show7s''' zss =
  let (xss, yss) = splitAt 68 zss
      uss = xss \\ (nubBy eqSnds xss)
      (wss,vss) = if null uss then (xss,[]) else (takeWhile (/= head uss) xss ++ head uss:(takeWhile (/= head uss) . tail . dropWhile (/= head uss) $ xss),
        dropWhile (/= head uss) . tail . dropWhile (/= head uss) $ xss) in
          (sort . filter (\x -> x /= "-" && x /= "1" && x /= "0") $ wss, listToString $ vss ++ yss)

-- | Function 'show7s4' takes Ukrainian text being a @String@ and returns a tuple, the first element of which is a list of Strings that correspond to the Ukrainian 
-- sounds representations that (except pauses) are unique and are not repeated starting from the beginning of the given text (this list is filtered from 
-- the representations for the silence and then sorted in the ascending order), and the second one is a @String@ obtained from the remainder
-- list of Strings starting from the first duplicated non-silent Ukrainian sound representation with whitespaces (whitespaces are substituted
-- instead of punctiuation symbols, too) and some phonetical conversions. 
show7s5 :: String -> ([String], String)
show7s5 xs = show7s''' . V.toList . convertToProperUkrainian $ xs