{-# OPTIONS_GHC -threaded -rtsopts #-} {-# OPTIONS_HADDOCK show-extensions #-} {-# LANGUAGE BangPatterns #-} -- | -- Module : Main -- Copyright : (c) OleksandrZhabenko 2020-2022 -- 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 Data.List (nub) import Phonetic.Languages.Common import Phonetic.Languages.Lines import CLI.Arguments import CLI.Arguments.Parsing import CLI.Arguments.Get import Phonetic.Languages.Permutations.Represent import Phonetic.Languages.Coeffs -- | 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. -- -- @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. -- -- @ since 0.6.0.0 -- There is also the possibility to use \'line growing\' that is to use the 'prepereGrowTextMN' function -- with the 'Int' arguments from the first argument tuple. This allows to rearrange the given text and then -- to rewrite it. For this you need to specify somewhere (withot \"+c\" modifier) \"+g73\" or something similar. -- -- @ since 0.12.0.0 -- You can run the comparative mode on the up to 7 different files simultaneously. -- @ since 0.13.0.0 -- You can provide your own durations and use just pairwise permutations for quick (though not complete) evaluation. main :: IO () main = do args50 <- getArgs let (argsA,argsB,argsC,argss) = args2Args31R fstCharsM specs1 args50 pairwisePermutations = bTransform2Perms . getB "+p" $ argsB compare2 = oneA "+c" argsA fileDu = concat . getB "+d" $ argsB args00 = snd . takeBsR [("+p",1)] . snd . takeBsR [("+d",1)] $ args50 (choicesC,args0) = takeCs1R fstCharsM cSpecs1 args50 coeffs = readCF . concat . take 1 $ args0 -- The first command line argument. If not sure, pass just \"1_\". if compare2 then do let args1 = filter (/= "+c") args0 (args2,file3) | null args1 = ([],[]) | otherwise = (init . nub $ args1,last args1) if null file3 then do putStrLn "Please, specify the file to save the data to. " file3 <- getLine compareFilesToOneCommon args2 file3 else compareFilesToOneCommon args2 file3 else do let 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) if isPair coeffs then do let !numericArgs = filter (all isDigit) . drop 3 $ args0 !choices | oneC "+m" argsC = getC "+m" choicesC | otherwise = drop 2 . take 3 $ args0 !numberI = fromMaybe 1 (readMaybe (concat . take 1 $ numericArgs)::Maybe Int) !file = concat . drop 1 . take 2 $ args0 generalProcessment fileDu pairwisePermutations (gr1,gr2) coeffs numericArgs choices numberI file else do let !numericArgs = filter (all isDigit) . drop 2 $ args0 !choices | oneC "+m" argsC = getC "+m" choicesC | otherwise = drop 1 . take 2 $ args0 !numberI = fromMaybe 1 (readMaybe (concat . take 1 $ numericArgs)::Maybe Int) !file = concat . take 1 $ args0 generalProcessment fileDu pairwisePermutations (gr1,gr2) coeffs numericArgs choices numberI file aSpecs :: CLSpecifications aSpecs = [("+c",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