-- |
-- Module      :  MMSyn7s
-- Copyright   :  (c) OleksandrZhabenko 2020
-- License     :  MIT
-- 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'
  , show7s3
  -- *** Inner predicate (auxiliary)
  , eqSnds
) where

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

-- | Function takes Ukrainian text being written without quotes as command line arguments and prints the sorted list of the Ukrainian sounds representations 
-- that can be used further in mmsyn7 series of programs.
main7s :: IO ()
main7s = do
  texts <- getArgs
  putStrLn ""
  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 Ukranianian 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 in
  let uss = xss \\ (nubBy eqSnds xss) in let (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)