-- | -- Module : Main -- Copyright : (c) OleksandrZhabenko 2020-2022 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Analyzes a poetic text in Ukrainian, for every line prints statistic data and -- then for the whole poem prints the hypothesis evaluation information. -- -- To enable parallel computations (potentially, they can speed up the work), please, run the @propertiesTextG3@ executable with -- @+RTS -threaded -RTS@ command line options with possibly @-N@ option inside. -- {-# OPTIONS_GHC -threaded -rtsopts #-} {-# LANGUAGE BangPatterns, FlexibleContexts #-} module Main where import Phonetic.Languages.GetTextualInfo import Data.Maybe (fromMaybe) import Text.Read (readMaybe) import System.Environment (getArgs) import Data.Monoid (mappend) import Phonetic.Languages.Common import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2 import Languages.UniquenessPeriods.Array.Constraints.Encoded import CLI.Arguments import CLI.Arguments.Parsing import CLI.Arguments.Get import Phonetic.Languages.Permutations.Represent import Phonetic.Languages.Coeffs main :: IO () main = do args50 <- getArgs let (!argsA,!argsB,argsC,argss) = args2Args31R fstCharsM specs1 args50 !args0000 = snd . takeBsR [("+d",1),("+p",1)] $ args50 !pairwisePermutations = bTransform2Perms . getB "+p" $ argsB !fileDu = concat . getB "+d" $ argsB !growing = concat . getB "+g" $ argsB (!gr1,!gr2) | null growing = (0,0) | otherwise = let (nms,mms) = splitAt 1 growing nm = readMaybe nms::Maybe Int mm = readMaybe mms::Maybe Int in case (nm,mm) of (Just n4,Just m4) -> if (m4 `rem` 7) < (n4 `rem` 7) then (n4 `rem` 7 + 1, m4 `rem` 7 + 1) else (0,0) _ -> (0,0) !coeffsWX = readCF . concat . getB "+x" . fst . takeBsR [("+x",1)] $ args0000 -- The command line argument that starts with \"+x\". (!aspecs1,!args00) = takeAsR aSpecs . snd . takeBsR [("+g",1),("+x",1)] $ args0000 !lstW = oneA "+b" aspecs1 !syllablesStats = oneA "+s" aspecs1 (!mls,!args0) = takeCs1R fstCharsM cSpecs1 args00 !multiples = getC "+m" mls -- Arguments for multiple properties mode !args = filter (\xs -> all (/= ':') xs && all (/= '@') xs) args0 !coeffs = readCF . concat . take 1 $ args -- The first command line argument. If not sure, just enter \"1_\". !lInes = filter (any (== ':')) args0 !numbersJustPrint = filter (== "@n") args0 if isPair coeffs then do let !file = concat . drop 1 . take 2 $ args -- The second command line argument except those ones that are RTS arguments if null numbersJustPrint then do let !gzS = concat . take 1 . drop 2 $ args -- The third command line argument that controls the choice of the number of intervals !printLine = fromMaybe 0 (readMaybe (concat . take 1 . drop 3 $ args)::(Maybe Int)) -- The fourth command line argument except those ones that are RTS arguments. Set to 1 if you would like to print the current line within the information !toOneLine = fromMaybe 0 (readMaybe (concat . take 1 . drop 4 $ args)::(Maybe Int)) -- The fifth command line argument except those ones that are RTS arguments. Set to 1 if you would like to convert the text into one single line before applying to it the processment (it can be more conceptually consistent in such a case) !choice = concat . drop 5 . take 6 $ args -- The sixth command line argument that controls what properties are used. generalProc fileDu pairwisePermutations (gr1,gr2) lstW multiples lInes coeffs coeffsWX file gzS printLine toOneLine syllablesStats choice else do contents <- do (if file == "+i" then getContents else readFile file) fLinesNIO (if pairwisePermutations /= Phonetic.Languages.Permutations.Represent.P 0 then 10 else 7) contents else do let !file = concat . take 1 $ args if null numbersJustPrint then do let !gzS = concat . take 1 . drop 1 $ args !printLine = fromMaybe 0 (readMaybe (concat . take 1 . drop 2 $ args)::(Maybe Int)) !toOneLine = fromMaybe 0 (readMaybe (concat . take 1 . drop 3 $ args)::(Maybe Int)) !choice = concat . drop 4 . take 5 $ args generalProc fileDu pairwisePermutations (gr1,gr2) lstW multiples lInes coeffs coeffsWX file gzS printLine toOneLine syllablesStats choice else do contents <- do (if file == "+i" then getContents else readFile file) fLinesNIO (if pairwisePermutations /= Phonetic.Languages.Permutations.Represent.P 0 then 10 else 7) contents aSpecs :: CLSpecifications aSpecs = [("+b",0),("+s",0)] aSpcs :: [String] -> Args aSpcs = fst . takeAsR aSpecs cSpecs1 :: CLSpecifications cSpecs1 = [("+m",-1)] fstCharsM :: FirstChars fstCharsM = ('+','-') bSpecs :: CLSpecifications bSpecs = zip ["+d","+g","+p"] . cycle $ [1] bSpcs :: [String] -> Args bSpcs = fst . takeBsR bSpecs specs1 :: CLSpecifications specs1 = aSpecs `mappend` bSpecs `mappend` cSpecs1