{-# OPTIONS_GHC -threaded -rtsopts #-} {-# OPTIONS_HADDOCK show-extensions #-} {-# LANGUAGE BangPatterns #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} -- | -- Module : Phonetic.Languages.Simple -- Copyright : (c) OleksandrZhabenko 2020-2022 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- The library functions for the lineVariantsG3 executable. Since 0.4.0.0 version it supports printing of the informational -- messages both in English and Ukrainian. Since the 0.13.0.0 version there is the possibility to provide custom durations -- instead of the default predefined ones. module Phonetic.Languages.Simple where import Data.Char --import Phonetic.Languages.Array.Ukrainian.Common import Phonetic.Languages.Parsing import Numeric import Languages.UniquenessPeriods.Array.Constraints.Encoded (decodeLConstraints,readMaybeECG) import GHC.Arr import CaseBi.Arr (getBFstLSorted') import Phonetic.Languages.Simplified.DataG.Base import Phonetic.Languages.Basis import Phonetic.Languages.Simplified.DataG.Partir import Phonetic.Languages.Filters (unsafeSwapVecIWithMaxI) import Phonetic.Languages.Simplified.StrictVG.Base import qualified Data.List as L (span,sort,zip4,isPrefixOf,nub,sortBy,intersperse) import Phonetic.Languages.Simplified.Array.Ukrainian.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.Simplified.DeEnCoding import Phonetic.Languages.Simplified.SimpleConstraints import Interpreter.ArgsConversion import Interpreter.StringConversion import Melodics.Ukrainian.ArrInt8 (Sound8) import Phonetic.Languages.Ukrainian.PrepareText (prepareTuneTextMN,isSpC,isUkrainianL) import Phonetic.Languages.Simplified.Array.Ukrainian.ReadProperties import Phonetic.Languages.Permutations.Represent import Languages.Ukrainian.Data import Phonetic.Languages.Emphasis 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 :: FilePath -- ^ Whether to use the own provided durations from the file specified here. -> PermutationsType -- ^ Whether to use just one of the express permutations, or the full universal set. -> [String] -> String -- ^ If empty, the function is just 'generalProc2G' with the arguments starting from the first 'Bool' here. -> Int -> Bool -> Bool -> FilePath -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> [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 -> IO () generalProc3G fileDu pairwisePermutations textProcessmentFss textProcessment0 textProcessment1 recursiveMode nativeUkrainian toFileMode1 interactiveP jstL0 args0 coeffs coeffsWX args lstW syllables syllablesVs verbose = do syllableDurationsDs <- readSyllableDurations fileDu generalProc3G' syllableDurationsDs pairwisePermutations textProcessmentFss textProcessment0 textProcessment1 recursiveMode nativeUkrainian toFileMode1 interactiveP jstL0 args0 coeffs coeffsWX args lstW syllables syllablesVs verbose where generalProc3G' syllableDurationsDs pairwisePermutations textProcessmentFss textProcessment0 textProcessment1 recursiveMode nativeUkrainian toFileMode1 interactiveP jstL0 args0 coeffs coeffsWX args lstW syllables syllablesVs verbose | null textProcessment0 = generalProc2G syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian toFileMode1 interactiveP jstL0 args0 coeffs coeffsWX args lstW syllables syllablesVs verbose | null textProcessmentFss = mapM_ (\_ -> do -- interactive training mode putStrLn . messageInfo 7 $ nativeUkrainian lineA <- getLine generalProc2G syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian toFileMode1 interactiveP jstL0 (fullArgsConvertTextualSimple mightNotUkrWord lineA args0) coeffs coeffsWX (fullArgsConvertTextualSimple mightNotUkrWord lineA args) lstW syllables syllablesVs verbose) [0..] | otherwise = mapM_ (\js -> do let !kss = lines js if pairwisePermutations /= P 0 then do let !wss | textProcessment1 `elem` [10,20,30,40,50,60,70,80,90] = kss | otherwise = prepareTuneTextMN m 1 . unwords $ kss mapM_ (\tss -> generalProc2G syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian toFileMode1 interactiveP jstL0 (fullArgsConvertTextualSimple mightNotUkrWord tss args0) coeffs coeffsWX (fullArgsConvertTextualSimple mightNotUkrWord tss args) lstW syllables syllablesVs verbose) 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 . unwords $ kss mapM_ (\tss -> generalProc2G syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian toFileMode1 interactiveP jstL0 (fullArgsConvertTextualSimple mightNotUkrWord tss args0) coeffs coeffsWX (fullArgsConvertTextualSimple mightNotUkrWord tss args) lstW syllables syllablesVs verbose) wss) textProcessmentFss m = if textProcessment1 == 10 || textProcessment1 == 11 then 10 else quot textProcessment1 10 {-| If 'False' then it might be the Ukrainian word in the phonetic languages approach. If 'True', it is not. Is an example of the predicate inside the 'fullArgsConvertTextual' function for the Ukrainian language. -} mightNotUkrWord :: String -> Bool mightNotUkrWord xs | null ts || ts == "-" = True | any isAlpha us = True | null (dropWhile (not . isUkrainianN) us) = False | otherwise = True where (ts,us) = L.span isUkrainianN xs {-# INLINE mightNotUkrWord #-} -- | Is taken from the @mmsyn6ukr@ package version 0.8.1.0 so that the amount of dependencies are reduced (and was slightly modified). isUkrainianN x = isUkrainianL x || isSpC x {-| @ since 0.3.0.0 Is used to do general processment. @ since 0.5.0.0 The meaning of the first command line argument (and 'Coeffs2' here everywhere in the module) depends on the 'String' argument -- whether it starts with \'w\', \'x\' or otherwise. In the first case it represents the k1 and k2 coefficients (default ones equal to 2.0 and 0.125) for the functions from the Rhythmicity.TwoFourth module. Otherwise, it is used for the functions to specify the level of emphasizing the two-based and three-based periods (the default values here are 1.0 both). @ since 0.6.0.0 Changed the arguments signing so that capital letters changed to the small ones, double ++ changed to just singular +. @ since 0.9.0.0 Added a new argument to control whether to use interactive recursive mode. -} generalProc2G :: [[[[Sound8]]] -> [[Double]]] -- ^ Whether to use the own provided durations. -> PermutationsType -- ^ Whether to use just one of the express permutations, or the full universal set. -> Bool -> Bool -> FilePath -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> [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 -> IO () generalProc2G syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian toFile1 interactive jstL0 args0 coeffs coeffsWX args lstW2 syllables syllablesVs verbose | variations args = do let !zsss = transformToVariations args variantsG <- mapM (\xss -> generalProc2 syllableDurationsDs [] pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX xss lstW2 syllables syllablesVs verbose) zsss if interactive then do (if recursiveMode then interactivePrintResultRecursive syllableDurationsDs [] pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX (showR . fst) variantsG args lstW2 syllables syllablesVs verbose else interactivePrintResult nativeUkrainian (showR . fst) variantsG syllables syllablesVs) >>= \(rs,cs) -> case toFile1 of "" -> return () ~fileName -> appendFile fileName (convFSL cs rs `mappend` newLineEnding) else return () | otherwise = generalProc2 syllableDurationsDs [] pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX args lstW2 syllables syllablesVs verbose >>= \(rs,cs) -> case toFile1 of "" -> return () ~fileName -> appendFile fileName (convFSL cs rs `mappend` newLineEnding) -- | -- @ since 0.3.0.0 The result is not 'IO' (), but 'IO' 'String'. The type also changed generally. generalProc2 :: [[[[Sound8]]] -> [[Double]]] -- ^ Whether to use the own provided durations. -> [[[[Sound8]]] -> [[Double]]] -- ^ Whether to use the volatile syllables durations -> PermutationsType -- ^ Whether to use just one of the express permutations, or the full universal set. -> Bool -> Bool -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> [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 -> IO (ReadyForConstructionUkr, String) generalProc2 syllableDurationsDs sDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX args lstW2 syllables syllablesVs verbose = 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 /= P 0 then 10 else 7) 1 . unwords . drop 1 $ textualArgs !xs = Str 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 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 syllablesVs (any (== 'a') choice) bs else return ([],[],Str [])) >>= \(syllDs,syllableDs,readys) -> do if compare l 2 == LT then let !frep20 = chooseMax tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (if any (== 'a') choice then syllableDs else syllableDurationsDs) id (if any (\t -> t == 'x' || t == 'w') choice then coeffsWX else coeffs) sels choice bs !wwss = (:[]) . toResultR2 frep20 $ xs in case recursiveMode of True -> interactivePrintResultRecursive syllableDurationsDs (if any (== 'a') choice then syllableDs else sDs) pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX (convFSL bs . line2) wwss args lstW2 syllables syllablesVs verbose _ -> if interactive then interactivePrintResult nativeUkrainian (convFSL bs . line2) wwss syllables syllablesVs else print1el jstL0 choice wwss else do let !subs = subG " " bs -- Probably, here it can just 'words' be used. if null argCs then let !perms | pairwisePermutations == P 2 = genPairwisePermutationsLN l | pairwisePermutations == P 1 = genElementaryPermutationsLN1 l | otherwise = genPermutationsL l in do temp <- generalProcMs syllableDurationsDs (if any (== 'a') choice then syllableDs else sDs) coeffs coeffsWX perms subs (intervalNmbrs, arg0, numberI, choice) syllables syllablesVs if recursiveMode then interactivePrintResultRecursive syllableDurationsDs (if any (== 'a') choice then syllableDs else sDs) pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX (convFSL bs . line2) temp args lstW2 syllables syllablesVs verbose else if interactive then interactivePrintResult nativeUkrainian (convFSL bs . line2) temp syllables syllablesVs else print1el jstL0 choice temp else do correct <- printWarning nativeUkrainian bs if correct == "n" then putStrLn (messageInfo 1 nativeUkrainian) >> return (Str [],[]) -- 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 == P 2 then genPairwisePermutationsLN else if pairwisePermutations == P 0 then genPermutationsL else genElementaryPermutationsLN1) $ l in do temp <- generalProcMs syllableDurationsDs (if any (== 'a') choice then syllableDs else sDs) coeffs coeffsWX perms subs (intervalNmbrs, arg0, numberI, choice) syllables syllablesVs if recursiveMode then interactivePrintResultRecursive syllableDurationsDs (if any (== 'a') choice then syllableDs else sDs) pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX (convFSL bs . line2) temp args lstW2 syllables syllablesVs verbose else if interactive then interactivePrintResult nativeUkrainian (convFSL 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 /= P 0 then 10 else 7) 1 . unwords $ args !xs = Str 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 syllablesVs (any id (map (any (== 'a')) choices)) bs else return ([],[],FSL []) if compare l 2 == LT then let !frep20 = chooseMax tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (if any (== 'a') . concat . take 1 $ choices then syllableDs else syllableDurationsDs) id coeffs [] (concat . take 1 $ choices) bs !wwss = (:[]) . toResultR2 frep20 $ xs in case recursiveMode of True -> interactivePrintResultRecursive syllableDurationsDs (if syllables then syllableDs else sDs) pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX (convFSL bs . line2) wwss args lstW2 syllables syllablesVs verbose _ -> if interactive then interactivePrintResult nativeUkrainian (convFSL bs . line2) wwss syllables syllablesVs else print1el jstL0 (concat . take 1 $ choices) wwss else do let !subs = subG " " bs if null argCs then let !perms | pairwisePermutations == P 2 = genPairwisePermutationsLN l | pairwisePermutations == P 1 = genElementaryPermutationsLN1 l | otherwise = genPermutationsL l in generalProcMMs syllableDurationsDs syllableDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX argsZipped perms subs args lstW2 syllables syllablesVs verbose else do correct <- printWarning nativeUkrainian bs if correct == "n" then putStrLn (messageInfo 1 nativeUkrainian) >> return (Str [],[]) -- 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 == P 2 then genPairwisePermutationsLN else if pairwisePermutations == P 0 then genPermutationsL else genElementaryPermutationsLN1) $ l in generalProcMMs syllableDurationsDs syllableDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX argsZipped perms subs args lstW2 syllables syllablesVs verbose {-| -- @ since 0.4.0.0 Function provides localized message information. If the 'Bool' argument is 'True' then it gives result in Ukrainian, otherwise -- in English. -} messageInfo :: Int -> Bool -> String messageInfo n True | n == 1 = "Ви зупинили програму, будь ласка, якщо потрібно, виконайте її знову з кращими аргументами. " | n == 2 = "Будь ласка, вкажіть варіант (який Ви бажаєте, щоб він став результуючим рядком) за його номером. " | n == 3 = "Будь ласка, перевірте, чи рядок нижче відповідає і узгоджується з обмеженнями, які Ви вказали між +a та -a опціями. Перевірте також, чи Ви вказали \"+b\" чи \"+bl\" опцію(ї). Якщо введені опції та аргументи не узгоджені з виведеним далі рядком, тоді введіть далі \"n\", натисніть Enter і опісля запустіть програму на виконання знову з кращими аргументами. " `mappend` newLineEnding `mappend` "Якщо рядок узгоджується з Вашим вводом між +a та -a, тоді просто натисніть Enter, щоб продовжити далі. " `mappend` newLineEnding | n == 4 = "Було задано недостатньо інформації для продовження обчислювального процесу " | n == 5 = "(/ Ви вказали властивості(ість) та діапазон(и) для них такі, що для даних слів та їх сполучень варіантів немає. Спробуйте змінити параметри виклику програми (бібліотеки) /)" | n == 6 = "Якщо бажаєте запустити програму (функцію) рекурсивно, змінюючи сполучення слів та букв, введіть тут закодований рядок інтерпретатора. Якщо бажаєте не використовувати програму (функцію) рекурсивно, просто натисніть Enter. " | n == 7 = "Введіть, будь ласка, рядок слів для аналізу. " | n == 8 = "Введіть, будь ласка, кількість слів чи їх сполучень, які програма розглядатиме як один рядок для аналізу. " | otherwise = "Ви вказали лише один варіант властивостей. " messageInfo n False | 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. " -- | -- @ since 0.3.0.0 The result is not 'IO' (), but 'IO' 'String'. The type also changed generally. -- @ since 0.8.0.0 The function has also the option for the empty result. interactivePrintResult :: Bool -> (a -> String) -> [a] -> 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' -> IO (ReadyForConstructionUkr, String) interactivePrintResult nativeUkrainian f xss syllables syllablesVs | null xss = (putStrLn . messageInfo 5 $ nativeUkrainian) >> return (Str [],[]) | otherwise = do let !datas = map (\(idx,str) -> show idx `mappend` ('\t' : str)) . trans232 . map f $ xss mapM_ putStrLn datas putStrLn "" putStrLn . messageInfo 2 $ nativeUkrainian number <- getLine let !lineRes = concat . filter ((number `mappend` "\t")`L.isPrefixOf`) $ datas !ts = drop 1 . dropWhile (/= '\t') $ lineRes putStrLn ts >> return (Str ts,ts) interactivePrintResultRecursive :: [[[[Sound8]]] -> [[Double]]] -- ^ Whether to use the own provided durations -> [[[[Sound8]]] -> [[Double]]] -- ^ Whether to use the own volatile syllable durations. -> PermutationsType -- ^ Whether to use just one of the express permutations, or the full universal set. -> Bool -> Bool -> 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 -> IO (ReadyForConstructionUkr, String) interactivePrintResultRecursive syllableDurationsDs sDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX f xss args lstW2 syllables syllablesVs verbose | null xss = (putStrLn . messageInfo 5 $ nativeUkrainian) >> return (Str [],[]) | otherwise = do let !datas = map (\(idx,str) -> show idx `mappend` ('\t' : str)) . trans232 . map f $ xss mapM_ putStrLn datas putStrLn "" putStrLn . messageInfo 2 $ nativeUkrainian number <- getLine let !lineRes = concat . filter ((number `mappend` "\t")`L.isPrefixOf`) $ datas !ts = drop 1 . dropWhile (/= '\t') $ lineRes putStrLn . messageInfo 6 $ nativeUkrainian stringInterpreted <- getLine if null stringInterpreted then putStrLn ts >> return (Str 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)) (fileDu1,pairwisePermutations1,nativeUkrainian1,jstL01,args01,coeffs1,coeffsWX1,args1,lstW1,syllables1,syllablesVs1,verbose1) = argsConversion convArgs nativeUkrainian2 | nativeUkrainian1 = nativeUkrainian1 | otherwise = nativeUkrainian 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 syllableDurationsDs2 <- (if null fileDu1 then return syllableDurationsDs else readSyllableDurations fileDu1) wordsNN <- if pairwisePermutations2 /= P 0 then do putStrLn . messageInfo 8 $ nativeUkrainian2 mStr <- getLine let m = fromMaybe 10 (readMaybe mStr::Maybe Int) in return . take m . words $ strIntrpr else return . take 7 . words $ strIntrpr generalProc2 syllableDurationsDs2 sDs pairwisePermutations2 recursiveMode nativeUkrainian2 interactive jstL02 args02 coeffs2 coeffsWX2 (firstArgs `mappend` wordsNN) lstW3 syllables2 syllablesVs2 verbose2 printWarning :: Bool -> String -> IO String printWarning nativeUkrainian xs = do putStrLn . messageInfo 3 $ nativeUkrainian putStrLn xs getLine generalProcMs :: [[[[Sound8]]] -> [[Double]]] -- ^ Whether to use the own provided durations. -> [[[[Sound8]]] -> [[Double]]] -- ^ Whether to use the own volatile syllables durations. -> Coeffs2 -> Coeffs2 -> [Array Int Int] -> [String] -> ([Int],String,Int,String) -> 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' -> IO [Result2 ReadyForConstructionUkr Double Double] generalProcMs syllableDurationsDs sDs coeffs coeffsWX perms subs (intervalNmbrs, arg0, numberI, choice) syllables syllablesVs = do let bs = unwords subs sels = parsey0Choice choice if compare numberI 2 == LT then let !frep2 = if any (\t -> t == 'x' || t == 'w') choice then chooseMax tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (if any (== 'a') choice then sDs else syllableDurationsDs) id coeffsWX sels choice bs else chooseMax tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (if any (== 'a') choice then sDs else syllableDurationsDs) id coeffs sels 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 Str . uniquenessVariants2GNBL ' ' id id id perms $ subs else do let !variants1 = uniquenessVariants2GNBL ' ' id id id perms subs !frep20 = chooseMax tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (if any (== 'a') choice then sDs else syllableDurationsDs) id (if any (\t -> t == 'x' || t == 'w') choice then coeffsWX else coeffs) sels choice bs (!minE,!maxE) = minMax11C . map (toPropertiesF'2 frep20) $ map Str variants1 !frep2 = chooseMax tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (if any (== 'a') choice then sDs else syllableDurationsDs) (unsafeSwapVecIWithMaxI minE maxE numberI intervalNmbrs) (if any (\t -> t == 'x' || t == 'w') choice then coeffsWX else coeffs) sels choice bs return . fst . (if any (== 'G') choice then partitioningR2 arg0 else maximumGroupsClassificationR_2 (fromMaybe 1 (readMaybe arg0::Maybe Int))) . map (toResultR2 frep2) $ map Str variants1 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 d2 == d1 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 -- | -- @ since 0.3.0.0 The result is not 'IO' (), but 'IO' 'String'. The type also changed generally. generalProcMMs :: [[[[Sound8]]] -> [[Double]]] -- ^ Whether to use the own provided durations. -> [[[[Sound8]]] -> [[Double]]] -- ^ Whether to use the own volatile syllables durations. -> PermutationsType -- ^ Whether to use just pairwise permutations, or the full universal set. -> Bool -> Bool -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> [([Int],String,Int,String)] -> [Array Int Int] -> [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 -> IO (ReadyForConstructionUkr, String) generalProcMMs syllableDurationsDs sDs pairwisePermutations recursiveMode nativeUkrainian interactiveMM jstL0 args0 coeffs coeffsWX rs perms subs args lstW2 syllables syllablesVs verbose = case length rs of 0 -> putStrLn (messageInfo 4 nativeUkrainian) >> return (Str [],[]) 1 -> putStrLn (messageInfo 5 nativeUkrainian) >> do temp <- generalProcMs syllableDurationsDs sDs coeffs coeffsWX perms subs (head rs) syllables syllablesVs if verbose `elem` [1..3] then print2 verbose temp >> putStrLn "" else putStr "" finalProc syllableDurationsDs sDs pairwisePermutations recursiveMode nativeUkrainian interactiveMM jstL0 args0 coeffs coeffsWX (convFSL (unwords args) . line2) temp args lstW2 syllables syllablesVs verbose _ -> do genVariants <- mapM (\k -> generalProcMs syllableDurationsDs sDs coeffs coeffsWX perms subs k syllables syllablesVs) rs if verbose `elem` [1..3] then mapM_ (\t -> print2 verbose t >> putStrLn "") genVariants else putStr "" finalProc syllableDurationsDs sDs pairwisePermutations recursiveMode nativeUkrainian interactiveMM jstL0 args0 coeffs coeffsWX (convFSL (unwords args)) (foldlI (unwords args) . map (map line2) $ genVariants) args lstW2 syllables syllablesVs verbose -- | -- @ since 0.3.0.0 The result is not 'IO' (), but 'IO' 'String'. The type also changed generally. finalProc :: [[[[Sound8]]] -> [[Double]]] -- ^ Whether to use the own provided durations. -> [[[[Sound8]]] -> [[Double]]] -- ^ Whether to use the own volatile syllables durations. -> PermutationsType -- ^ Whether to use just one of the express permutations, or the full universal set. -> Bool -> Bool -> 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 -> IO (ReadyForConstructionUkr, String) finalProc syllableDurationsDs sDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX f xss args lstW2 syllables syllablesVs verbose | recursiveMode = interactivePrintResultRecursive syllableDurationsDs sDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX f xss args lstW2 syllables syllablesVs verbose | interactive = interactivePrintResult nativeUkrainian f xss syllables syllablesVs | otherwise = putStrLn ts >> return (Str ts,ts) where ts = concatMap (\t -> f t `mappend` newLineEnding) xss -- | -- @ since 0.3.0.0 The result is not 'IO' (), but 'IO' 'String'. The type also changed generally. print1el :: Bool -> String -> [Result2 ReadyForConstructionUkr Double Double] -> IO (ReadyForConstructionUkr, String) print1el jstlines choice y | jstlines == True = putStrLn us >> return (Str us,us) | otherwise = putStrLn zs >> return (Str 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