-- | -- 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. -- The most interesting is the first line of the output. But other ones also are noteworthy. {-# OPTIONS_GHC -threaded -rtsopts #-} {-# LANGUAGE BangPatterns #-} module Main where import Control.Parallel.Strategies import qualified Data.Vector as V import Data.Print.Info import String.Languages.UniquenessPeriods.Vector import Languages.UniquenessPeriods.Vector.General.Debug import Languages.UniquenessPeriods.Vector.PropertiesFuncRep import Languages.UniquenessPeriods.Vector.Properties import Languages.UniquenessPeriods.Vector.AuxiliaryG import Languages.UniquenessPeriods.Vector.StrictV import Languages.UniquenessPeriods.Vector.Filters (unsafeSwapVecIWithMaxI) import Text.Read (readMaybe) import Data.Maybe (fromMaybe) import System.Environment import Languages.Phonetic.Ukrainian.PrepareText import Languages.UniquenessPeriods.Vector.Data import Data.Char (isDigit) import Data.List (span,sort) import Languages.UniquenessPeriods.Vector.FuncRepRelated -- | 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\" and specifies, which property or properties is or are evaluated. -- The rest of the command line arguments is the Ukrainian text. -- -- The most interesting is the first line of the output. But other ones also are noteworthy. main :: IO () main = do args <- getArgs let (!numericArgs,!textualArgs) = span (all isDigit) args !arg0 = fromMaybe 1 $ (readMaybe (concat . take 1 $ numericArgs)::Maybe Int) !numberI = fromMaybe 1 $ (readMaybe (concat . drop 1 . take 2 $ numericArgs)::Maybe Int) !choice = concat . take 1 $ textualArgs !xs = concat . take 1 . prepareText . unwords . drop 1 $ textualArgs if compare numberI 2 == LT then printUniquenessG1ListStr (I1 H) . fst . get22 . uniqNProperties2GN " 01-" K arg0 1 (V.singleton (oneProperty)) (chooseMax choice) . unwords . prepareText $ xs else do let !intervalNmbrs = (\zs -> if null zs then V.singleton numberI else V.uniq . V.fromList $ zs) . sort . filter (<= numberI) . map (\t -> fromMaybe numberI $ (readMaybe t::Maybe Int)) . drop 2 $ numericArgs (!maxE,!minE) = runEval ((parTuple2 rpar rpar) ((\k -> if k == 0.0 then 1.0 else k) . (\rs -> if null rs then 0.0 else head rs) . firstFrom3 . maximumElBy 1 (V.singleton (oneProperty)) $ UL2 ([],uniquenessVariants2GN " 01-" (V.singleton (oneProperty)) (chooseMax choice) $ xs), (\k -> if k == 0.0 then 1.0 else k) . abs . (\rs -> if null rs then 0.0 else head rs) . firstFrom3 . maximumElBy 1 (V.singleton (oneProperty)) $ UL2 ([],uniquenessVariants2GN " 01-" (V.singleton (oneProperty)) (chooseMin choice) $ xs))) printUniquenessG1ListStr (I1 H) . fst . get22 . uniqNProperties2GN " 01-" K arg0 1 (V.singleton (unsafeSwapVecIWithMaxI minE maxE numberI intervalNmbrs . oneProperty)) (chooseMax choice) $ xs