-- | -- Module : Main -- Copyright : (c) OleksandrZhabenko 2020 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Prints the rearrangements with the \"property\" information for the Ukrainian language text. {-# OPTIONS_GHC -threaded -rtsopts #-} {-# LANGUAGE BangPatterns #-} module Main where import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2 import System.Environment (getArgs) import Phonetic.Languages.Simple -- | Prints the rearrangements with the \"property\" information for the Ukrainian language text. The first command line argument must be a -- positive 'Int' number and is a number of printed variants for the line (if they are present, otherwise just all possible variants are printed). -- The second one is the number of the intervals into which the all range of possible metrics values are divided. The next numeric arguments that must be -- sequenced without interruptions further are treated as the numbers of the intervals (counting is started from 1) which values are moved to the maximum -- values of the metrics interval using the 'unsafeSwapVecIWithMaxI' function. The first textual command line argument should be in the form either \"y0\", -- or \"0y\", or \"yy\", or \"y\", or \"02y\", or \"y2\", or \"03y\", or \"yy2\", or \"y3\", or some other variant and specifies, which property or properties is or are evaluated. -- The rest of the command line arguments is the Ukrainian text. Besides, you can use multiple metrices (no more than 5 different ones) together by -- using \"+M\" ... \"-M\" command line arguments. -- -- You can specify constraints according to the 'decodeLConstraints' function between +A and -A command line arguments. If so, the program will -- ask you additional question before proceeding. The \"+M\" ... \"-M\" and \"+A\" ... \"-A\" groups must not mutually intersect one another. main :: IO () main = do args00 <- getArgs let args0 = filter (\xs -> xs /= "++B" && xs /= "++L" && xs /= "++BL" && xs /= "++I" && xs /= "+U") args00 lstW = if any (\x -> x == "++B" || x == "++BL") args00 then True else False -- If one of the command line options is \"++B\" or \"++BL\" then the last word of the line will remain the last one. jstL0 = if any (\x -> x == "++L" || x == "++BL") args00 then True else False -- If one of the command line options is \"++L\" or \"++BL\" then the program outputs just lines without metrices values. nativeUkrainian = if any (== "+U") args00 then True else False -- If one of the command line options is \"+U\" then the informational messages are printed in Ukrainian, otherwise (the default behaviour) they are in English. toFileMode1 = concat . take 1 . drop 1 . dropWhile (/= "+IF") . takeWhile (/= "-IF") $ args0 -- Prints the last resulting line of the interactive mode processment (the last selected variant) to the file and also to the stdout. interactiveP = if any (\xs -> xs == "++I" || xs == "+IF") args00 then True else False -- If one of the command line options is \"++I\", or \"+IF\" then the program prints the variants and then prompts for the preferred variant. Afterwards, it prints just that variant alone. args01 = takeWhile (/= "+A") args0 `mappend` (drop 1 . dropWhile (/= "-A") $ args0) args02 | null toFileMode1 = filter (\xs -> xs /= "+IF" && xs /= "-IF") args01 | otherwise = takeWhile (/= "+IF") args01 `mappend` (drop 1 . dropWhile (/= "-IF") $ args01) args = takeWhile (/= "+M") args02 `mappend` (drop 1 . dropWhile (/= "-M") $ args02) coeffs = readCF . concat . take 1 $ args -- The first command line argument. if isPair coeffs then generalProc2G nativeUkrainian toFileMode1 interactiveP jstL0 args0 coeffs (drop 1 args) lstW else generalProc2G nativeUkrainian toFileMode1 interactiveP jstL0 args0 coeffs args lstW