{-# OPTIONS_GHC -threaded -rtsopts #-} {-# OPTIONS_HADDOCK show-extensions #-} {-# LANGUAGE BangPatterns #-} -- | -- Module : Phonetic.Languages.General.Simple -- Copyright : (c) OleksandrZhabenko 2020-2022 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Library module that contains functions earlier used by the lineVariantsG3 -- executable for the Ukrainian language (see: https://hackage.haskell.org/package/phonetic-languages-simplified-examples-array). -- Is rewritten from the Phonetic.Languages.Simple module from the -- @phonetic-languages-simplified-examples-array@ package. module Phonetic.Languages.General.Simple where import Phonetic.Languages.General.Parsing import Numeric import Languages.UniquenessPeriods.Array.Constraints.Encoded (decodeLConstraints,readMaybeECG) import GHC.Arr import Phonetic.Languages.Simplified.DataG.Base import Phonetic.Languages.Basis import Phonetic.Languages.Simplified.DataG.Partir import Phonetic.Languages.Array.General.PropertiesSyllablesG2 import Phonetic.Languages.Filters (unsafeSwapVecIWithMaxI) import Phonetic.Languages.Simplified.StrictVG.Base import Data.Phonetic.Languages.Base import Data.Phonetic.Languages.PrepareText import Data.Char (isDigit,isAlpha,isLetter) import qualified Data.List as L (span,sort,zip4,isPrefixOf,nub) import Phonetic.Languages.Simplified.Array.General.FuncRep2RelatedG2 import Phonetic.Languages.Permutations.Arr import Phonetic.Languages.Permutations.ArrMini import Phonetic.Languages.Permutations.ArrMini1 import Data.SubG hiding (takeWhile,dropWhile) import Data.Maybe import Data.MinMax.Preconditions import Text.Read (readMaybe) import Phonetic.Languages.General.DeEnCoding import Phonetic.Languages.General.SimpleConstraints import Phonetic.Languages.General.Common import Data.Phonetic.Languages.Syllables import Interpreter.StringConversion import qualified Phonetic.Languages.Permutations.Represent as R forMultiplePropertiesF :: [String] -> [(String,[String])] forMultiplePropertiesF (xs:xss) | any isAlpha xs = (xs,yss):forMultiplePropertiesF zss | otherwise = [] where l = length . takeWhile (all isDigit) $ xss (yss,zss) = splitAt l xss forMultiplePropertiesF _ = [] {-| Is used to organize the most complex processment -- for multiple sources and probably recursively. -} generalProc3G :: R.PermutationsType -- ^ Whether to use just one of the express permutations, or the full universal set. -> (String -> Bool) -- ^ The predicate that checks whether the given argument is not a phonetic language word in the representation. -> [String] -> String -- ^ If empty, the function is just 'generalProc2G' with the arguments starting from the first 'Bool' here. -> Int -> GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text. -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon -- (e. g. allophones). Must be sorted in the ascending order to be used correctly. -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly. -> SegmentRulesG -> String -> String -> (Double -> String -> ([[[PRS]]] -> [[Double]])) -- ^ 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@. -> [([[[PRS]]] -> [[Double]])] -- ^ A list of 4 different functions that specifies the syllables durations, analogues of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most -- exact one and, therefore, the default one. -> Concatenations -- ^ Data used to concatenate (prepend) the basic grammar preserving words and word sequences to the next word to -- leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to. -> Concatenations -- ^ Data used to concatenate (append) the basic grammar preserving words and word sequences to the next word to -- leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to. -> String -> FilePath -> Bool -- ^ Whether to run in the recursive mode. -> Bool -> Bool -> [String] -> Coeffs2 -- ^ This value is used when property choice is NOT from the \"w\" or \"x\" lines. -> Coeffs2 -- ^ This value is used when property choice is from the \"w\" or \"x\" lines. -> [String] -> Bool -> IO () generalProc3G pairwisePermutations p textProcessmentFss textProcessment0 textProcessment1 wrs ks arr gs js vs h qs ysss zzzsss ws toFile1 recursiveMode interactive jstL0 args0 coeffs coeffsWX args lstW2 | null textProcessment0 = generalProc2G pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws toFile1 recursiveMode interactive jstL0 args0 coeffs coeffsWX args lstW2 | null textProcessmentFss = mapM_ (\_ -> do -- interactive training mode putStrLn . messageInfo $ 7 lineA <- getLine generalProc2G pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws toFile1 recursiveMode interactive jstL0 (fullArgsConvertTextualSimple p lineA args0) coeffs coeffsWX (fullArgsConvertTextualSimple p lineA args) lstW2) [0..] | otherwise = mapM_ (\js -> do let !kss = lines js if pairwisePermutations /= R.P 0 then do let !wss | textProcessment1 `elem` [10,20,30,40,50,60,70,80,90] = kss | otherwise = prepareTuneTextMN m 1 ysss zzzsss ws . unwords $ kss mapM_ (\tss -> generalProc2G pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws toFile1 recursiveMode interactive jstL0 (fullArgsConvertTextualSimple p tss args0) coeffs coeffsWX (fullArgsConvertTextualSimple p tss args) lstW2) wss else do let !wss | textProcessment1 `elem` [20,30,40,50,60,70] = kss | otherwise = prepareTuneTextMN (if textProcessment1 `elem` [21,31,41,51,61] then m else 7) 1 ysss zzzsss ws . unwords $ kss mapM_ (\tss -> generalProc2G pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws toFile1 recursiveMode interactive jstL0 (fullArgsConvertTextualSimple p tss args0) coeffs coeffsWX (fullArgsConvertTextualSimple p tss args) lstW2) wss) textProcessmentFss where m = if textProcessment1 == 10 || textProcessment1 == 11 then 10 else quot textProcessment1 10 -- | Is used to do general processment. generalProc2G :: R.PermutationsType -- ^ Whether to use just one of the express permutations, or the full universal set. -> GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text. -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon -- (e. g. allophones). Must be sorted in the ascending order to be used correctly. -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly. -> SegmentRulesG -> String -> String -> (Double -> String -> ([[[PRS]]] -> [[Double]])) -- ^ 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@. -> [([[[PRS]]] -> [[Double]])] -- ^ A list of 4 different functions that specifies the syllables durations, analogues of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most -- exact one and, therefore, the default one. -> Concatenations -- ^ Data used to concatenate (prepend) the basic grammar preserving words and word sequences to the next word to -- leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to. -> Concatenations -- ^ Data used to concatenate (append) the basic grammar preserving words and word sequences to the next word to -- leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to. -> String -> FilePath -> Bool -- ^ Whether to run in the recursive mode. -> Bool -> Bool -> [String] -> Coeffs2 -- ^ This value is used when property choice is NOT from the \"w\" or \"x\" lines. -> Coeffs2 -- ^ This value is used when property choice is from the \"w\" or \"x\" lines. -> [String] -> Bool -> IO () generalProc2G pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws toFile1 recursiveMode interactive jstL0 args0 coeffs coeffsWX args lstW2 | variations args = do let !zsss = transformToVariations args variantsG <- mapM (\xss -> generalProc2 pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX xss lstW2) zsss if interactive then do (if recursiveMode then interactivePrintResultRecursive pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX id variantsG args lstW2 else interactivePrintResult id variantsG) >>= \rs -> case toFile1 of "" -> return () ~fileName -> appendFile fileName (rs `mappend` newLineEnding) else return () | otherwise = generalProc2 pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX args lstW2 >>= \rs -> case toFile1 of "" -> return () ~fileName -> appendFile fileName (rs `mappend` newLineEnding) -- | generalProc2 :: R.PermutationsType -- ^ Whether to use just one of the express permutations, or the full universal set. -> GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text. -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon -- (e. g. allophones). Must be sorted in the ascending order to be used correctly. -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly. -> SegmentRulesG -> String -> String -> (Double -> String -> ([[[PRS]]] -> [[Double]])) -- ^ 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@. -> [([[[PRS]]] -> [[Double]])] -- ^ A list of 4 different functions that specifies the syllables durations, analogues of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most -- exact one and, therefore, the default one. -> Concatenations -- ^ Data used to concatenate (prepend) the basic grammar preserving words and word sequences to the next word to -- leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to. -> Concatenations -- ^ Data used to concatenate (append) the basic grammar preserving words and word sequences to the next word to -- leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to. -> String -> Bool -- ^ Whether to run in the recursive mode. -> Bool -> Bool -> [String] -> Coeffs2 -- ^ This value is used when property choice is NOT from the \"w\" or \"x\" lines. -> Coeffs2 -- ^ This value is used when property choice is from the \"w\" or \"x\" lines. -> [String] -> Bool -> IO String generalProc2 pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX args lstW2 = do let !argMss = take 5 . filter (not . null) . forMultiplePropertiesF . drop 1 . dropWhile (/= "+m") . takeWhile (/= "-m") $ args0 if null argMss then do let (!numericArgs,!textualArgs) = L.span (all isDigit) $ args !xs = concat . take 1 . prepareTuneTextMN (if pairwisePermutations /= R.P 0 then 10 else 7) 1 ysss zzzsss ws . unwords . drop 1 $ textualArgs !l = length . words $ xs !argCs = catMaybes (fmap (readMaybeECG (l - 1)) . (showB l lstW2:) . drop 1 . dropWhile (/= "+a") . takeWhile (/= "-a") $ args0) !arg0 = concat . take 1 $ numericArgs !numberI = fromMaybe 1 $ (readMaybe (concat . drop 1 . take 2 $ numericArgs)::Maybe Int) !choice = concat . take 1 $ textualArgs !intervalNmbrs = (\zs -> if null zs then [numberI] else L.nub zs) . L.sort . filter (<= numberI) . map (\t -> fromMaybe numberI $ (readMaybe t::Maybe Int)) . drop 2 $ numericArgs if compare l 2 == LT then let !frep20 = chooseMax wrs ks arr gs js vs id h coeffs qs choice in let !wwss = (:[]) . toResultR frep20 $ xs in if recursiveMode then interactivePrintResultRecursive pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX line wwss args lstW2 else if interactive then interactivePrintResult line wwss else print1el jstL0 choice wwss else do let !subs = subG (' ':js `mappend` vs) xs if null argCs then let !perms = genPermutationsL l in do temp <- generalProcMs wrs ks arr gs js vs h qs coeffs coeffsWX perms subs (intervalNmbrs, arg0, numberI, choice) if recursiveMode then interactivePrintResultRecursive pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX line temp args lstW2 else if interactive then interactivePrintResult line temp else print1el jstL0 choice temp else do correct <- printWarning xs if correct == "n" then putStrLn (messageInfo 1) >> return "" -- for the multiple variations mode (with curly brackets and slash in the text) the program does not stop here, but the variation is made empty and is proposed further as a variant. else let !perms = decodeLConstraints argCs . genPermutationsL $ l in do temp <- generalProcMs wrs ks arr gs js vs h qs coeffs coeffsWX perms subs (intervalNmbrs, arg0, numberI, choice) if recursiveMode then interactivePrintResultRecursive pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX line temp args lstW2 else if interactive then interactivePrintResult line temp else print1el jstL0 choice temp else do let !choices = map fst argMss !numericArgss = map snd argMss !arg0s = map (concat . take 1) numericArgss !numberIs = map (\ts -> fromMaybe 1 $ (readMaybe (concat . drop 1 . take 2 $ ts)::Maybe Int)) numericArgss !intervalNmbrss = map (\us -> let !numberI = fromMaybe 1 $ (readMaybe (concat . drop 1 . take 2 $ us)::Maybe Int) in (\zs -> if null zs then [numberI] else L.nub zs) . L.sort . filter (<= numberI) . map (\t -> fromMaybe numberI $ (readMaybe t::Maybe Int)) . drop 2 $ us) $ numericArgss !argsZipped = L.zip4 intervalNmbrss arg0s numberIs choices !xs = concat . take 1 . prepareTuneTextMN (if pairwisePermutations /= R.P 0 then 10 else 7) 1 ysss zzzsss ws . unwords $ args !l = length . words $ xs !argCs = catMaybes (fmap (readMaybeECG (l - 1)) . (showB l lstW2:) . drop 1 . dropWhile (/= "+a") . takeWhile (/= "-a") $ args0) if compare l 2 == LT then let !frep20 = chooseMax wrs ks arr gs js vs id h coeffs qs (concat . take 1 $ choices) in let !wwss = (:[]) . toResultR frep20 $ xs in if recursiveMode then interactivePrintResultRecursive pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX line wwss args lstW2 else if interactive then interactivePrintResult line wwss else print1el jstL0 (concat . take 1 $ choices) wwss else do let !subs = subG (' ':js `mappend` vs) xs if null argCs then let !perms | pairwisePermutations == R.P 2 = genPairwisePermutationsLN l | pairwisePermutations == R.P 1 = genElementaryPermutationsLN1 l | otherwise = genPermutationsL l in generalProcMMs pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX argsZipped perms subs args lstW2 else do correct <- printWarning xs if correct == "n" then putStrLn (messageInfo 1) >> return "" -- for the multiple variations mode (with curly brackets and slash in the text) the program does not stop here, but the variation is made empty and is proposed further as a variant. else let !perms = decodeLConstraints argCs . (case pairwisePermutations of {R.P 2 -> genPairwisePermutationsLN ; R.P 1 -> genElementaryPermutationsLN1 ; ~rrr -> genPermutationsL}) $ l in generalProcMMs pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX argsZipped perms subs args lstW2 -- | Function provides message information. messageInfo :: Int -> String messageInfo n | n == 1 = "You stopped the program, please, if needed, run it again with better arguments. " | n == 2 = "Please, specify the variant which you would like to become the resulting string by its number. " | n == 3 = "Please, check whether the line below corresponds and is consistent with the constraints you have specified between the +a and -a options. Check also whether you have specified the \"+b\" or \"+bl\" option(s). If it is inconsistent then enter further \"n\", press Enter and then run the program again with better arguments. " `mappend` newLineEnding `mappend` "If the line is consistent with your input between +a and -a then just press Enter to proceed further. " `mappend` newLineEnding | n == 4 = "No data has been specified to control the computation process. " | n == 5 = "(/ You have specified properties / property and the range(s) so that for the words and their concatenations there are no variants available. Try to change the call parameters /)" | n == 6 = "If you would like to run the program (call the function) recursively with changes for the words or letter connections then, please, enter here the encoded string of the interpreter. If you would NOT like to use it recursively, then just press Enter." | n == 7 = "Please, input the text line for analysis. " | n == 8 = "Please, input the number of words or their concatenations that the program takes as one line for analysis. " | otherwise = "You have specified just one variant of the properties. " -- | interactivePrintResult :: (a -> String) -> [a] -> IO String interactivePrintResult f xss | null xss = (putStrLn . messageInfo $ 5) >> return "" | otherwise = do let !datas = map (\(idx,str) -> show idx `mappend` ('\t' : str)) . trans232 . map f $ xss if null datas then (putStrLn . messageInfo $ 5) >> return "" else do mapM_ putStrLn datas putStrLn "" putStrLn . messageInfo $ 2 number <- getLine let !lineRes = concat . filter ((number `mappend` "\t")`L.isPrefixOf`) $ datas !ts = drop 1 . dropWhile (/= '\t') $ lineRes putStrLn ts >> return ts interactivePrintResultRecursive :: R.PermutationsType -- ^ Whether to use just one of the express permutations, or the full universal set. -> GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text. -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon -- (e. g. allophones). Must be sorted in the ascending order to be used correctly. -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly. -> SegmentRulesG -> String -> String -> (Double -> String -> ([[[PRS]]] -> [[Double]])) -- ^ 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@. -> [([[[PRS]]] -> [[Double]])] -- ^ A list of 4 different functions that specifies the syllables durations, analogues of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most -- exact one and, therefore, the default one. -> Concatenations -- ^ Data used to concatenate (prepend) the basic grammar preserving words and word sequences to the next word to -- leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to. -> Concatenations -- ^ Data used to concatenate (append) the basic grammar preserving words and word sequences to the next word to -- leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to. -> String -> Bool -- ^ Whether to run in the recursive mode. -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> (a -> String) -> [a] -> [String] -> Bool -> IO String interactivePrintResultRecursive pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX f xss args lstW2 | null xss = (putStrLn . messageInfo $ 5) >> return "" | otherwise = do let !datas = map (\(idx,str) -> show idx `mappend` ('\t' : str)) . trans232 . map f $ xss mapM_ putStrLn datas putStrLn "" putStrLn . messageInfo $ 2 number <- getLine let !lineRes = concat . filter ((number `mappend` "\t")`L.isPrefixOf`) $ datas !ts = drop 1 . dropWhile (/= '\t') $ lineRes putStrLn . messageInfo $ 6 stringInterpreted <- getLine if null stringInterpreted then putStrLn ts >> return ts else do let !firstArgs = takeWhile (not . all isLetter) args strIntrpr <- convStringInterpreterIO stringInterpreted ts wordsNN <- if pairwisePermutations /= R.P 0 then do putStrLn . messageInfo $ 8 mStr <- getLine let m = fromMaybe 10 (readMaybe mStr::Maybe Int) in return . take m . words $ strIntrpr else return . take 7 . words $ strIntrpr generalProc2 pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX (firstArgs `mappend` wordsNN) lstW2 printWarning :: String -> IO String printWarning xs = do putStrLn . messageInfo $ 3 putStrLn xs getLine generalProcMs :: GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text. -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon -- (e. g. allophones). Must be sorted in the ascending order to be used correctly. -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly. -> SegmentRulesG -> String -> String -> (Double -> String -> ([[[PRS]]] -> [[Double]])) -- ^ 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@. -> [([[[PRS]]] -> [[Double]])] -- ^ A list of 4 different functions that specifies the syllables durations, analogues of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most -- exact one and, therefore, the default one. -> Coeffs2 -- ^ This value is used when property choice is NOT from the \"w\" or \"x\" lines. -> Coeffs2 -- ^ This value is used when property choice is from the \"w\" or \"x\" lines. -> [Array Int Int] -- ^ Permutations data. -> [String] -> ([Int],String,Int,String) -- ^ The 'String' is intended to be one of the following strings: \"02y\", \"02z\", \"03y\", \"03z\", \"04y\", \"04z\", -- \"0y\", \"0z\", \"y\", \"y0\", \"y2\", \"y3\", \"y4\", \"yy\", \"yy2\", \"yy3\", \"z\", \"z2\", \"z3\", \"z4\", -- \"zz\", \"zz2\", \"zz3\", \"zz4\" or some other one (that is the default one). Since 0.5.0.0 version can also -- process \"w\" and \"x\"-based lines properties. Specifies the applied properties -- to get the result. The \"z\"-line uses \'F\' functions. -- @ since 0.6.0.0 -- Changed the arguments signing so that capital letters changed to the small ones, double ++ changed to just singular +. -> IO [Result [] Char Double Double] generalProcMs wrs ks arr gs js vs h qs coeffs coeffsWX perms subs (intervalNmbrs, arg0, numberI, choice) = do if compare numberI 2 == LT then let !frep2 | take 1 choice == "w" || take 1 choice == "x" = chooseMax wrs ks arr gs js vs id h coeffsWX qs choice | otherwise = chooseMax wrs ks arr gs js vs id h coeffs qs choice in return . fst . (if any (== 'G') choice then partitioningR arg0 else maximumGroupsClassificationR (fromMaybe 1 (readMaybe arg0::Maybe Int))) . map (toResultR frep2) . uniquenessVariants2GNBL ' ' id id id perms $ subs else do let !variants1 = uniquenessVariants2GNBL ' ' id id id perms subs !frep20 | take 1 choice == "w" || take 1 choice == "x" = chooseMax wrs ks arr gs js vs id h coeffsWX qs choice | otherwise = chooseMax wrs ks arr gs js vs id h coeffs qs choice (!minE,!maxE) = minMax11C . map (toPropertiesF' frep20) $ variants1 !frep2 | take 1 choice == "w" || take 1 choice == "x" = chooseMax wrs ks arr gs js vs (unsafeSwapVecIWithMaxI minE maxE numberI intervalNmbrs) h coeffsWX qs choice | otherwise = chooseMax wrs ks arr gs js vs (unsafeSwapVecIWithMaxI minE maxE numberI intervalNmbrs) h coeffs qs choice return . fst . (if any (== 'G') choice then partitioningR arg0 else maximumGroupsClassificationR (fromMaybe 1 (readMaybe arg0::Maybe Int))) . map (toResultR frep2) $ variants1 -- | generalProcMMs :: R.PermutationsType -- ^ Whether to use just one of the express permutations, or the full universal set. -> GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text. -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon -- (e. g. allophones). Must be sorted in the ascending order to be used correctly. -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly. -> SegmentRulesG -> String -> String -> (Double -> String -> ([[[PRS]]] -> [[Double]])) -- ^ 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@. -> [([[[PRS]]] -> [[Double]])] -- ^ A list of 4 different functions that specifies the syllables durations, analogues of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most -- exact one and, therefore, the default one. -> Concatenations -- ^ Data used to concatenate (prepend) the basic grammar preserving words and word sequences to the next word to -- leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to. -> Concatenations -- ^ Data used to concatenate (append) the basic grammar preserving words and word sequences to the next word to -- leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to. -> String -> Bool -- ^ Whether to run in the recursive mode. -> Bool -> Bool -> [String] -> Coeffs2 -- ^ This value is used when property choice is NOT from the \"w\" or \"x\" lines. -> Coeffs2 -- ^ This value is used when property choice is from the \"w\" or \"x\" lines. -> [([Int],String,Int,String)] -- ^ The 'String' is intended to be one of the following strings: \"02y\", \"02z\", \"03y\", \"03z\", \"04y\", \"04z\", -- \"0y\", \"0z\", \"y\", \"y0\", \"y2\", \"y3\", \"y4\", \"yy\", \"yy2\", \"yy3\", \"z\", \"z2\", \"z3\", \"z4\", -- \"zz\", \"zz2\", \"zz3\", \"zz4\" or some other one (that is the default one). Since 0.5.0.0 version can also -- process \"w\" and \"x\"-based lines properties. Specifies the applied properties -- to get the result. The \"z\"-line uses \'F\' functions. -- @ since 0.6.0.0 -- Changed the arguments signing so that capital letters changed to the small ones, double ++ changed to just singular +. -> [Array Int Int] -- ^ Permutations data. -> [String] -> [String] -> Bool -> IO String generalProcMMs pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws recursiveMode interactiveMM jstL0 args0 coeffs coeffsWX rs perms subs args lstW2 = case length rs of 0 -> putStrLn (messageInfo 4) >> return "" 1 -> putStrLn (messageInfo 5) >> do temp <- generalProcMs wrs ks arr gs js vs h qs coeffs coeffsWX perms subs (head rs) finalProc pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws recursiveMode interactiveMM jstL0 args0 coeffs coeffsWX line temp args lstW2 _ -> do genVariants <- mapM (generalProcMs wrs ks arr gs js vs h qs coeffs coeffsWX perms subs) rs finalProc pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws recursiveMode interactiveMM jstL0 args0 coeffs coeffsWX id (foldlI . map (map line) $ genVariants) args lstW2 foldlI :: [[String]] -> [String] foldlI ((!xs):ys:xss) = foldlI (intersectInterResults xs ys : xss) foldlI ((!xs):_) = xs foldlI _ = [] -- | finalProc :: R.PermutationsType -- ^ Whether to use just one of the express permutations, or the full universal set. -> GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text. -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon -- (e. g. allophones). Must be sorted in the ascending order to be used correctly. -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly. -> SegmentRulesG -> String -> String -> (Double -> String -> ([[[PRS]]] -> [[Double]])) -- ^ 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@. -> [([[[PRS]]] -> [[Double]])] -- ^ A list of 4 different functions that specifies the syllables durations, analogues of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most -- exact one and, therefore, the default one. -> Concatenations -- ^ Data used to concatenate (prepend) the basic grammar preserving words and word sequences to the next word to -- leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to. -> Concatenations -- ^ Data used to concatenate (append) the basic grammar preserving words and word sequences to the next word to -- leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to. -> String -> Bool -- ^ Whether to run in the recursive mode. -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> (a -> String) -> [a] -> [String] -> Bool -> IO String finalProc pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX f xss args lstW2 | recursiveMode = interactivePrintResultRecursive pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX f xss args lstW2 | otherwise = if interactive then interactivePrintResult f xss else putStrLn ts >> return ts where ts = concatMap (\t -> f t `mappend` newLineEnding) xss -- | print1el :: Bool -> String -> [Result [] Char Double Double] -> IO String print1el jstlines choice y | jstlines == True = putStrLn us >> return us | otherwise = putStrLn zs >> return zs where !ch = precChoice choice !us = concatMap (\ys -> line ys `mappend` newLineEnding) y !zs = concatMap (\ys -> line ys `mappend` newLineEnding `mappend` showFFloat ch (propertiesF ys) (newLineEnding `mappend` showFFloat ch (transPropertiesF ys) newLineEnding)) y