-- | -- 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 , show7s6 , show7s7 , show7s8 -- *** Inner predicate (auxiliary) , eqSnds -- *** Inner backward conversion function , listToString -- *** Some statistic metrics , countSnds , sndsDensity ) where import Data.Char (isSpace) 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; -- -- \"-s\" -- prints a ratio of the total number of the Ukrainian sounds representations needed if every one is used just once -- (except silent) to the total number of the represenations if they are the same no matter where the corresponding sound is located; -- -- \"1\" -- prints the list of String being unique (without silence) and then the rest of the text with whitespaces and some phonetical conversions; -- -- \"-1\" -- prints the rest of the text after the first duplicated sound representation (except silent ones) including it with whitespaces and some phonetical conversions; -- -- \"0\" -- prints the list of String for the whole text. -- -- \"2\" -- prints the list of String for the whole text where every sound representation is unique; -- -- \"3\" -- prints the list of lists of Strings for the whole text, which shows what sound representations are needed to be -- created if every sound is unique; -- -- 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 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 -s OR: " ; putStrLn "mmsyn7s 1 {Ukrainian text} 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; " ; putStr " the third one prints a ratio of the total number of the Ukrainian sounds representations needed if every one is used just once " ; putStrLn "(except silent) to the total number of the represenations if they are the same no matter where the corresponding sound is located; " ; putStrLn " the \"1\" option prints the list of String being unique (without silence)" ; putStr " the \"-1\" option prints the rest of the text after the first duplicated sound representation (except silent ones) " ; putStrLn "including it with whitespaces and some phonetical conversions; " ; putStrLn " the \"0\" option prints the list of String for the whole text; " ; putStrLn " the \"2\" option prints the list of String for the whole text where every sound representation is unique; " ; putStr " the \"3\" option prints the list of lists of Strings for the whole text, which shows what sound representations are needed to be " ; putStrLn "created if every sound is unique; " ; putStrLn " the other beginning is equivalent to the previous one behaviour." } "-v" -> putStrLn "mmsyn7s: version 0.4.0.0" "-s" -> putStrLn . show . sndsDensity . unwords . drop 1 $ texts "1" -> putStrLn . show . fst . show7s5 . unwords . drop 1 $ texts "-1" -> putStrLn . snd . show7s5 . unwords . drop 1 $ texts "0" -> putStrLn . show7s2 . unwords . drop 1 $ texts "2" -> putStrLn . show . show7s8 . unwords . drop 1 $ texts "3" -> putStrLn . show . show7s6 . unwords . drop 1 $ texts _ -> putStrLn . show7s2 . unwords $ texts -- | Function takes a 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 a 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 a 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 a 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 'show7s5' takes a 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 -- | Function 'show7s6' takes a Ukrainian text being a @String@ and returns a list of lists of Strings, each latter one of which is obtained for the unique parts of -- the text from the Ukrainian sounds representations point of view. It can show how many and what sound representations are needed to be created to completely cover -- the given text providing all the needed sound parameters. show7s6 :: String -> [[String]] show7s6 t@(_:_) = (fst . show7s5 $ t):(show7s6 . snd . show7s5 $ t) show7s6 _ = [] -- | Function 'countSnds' counts total number of Strings in the list of list of Strings. It can be successfully used to count how many Ukrainian sounds representations -- are needed to be created to completely cover the given Ukrainian text. It can be used as a some statistics parameter for the text. countSnds :: [[String]] -> Int countSnds xss = sum . map length $ xss -- | Function 'sndsDensity' counts the ratio of total number of Ukrainian sounds representations (each of which gives an opportunity to use a unique ones) to the -- total number of the Ukrainian sounds representations if all the non-silent sounds in the text are the same for the one sound representation no matter where it is -- located. It can be used as a some statistics parameter for the text. The greater is the result, the greater number of the Ukrainian sounds representations -- is needed to be created for the text to create a unique sound for every location alongside the text. If it is equal to 1.0, then every non-silent sound -- in the text appears just once (if any). sndsDensity :: String -> Double sndsDensity xs | null . filter (not . isSpace) $ xs = 1.0 | otherwise = let x = countSnds . show7s6 $ xs y = length . show7s $ xs in fromIntegral x / fromIntegral y -- | Function 'show7s7' takes a Ukrainian text being a @String@ and returns a tuple of Strings. The first element is a String corresponding to the beginning of the -- text with only unique non-silent sounds representations, and the second one is the rest of the text. Each resulting String is modified so that it contains some -- phonetical conversions and (may be) changed punctuation and whitespaces. show7s7 :: String -> (String, String) show7s7 xs = (listToString . fst $ y, listToString . snd $ y) where y = show7s3 xs -- | Function 'show7s8' takes a Ukrainian text being a @String@ and returns a list of Strings. Each String contains only unique Ukrainian sounds representations so -- that being sequenced from head of the list they all correspond to the whole text. show7s8 :: String -> [String] show7s8 t@(_:_) = (fst . show7s7 $ t):(show7s8 . snd . show7s7 $ t) show7s8 _ = []