{-# 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' -- main :: IO () main = do args <- getArgs let coeffs = readCF . concat . take 1 $ args -- The first command line argument. If not sure, pass just \"1_\". if isPair coeffs then do let !numericArgs = filter (all isDigit) . drop 3 $ args !choice = concat . drop 2 . take 3 $ args !numberI = fromMaybe 1 (readMaybe (concat . take 1 $ numericArgs)::Maybe Int) !file = concat . drop 1 . take 2 $ args generalProcessment coeffs numericArgs choice numberI file else do let !numericArgs = filter (all isDigit) . drop 2 $ args !choice = concat . drop 1 . take 2 $ args !numberI = fromMaybe 1 (readMaybe (concat . take 1 $ numericArgs)::Maybe Int) !file = concat . take 1 $ args generalProcessment coeffs numericArgs choice numberI file