-- | -- 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 first command line argument must be a -- positive 'Int' number. The rest is the Ukrainian text. The most interesting is the first line of the output. But other ones also are noteworthy. module Main where 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.Properties import Melodics.Ukrainian import System.Environment import Languages.Phonetic.Ukrainian.PrepareText import Languages.UniquenessPeriods.Vector.Data -- | Prints the rearrangements with the \"property\" information for the Ukrainian language text. The first command line argument must be a -- positive 'Int' number. The rest 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 arg0 = read (concat . take 1 $ args)::Int xs = unwords . drop 1 $ args printUniquenessG1List (I1 H) . fst . get22 . uniqNProperties2GN " 01-" K arg0 1 (V.singleton (oneProperty)) (uniquenessPeriodsVector3 " 01-" . aux0 . convertToProperUkrainian) (justOneValue2Property . diverse2) . unwords . prepareText $ xs