{-# OPTIONS_GHC -threaded -rtsopts #-} {-# OPTIONS_HADDOCK show-extensions #-} {-# LANGUAGE BangPatterns #-} -- | -- Module : Phonetic.Languages.Simple -- Copyright : (c) OleksandrZhabenko 2020-2021 -- 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 Phonetic.Languages.Parsing import Numeric import Languages.UniquenessPeriods.Array.Constraints.Encoded (decodeLConstraints,readMaybeECG) import GHC.Arr import Phonetic.Languages.Simplified.DataG.Base import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2 import Phonetic.Languages.Filters (unsafeSwapVecIWithMaxI) import Phonetic.Languages.Simplified.StrictVG.Base import Data.Char (isDigit,isAlpha,isLetter) import qualified Data.List as L (span,sort,zip4,isPrefixOf,nub) import Phonetic.Languages.Simplified.Array.Ukrainian.FuncRep2RelatedG2 import Phonetic.Languages.Permutations.Arr import Phonetic.Languages.Permutations.ArrMini 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 Phonetic.Languages.Common import Interpreter.StringConversion import qualified Languages.Phonetic.Ukrainian.Syllable.Arr as S (UZPP2) import Data.Monoid (mappend) import Phonetic.Languages.Ukrainian.PrepareText (prepareGrowTextMN, prepareTuneTextMN,isSpC,isUkrainianL) import Phonetic.Languages.Simplified.Array.Ukrainian.ReadProperties 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. -> Bool -- ^ Whether to use just pairwise 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 -> IO () generalProc3G fileDu pairwisePermutations textProcessmentFss textProcessment0 textProcessment1 recursiveMode nativeUkrainian toFileMode1 interactiveP jstL0 args0 coeffs coeffsWX args lstW = do syllableDurationsDs <- readSyllableDurations fileDu generalProc3G' syllableDurationsDs pairwisePermutations textProcessmentFss textProcessment0 textProcessment1 recursiveMode nativeUkrainian toFileMode1 interactiveP jstL0 args0 coeffs coeffsWX args lstW where generalProc3G' syllableDurationsDs pairwisePermutations textProcessmentFss textProcessment0 textProcessment1 recursiveMode nativeUkrainian toFileMode1 interactiveP jstL0 args0 coeffs coeffsWX args lstW | null textProcessment0 = generalProc2G syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian toFileMode1 interactiveP jstL0 args0 coeffs coeffsWX args lstW | 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) [0..] | otherwise = mapM_ (\js -> do let !kss = lines js if pairwisePermutations 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) 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) 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 :: [[[[S.UZPP2]]] -> [[Double]]] -- ^ Whether to use the own provided durations. -> Bool -- ^ Whether to use just pairwise permutations, or the full universal set. -> Bool -> Bool -> FilePath -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> [String] -> Bool -> IO () generalProc2G syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian toFile1 interactive jstL0 args0 coeffs coeffsWX args lstW2 | variations args = do let !zsss = transformToVariations args print zsss variantsG <- mapM (\xss -> generalProc2 syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX xss lstW2) zsss (if recursiveMode then interactivePrintResultRecursive syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX id variantsG args lstW2 else interactivePrintResult nativeUkrainian id variantsG) >>= \rs -> case toFile1 of "" -> return () ~fileName -> appendFile fileName (rs `mappend` newLineEnding) | otherwise = generalProc2 syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX args lstW2 >>= \rs -> case toFile1 of "" -> return () ~fileName -> appendFile fileName (rs `mappend` newLineEnding) -- | -- @ since 0.3.0.0 The result is not 'IO' (), but 'IO' 'String'. The type also changed generally. generalProc2 :: [[[[S.UZPP2]]] -> [[Double]]] -- ^ Whether to use the own provided durations. -> Bool -- ^ Whether to use just pairwise permutations, or the full universal set. -> Bool -> Bool -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> [String] -> Bool -> IO String generalProc2 syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian 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 then 10 else 7) 1 . 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 = fromMaybe 1 $ (readMaybe (concat . take 1 $ numericArgs)::Maybe Int) !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 | take 1 choice == "x" || take 1 choice == "w" || (take 1 choice == "H" && (drop 1 (take 2 choice) `elem` ["x","w"]))= chooseMax syllableDurationsDs id coeffsWX choice | otherwise = chooseMax syllableDurationsDs id coeffs choice !wwss = (:[]) . toResultR frep20 $ xs in case recursiveMode of True -> interactivePrintResultRecursive syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX line wwss args lstW2 _ -> if interactive then interactivePrintResult nativeUkrainian line wwss else print1el jstL0 choice wwss else do let !subs = subG " 01-" xs if null argCs then let !perms | pairwisePermutations = genPairwisePermutationsLN l | otherwise = genPermutationsL l in do temp <- generalProcMs syllableDurationsDs coeffs coeffsWX perms subs (intervalNmbrs, arg0, numberI, choice) if recursiveMode then interactivePrintResultRecursive syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX line temp args lstW2 else if interactive then interactivePrintResult nativeUkrainian line temp else print1el jstL0 choice temp else do correct <- printWarning nativeUkrainian xs if correct == "n" then putStrLn (messageInfo 1 nativeUkrainian) >> 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 . (if pairwisePermutations then genPairwisePermutationsLN else genPermutationsL) $ l in do temp <- generalProcMs syllableDurationsDs coeffs coeffsWX perms subs (intervalNmbrs, arg0, numberI, choice) if recursiveMode then interactivePrintResultRecursive syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX line temp args lstW2 else if interactive then interactivePrintResult nativeUkrainian line temp else print1el jstL0 choice temp else do let !choices = map fst argMss !numericArgss = map snd argMss !arg0s = map (\ts -> fromMaybe 1 $ (readMaybe (concat . take 1 $ ts)::Maybe Int)) 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 then 10 else 7) 1 . 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 syllableDurationsDs id coeffs (concat . take 1 $ choices) !wwss = (:[]) . toResultR frep20 $ xs in case recursiveMode of True -> interactivePrintResultRecursive syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX line wwss args lstW2 _ -> if interactive then interactivePrintResult nativeUkrainian line wwss else print1el jstL0 (concat . take 1 $ choices) wwss else do let !subs = subG " 01-" xs if null argCs then let !perms | pairwisePermutations = genPairwisePermutationsLN l | otherwise = genPermutationsL l in generalProcMMs syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX argsZipped perms subs args lstW2 else do correct <- printWarning nativeUkrainian xs if correct == "n" then putStrLn (messageInfo 1 nativeUkrainian) >> 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 . (if pairwisePermutations then genPairwisePermutationsLN else genPermutationsL) $ l in generalProcMMs syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX argsZipped perms subs args lstW2 {-| -- @ 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] -> IO String interactivePrintResult nativeUkrainian f xss | null xss = (putStrLn . messageInfo 5 $ nativeUkrainian) >> return "" | 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 ts interactivePrintResultRecursive :: [[[[S.UZPP2]]] -> [[Double]]] -- ^ Whether to use the own provided durations. -> Bool -- ^ Whether to use just pairwise permutations, or the full universal set. -> Bool -> Bool -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> (a -> String) -> [a] -> [String] -> Bool -> IO String interactivePrintResultRecursive syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX f xss args lstW2 | null xss = (putStrLn . messageInfo 5 $ nativeUkrainian) >> return "" | 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 ts else do let strIntrpr = convStringInterpreter stringInterpreted ts !firstArgs = takeWhile (not . all isLetter) args wordsNN <- if pairwisePermutations then do putStrLn . messageInfo 8 $ nativeUkrainian mStr <- getLine let m = fromMaybe 10 (readMaybe mStr::Maybe Int) in return . take m . words $ strIntrpr else return . take 7 . words $ strIntrpr generalProc2 syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX (firstArgs `mappend` wordsNN) lstW2 printWarning :: Bool -> String -> IO String printWarning nativeUkrainian xs = do putStrLn . messageInfo 3 $ nativeUkrainian putStrLn xs getLine generalProcMs :: [[[[S.UZPP2]]] -> [[Double]]] -- ^ Whether to use the own provided durations. -> Coeffs2 -> Coeffs2 -> [Array Int Int] -> [String] -> ([Int],Int,Int,String) -> IO [Result [] Char Double Double] generalProcMs syllableDurationsDs coeffs coeffsWX perms subs (intervalNmbrs, arg0, numberI, choice) = do if compare numberI 2 == LT then let !frep2 = if take 1 choice == "x" || take 1 choice == "w" || (take 1 choice == "H" && (drop 1 (take 2 choice) `elem` ["x","w"])) then chooseMax syllableDurationsDs id coeffsWX choice else chooseMax syllableDurationsDs id coeffs choice in return . fst . maximumGroupsClassificationR arg0 . map (toResultR frep2) . uniquenessVariants2GNBL ' ' id id id perms $ subs else do let !variants1 = uniquenessVariants2GNBL ' ' id id id perms subs !frep20 | take 1 choice == "x" || take 1 choice == "w" || (take 1 choice == "H" && (drop 1 (take 2 choice) `elem` ["x","w"])) = chooseMax syllableDurationsDs id coeffsWX choice | otherwise = chooseMax syllableDurationsDs id coeffs choice (!minE,!maxE) = minMax11C . map (toPropertiesF' frep20) $ variants1 !frep2 | take 1 choice == "x" || take 1 choice == "w" || (take 1 choice == "H" && (drop 1 (take 2 choice) `elem` ["x","w"])) = chooseMax syllableDurationsDs (unsafeSwapVecIWithMaxI minE maxE numberI intervalNmbrs) coeffsWX choice | otherwise = chooseMax syllableDurationsDs (unsafeSwapVecIWithMaxI minE maxE numberI intervalNmbrs) coeffs choice return . fst . maximumGroupsClassificationR arg0 . map (toResultR frep2) $ variants1 -- | -- @ since 0.3.0.0 The result is not 'IO' (), but 'IO' 'String'. The type also changed generally. generalProcMMs :: [[[[S.UZPP2]]] -> [[Double]]] -- ^ Whether to use the own provided durations. -> Bool -- ^ Whether to use just pairwise permutations, or the full universal set. -> Bool -> Bool -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> [([Int],Int,Int,String)] -> [Array Int Int] -> [String] -> [String] -> Bool -> IO String generalProcMMs syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian interactiveMM jstL0 args0 coeffs coeffsWX rs perms subs args lstW2 = case length rs of 0 -> putStrLn (messageInfo 4 nativeUkrainian) >> return "" 1 -> putStrLn (messageInfo 5 nativeUkrainian) >> do temp <- generalProcMs syllableDurationsDs coeffs coeffsWX perms subs (head rs) finalProc syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian interactiveMM jstL0 args0 coeffs coeffsWX line temp args lstW2 _ -> do genVariants <- mapM (generalProcMs syllableDurationsDs coeffs coeffsWX perms subs) rs finalProc syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian 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 _ = [] -- | -- @ since 0.3.0.0 The result is not 'IO' (), but 'IO' 'String'. The type also changed generally. finalProc :: [[[[S.UZPP2]]] -> [[Double]]] -- ^ Whether to use the own provided durations. -> Bool -- ^ Whether to use just pairwise permutations, or the full universal set. -> Bool -> Bool -> Bool -> Bool -> [String] -> Coeffs2 -> Coeffs2 -> (a -> String) -> [a] -> [String] -> Bool -> IO String finalProc syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX f xss args lstW2 | recursiveMode = interactivePrintResultRecursive syllableDurationsDs pairwisePermutations recursiveMode nativeUkrainian interactive jstL0 args0 coeffs coeffsWX f xss args lstW2 | interactive = interactivePrintResult nativeUkrainian f xss | otherwise = putStrLn ts >> return 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 -> [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