{-# OPTIONS_GHC -threaded -rtsopts #-}
{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE BangPatterns #-}

-- |
-- Module      :  Phonetic.Languages.General.Simple
-- Copyright   :  (c) OleksandrZhabenko 2020-2021
-- 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.Array.General.PropertiesSyllablesG2
import Phonetic.Languages.Filters (unsafeSwapVecIWithMaxI)
import Phonetic.Languages.Simplified.StrictVG.Base
import Data.Phonetic.Languages.Base
import Data.Phonetic.Languages.PrepareText
import Data.Char (isDigit,isAlpha,isLetter)
import qualified Data.List  as L (span,sort,zip4,isPrefixOf,nub)
import Phonetic.Languages.Simplified.Array.General.FuncRep2RelatedG2
import Phonetic.Languages.Permutations.Arr
import 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 (convStringInterpreter)


forMultiplePropertiesF :: [String] -> [(String,[String])]
forMultiplePropertiesF :: [String] -> [(String, [String])]
forMultiplePropertiesF (String
xs:[String]
xss)
 | (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Char -> Bool
isAlpha String
xs = (String
xs,[String]
yss)(String, [String]) -> [(String, [String])] -> [(String, [String])]
forall a. a -> [a] -> [a]
:[String] -> [(String, [String])]
forMultiplePropertiesF [String]
zss
 | Bool
otherwise = []
     where l :: Int
l = [String] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([String] -> Int) -> ([String] -> [String]) -> [String] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile ((Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isDigit) ([String] -> Int) -> [String] -> Int
forall a b. (a -> b) -> a -> b
$ [String]
xss
           ([String]
yss,[String]
zss) = Int -> [String] -> ([String], [String])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
l [String]
xss
forMultiplePropertiesF [String]
_ = []

-- | Is used to do general processment.
generalProc2G
 :: GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text.
 -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon
  -- (e. g. allophones). Must be sorted in the ascending order to be used correctly.
 -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly.
 -> SegmentRulesG
 -> String
 -> String
 -> (Double -> String -> ([[[PRS]]] -> [[Double]])) -- ^ The function that is needed in the 'procRhythmicity23F' function.
 -- Specifies a way how the syllables represented in the phonetic language approach transforms into their durations and
 -- depends on two parameters. Is specific for every phonetic language and every representation, so must be provided
 -- by the user in every case. The example of the function can be found in the package @phonetic-languages-simplified-properties-array@.
 -> [([[[PRS]]] -> [[Double]])] -- ^ A list of 4 different functions that specifies the syllables durations, analogues of the
  -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most
  -- exact one and, therefore, the default one.
 -> Concatenations -- ^ Data used to concatenate the basic grammar preserving words and word sequences to the next word to
 -- leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to.
 -> String
 -> FilePath
 -> Bool -- ^ Whether to run in the recursive mode.
 -> Bool
 -> Bool
 -> [String]
 -> Coeffs2 -- ^ This value is used when property choice is NOT from the \"w\" or \"x\" lines.
 -> Coeffs2 -- ^ This value is used when property choice is from the \"w\" or \"x\" lines.
 -> [String]
 -> Bool
 -> IO ()
generalProc2G :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> [String]
-> Bool
-> IO ()
generalProc2G GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Concatenations
ysss String
ws String
toFile1 Bool
recursiveMode Bool
interactive Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX [String]
args Bool
lstW2
 | [String] -> Bool
variations [String]
args = do
    let !zsss :: Concatenations
zsss = [String] -> Concatenations
transformToVariations [String]
args
    Concatenations -> IO ()
forall a. Show a => a -> IO ()
print Concatenations
zsss
    [String]
variantsG <- ([String] -> IO String) -> Concatenations -> IO [String]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (\[String]
xss -> GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> [String]
-> Bool
-> IO String
generalProc2 GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Concatenations
ysss String
ws Bool
recursiveMode Bool
interactive Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX [String]
xss Bool
lstW2) Concatenations
zsss
    (if Bool
recursiveMode then GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> (String -> String)
-> [String]
-> [String]
-> Bool
-> IO String
forall a.
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> (a -> String)
-> [a]
-> [String]
-> Bool
-> IO String
interactivePrintResultRecursive GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Concatenations
ysss String
ws Bool
recursiveMode Bool
interactive Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX String -> String
forall a. a -> a
id [String]
variantsG [String]
args Bool
lstW2
     else (String -> String) -> [String] -> IO String
forall a. (a -> String) -> [a] -> IO String
interactivePrintResult String -> String
forall a. a -> a
id [String]
variantsG) IO String -> (String -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \String
rs ->
      case String
toFile1 of
       String
"" -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
       ~String
fileName -> String -> String -> IO ()
appendFile String
fileName (String
rs String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` String
newLineEnding)
 | Bool
otherwise = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> [String]
-> Bool
-> IO String
generalProc2 GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Concatenations
ysss String
ws Bool
recursiveMode Bool
interactive Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX [String]
args Bool
lstW2 IO String -> (String -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \String
rs ->
      case String
toFile1 of
       String
"" -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
       ~String
fileName -> String -> String -> IO ()
appendFile String
fileName (String
rs String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` String
newLineEnding)

-- |
generalProc2
  :: GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text.
  -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon
  -- (e. g. allophones). Must be sorted in the ascending order to be used correctly.
  -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly.
  -> SegmentRulesG
  -> String
  -> String
  -> (Double -> String -> ([[[PRS]]] -> [[Double]])) -- ^ The function that is needed in the 'procRhythmicity23F' function.
 -- Specifies a way how the syllables represented in the phonetic language approach transforms into their durations and
 -- depends on two parameters. Is specific for every phonetic language and every representation, so must be provided
 -- by the user in every case. The example of the function can be found in the package @phonetic-languages-simplified-properties-array@.
  -> [([[[PRS]]] -> [[Double]])] -- ^ A list of 4 different functions that specifies the syllables durations, analogues of the
  -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most
  -- exact one and, therefore, the default one.
  -> Concatenations -- ^ Data used to concatenate the basic grammar preserving words and word sequences to the next word to
 -- leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to.
  -> String
  -> Bool -- ^ Whether to run in the recursive mode.
  -> Bool
  -> Bool
  -> [String]
  -> Coeffs2 -- ^ This value is used when property choice is NOT from the \"w\" or \"x\" lines.
  -> Coeffs2 -- ^ This value is used when property choice is from the \"w\" or \"x\" lines.
  -> [String]
  -> Bool
  -> IO String
generalProc2 :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> [String]
-> Bool
-> IO String
generalProc2 GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Concatenations
ysss String
ws Bool
recursiveMode Bool
interactive Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX [String]
args Bool
lstW2 = do
  let !argMss :: [(String, [String])]
argMss = Int -> [(String, [String])] -> [(String, [String])]
forall a. Int -> [a] -> [a]
take Int
5 ([(String, [String])] -> [(String, [String])])
-> ([String] -> [(String, [String])])
-> [String]
-> [(String, [String])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((String, [String]) -> Bool)
-> [(String, [String])] -> [(String, [String])]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool)
-> ((String, [String]) -> Bool) -> (String, [String]) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String, [String]) -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) ([(String, [String])] -> [(String, [String])])
-> ([String] -> [(String, [String])])
-> [String]
-> [(String, [String])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [(String, [String])]
forMultiplePropertiesF ([String] -> [(String, [String])])
-> ([String] -> [String]) -> [String] -> [(String, [String])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop Int
1 ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"+m") ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"-m") ([String] -> [(String, [String])])
-> [String] -> [(String, [String])]
forall a b. (a -> b) -> a -> b
$ [String]
args0
  if [(String, [String])] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(String, [String])]
argMss then do
   let (![String]
numericArgs,![String]
textualArgs) = (String -> Bool) -> [String] -> ([String], [String])
forall a. (a -> Bool) -> [a] -> ([a], [a])
L.span ((Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isDigit) ([String] -> ([String], [String]))
-> [String] -> ([String], [String])
forall a b. (a -> b) -> a -> b
$ [String]
args
       !xs :: String
xs = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
1 ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Concatenations
-> String -> String -> String -> Int -> String -> [String]
fLines Concatenations
ysss String
ws String
js String
vs Int
0 (String -> [String])
-> ([String] -> String) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
unwords ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop Int
1 ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
textualArgs
       !l :: Int
l = [String] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([String] -> Int) -> (String -> [String]) -> String -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words (String -> Int) -> String -> Int
forall a b. (a -> b) -> a -> b
$ String
xs
       !argCs :: [EncodedCnstrs]
argCs = [Maybe EncodedCnstrs] -> [EncodedCnstrs]
forall a. [Maybe a] -> [a]
catMaybes ((String -> Maybe EncodedCnstrs)
-> [String] -> [Maybe EncodedCnstrs]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> String -> Maybe EncodedCnstrs
readMaybeECG (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)) ([String] -> [Maybe EncodedCnstrs])
-> ([String] -> [String]) -> [String] -> [Maybe EncodedCnstrs]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Bool -> String
showB Int
l Bool
lstW2String -> [String] -> [String]
forall a. a -> [a] -> [a]
:) ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop Int
1 ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"+a") ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
          (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"-a") ([String] -> [Maybe EncodedCnstrs])
-> [String] -> [Maybe EncodedCnstrs]
forall a b. (a -> b) -> a -> b
$ [String]
args0)
       !arg0 :: Int
arg0 = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
1 (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ (String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe ([String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
1 ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
numericArgs)::Maybe Int)
       !numberI :: Int
numberI = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
1 (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ (String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe ([String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop Int
1 ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
2 ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
numericArgs)::Maybe Int)
       !choice :: String
choice = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
1 ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
textualArgs
       !intervalNmbrs :: [Int]
intervalNmbrs = (\[Int]
zs -> if [Int] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Int]
zs then [Int
numberI] else [Int] -> [Int]
forall a. Eq a => [a] -> [a]
L.nub [Int]
zs) ([Int] -> [Int]) -> ([String] -> [Int]) -> [String] -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [Int]
forall a. Ord a => [a] -> [a]
L.sort ([Int] -> [Int]) -> ([String] -> [Int]) -> [String] -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Bool) -> [Int] -> [Int]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
numberI) ([Int] -> [Int]) -> ([String] -> [Int]) -> [String] -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
           (String -> Int) -> [String] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (\String
t -> Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
numberI (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ (String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
t::Maybe Int)) ([String] -> [Int]) -> ([String] -> [String]) -> [String] -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop Int
2 ([String] -> [Int]) -> [String] -> [Int]
forall a b. (a -> b) -> a -> b
$ [String]
numericArgs
   if Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
l Int
2 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
LT then let !frep20 :: FuncRep2 String Double Double
frep20 = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> Double)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double Double
forall c.
Ord c =>
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> c)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double c
chooseMax GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> Double
forall a. a -> a
id Double -> String -> [[[PRS]]] -> [[Double]]
h Coeffs2
coeffs [[[[PRS]]] -> [[Double]]]
qs String
choice in let !wwss :: [Result [] Char Double Double]
wwss = (Result [] Char Double Double
-> [Result [] Char Double Double] -> [Result [] Char Double Double]
forall a. a -> [a] -> [a]
:[]) (Result [] Char Double Double -> [Result [] Char Double Double])
-> (String -> Result [] Char Double Double)
-> String
-> [Result [] Char Double Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FuncRep2 String Double Double
-> String -> Result [] Char Double Double
forall (t :: * -> *) a b c.
FuncRep2 (t a) b c -> t a -> Result t a b c
toResultR FuncRep2 String Double Double
frep20 (String -> [Result [] Char Double Double])
-> String -> [Result [] Char Double Double]
forall a b. (a -> b) -> a -> b
$ String
xs in
    if Bool
recursiveMode then GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> (Result [] Char Double Double -> String)
-> [Result [] Char Double Double]
-> [String]
-> Bool
-> IO String
forall a.
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> (a -> String)
-> [a]
-> [String]
-> Bool
-> IO String
interactivePrintResultRecursive GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Concatenations
ysss String
ws Bool
recursiveMode Bool
interactive Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX Result [] Char Double Double -> String
forall (t :: * -> *) a b c. Result t a b c -> t a
line [Result [] Char Double Double]
wwss [String]
args Bool
lstW2
    else if Bool
interactive then (Result [] Char Double Double -> String)
-> [Result [] Char Double Double] -> IO String
forall a. (a -> String) -> [a] -> IO String
interactivePrintResult Result [] Char Double Double -> String
forall (t :: * -> *) a b c. Result t a b c -> t a
line [Result [] Char Double Double]
wwss else Bool -> String -> [Result [] Char Double Double] -> IO String
print1el Bool
jstL0 String
choice [Result [] Char Double Double]
wwss
   else do
    let !subs :: [String]
subs = String -> String -> [String]
forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a), Monoid (t (t a))) =>
t a -> t a -> t (t a)
subG (Char
' 'Char -> String -> String
forall a. a -> [a] -> [a]
:String
js String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` String
vs) String
xs
    if [EncodedCnstrs] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [EncodedCnstrs]
argCs then let !perms :: [Array Int Int]
perms = Int -> [Array Int Int]
genPermutationsL Int
l in do
          [Result [] Char Double Double]
temp <- GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Coeffs2
-> Coeffs2
-> [Array Int Int]
-> [String]
-> ([Int], Int, Int, String)
-> IO [Result [] Char Double Double]
generalProcMs GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Coeffs2
coeffs Coeffs2
coeffsWX [Array Int Int]
perms [String]
subs ([Int]
intervalNmbrs, Int
arg0, Int
numberI, String
choice)
          if Bool
recursiveMode then GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> (Result [] Char Double Double -> String)
-> [Result [] Char Double Double]
-> [String]
-> Bool
-> IO String
forall a.
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> (a -> String)
-> [a]
-> [String]
-> Bool
-> IO String
interactivePrintResultRecursive GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Concatenations
ysss String
ws Bool
recursiveMode Bool
interactive Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX Result [] Char Double Double -> String
forall (t :: * -> *) a b c. Result t a b c -> t a
line [Result [] Char Double Double]
temp [String]
args Bool
lstW2
          else if Bool
interactive then (Result [] Char Double Double -> String)
-> [Result [] Char Double Double] -> IO String
forall a. (a -> String) -> [a] -> IO String
interactivePrintResult Result [] Char Double Double -> String
forall (t :: * -> *) a b c. Result t a b c -> t a
line [Result [] Char Double Double]
temp else Bool -> String -> [Result [] Char Double Double] -> IO String
print1el Bool
jstL0 String
choice [Result [] Char Double Double]
temp
    else do
     String
correct <- String -> IO String
printWarning String
xs
     if String
correct String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"n" then String -> IO ()
putStrLn (Int -> String
messageInfo Int
1) IO () -> IO String -> IO String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
"" -- 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 :: [Array Int Int]
perms = [EncodedCnstrs] -> [Array Int Int] -> [Array Int Int]
forall (t :: * -> *).
(InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) =>
[EncodedCnstrs] -> t (Array Int Int) -> t (Array Int Int)
decodeLConstraints [EncodedCnstrs]
argCs ([Array Int Int] -> [Array Int Int])
-> (Int -> [Array Int Int]) -> Int -> [Array Int Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Array Int Int]
genPermutationsL (Int -> [Array Int Int]) -> Int -> [Array Int Int]
forall a b. (a -> b) -> a -> b
$ Int
l in do
          [Result [] Char Double Double]
temp <- GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Coeffs2
-> Coeffs2
-> [Array Int Int]
-> [String]
-> ([Int], Int, Int, String)
-> IO [Result [] Char Double Double]
generalProcMs GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Coeffs2
coeffs Coeffs2
coeffsWX [Array Int Int]
perms [String]
subs ([Int]
intervalNmbrs, Int
arg0, Int
numberI, String
choice)
          if Bool
recursiveMode then GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> (Result [] Char Double Double -> String)
-> [Result [] Char Double Double]
-> [String]
-> Bool
-> IO String
forall a.
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> (a -> String)
-> [a]
-> [String]
-> Bool
-> IO String
interactivePrintResultRecursive GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Concatenations
ysss String
ws Bool
recursiveMode Bool
interactive Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX Result [] Char Double Double -> String
forall (t :: * -> *) a b c. Result t a b c -> t a
line [Result [] Char Double Double]
temp [String]
args Bool
lstW2
          else if Bool
interactive then (Result [] Char Double Double -> String)
-> [Result [] Char Double Double] -> IO String
forall a. (a -> String) -> [a] -> IO String
interactivePrintResult Result [] Char Double Double -> String
forall (t :: * -> *) a b c. Result t a b c -> t a
line [Result [] Char Double Double]
temp else Bool -> String -> [Result [] Char Double Double] -> IO String
print1el Bool
jstL0 String
choice [Result [] Char Double Double]
temp
  else do
   let !choices :: [String]
choices = ((String, [String]) -> String) -> [(String, [String])] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String, [String]) -> String
forall a b. (a, b) -> a
fst [(String, [String])]
argMss
       !numericArgss :: Concatenations
numericArgss = ((String, [String]) -> [String])
-> [(String, [String])] -> Concatenations
forall a b. (a -> b) -> [a] -> [b]
map (String, [String]) -> [String]
forall a b. (a, b) -> b
snd [(String, [String])]
argMss
       !arg0s :: [Int]
arg0s = ([String] -> Int) -> Concatenations -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (\[String]
ts -> Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
1 (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ (String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe ([String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
1 ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
ts)::Maybe Int)) Concatenations
numericArgss
       !numberIs :: [Int]
numberIs = ([String] -> Int) -> Concatenations -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (\[String]
ts -> Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
1 (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ (String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe ([String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop Int
1 ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
2 ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
ts)::Maybe Int)) Concatenations
numericArgss
       !intervalNmbrss :: [[Int]]
intervalNmbrss = ([String] -> [Int]) -> Concatenations -> [[Int]]
forall a b. (a -> b) -> [a] -> [b]
map (\[String]
us -> let !numberI :: Int
numberI = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
1 (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ (String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe ([String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop Int
1 ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
2 ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
us)::Maybe Int) in
         (\[Int]
zs -> if [Int] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Int]
zs then [Int
numberI] else [Int] -> [Int]
forall a. Eq a => [a] -> [a]
L.nub [Int]
zs) ([Int] -> [Int]) -> ([String] -> [Int]) -> [String] -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [Int]
forall a. Ord a => [a] -> [a]
L.sort ([Int] -> [Int]) -> ([String] -> [Int]) -> [String] -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Bool) -> [Int] -> [Int]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
numberI) ([Int] -> [Int]) -> ([String] -> [Int]) -> [String] -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
           (String -> Int) -> [String] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (\String
t -> Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
numberI (Maybe Int -> Int) -> Maybe Int -> Int
forall a b. (a -> b) -> a -> b
$ (String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
t::Maybe Int)) ([String] -> [Int]) -> ([String] -> [String]) -> [String] -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop Int
2 ([String] -> [Int]) -> [String] -> [Int]
forall a b. (a -> b) -> a -> b
$ [String]
us) (Concatenations -> [[Int]]) -> Concatenations -> [[Int]]
forall a b. (a -> b) -> a -> b
$ Concatenations
numericArgss
       !argsZipped :: [([Int], Int, Int, String)]
argsZipped = [[Int]]
-> [Int] -> [Int] -> [String] -> [([Int], Int, Int, String)]
forall a b c d. [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)]
L.zip4 [[Int]]
intervalNmbrss [Int]
arg0s [Int]
numberIs [String]
choices
       !xs :: String
xs = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
1 ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Concatenations
-> String -> String -> String -> Int -> String -> [String]
fLines Concatenations
ysss String
ws String
js String
vs Int
0 (String -> [String])
-> ([String] -> String) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
unwords ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
args
       !l :: Int
l = [String] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([String] -> Int) -> (String -> [String]) -> String -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words (String -> Int) -> String -> Int
forall a b. (a -> b) -> a -> b
$ String
xs
       !argCs :: [EncodedCnstrs]
argCs = [Maybe EncodedCnstrs] -> [EncodedCnstrs]
forall a. [Maybe a] -> [a]
catMaybes ((String -> Maybe EncodedCnstrs)
-> [String] -> [Maybe EncodedCnstrs]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> String -> Maybe EncodedCnstrs
readMaybeECG (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)) ([String] -> [Maybe EncodedCnstrs])
-> ([String] -> [String]) -> [String] -> [Maybe EncodedCnstrs]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Bool -> String
showB Int
l Bool
lstW2String -> [String] -> [String]
forall a. a -> [a] -> [a]
:) ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop Int
1 ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"+a") ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
          (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"-a") ([String] -> [Maybe EncodedCnstrs])
-> [String] -> [Maybe EncodedCnstrs]
forall a b. (a -> b) -> a -> b
$ [String]
args0)
   if Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
l Int
2 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
LT then let !frep20 :: FuncRep2 String Double Double
frep20 = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> Double)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double Double
forall c.
Ord c =>
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> c)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double c
chooseMax GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> Double
forall a. a -> a
id Double -> String -> [[[PRS]]] -> [[Double]]
h Coeffs2
coeffs [[[[PRS]]] -> [[Double]]]
qs ([String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
1 ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
choices) in
    let !wwss :: [Result [] Char Double Double]
wwss = (Result [] Char Double Double
-> [Result [] Char Double Double] -> [Result [] Char Double Double]
forall a. a -> [a] -> [a]
:[]) (Result [] Char Double Double -> [Result [] Char Double Double])
-> (String -> Result [] Char Double Double)
-> String
-> [Result [] Char Double Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FuncRep2 String Double Double
-> String -> Result [] Char Double Double
forall (t :: * -> *) a b c.
FuncRep2 (t a) b c -> t a -> Result t a b c
toResultR FuncRep2 String Double Double
frep20 (String -> [Result [] Char Double Double])
-> String -> [Result [] Char Double Double]
forall a b. (a -> b) -> a -> b
$ String
xs in
       if Bool
recursiveMode then GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> (Result [] Char Double Double -> String)
-> [Result [] Char Double Double]
-> [String]
-> Bool
-> IO String
forall a.
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> (a -> String)
-> [a]
-> [String]
-> Bool
-> IO String
interactivePrintResultRecursive GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Concatenations
ysss String
ws Bool
recursiveMode Bool
interactive Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX Result [] Char Double Double -> String
forall (t :: * -> *) a b c. Result t a b c -> t a
line [Result [] Char Double Double]
wwss [String]
args Bool
lstW2
       else if Bool
interactive then (Result [] Char Double Double -> String)
-> [Result [] Char Double Double] -> IO String
forall a. (a -> String) -> [a] -> IO String
interactivePrintResult Result [] Char Double Double -> String
forall (t :: * -> *) a b c. Result t a b c -> t a
line [Result [] Char Double Double]
wwss
            else Bool -> String -> [Result [] Char Double Double] -> IO String
print1el Bool
jstL0 ([String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
1 ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
choices) [Result [] Char Double Double]
wwss
   else do
    let !subs :: [String]
subs = String -> String -> [String]
forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a), Monoid (t (t a))) =>
t a -> t a -> t (t a)
subG (Char
' 'Char -> String -> String
forall a. a -> [a] -> [a]
:String
js String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` String
vs) String
xs
    if [EncodedCnstrs] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [EncodedCnstrs]
argCs then let !perms :: [Array Int Int]
perms = Int -> [Array Int Int]
genPermutationsL Int
l in
      GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> [([Int], Int, Int, String)]
-> [Array Int Int]
-> [String]
-> [String]
-> Bool
-> IO String
generalProcMMs GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Concatenations
ysss String
ws Bool
recursiveMode Bool
interactive Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX [([Int], Int, Int, String)]
argsZipped [Array Int Int]
perms [String]
subs [String]
args Bool
lstW2
    else do
     String
correct <- String -> IO String
printWarning String
xs
     if String
correct String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"n" then String -> IO ()
putStrLn (Int -> String
messageInfo Int
1) IO () -> IO String -> IO String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
"" -- 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 :: [Array Int Int]
perms = [EncodedCnstrs] -> [Array Int Int] -> [Array Int Int]
forall (t :: * -> *).
(InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) =>
[EncodedCnstrs] -> t (Array Int Int) -> t (Array Int Int)
decodeLConstraints [EncodedCnstrs]
argCs ([Array Int Int] -> [Array Int Int])
-> (Int -> [Array Int Int]) -> Int -> [Array Int Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Array Int Int]
genPermutationsL (Int -> [Array Int Int]) -> Int -> [Array Int Int]
forall a b. (a -> b) -> a -> b
$ Int
l in
            GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> [([Int], Int, Int, String)]
-> [Array Int Int]
-> [String]
-> [String]
-> Bool
-> IO String
generalProcMMs GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Concatenations
ysss String
ws Bool
recursiveMode Bool
interactive Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX [([Int], Int, Int, String)]
argsZipped [Array Int Int]
perms [String]
subs [String]
args Bool
lstW2

-- | Function provides message information.
messageInfo :: Int -> String
messageInfo :: Int -> String
messageInfo Int
n
 | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = String
"You stopped the program, please, if needed, run it again with better arguments. "
 | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2 = String
"Please, specify the variant which you would like to become the resulting string by its number. "
 | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
3 = String
"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. " String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` String
newLineEnding String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` String
"If the line is consistent with your input between +a and -a then just press Enter to proceed further. " String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` String
newLineEnding
 | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
4 = String
"No data has been specified to control the computation process. "
 | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
5 = String
"(/ 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 /)"
 | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
6 = String
"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."
 | Bool
otherwise = String
"You have specified just one variant of the properties. "

-- |
interactivePrintResult :: (a -> String) -> [a] -> IO String
interactivePrintResult :: (a -> String) -> [a] -> IO String
interactivePrintResult a -> String
f [a]
xss
  | [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
xss = (String -> IO ()
putStrLn (String -> IO ()) -> (Int -> String) -> Int -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
messageInfo (Int -> IO ()) -> Int -> IO ()
forall a b. (a -> b) -> a -> b
$ Int
5) IO () -> IO String -> IO String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
""
  | Bool
otherwise = do
     let !datas :: [String]
datas = ((Int, String) -> String) -> [(Int, String)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\(Int
idx,String
str) -> Int -> String
forall a. Show a => a -> String
show Int
idx String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` (Char
'\t' Char -> String -> String
forall a. a -> [a] -> [a]
: String
str)) ([(Int, String)] -> [String])
-> ([a] -> [(Int, String)]) -> [a] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [(Int, String)]
forall a. [[a]] -> [(Int, [a])]
trans232 ([String] -> [(Int, String)])
-> ([a] -> [String]) -> [a] -> [(Int, String)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> String) -> [a] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map a -> String
f ([a] -> [String]) -> [a] -> [String]
forall a b. (a -> b) -> a -> b
$ [a]
xss
     if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
datas then (String -> IO ()
putStrLn (String -> IO ()) -> (Int -> String) -> Int -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
messageInfo (Int -> IO ()) -> Int -> IO ()
forall a b. (a -> b) -> a -> b
$ Int
5) IO () -> IO String -> IO String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
""
     else do
      (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ String -> IO ()
putStrLn [String]
datas
      String -> IO ()
putStrLn String
""
      String -> IO ()
putStrLn (String -> IO ()) -> (Int -> String) -> Int -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
messageInfo (Int -> IO ()) -> Int -> IO ()
forall a b. (a -> b) -> a -> b
$ Int
2
      String
number <- IO String
getLine
      let !lineRes :: String
lineRes = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter ((String
number String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` String
"\t")String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`L.isPrefixOf`) ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
datas
          !ts :: String
ts = Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\t') (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
lineRes
      String -> IO ()
putStrLn String
ts IO () -> IO String -> IO String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
ts

interactivePrintResultRecursive
 :: GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text.
 -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon
 -- (e. g. allophones). Must be sorted in the ascending order to be used correctly.
 -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly.
 -> SegmentRulesG
 -> String
 -> String
 -> (Double -> String -> ([[[PRS]]] -> [[Double]])) -- ^ The function that is needed in the 'procRhythmicity23F' function.
 -- Specifies a way how the syllables represented in the phonetic language approach transforms into their durations and
 -- depends on two parameters. Is specific for every phonetic language and every representation, so must be provided
 -- by the user in every case. The example of the function can be found in the package @phonetic-languages-simplified-properties-array@.
 -> [([[[PRS]]] -> [[Double]])] -- ^ A list of 4 different functions that specifies the syllables durations, analogues of the
 -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most
 -- exact one and, therefore, the default one.
 -> Concatenations -- ^ Data used to concatenate the basic grammar preserving words and word sequences to the next word to
 -- leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to.
 -> String
 -> Bool -- ^ Whether to run in the recursive mode.
 -> Bool
 -> Bool
 -> [String]
 -> Coeffs2
 -> Coeffs2
 -> (a -> String)
 -> [a]
 -> [String]
 -> Bool
 -> IO String
interactivePrintResultRecursive :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> (a -> String)
-> [a]
-> [String]
-> Bool
-> IO String
interactivePrintResultRecursive GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Concatenations
ysss String
ws Bool
recursiveMode Bool
interactive Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX a -> String
f [a]
xss [String]
args Bool
lstW2
  | [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
xss = (String -> IO ()
putStrLn (String -> IO ()) -> (Int -> String) -> Int -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
messageInfo (Int -> IO ()) -> Int -> IO ()
forall a b. (a -> b) -> a -> b
$ Int
5) IO () -> IO String -> IO String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
""
  | Bool
otherwise = do
     let !datas :: [String]
datas = ((Int, String) -> String) -> [(Int, String)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\(Int
idx,String
str) -> Int -> String
forall a. Show a => a -> String
show Int
idx String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` (Char
'\t' Char -> String -> String
forall a. a -> [a] -> [a]
: String
str)) ([(Int, String)] -> [String])
-> ([a] -> [(Int, String)]) -> [a] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [(Int, String)]
forall a. [[a]] -> [(Int, [a])]
trans232 ([String] -> [(Int, String)])
-> ([a] -> [String]) -> [a] -> [(Int, String)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> String) -> [a] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map a -> String
f ([a] -> [String]) -> [a] -> [String]
forall a b. (a -> b) -> a -> b
$ [a]
xss
     (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ String -> IO ()
putStrLn [String]
datas
     String -> IO ()
putStrLn String
""
     String -> IO ()
putStrLn (String -> IO ()) -> (Int -> String) -> Int -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
messageInfo (Int -> IO ()) -> Int -> IO ()
forall a b. (a -> b) -> a -> b
$ Int
2
     String
number <- IO String
getLine
     let !lineRes :: String
lineRes = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter ((String
number String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` String
"\t")String -> String -> Bool
forall a. Eq a => [a] -> [a] -> Bool
`L.isPrefixOf`) ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
datas
         !ts :: String
ts = Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'\t') (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
lineRes
     String -> IO ()
putStrLn (String -> IO ()) -> (Int -> String) -> Int -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
messageInfo (Int -> IO ()) -> Int -> IO ()
forall a b. (a -> b) -> a -> b
$ Int
6
     String
stringInterpreted <- IO String
getLine
     if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
stringInterpreted then String -> IO ()
putStrLn String
ts IO () -> IO String -> IO String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
ts
     else do
       let strIntrpr :: String
strIntrpr = String -> String -> String
convStringInterpreter String
stringInterpreted String
ts
           wordsNN :: [String]
wordsNN = Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
7 ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words (String -> [String]) -> String -> [String]
forall a b. (a -> b) -> a -> b
$ String
strIntrpr
           !firstArgs :: [String]
firstArgs = (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Bool -> Bool
not (Bool -> Bool) -> (String -> Bool) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Char -> Bool
isLetter) [String]
args
       GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> [String]
-> Bool
-> IO String
generalProc2 GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Concatenations
ysss String
ws Bool
recursiveMode Bool
interactive Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX ([String]
firstArgs [String] -> [String] -> [String]
forall a. Monoid a => a -> a -> a
`mappend` [String]
wordsNN) Bool
lstW2

printWarning :: String -> IO String
printWarning :: String -> IO String
printWarning String
xs = do
  String -> IO ()
putStrLn (String -> IO ()) -> (Int -> String) -> Int -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
messageInfo (Int -> IO ()) -> Int -> IO ()
forall a b. (a -> b) -> a -> b
$ Int
3
  String -> IO ()
putStrLn String
xs
  IO String
getLine

generalProcMs
 :: GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text.
 -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon
  -- (e. g. allophones). Must be sorted in the ascending order to be used correctly.
 -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly.
 -> SegmentRulesG
 -> String
 -> String
 -> (Double -> String -> ([[[PRS]]] -> [[Double]])) -- ^ The function that is needed in the 'procRhythmicity23F' function.
 -- Specifies a way how the syllables represented in the phonetic language approach transforms into their durations and
 -- depends on two parameters. Is specific for every phonetic language and every representation, so must be provided
 -- by the user in every case. The example of the function can be found in the package @phonetic-languages-simplified-properties-array@.
 -> [([[[PRS]]] -> [[Double]])] -- ^ A list of 4 different functions that specifies the syllables durations, analogues of the
  -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most
  -- exact one and, therefore, the default one.
 -> Coeffs2 -- ^ This value is used when property choice is NOT from the \"w\" or \"x\" lines.
 -> Coeffs2 -- ^ This value is used when property choice is from the \"w\" or \"x\" lines.
 -> [Array Int Int]  -- ^ Permutations data.
 -> [String]
 -> ([Int],Int,Int,String) -- ^ The 'String' is intended to be one of the following strings: \"02y\", \"02z\", \"03y\", \"03z\", \"04y\", \"04z\",
 -- \"0y\", \"0z\", \"y\", \"y0\", \"y2\", \"y3\", \"y4\", \"yy\", \"yy2\", \"yy3\", \"z\", \"z2\", \"z3\", \"z4\",
 -- \"zz\", \"zz2\", \"zz3\", \"zz4\" or some other one (that is the default one). Since 0.5.0.0 version can also
 -- process \"w\" and \"x\"-based lines properties. Specifies the applied properties
 -- to get the result. The \"z\"-line uses \'F\' functions.
 -- @ since 0.6.0.0
 -- Changed the arguments signing so that capital letters changed to the small ones, double ++ changed to just singular +.
 -> IO [Result [] Char Double Double]
generalProcMs :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Coeffs2
-> Coeffs2
-> [Array Int Int]
-> [String]
-> ([Int], Int, Int, String)
-> IO [Result [] Char Double Double]
generalProcMs GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Coeffs2
coeffs Coeffs2
coeffsWX [Array Int Int]
perms [String]
subs ([Int]
intervalNmbrs, Int
arg0, Int
numberI, String
choice) = do
  if Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
numberI Int
2 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
LT
   then let !frep2 :: FuncRep2 String Double Double
frep2
              | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"w" Bool -> Bool -> Bool
|| Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"x" = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> Double)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double Double
forall c.
Ord c =>
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> c)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double c
chooseMax GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> Double
forall a. a -> a
id Double -> String -> [[[PRS]]] -> [[Double]]
h Coeffs2
coeffsWX [[[[PRS]]] -> [[Double]]]
qs String
choice
              | Bool
otherwise = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> Double)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double Double
forall c.
Ord c =>
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> c)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double c
chooseMax GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> Double
forall a. a -> a
id Double -> String -> [[[PRS]]] -> [[Double]]
h Coeffs2
coeffs [[[[PRS]]] -> [[Double]]]
qs String
choice
                 in [Result [] Char Double Double] -> IO [Result [] Char Double Double]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Result [] Char Double Double]
 -> IO [Result [] Char Double Double])
-> ([String] -> [Result [] Char Double Double])
-> [String]
-> IO [Result [] Char Double Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Result [] Char Double Double], [Result [] Char Double Double])
-> [Result [] Char Double Double]
forall a b. (a, b) -> a
fst (([Result [] Char Double Double], [Result [] Char Double Double])
 -> [Result [] Char Double Double])
-> ([String]
    -> ([Result [] Char Double Double],
        [Result [] Char Double Double]))
-> [String]
-> [Result [] Char Double Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int
-> [Result [] Char Double Double]
-> ([Result [] Char Double Double], [Result [] Char Double Double])
forall (t2 :: * -> *) (t :: * -> *) a b c d.
(InsertLeft t2 (Result t a b c), Monoid (t2 (Result t a b c)),
 InsertLeft t2 c, Monoid (t2 c), Ord c, Integral d) =>
d
-> t2 (Result t a b c)
-> (t2 (Result t a b c), t2 (Result t a b c))
maximumGroupsClassificationR Int
arg0 ([Result [] Char Double Double]
 -> ([Result [] Char Double Double],
     [Result [] Char Double Double]))
-> ([String] -> [Result [] Char Double Double])
-> [String]
-> ([Result [] Char Double Double], [Result [] Char Double Double])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Result [] Char Double Double)
-> [String] -> [Result [] Char Double Double]
forall a b. (a -> b) -> [a] -> [b]
map (FuncRep2 String Double Double
-> String -> Result [] Char Double Double
forall (t :: * -> *) a b c.
FuncRep2 (t a) b c -> t a -> Result t a b c
toResultR FuncRep2 String Double Double
frep2) ([String] -> [Result [] Char Double Double])
-> ([String] -> [String])
-> [String]
-> [Result [] Char Double Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char
-> (String -> String)
-> ([String] -> [String])
-> (String -> String)
-> [Array Int Int]
-> [String]
-> [String]
forall a (t :: * -> *).
(Eq a, Foldable t, InsertLeft t a, Monoid (t a),
 Monoid (t (t a))) =>
a
-> (t a -> [a])
-> (t (t a) -> [[a]])
-> ([a] -> t a)
-> [Array Int Int]
-> t (t a)
-> [t a]
uniquenessVariants2GNBL Char
' ' String -> String
forall a. a -> a
id [String] -> [String]
forall a. a -> a
id String -> String
forall a. a -> a
id [Array Int Int]
perms ([String] -> IO [Result [] Char Double Double])
-> [String] -> IO [Result [] Char Double Double]
forall a b. (a -> b) -> a -> b
$ [String]
subs
   else do
    let !variants1 :: [String]
variants1 = Char
-> (String -> String)
-> ([String] -> [String])
-> (String -> String)
-> [Array Int Int]
-> [String]
-> [String]
forall a (t :: * -> *).
(Eq a, Foldable t, InsertLeft t a, Monoid (t a),
 Monoid (t (t a))) =>
a
-> (t a -> [a])
-> (t (t a) -> [[a]])
-> ([a] -> t a)
-> [Array Int Int]
-> t (t a)
-> [t a]
uniquenessVariants2GNBL Char
' ' String -> String
forall a. a -> a
id [String] -> [String]
forall a. a -> a
id String -> String
forall a. a -> a
id [Array Int Int]
perms [String]
subs
        !frep20 :: FuncRep2 String Double Double
frep20
          | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"w" Bool -> Bool -> Bool
|| Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"x" = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> Double)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double Double
forall c.
Ord c =>
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> c)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double c
chooseMax GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> Double
forall a. a -> a
id Double -> String -> [[[PRS]]] -> [[Double]]
h Coeffs2
coeffsWX [[[[PRS]]] -> [[Double]]]
qs String
choice
          | Bool
otherwise = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> Double)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double Double
forall c.
Ord c =>
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> c)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double c
chooseMax GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> Double
forall a. a -> a
id Double -> String -> [[[PRS]]] -> [[Double]]
h Coeffs2
coeffs [[[[PRS]]] -> [[Double]]]
qs String
choice
        (!Double
minE,!Double
maxE) = [Double] -> (Double, Double)
forall a (t :: * -> *).
(Ord a, InsertLeft t a, Monoid (t a)) =>
t a -> (a, a)
minMax11C ([Double] -> (Double, Double))
-> ([String] -> [Double]) -> [String] -> (Double, Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Double) -> [String] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map (FuncRep2 String Double Double -> String -> Double
forall (t :: * -> *) a b c. FuncRep2 (t a) b c -> t a -> b
toPropertiesF' FuncRep2 String Double Double
frep20) ([String] -> (Double, Double)) -> [String] -> (Double, Double)
forall a b. (a -> b) -> a -> b
$ [String]
variants1
        !frep2 :: FuncRep2 String Double Double
frep2
          | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"w" Bool -> Bool -> Bool
|| Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"x" = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> Double)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double Double
forall c.
Ord c =>
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> c)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double c
chooseMax GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs (Double -> Double -> Int -> [Int] -> Double -> Double
forall b c.
(RealFrac b, Integral c) =>
b -> b -> c -> [c] -> b -> b
unsafeSwapVecIWithMaxI Double
minE Double
maxE Int
numberI [Int]
intervalNmbrs) Double -> String -> [[[PRS]]] -> [[Double]]
h Coeffs2
coeffsWX [[[[PRS]]] -> [[Double]]]
qs String
choice
          | Bool
otherwise = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> Double)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double Double
forall c.
Ord c =>
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> c)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double c
chooseMax GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs (Double -> Double -> Int -> [Int] -> Double -> Double
forall b c.
(RealFrac b, Integral c) =>
b -> b -> c -> [c] -> b -> b
unsafeSwapVecIWithMaxI Double
minE Double
maxE Int
numberI [Int]
intervalNmbrs) Double -> String -> [[[PRS]]] -> [[Double]]
h Coeffs2
coeffs [[[[PRS]]] -> [[Double]]]
qs String
choice
    [Result [] Char Double Double] -> IO [Result [] Char Double Double]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Result [] Char Double Double]
 -> IO [Result [] Char Double Double])
-> ([String] -> [Result [] Char Double Double])
-> [String]
-> IO [Result [] Char Double Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Result [] Char Double Double], [Result [] Char Double Double])
-> [Result [] Char Double Double]
forall a b. (a, b) -> a
fst (([Result [] Char Double Double], [Result [] Char Double Double])
 -> [Result [] Char Double Double])
-> ([String]
    -> ([Result [] Char Double Double],
        [Result [] Char Double Double]))
-> [String]
-> [Result [] Char Double Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int
-> [Result [] Char Double Double]
-> ([Result [] Char Double Double], [Result [] Char Double Double])
forall (t2 :: * -> *) (t :: * -> *) a b c d.
(InsertLeft t2 (Result t a b c), Monoid (t2 (Result t a b c)),
 InsertLeft t2 c, Monoid (t2 c), Ord c, Integral d) =>
d
-> t2 (Result t a b c)
-> (t2 (Result t a b c), t2 (Result t a b c))
maximumGroupsClassificationR Int
arg0 ([Result [] Char Double Double]
 -> ([Result [] Char Double Double],
     [Result [] Char Double Double]))
-> ([String] -> [Result [] Char Double Double])
-> [String]
-> ([Result [] Char Double Double], [Result [] Char Double Double])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Result [] Char Double Double)
-> [String] -> [Result [] Char Double Double]
forall a b. (a -> b) -> [a] -> [b]
map (FuncRep2 String Double Double
-> String -> Result [] Char Double Double
forall (t :: * -> *) a b c.
FuncRep2 (t a) b c -> t a -> Result t a b c
toResultR FuncRep2 String Double Double
frep2) ([String] -> IO [Result [] Char Double Double])
-> [String] -> IO [Result [] Char Double Double]
forall a b. (a -> b) -> a -> b
$ [String]
variants1

-- |
generalProcMMs
 :: GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text.
 -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon
  -- (e. g. allophones). Must be sorted in the ascending order to be used correctly.
 -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly.
 -> SegmentRulesG
 -> String
 -> String
 -> (Double -> String -> ([[[PRS]]] -> [[Double]])) -- ^ The function that is needed in the 'procRhythmicity23F' function.
 -- Specifies a way how the syllables represented in the phonetic language approach transforms into their durations and
 -- depends on two parameters. Is specific for every phonetic language and every representation, so must be provided
 -- by the user in every case. The example of the function can be found in the package @phonetic-languages-simplified-properties-array@.
 -> [([[[PRS]]] -> [[Double]])] -- ^ A list of 4 different functions that specifies the syllables durations, analogues of the
  -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most
  -- exact one and, therefore, the default one.
 -> Concatenations -- ^ Data used to concatenate 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],Int,Int,String)] -- ^ The 'String' is intended to be one of the following strings: \"02y\", \"02z\", \"03y\", \"03z\", \"04y\", \"04z\",
 -- \"0y\", \"0z\", \"y\", \"y0\", \"y2\", \"y3\", \"y4\", \"yy\", \"yy2\", \"yy3\", \"z\", \"z2\", \"z3\", \"z4\",
 -- \"zz\", \"zz2\", \"zz3\", \"zz4\" or some other one (that is the default one). Since 0.5.0.0 version can also
 -- process \"w\" and \"x\"-based lines properties. Specifies the applied properties
 -- to get the result. The \"z\"-line uses \'F\' functions.
 -- @ since 0.6.0.0
 -- Changed the arguments signing so that capital letters changed to the small ones, double ++ changed to just singular +.
 -> [Array Int Int] -- ^ Permutations data.
 -> [String]
 -> [String]
 -> Bool
 -> IO String
generalProcMMs :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> [([Int], Int, Int, String)]
-> [Array Int Int]
-> [String]
-> [String]
-> Bool
-> IO String
generalProcMMs GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Concatenations
ysss String
ws Bool
recursiveMode Bool
interactiveMM Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX [([Int], Int, Int, String)]
rs [Array Int Int]
perms [String]
subs [String]
args Bool
lstW2 =
 case [([Int], Int, Int, String)] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [([Int], Int, Int, String)]
rs of
  Int
0 -> String -> IO ()
putStrLn (Int -> String
messageInfo Int
4) IO () -> IO String -> IO String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
""
  Int
1 -> String -> IO ()
putStrLn (Int -> String
messageInfo Int
5) IO () -> IO String -> IO String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> do
        [Result [] Char Double Double]
temp <- GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Coeffs2
-> Coeffs2
-> [Array Int Int]
-> [String]
-> ([Int], Int, Int, String)
-> IO [Result [] Char Double Double]
generalProcMs GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Coeffs2
coeffs Coeffs2
coeffsWX [Array Int Int]
perms [String]
subs ([([Int], Int, Int, String)] -> ([Int], Int, Int, String)
forall a. [a] -> a
head [([Int], Int, Int, String)]
rs)
        GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> (Result [] Char Double Double -> String)
-> [Result [] Char Double Double]
-> [String]
-> Bool
-> IO String
forall a.
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> (a -> String)
-> [a]
-> [String]
-> Bool
-> IO String
finalProc GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Concatenations
ysss String
ws Bool
recursiveMode Bool
interactiveMM Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX Result [] Char Double Double -> String
forall (t :: * -> *) a b c. Result t a b c -> t a
line [Result [] Char Double Double]
temp [String]
args Bool
lstW2
  Int
_ -> do
         [[Result [] Char Double Double]]
genVariants <- (([Int], Int, Int, String) -> IO [Result [] Char Double Double])
-> [([Int], Int, Int, String)]
-> IO [[Result [] Char Double Double]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Coeffs2
-> Coeffs2
-> [Array Int Int]
-> [String]
-> ([Int], Int, Int, String)
-> IO [Result [] Char Double Double]
generalProcMs GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Coeffs2
coeffs Coeffs2
coeffsWX [Array Int Int]
perms [String]
subs) [([Int], Int, Int, String)]
rs
         GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> (String -> String)
-> [String]
-> [String]
-> Bool
-> IO String
forall a.
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> (a -> String)
-> [a]
-> [String]
-> Bool
-> IO String
finalProc GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Concatenations
ysss String
ws Bool
recursiveMode Bool
interactiveMM Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX String -> String
forall a. a -> a
id (Concatenations -> [String]
foldlI (Concatenations -> [String])
-> ([[Result [] Char Double Double]] -> Concatenations)
-> [[Result [] Char Double Double]]
-> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Result [] Char Double Double] -> [String])
-> [[Result [] Char Double Double]] -> Concatenations
forall a b. (a -> b) -> [a] -> [b]
map ((Result [] Char Double Double -> String)
-> [Result [] Char Double Double] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Result [] Char Double Double -> String
forall (t :: * -> *) a b c. Result t a b c -> t a
line) ([[Result [] Char Double Double]] -> [String])
-> [[Result [] Char Double Double]] -> [String]
forall a b. (a -> b) -> a -> b
$ [[Result [] Char Double Double]]
genVariants) [String]
args Bool
lstW2

foldlI :: [[String]] -> [String]
foldlI :: Concatenations -> [String]
foldlI ([String]
xs:[String]
ys:Concatenations
xss) = Concatenations -> [String]
foldlI ([String] -> [String] -> [String]
intersectInterResults [String]
xs [String]
ys [String] -> Concatenations -> Concatenations
forall a. a -> [a] -> [a]
: Concatenations
xss)
foldlI ([String]
xs:Concatenations
_) = [String]
xs
foldlI Concatenations
_ = []

-- |
finalProc
 :: GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text.
 -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon
  -- (e. g. allophones). Must be sorted in the ascending order to be used correctly.
 -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly.
 -> SegmentRulesG
 -> String
 -> String
 -> (Double -> String -> ([[[PRS]]] -> [[Double]])) -- ^ The function that is needed in the 'procRhythmicity23F' function.
 -- Specifies a way how the syllables represented in the phonetic language approach transforms into their durations and
 -- depends on two parameters. Is specific for every phonetic language and every representation, so must be provided
 -- by the user in every case. The example of the function can be found in the package @phonetic-languages-simplified-properties-array@.
 -> [([[[PRS]]] -> [[Double]])] -- ^ A list of 4 different functions that specifies the syllables durations, analogues of the
  -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most
  -- exact one and, therefore, the default one.
 -> Concatenations -- ^ Data used to concatenate the basic grammar preserving words and word sequences to the next word to
 -- leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to.
 -> String
 -> Bool -- ^ Whether to run in the recursive mode.
 -> Bool
 -> Bool
 -> [String]
 -> Coeffs2
 -> Coeffs2
 -> (a -> String)
 -> [a]
 -> [String]
 -> Bool
 -> IO String
finalProc :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> (a -> String)
-> [a]
-> [String]
-> Bool
-> IO String
finalProc  GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Concatenations
ysss String
ws Bool
recursiveMode Bool
interactive Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX a -> String
f [a]
xss [String]
args Bool
lstW2
 | Bool
recursiveMode = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> (a -> String)
-> [a]
-> [String]
-> Bool
-> IO String
forall a.
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> (a -> String)
-> [a]
-> [String]
-> Bool
-> IO String
interactivePrintResultRecursive GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Concatenations
ysss String
ws Bool
recursiveMode Bool
interactive Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX a -> String
f [a]
xss [String]
args Bool
lstW2
 | Bool
otherwise = if Bool
interactive then (a -> String) -> [a] -> IO String
forall a. (a -> String) -> [a] -> IO String
interactivePrintResult a -> String
f [a]
xss else String -> IO ()
putStrLn String
ts IO () -> IO String -> IO String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
ts
  where ts :: String
ts = (a -> String) -> [a] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\a
t -> a -> String
f a
t String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` String
newLineEnding) [a]
xss

-- |
print1el :: Bool -> String -> [Result [] Char Double Double] -> IO String
print1el :: Bool -> String -> [Result [] Char Double Double] -> IO String
print1el Bool
jstlines String
choice [Result [] Char Double Double]
y
 | Bool
jstlines Bool -> Bool -> Bool
forall a. Eq a => a -> a -> Bool
== Bool
True = String -> IO ()
putStrLn String
us IO () -> IO String -> IO String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
us
 | Bool
otherwise = String -> IO ()
putStrLn String
zs IO () -> IO String -> IO String
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
zs
       where !ch :: Maybe Int
ch = String -> Maybe Int
precChoice String
choice
             !us :: String
us = (Result [] Char Double Double -> String)
-> [Result [] Char Double Double] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\Result [] Char Double Double
ys -> Result [] Char Double Double -> String
forall (t :: * -> *) a b c. Result t a b c -> t a
line Result [] Char Double Double
ys String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` String
newLineEnding) [Result [] Char Double Double]
y
             !zs :: String
zs = (Result [] Char Double Double -> String)
-> [Result [] Char Double Double] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\Result [] Char Double Double
ys -> Result [] Char Double Double -> String
forall (t :: * -> *) a b c. Result t a b c -> t a
line Result [] Char Double Double
ys String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` String
newLineEnding String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` Maybe Int -> Double -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat Maybe Int
ch (Result [] Char Double Double -> Double
forall (t :: * -> *) a b c. Result t a b c -> b
propertiesF Result [] Char Double Double
ys) (String
newLineEnding String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` Maybe Int -> Double -> String -> String
forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat Maybe Int
ch (Result [] Char Double Double -> Double
forall (t :: * -> *) a b c. Result t a b c -> c
transPropertiesF Result [] Char Double Double
ys) String
newLineEnding)) [Result [] Char Double Double]
y