{-# LANGUAGE NoImplicitPrelude #-} -- | -- Module : Interpreter.ArgsConversion -- Copyright : (c) OleksandrZhabenko 2020-2023 -- License : MIT -- Stability : Experimental -- Maintainer : oleksandr.zhabenko@yahoo.com -- -- Prints the rearrangements with the \"property\" information for the Ukrainian language text. {-# OPTIONS_GHC -threaded -rtsopts #-} module Interpreter.ArgsConversion where import GHC.Base import Data.Tuple import GHC.List import Data.List (words) import GHC.Num import GHC.Real (rem) import Phladiprelio.Coeffs import Interpreter.StringConversion (readFileIfAny) import Data.Maybe (fromMaybe) import Text.Read (readMaybe) import CLI.Arguments import CLI.Arguments.Parsing import CLI.Arguments.Get import Phladiprelio.PermutationsRepresent argsConversion :: String -> ([Char], PermutationsType, Bool, Bool, [String], Coeffs2, Coeffs2, [String], Bool, Bool, Int, Int) argsConversion xs = let args50 = words xs (cfWX,args501) = takeBsR [("+x",1)] args50 coeffsWX = readCF . concat . getB "+x" $ cfWX -- The line argument that starts with \"+x\". (argsA,argsB,argsC1,argss) = args2Args31R fstCharsMA specs1 args501 pairwisePermutations = bTransform2Perms . getB "+p" $ argsB fileDu = concat . getB "+d" $ argsB -- Whether to use the own PhoPaaW weights (durations) from the file specified here. Is used only in @phonetic-languages-simplified-examples-array@ package lstW = listA ["+b","+bl"] argsA -- If one of the 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 line options is \"+l\" or \"+bl\" then the program outputs just lines without metrices values. nativeUkrainian = oneA "+u" argsA -- If one of the line options is \"+u\" then the informational messages are printed in Ukrainian, otherwise (the default behaviour) they are in English. -- Is used only in @phonetic-languages-simplified-examples-array@ package. verbose0 = concat . getB "+v" $ argsB -- ^ Whether to use more verbose output verbose = abs (fromMaybe 0 (readMaybe verbose0::Maybe Int) `rem` 4) 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 args0 = snd . takeAsR aSpecs . snd . takeBsR [("+d",1)] $ args501 args = snd . takeCs1R fstCharsMA [("+m",-1)] $ argss coeffs = readCF . concat . take 1 $ args -- The first line argument. in (fileDu,pairwisePermutations,nativeUkrainian,jstL0,args0,coeffs,coeffsWX,args,lstW,syllables,syllablesVs,verbose) aSpecs :: CLSpecifications aSpecs = zip ["+b","+l","+bl","+u"] . cycle $ [0] aSpcs :: [String] -> Args aSpcs = fst . takeAsR aSpecs cSpecs1MA :: CLSpecifications cSpecs1MA = [("+m",-1)] fstCharsMA :: FirstChars fstCharsMA = ('+','-') bSpecs :: CLSpecifications bSpecs = zip ["+d","+p","+s","+v"] . cycle $ [1] bSpcs :: [String] -> Args bSpcs = fst . takeBsR bSpecs specs1 :: CLSpecifications specs1 = aSpecs `mappend` bSpecs `mappend` cSpecs1MA