-- | -- Module : Main -- Copyright : (c) OleksandrZhabenko 2020-2022 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Prints the rearrangements with the \"property\" information for the Ukrainian language text. {-# OPTIONS_GHC -threaded -rtsopts #-} module Main where import System.Environment (getArgs) import Phonetic.Languages.Simple import Interpreter.StringConversion (readFileIfAny) import Data.Maybe (fromMaybe) import Text.Read (readMaybe) import CLI.Arguments import CLI.Arguments.Parsing import CLI.Arguments.Get import Phonetic.Languages.Permutations.Represent import Phonetic.Languages.Coeffs -- | Prints the rearrangements with the \"property\" information for the Ukrainian language text. main :: IO () main = do args50 <- getArgs let (cfWX,args501) = takeBsR [("+x",1)] args50 coeffsWX = readCF . concat . getB "+x" $ cfWX -- The command line argument that starts with \"+x\". (argsA,argsB,argsC1,argss) = args2Args31R fstCharsMA specs1 args501 (argsC2,arg2ss) = takeCs1R fstCharsT cSpecs1T argss pairwisePermutations = bTransform2Perms . getB "+p" $ argsB fileDu = concat . getB "+d" $ argsB recursiveMode = oneA "+r" argsA -- Specifies whether to use the interactive recursive mode lstW = listA ["+b","+bl"] argsA -- If one of the command line options is \"+b\" or \"+bl\" then the last word of the line will remain the last one. jstL0 = listA ["+l","+bl"] argsA -- If one of the command line options is \"+l\" or \"+bl\" then the program outputs just lines without metrices values. nativeUkrainian = oneA "+u" argsA -- 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. verbose0 = concat . getB "+v" $ argsB -- ^ Whether to use more verbose output verbose = abs (fromMaybe 0 (readMaybe verbose0::Maybe Int) `rem` 4) toFileMode1 = concat . getB "+f" $ argsB -- Prints the last resulting line of the interactive mode processment (the last selected variant) to the file and also to the stdout. interactiveP = recursiveMode || oneA "+i" argsA || oneB "+f" argsB -- If one of the command line options is \"+i\", or \"+f\" then the program prints the variants and then prompts for the preferred variant. Afterwards, it prints just that variant alone. textProcessmentFssFs = drop 1 . getC "+t" $ argsC2 syllables = oneB "+s" argsB -- Whether to use syllable durations, up to 9 different sets. syllablesVs = max 1 . fromMaybe 1 $ (readMaybe (concat . getB "+s" $ argsB)::Maybe Int) -- Number of sets of syllable durations to be used textProcessment0 | null . concat . getB "+t" . fst . takeBsR [("+t",1)] $ argss = [] | otherwise = "+t" `mappend` (concat . getB "+t" . fst . takeBsR [("+t",1)] $ argss) textProcessment1 = fromMaybe 70 (readMaybe (drop 2 textProcessment0)::Maybe Int) args0 = snd . takeAsR aSpecs . snd . takeBsR [("+d",1)] $ args501 let args = snd . takeCs1R fstCharsMA [("+m",-1)] . snd . takeBsR [("+f",1)] . snd . takeCs1R fstCharsMA [("+a",-1)] $ arg2ss coeffs = readCF . concat . take 1 $ args -- The first command line argument. textProcessmentFss0 <- mapM (readFileIfAny) textProcessmentFssFs print verbose let textProcessmentFss = filter (not . null) textProcessmentFss0 if isPair coeffs then generalProc3G fileDu pairwisePermutations textProcessmentFss textProcessment0 textProcessment1 recursiveMode nativeUkrainian toFileMode1 interactiveP jstL0 args0 coeffs coeffsWX (drop 1 args) lstW syllables syllablesVs verbose else generalProc3G fileDu pairwisePermutations textProcessmentFss textProcessment0 textProcessment1 recursiveMode nativeUkrainian toFileMode1 interactiveP jstL0 args0 coeffs coeffsWX args lstW syllables syllablesVs verbose aSpecs :: CLSpecifications aSpecs = zip ["+r","+b","+l","+bl","+i","+u"] . cycle $ [0] aSpcs :: [String] -> Args aSpcs = fst . takeAsR aSpecs cSpecs1MA :: CLSpecifications cSpecs1MA = zip ["+m","+a"] . cycle $ [-1] fstCharsMA :: FirstChars fstCharsMA = ('+','-') cSpecs1T :: CLSpecifications cSpecs1T = [("+t",-1)] fstCharsT :: FirstChars fstCharsT = ('+','^') bSpecs :: CLSpecifications bSpecs = zip ["+d","+f","+p","+s","+v"] . cycle $ [1] bSpcs :: [String] -> Args bSpcs = fst . takeBsR bSpecs specs1 :: CLSpecifications specs1 = aSpecs `mappend` bSpecs `mappend` cSpecs1MA