{-# OPTIONS_GHC -threaded -rtsopts #-} {-# OPTIONS_HADDOCK show-extensions #-} {-# LANGUAGE BangPatterns #-} -- | -- Module : Main -- Copyright : (c) OleksandrZhabenko 2020 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Inspired by: https://functional-art.org/2020/papers/Poetry-OleksandrZhabenko.pdf from the https://functional-art.org/2020/performances ; -- Allows to rewrite the given text (usually a poetical one). module Main where import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2 import Text.Read (readMaybe) import Data.Maybe (fromMaybe) import System.Environment (getArgs) import Data.Char (isDigit) import Phonetic.Languages.Common import Phonetic.Languages.Lines -- | The function allows to rewrite the Ukrainian text in the file given as the first command line argument to a new file. In between, it is rewritten -- so that every last word on the lines is preserved at its position, and the rest of the line is rearranged using the specified other command line -- arguments. They are general for the whole program. The first command line argument is a FilePath to the file with a Ukrainian text to be rewritten. -- The second one is a variant of the \"properties\" used to evaluate the variants. -- The further command line arguments are: the number of the intervals and the numbers of the intervals -- that are swapped with the maximum one so that they are available for further usage by the program. See documentation for @uniqueness-periods-vector-filters@ -- package -- 'https://hackage.haskell.org/package/uniqueness-periods-vector-filters' -- -- @since 0.2.0.0 -- You can also run program in a \'comparative\' mode by specifying \"+C\" as one of the command line arguments and then -- three files -- the first two -- the existing ones with probably rewritten text by the program for different arguments -- and the third one is the resulting file. While running in such a mode the program outputs line-by-line the contents of -- the two first files and writes one of them (or an empty line if neither one) to the third file. main :: IO () main = do args0 <- getArgs let coeffs = readCF . concat . take 1 $ args0 -- The first command line argument. If not sure, pass just \"1_\". compare2 = (\xs -> if null xs then False else True) . filter (== "+C") $ args0 if compare2 then do let args1 = filter (/= "+C") args0 file1 = concat . take 1 $ args1 file2 = concat . drop 1 . take 2 $ args1 file3 = concat . drop 2 . take 3 $ args1 if file3 /= file1 && file3 /= file2 then compareFilesToOneCommon file1 file2 file3 else do putStrLn "You specified some files twice being in the comparative mode, the program has no well-defined behaviour in such a mode. " putStrLn "Please, run it again and specify the three different arguments with the first two being the existing files. " else do if isPair coeffs then do let !numericArgs = filter (all isDigit) . drop 3 $ args0 !choice = concat . drop 2 . take 3 $ args0 !numberI = fromMaybe 1 (readMaybe (concat . take 1 $ numericArgs)::Maybe Int) !file = concat . drop 1 . take 2 $ args0 generalProcessment coeffs numericArgs choice numberI file else do let !numericArgs = filter (all isDigit) . drop 2 $ args0 !choice = concat . drop 1 . take 2 $ args0 !numberI = fromMaybe 1 (readMaybe (concat . take 1 $ numericArgs)::Maybe Int) !file = concat . take 1 $ args0 generalProcessment coeffs numericArgs choice numberI file