{-# OPTIONS_GHC -threaded -rtsopts #-} {-# OPTIONS_HADDOCK show-extensions #-} {-# LANGUAGE BangPatterns #-} -- | -- Module : Phonetic.Languages.General.Lines.Parsing -- 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 poetic one). module Phonetic.Languages.General.Lines.Parsing where import Phonetic.Languages.Array.General.PropertiesSyllablesG2 import Text.Read (readMaybe) import Data.Maybe (fromMaybe) import System.Environment (getArgs) import Data.Char (isDigit) import Phonetic.Languages.General.Lines import Data.Phonetic.Languages.PrepareText import Data.List (nub) import Data.Phonetic.Languages.Base import Data.Phonetic.Languages.Syllables import Phonetic.Languages.General.Simple.Parsing (innerProcessmentSimple) import CLI.Arguments import CLI.Arguments.Parsing import CLI.Arguments.Get import qualified Phonetic.Languages.Permutations.Represent as R -- | The function allows to rewrite the phonetic language 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 phonetic 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' -- -- (Taken from the https://hackage.haskell.org/package/phonetic-languages-simplified-examples-array-0.4.1.0/docs/Phonetic-Languages-Lines.html -- from the @phonetic-languages-simplified-examples-array@ package) 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.12.0.0 -- You can run the comparative mode on the up to 7 different files simultaneously. -- Besides, there is also a multiple properties mode. argsToLinePrepare :: (Double -> String -> MappingFunctionPL) -- ^ The function that is needed in the 'procRhythmicity23F' function. -- Specifies a way how the syllables represented in the phonetic language approach transforms into their durations and -- depends on two parameters. Is specific for every phonetic language and every representation, so must be provided -- by the user in every case. The example of the function can be found in the package @phonetic-languages-simplified-properties-array@. -> [MappingFunctionPL] -- ^ A list of 'PhoPaaW'-based different functions that specifies the syllables durations in the PhoPaaW mode, analogues of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The first one must be probably the most -- exact one and, therefore, the default one. -> IO () argsToLinePrepare h qs = do args50 <- getArgs let (argsA,argsB,argsC1,_) = args2Args31R fstCharsM specs1 args50 (prWP,args000) = takeBsR [("+p",1)] args50 pairwisePermutations = R.bTransform2Perms . getB "+p" $ prWP multiple | null argsC1 = 0 | otherwise = 1 args00 = snd . takeCs1R fstCharsM cSpecs1 $ args000 coeffs = readCF . concat . take 1 $ args00 -- The first command line argument. If not sure, pass just \"1_\". compare2 = oneA "+c" argsA if compare2 then do let args1 = snd . takeAsR [("+c",0)] . snd . takeBsR [("+g",1)] $ args00 (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) args0 = drop 5 args000 [fileGWrSys, controlFile, segmentRulesFile, concatenationsFileP, concatenationsFileA] = drop 1 . take 6 $ args00 -- To get the valid 'Concatenations' data. (wrs, ks, arr, gs, js, vs, ysss, zzzsss, xs, numericArgs, choices, numberI, file) <- files4Processment fileGWrSys controlFile segmentRulesFile concatenationsFileP concatenationsFileA multiple args0 generalProcessment pairwisePermutations (gr1,gr2) wrs ks arr gs h qs ysss zzzsss xs js vs {- the old arguments afterwards -} coeffs numericArgs choices numberI file -- | Is used internally in the 'argsToLinePrepare'. Nevertheless, can be used independently if the semantics -- of the arguments and their structure are preserved. files4Processment :: FilePath -- ^ With the 'GWritingSystemPRPLX' specifications only (see the gwrsysExample.txt file in the @phonetic-languages-phonetics-basics@ package as a schema); -> FilePath -- ^ With the 5 meaningful lines that are delimited with the \'~\' line one from another with the specifications for the possible allophones (if any), 'CharPhoneticClassification', white spaces information (two 'String's) and the 'String' of all the possible 'PLL' 'Char's; -> FilePath -- ^ With the 'SegmentRulesG' specifications only; -> FilePath -- ^ With the 'Concatenations' specifications only (see the data in the EnglishConcatenated.txt file in the @phonetic-languages-phonetics-basics@ package as a list of English equivalents of the needed 'String's). These are to be prepended to the next word. -> FilePath -- ^ With the 'Concatenations' specifications only (see the data in the EnglishConcatenated.txt file in the @phonetic-languages-phonetics-basics@ package as a list of English equivalents of the needed 'String's). These are to be appended to the previous word. -> Int -- ^ If equal to 1, then the function is intended to be used in the multiple properties mode, else it is intended to be used in the single property mode. -> [String] -- ^ List of other command line arguments -> IO (GWritingSystemPRPLX, [(Char, Char)], CharPhoneticClassification, SegmentRulesG, String, String, Concatenations, Concatenations, String, [String], [String], Int, FilePath) files4Processment fileGWrSys controlFile segmentRulesFile concatenationsFileP concatenationsFileA multiple args0 = do [controlConts, gwrsCnts, segmentData, concatenationsFileP1, concatenationsFileA1] <- mapM readFile [controlFile, fileGWrSys, segmentRulesFile, concatenationsFileP, concatenationsFileA] let (choices,args00) | multiple == 1 = (\(rs,js) -> (getC "+m" rs,js)) . takeCs1R fstCharsM cSpecs1 $ args0 | otherwise = (drop 1 . take 2 . snd . takeBsR [("+g",1)] $ args0,args0) !args1 = snd . takeBsR [("+g",1)] $ args00 !numericArgs = filter (all isDigit) args1 !numberI = fromMaybe 1 (readMaybe (concat . take 1 $ numericArgs)::Maybe Int) !file = concat . take 1 $ args0 (wrs, ks, arr, gs, js, vs, ysss, zzzsss, xs) = innerProcessmentSimple gwrsCnts controlConts segmentData concatenationsFileP1 concatenationsFileA1 in return (wrs, ks, arr, gs, js, vs, ysss, zzzsss, xs, 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