{-# OPTIONS_GHC -threaded -rtsopts #-} {-# OPTIONS_HADDOCK show-extensions #-} {-# LANGUAGE BangPatterns #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} -- | -- 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 import qualified Data.List as L (span,sort,zip4,isPrefixOf,nub,sortBy,intersperse) 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 Interpreter.ArgsConversion import qualified Phonetic.Languages.Permutations.Represent as R import Phonetic.Languages.EmphasisG import CaseBi.Arr (getBFstLSorted') import Phonetic.Languages.Coeffs 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 -> 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. -> 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 -> Bool -- ^ Whether to use volatile string weights -> Int -- ^ Number of sets of volatile string weights for every processed line. Is used when the previous one is 'True' -> Int -- ^ Whether to print more verbose information in the output with sorting in some way -> (String -> String) -- ^ A function that specifies what 'Char's in the list the first argument makes to be the function sensitive to. Analogue of the @g@ function in the definition: https://hackage.haskell.org/package/phonetic-languages-simplified-examples-array-0.21.0.0/docs/src/Phonetic.Languages.Simplified.Array.Ukrainian.FuncRep2RelatedG2.html#parsey0Choice. Use just small 'Char' if they are letters, do not use \'.\' and spaces. -> 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 syllables syllablesVs verbose g1 | null textProcessment0 = generalProc2G pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws toFile1 recursiveMode interactive jstL0 args0 coeffs coeffsWX args lstW2 syllables syllablesVs verbose g1 | 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 syllables syllablesVs verbose g1) [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 syllables syllablesVs verbose g1) 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 syllables syllablesVs verbose g1) 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 -> 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. -> 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 -> Bool -- ^ Whether to use volatile string weights -> Int -- ^ Number of sets of volatile string weights for every processed line. Is used when the previous one is 'True' -> Int -> (String -> String) -- ^ A function that specifies what 'Char's in the list the first argument makes to be the function sensitive to. Analogue of the @g@ function in the definition: https://hackage.haskell.org/package/phonetic-languages-simplified-examples-array-0.21.0.0/docs/src/Phonetic.Languages.Simplified.Array.Ukrainian.FuncRep2RelatedG2.html#parsey0Choice. Use just small 'Char' if they are letters, do not use \'.\' and spaces. -> IO () generalProc2G pairwisePermutations wrs ks arr gs js vs h qs ysss zzzsss ws toFile1 recursiveMode interactive jstL0 args0 coeffs coeffsWX args lstW2 syllables syllablesVs verbose g1 | 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 syllables syllablesVs verbose g1) 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 (showR . fst) variantsG args lstW2 syllables syllablesVs verbose g1 else interactivePrintResult (showR . fst) variantsG syllables syllablesVs) >>= \(rs,cs) -> case toFile1 of "" -> return () ~fileName -> appendFile fileName (convFSL wrs ks arr gs js vs cs 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 syllables syllablesVs verbose g1 >>= \(rs,cs) -> case toFile1 of "" -> return () ~fileName -> appendFile fileName (convFSL wrs ks arr gs js vs cs 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 -> 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. -> [MappingFunctionPL] -> 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 -> Bool -- ^ Whether to use volatile string weights -> Int -- ^ Number of sets of volatile string weights for every processed line. Is used when the previous one is 'True' -> Int -> (String -> String) -- ^ A function that specifies what 'Char's in the list the first argument makes to be the function sensitive to. Analogue of the @g@ function in the definition: https://hackage.haskell.org/package/phonetic-languages-simplified-examples-array-0.21.0.0/docs/src/Phonetic.Languages.Simplified.Array.Ukrainian.FuncRep2RelatedG2.html#parsey0Choice. Use just small 'Char' if they are letters, do not use \'.\' and spaces. -> IO (ReadyForConstructionPL, String) generalProc2 pairwisePermutations wrs ks arr gs js vs h qs sDs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX args lstW2 syllables syllablesVs verbose g1 = 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 !bs = concat . take 1 . prepareTuneTextMN (if pairwisePermutations /= R.P 0 then 10 else 7) 1 ysss zzzsss ws . unwords . drop 1 $ textualArgs !xs = StrG bs !l = length . words $ bs !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 !sels = parsey0Choice g1 choice !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 syllables then do weightsString3NIO wrs ks arr gs js vs syllablesVs (any (== 'a') choice) bs else return ([],[],StrG [])) >>= \(syllDs,syllableDs,readys) -> do if compare l 2 == LT then let !frep20 = chooseMax wrs ks arr gs js vs id h (if any (\t -> t == 'x' || t == 'w') choice then coeffsWX else coeffs) sels (if any (== 'a') choice then map SaaW syllableDs else qs) choice bs in let !wwss = (:[]) . toResultR2 frep20 $ xs in if recursiveMode then interactivePrintResultRecursive pairwisePermutations wrs ks arr gs js vs h qs (if any (== 'a') choice then map SaaW syllableDs else sDs) ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX (convFSL wrs ks arr gs js vs bs . line2) wwss args lstW2 syllables syllablesVs verbose g1 else if interactive then interactivePrintResult (convFSL wrs ks arr gs js vs bs . line2) wwss syllables syllablesVs else print1el jstL0 choice wwss else do let !subs = subG (' ':js `mappend` vs) bs if null argCs then let !perms | pairwisePermutations == R.P 2 = genPairwisePermutationsLN l | pairwisePermutations == R.P 1 = genElementaryPermutationsLN1 l | otherwise = genPermutationsL l in do temp <- generalProcMs wrs ks arr gs js vs h qs (if any (== 'a') choice then map SaaW syllableDs else sDs) coeffs coeffsWX perms subs (intervalNmbrs, arg0, numberI, choice) g1 if recursiveMode then interactivePrintResultRecursive pairwisePermutations wrs ks arr gs js vs h qs (if any (== 'a') choice then map SaaW syllableDs else sDs) ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX (convFSL wrs ks arr gs js vs bs . line2) temp args lstW2 syllables syllablesVs verbose g1 else if interactive then interactivePrintResult (convFSL wrs ks arr gs js vs bs . line2) temp syllables syllablesVs else print1el jstL0 choice temp else do correct <- printWarning bs if correct == "n" then putStrLn (messageInfo 1) >> return (StrG "","") -- 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 . (if pairwisePermutations == R.P 2 then genPairwisePermutationsLN else if pairwisePermutations == R.P 0 then genPermutationsL else genElementaryPermutationsLN1) $ l in do temp <- generalProcMs wrs ks arr gs js vs h qs (if any (== 'a') choice then map SaaW syllableDs else sDs) coeffs coeffsWX perms subs (intervalNmbrs, arg0, numberI, choice) g1 if recursiveMode then interactivePrintResultRecursive pairwisePermutations wrs ks arr gs js vs h qs (if any (== 'a') choice then map SaaW syllableDs else sDs) ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX (convFSL wrs ks arr gs js vs bs . line2) temp args lstW2 syllables syllablesVs verbose g1 else if interactive then interactivePrintResult (convFSL wrs ks arr gs js vs bs . line2) temp syllables syllablesVs 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 !bs = concat . take 1 . prepareTuneTextMN (if pairwisePermutations /= R.P 0 then 10 else 7) 1 ysss zzzsss ws . unwords $ args !xs = StrG bs !l = length . words $ bs !argCs = catMaybes (fmap (readMaybeECG (l - 1)) . (showB l lstW2:) . drop 1 . dropWhile (/= "+a") . takeWhile (/= "-a") $ args0) (syllDs,syllableDs,readys) <- do if syllables then weightsString3NIO wrs ks arr gs js vs syllablesVs (any id (map (any (== 'a')) choices)) bs else return ([],[],FSLG []) if compare l 2 == LT then let !frep20 = chooseMax wrs ks arr gs js vs id h coeffs [] (if any (== 'a') . concat . take 1 $ choices then map SaaW syllableDs else qs) (concat . take 1 $ choices) bs in let !wwss = (:[]) . toResultR2 frep20 $ xs in if recursiveMode then interactivePrintResultRecursive pairwisePermutations wrs ks arr gs js vs h qs (if syllables then map SaaW syllableDs else sDs) ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX (convFSL wrs ks arr gs js vs bs . line2) wwss args lstW2 syllables syllablesVs verbose g1 else if interactive then interactivePrintResult (convFSL wrs ks arr gs js vs bs . line2) wwss syllables syllablesVs else print1el jstL0 (concat . take 1 $ choices) wwss else do let !subs = subG (' ':js `mappend` vs) bs 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 (map SaaW syllableDs) ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX argsZipped perms subs args lstW2 syllables syllablesVs verbose g1 else do correct <- printWarning bs if correct == "n" then putStrLn (messageInfo 1) >> return (StrG "","") -- 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 (map SaaW syllableDs) ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX argsZipped perms subs args lstW2 syllables syllablesVs verbose g1 -- | 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] -> Bool -> Int -> IO (ReadyForConstructionPL,String) interactivePrintResult f xss syllables syllablesVs | null xss = (putStrLn . messageInfo $ 5) >> return (StrG "","") | otherwise = do let !datas = map (\(idx,str) -> show idx `mappend` ('\t' : str)) . trans232 . map f $ xss if null datas then (putStrLn . messageInfo $ 5) >> return (StrG "","") 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 (StrG ts,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 -> 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. -> [MappingFunctionPL] -> 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 -> Bool -- ^ Whether to use volatile string weights -> Int -- ^ Number of sets of volatile string weights for every processed line. Is used when the previous one is 'True' -> Int -> (String -> String) -- ^ A function that specifies what 'Char's in the list the first argument makes to be the function sensitive to. Analogue of the @g@ function in the definition: https://hackage.haskell.org/package/phonetic-languages-simplified-examples-array-0.21.0.0/docs/src/Phonetic.Languages.Simplified.Array.Ukrainian.FuncRep2RelatedG2.html#parsey0Choice. Use just small 'Char' if they are letters, do not use \'.\' and spaces. -> IO (ReadyForConstructionPL,String) interactivePrintResultRecursive pairwisePermutations wrs ks arr gs js vs h qs sDs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX f xss args lstW2 syllables syllablesVs verbose g1 | null xss = (putStrLn . messageInfo $ 5) >> return (StrG "","") | 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 (StrG ts,ts) else do let (strI10,convArgs0) = break (== '+') stringInterpreted strI1 = filter (not . isSpace) strI10 (convArgs1,convArgs) = splitAt 2 convArgs0 cnvArgs = min 1 (fromMaybe 0 (readMaybe (drop 1 convArgs1)::Maybe Int)) (_,pairwisePermutations1,_,jstL01,args01,coeffs1,coeffsWX1,args1,lstW1,syllables1,syllablesVs1,verbose1) = argsConversion convArgs lstW3 = if lstW1 then lstW1 else lstW2 jstL02 = if jstL01 then jstL01 else jstL0 -- !firstArgs = takeWhile (not . all isLetter) args2 args02 = if cnvArgs > 0 && cnvArgs < 5 then args01 else args0 args2 = if cnvArgs `elem` [1,2,5,6] then args1 else args firstArgs = takeWhile (not . all isLetter) args2 coeffs2 = if isPair coeffs1 then coeffs1 else coeffs coeffsWX2 = if isPair coeffsWX1 then coeffsWX1 else coeffsWX syllables2 = if syllables1 then syllables1 else syllables syllablesVs2 = if syllables1 then syllablesVs1 else syllablesVs pairwisePermutations2 = if cnvArgs `elem` [1,3,5,7] then pairwisePermutations1 else pairwisePermutations verbose2 = if verbose1 == 0 then verbose else verbose1 strIntrpr <- convStringInterpreterIO strI1 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 sDs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX (firstArgs `mappend` wordsNN) lstW2 syllables syllablesVs verbose g1 printWarning :: String -> IO String printWarning xs = do putStrLn . messageInfo $ 3 putStrLn xs getLine show2 verbose jjs@(R2 x y z:_) = show1 bs where bs = L.sortBy (\(R2 xs d1 k1) (R2 ys d2 k2) -> case verbose of 2 -> if d1 == d2 then compare xs ys else compare d2 d1 1 -> compare xs ys 3 -> compare k2 k1 _ -> EQ) jjs show1 qqs@(R2 x y z:ks) = showR x `mappend` "->" `mappend` show y `mappend` "->" `mappend` show z `mappend` "\n" `mappend` show1 ks show1 _ = "" print2 verbose = putStrLn . show2 verbose 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 -> 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. -> [MappingFunctionPL] -> 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 +. -> (String -> String) -- ^ A function that specifies what 'Char's in the list the first argument makes to be the function sensitive to. Analogue of the @g@ function in the definition: https://hackage.haskell.org/package/phonetic-languages-simplified-examples-array-0.21.0.0/docs/src/Phonetic.Languages.Simplified.Array.Ukrainian.FuncRep2RelatedG2.html#parsey0Choice. Use just small 'Char' if they are letters, do not use \'.\' and spaces. -> IO [Result2 ReadyForConstructionPL Double Double] generalProcMs wrs ks arr gs js vs h qs sDs coeffs coeffsWX perms subs (intervalNmbrs, arg0, numberI, choice) g1 = do let bs = unwords subs sels = parsey0Choice g1 choice if compare numberI 2 == LT then let !frep2 = chooseMax wrs ks arr gs js vs id h (if any (\t -> t == 'w' || t == 'x') choice then coeffsWX else coeffs) sels (if any (== 'a') choice then sDs else qs) choice bs in return . fst . (if any (== 'G') choice then partitioningR2 arg0 else maximumGroupsClassificationR_2 (fromMaybe 1 (readMaybe arg0::Maybe Int))) . map (toResultR2 frep2) . map StrG . uniquenessVariants2GNBL ' ' id id id perms $ subs else do let !variants1 = uniquenessVariants2GNBL ' ' id id id perms subs !frep20 = chooseMax wrs ks arr gs js vs id h (if any (\t -> t == 'x' || t == 'w') choice then coeffsWX else coeffs) sels (if any (== 'a') choice then sDs else qs) choice bs (!minE,!maxE) = minMax11C . map (toPropertiesF'2 frep20) $ map StrG variants1 !frep2 = chooseMax wrs ks arr gs js vs (unsafeSwapVecIWithMaxI minE maxE numberI intervalNmbrs) h (if any (\t -> t == 'x' || t == 'w') choice then coeffsWX else coeffs) sels (if any (== 'a') choice then sDs else qs) choice bs return . fst . (if any (== 'G') choice then partitioningR2 arg0 else maximumGroupsClassificationR_2 (fromMaybe 1 (readMaybe arg0::Maybe Int))) . map (toResultR2 frep2) $ map StrG 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 -> 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. -> [MappingFunctionPL] -> 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 -> Bool -- ^ Whether to use volatile string weights -> Int -- ^ Number of sets of volatile string weights for every processed line. Is used when the previous one is 'True' -> Int -> (String -> String) -- ^ A function that specifies what 'Char's in the list the first argument makes to be the function sensitive to. Analogue of the @g@ function in the definition: https://hackage.haskell.org/package/phonetic-languages-simplified-examples-array-0.21.0.0/docs/src/Phonetic.Languages.Simplified.Array.Ukrainian.FuncRep2RelatedG2.html#parsey0Choice. Use just small 'Char' if they are letters, do not use \'.\' and spaces. -> IO (ReadyForConstructionPL, String) generalProcMMs pairwisePermutations wrs ks arr gs js vs h qs sDs ysss zzzsss ws recursiveMode interactiveMM jstL0 args0 coeffs coeffsWX rs perms subs args lstW2 syllables syllablesVs verbose g1 = case length rs of 0 -> putStrLn (messageInfo 4) >> return (StrG "","") 1 -> putStrLn (messageInfo 5) >> do temp <- generalProcMs wrs ks arr gs js vs h qs sDs coeffs coeffsWX perms subs (head rs) g1 if verbose `elem` [1..3] then print2 verbose temp >> putStrLn "" else putStr "" finalProc pairwisePermutations wrs ks arr gs js vs h qs sDs ysss zzzsss ws recursiveMode interactiveMM jstL0 args0 coeffs coeffsWX (convFSL wrs ks arr gs js vs (unwords args) . line2) temp args lstW2 syllables syllablesVs verbose g1 _ -> do genVariants <- mapM (\k-> generalProcMs wrs ks arr gs js vs h qs sDs coeffs coeffsWX perms subs k g1) rs if verbose `elem` [1..3] then mapM_ (\t -> print2 verbose t >> putStrLn "") genVariants else putStr "" finalProc pairwisePermutations wrs ks arr gs js vs h qs sDs ysss zzzsss ws recursiveMode interactiveMM jstL0 args0 coeffs coeffsWX (convFSL wrs ks arr gs js vs (unwords args)) (foldlI wrs ks arr gs js vs (unwords args). map (map line2) $ genVariants) args lstW2 syllables syllablesVs verbose g1 -- | 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 -> 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. -> [MappingFunctionPL] -> 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 -> Bool -- ^ Whether to use volatile string weights -> Int -- ^ Number of sets of volatile string weights for every processed line. Is used when the previous one is 'True' -> Int -> (String -> String) -- ^ A function that specifies what 'Char's in the list the first argument makes to be the function sensitive to. Analogue of the @g@ function in the definition: https://hackage.haskell.org/package/phonetic-languages-simplified-examples-array-0.21.0.0/docs/src/Phonetic.Languages.Simplified.Array.Ukrainian.FuncRep2RelatedG2.html#parsey0Choice. Use just small 'Char' if they are letters, do not use \'.\' and spaces. -> IO (ReadyForConstructionPL,String) finalProc pairwisePermutations wrs ks arr gs js vs h qs sDs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX f xss args lstW2 syllables syllablesVs verbose g1 | recursiveMode = interactivePrintResultRecursive pairwisePermutations wrs ks arr gs js vs h qs sDs ysss zzzsss ws recursiveMode interactive jstL0 args0 coeffs coeffsWX f xss args lstW2 syllables syllablesVs verbose g1 | otherwise = if interactive then interactivePrintResult f xss syllables syllablesVs else putStrLn ts >> return (StrG ts,ts) where ts = concatMap (\t -> f t `mappend` newLineEnding) xss -- | print1el :: Bool -> String -> [Result2 ReadyForConstructionPL Double Double] -> IO (ReadyForConstructionPL,String) print1el jstlines choice y | jstlines == True = putStrLn us >> return (StrG us,us) | otherwise = putStrLn zs >> return (StrG zs,zs) where !ch = precChoice choice !us = concatMap (\ys -> showR (line2 ys) `mappend` newLineEnding) y !zs = concatMap (\ys -> showR (line2 ys) `mappend` newLineEnding `mappend` showFFloat ch (propertiesF2 ys) (newLineEnding `mappend` showFFloat ch (transPropertiesF2 ys) newLineEnding)) y