-- | -- Module : Main -- Copyright : (c) OleksandrZhabenko 2020 -- 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 @propertiesText@ 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 main :: IO () main = do args000 <- getArgs let !args00 = filter (/= "++B") args000 !lstW = any (== "++B") args000 !args0 = takeWhile (/= "+M") args00 `mappend` drop 1 (dropWhile (/= "-M") args00) !multiples = drop 1 . dropWhile (/= "+M") . takeWhile (/= "-M") $ args00 -- Arguments for multiple metrices 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 lstW multiples lInes coeffs file gzS printLine toOneLine choice else do contents <- readFile file fLinesIO 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 lstW multiples lInes coeffs file gzS printLine toOneLine choice else do contents <- readFile file fLinesIO contents