-- | -- Module : Phonetic.Languages.Simplified.Array.General.FuncRep2RelatedG2 -- Copyright : (c) OleksandrZhabenko 2020-2021 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Functions to choose from the 'FuncRep2' variants for the general phonetic languages approach. {-# LANGUAGE BangPatterns #-} module Phonetic.Languages.Simplified.Array.General.FuncRep2RelatedG2 where import CaseBi.Arr (getBFstL') import Phonetic.Languages.Simplified.DataG.Base import Phonetic.Languages.Array.General.PropertiesFuncRepG2 import Phonetic.Languages.Array.General.PropertiesSyllablesG2 import Data.Monoid (mappend) import Data.Phonetic.Languages.Base import Data.Phonetic.Languages.Syllables -- | Allows to choose the variant of the computations in case of usual processment. The coefficient 1.3 (anyway, it must -- be greater than 1.0) )is an empirical and approximate, you can use your own if you like. chooseMax :: (Ord c) => 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 -- ^ Corresponds to the \'0\' symbol delimiter in the @ukrainian-phonetics-basic-array@ package. -> String -- ^ Corresponds to the \'1\' and \'-\' symbol delimiters in the @ukrainian-phonetics-basic-array@ package. -> (Double -> c) -> (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. -> Coeffs2 -> [([[[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. -> 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 the 0.5.0.0 version -- you can use also \"w\" and \"x\"-based lines of properties. Specifies the applied properties -- to get the result. The \"z\"-line uses \'F\' functions. -> FuncRep2 String Double c chooseMax = chooseMaxG 1.3 {-# INLINE chooseMax #-} -- | Allows to choose the variant of the computations in case of usual processment. chooseMaxG :: (Ord c) => Double -- ^ Must be greater than 1.0 though it is not checked. -> 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 -- ^ Corresponds to the \'0\' symbol delimiter in the @ukrainian-phonetics-basic-array@ package. -> String -- ^ Corresponds to the \'1\' and \'-\' symbol delimiters in the @ukrainian-phonetics-basic-array@ package. -> (Double -> c) -> (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. -> Coeffs2 -> [([[[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. -> 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 the 0.5.0.0 version -- you can use also \"w\" and \"x\"-based lines of properties. Specifies the applied properties -- to get the result. The \"z\"-line uses \'F\' functions. -- @ since 0.6.0.0 -- There is also the possibility to use \'line growing\' that is to use the 'prepereGrowTextMN' function -- with the 'Int' arguments from the first argument tuple. This allows to rearrange the given text and then -- to rewrite it. -- Besides there are new lines of the arguments for the 'String' argument that can begin with \"c\", \"s\", \"t\", -- \"u\", \"v\" letters. For more information, please, refer to the 'Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2.rhythmicity'. -> FuncRep2 String Double c chooseMaxG k wrs ks arr gs us vs g h coeffs xs choice | take 1 choice == "c" = procRhythmicity23F k g h choice coeffs wrs ks arr gs us vs | otherwise = getBFstL' (procB2InvF wrs ks arr gs us vs g (xs !! 3) coeffs) [("02y",procRhythmicity23F k g h "02y" coeffs wrs ks arr gs us vs), ("02z",procRhythmicity23F k g h "02z" coeffs wrs ks arr gs us vs), ("03y",procRhythmicity23F k g h "03y" coeffs wrs ks arr gs us vs), ("03z",procRhythmicity23F k g h "03z" coeffs wrs ks arr gs us vs), ("04y",procRhythmicity23F k g h "04y" coeffs wrs ks arr gs us vs), ("04z",procRhythmicity23F k g h "04z" coeffs wrs ks arr gs us vs), ("0y",procRhythmicity23F k g h "0y" coeffs wrs ks arr gs us vs), ("0z",procRhythmicity23F k g h "0z" coeffs wrs ks arr gs us vs), ("s01",procRhythmicity23F k g h "s01" coeffs wrs ks arr gs us vs), ("s02",procRhythmicity23F k g h "s02" coeffs wrs ks arr gs us vs), ("s03",procRhythmicity23F k g h "s03" coeffs wrs ks arr gs us vs), ("s04",procRhythmicity23F k g h "s04" coeffs wrs ks arr gs us vs), ("s11",procRhythmicity23F k g h "s11" coeffs wrs ks arr gs us vs), ("s12",procRhythmicity23F k g h "s12" coeffs wrs ks arr gs us vs), ("s13",procRhythmicity23F k g h "s13" coeffs wrs ks arr gs us vs), ("s14",procRhythmicity23F k g h "s14" coeffs wrs ks arr gs us vs), ("s21",procRhythmicity23F k g h "s21" coeffs wrs ks arr gs us vs), ("s22",procRhythmicity23F k g h "s22" coeffs wrs ks arr gs us vs), ("s23",procRhythmicity23F k g h "s23" coeffs wrs ks arr gs us vs), ("s24",procRhythmicity23F k g h "s24" coeffs wrs ks arr gs us vs), ("s31",procRhythmicity23F k g h "s31" coeffs wrs ks arr gs us vs), ("s32",procRhythmicity23F k g h "s32" coeffs wrs ks arr gs us vs), ("s33",procRhythmicity23F k g h "s33" coeffs wrs ks arr gs us vs), ("s34",procRhythmicity23F k g h "s34" coeffs wrs ks arr gs us vs), ("s41",procRhythmicity23F k g h "s41" coeffs wrs ks arr gs us vs), ("s42",procRhythmicity23F k g h "s42" coeffs wrs ks arr gs us vs), ("s43",procRhythmicity23F k g h "s43" coeffs wrs ks arr gs us vs), ("s44",procRhythmicity23F k g h "s44" coeffs wrs ks arr gs us vs), ("s51",procRhythmicity23F k g h "s51" coeffs wrs ks arr gs us vs), ("s52",procRhythmicity23F k g h "s52" coeffs wrs ks arr gs us vs), ("s53",procRhythmicity23F k g h "s53" coeffs wrs ks arr gs us vs), ("s54",procRhythmicity23F k g h "s54" coeffs wrs ks arr gs us vs), ("s61",procRhythmicity23F k g h "s61" coeffs wrs ks arr gs us vs), ("s62",procRhythmicity23F k g h "s62" coeffs wrs ks arr gs us vs), ("s63",procRhythmicity23F k g h "s63" coeffs wrs ks arr gs us vs), ("s64",procRhythmicity23F k g h "s64" coeffs wrs ks arr gs us vs), ("s71",procRhythmicity23F k g h "s71" coeffs wrs ks arr gs us vs), ("s72",procRhythmicity23F k g h "s73" coeffs wrs ks arr gs us vs), ("s74",procRhythmicity23F k g h "s74" coeffs wrs ks arr gs us vs), ("t01",procRhythmicity23F k g h "t01" coeffs wrs ks arr gs us vs), ("t02",procRhythmicity23F k g h "t02" coeffs wrs ks arr gs us vs), ("t03",procRhythmicity23F k g h "t03" coeffs wrs ks arr gs us vs), ("t04",procRhythmicity23F k g h "t04" coeffs wrs ks arr gs us vs), ("t11",procRhythmicity23F k g h "t11" coeffs wrs ks arr gs us vs), ("t12",procRhythmicity23F k g h "t12" coeffs wrs ks arr gs us vs), ("t13",procRhythmicity23F k g h "t13" coeffs wrs ks arr gs us vs), ("t14",procRhythmicity23F k g h "t14" coeffs wrs ks arr gs us vs), ("t21",procRhythmicity23F k g h "t21" coeffs wrs ks arr gs us vs), ("t22",procRhythmicity23F k g h "t22" coeffs wrs ks arr gs us vs), ("t23",procRhythmicity23F k g h "t23" coeffs wrs ks arr gs us vs), ("t24",procRhythmicity23F k g h "t24" coeffs wrs ks arr gs us vs), ("t31",procRhythmicity23F k g h "t31" coeffs wrs ks arr gs us vs), ("t32",procRhythmicity23F k g h "t32" coeffs wrs ks arr gs us vs), ("t33",procRhythmicity23F k g h "t33" coeffs wrs ks arr gs us vs), ("t34",procRhythmicity23F k g h "t34" coeffs wrs ks arr gs us vs), ("t41",procRhythmicity23F k g h "t41" coeffs wrs ks arr gs us vs), ("t42",procRhythmicity23F k g h "t42" coeffs wrs ks arr gs us vs), ("t43",procRhythmicity23F k g h "t43" coeffs wrs ks arr gs us vs), ("t44",procRhythmicity23F k g h "t44" coeffs wrs ks arr gs us vs), ("t51",procRhythmicity23F k g h "t51" coeffs wrs ks arr gs us vs), ("t52",procRhythmicity23F k g h "t52" coeffs wrs ks arr gs us vs), ("t53",procRhythmicity23F k g h "t53" coeffs wrs ks arr gs us vs), ("t54",procRhythmicity23F k g h "t54" coeffs wrs ks arr gs us vs), ("t61",procRhythmicity23F k g h "t61" coeffs wrs ks arr gs us vs), ("t62",procRhythmicity23F k g h "t62" coeffs wrs ks arr gs us vs), ("t63",procRhythmicity23F k g h "t63" coeffs wrs ks arr gs us vs), ("t64",procRhythmicity23F k g h "t64" coeffs wrs ks arr gs us vs), ("t71",procRhythmicity23F k g h "t71" coeffs wrs ks arr gs us vs), ("t72",procRhythmicity23F k g h "t73" coeffs wrs ks arr gs us vs), ("t74",procRhythmicity23F k g h "t74" coeffs wrs ks arr gs us vs), ("u01",procRhythmicity23F k g h "u01" coeffs wrs ks arr gs us vs), ("u02",procRhythmicity23F k g h "u02" coeffs wrs ks arr gs us vs), ("u03",procRhythmicity23F k g h "u03" coeffs wrs ks arr gs us vs), ("u04",procRhythmicity23F k g h "u04" coeffs wrs ks arr gs us vs), ("u11",procRhythmicity23F k g h "u11" coeffs wrs ks arr gs us vs), ("u12",procRhythmicity23F k g h "u12" coeffs wrs ks arr gs us vs), ("u13",procRhythmicity23F k g h "u13" coeffs wrs ks arr gs us vs), ("u14",procRhythmicity23F k g h "u14" coeffs wrs ks arr gs us vs), ("u21",procRhythmicity23F k g h "u21" coeffs wrs ks arr gs us vs), ("u22",procRhythmicity23F k g h "u22" coeffs wrs ks arr gs us vs), ("u23",procRhythmicity23F k g h "u23" coeffs wrs ks arr gs us vs), ("u24",procRhythmicity23F k g h "u24" coeffs wrs ks arr gs us vs), ("u31",procRhythmicity23F k g h "u31" coeffs wrs ks arr gs us vs), ("u32",procRhythmicity23F k g h "u32" coeffs wrs ks arr gs us vs), ("u33",procRhythmicity23F k g h "u33" coeffs wrs ks arr gs us vs), ("u34",procRhythmicity23F k g h "u34" coeffs wrs ks arr gs us vs), ("u41",procRhythmicity23F k g h "u41" coeffs wrs ks arr gs us vs), ("u42",procRhythmicity23F k g h "u42" coeffs wrs ks arr gs us vs), ("u43",procRhythmicity23F k g h "u43" coeffs wrs ks arr gs us vs), ("u44",procRhythmicity23F k g h "u44" coeffs wrs ks arr gs us vs), ("u51",procRhythmicity23F k g h "u51" coeffs wrs ks arr gs us vs), ("u52",procRhythmicity23F k g h "u52" coeffs wrs ks arr gs us vs), ("u53",procRhythmicity23F k g h "u53" coeffs wrs ks arr gs us vs), ("u54",procRhythmicity23F k g h "u54" coeffs wrs ks arr gs us vs), ("u61",procRhythmicity23F k g h "u61" coeffs wrs ks arr gs us vs), ("u62",procRhythmicity23F k g h "u62" coeffs wrs ks arr gs us vs), ("u63",procRhythmicity23F k g h "u63" coeffs wrs ks arr gs us vs), ("u64",procRhythmicity23F k g h "u64" coeffs wrs ks arr gs us vs), ("u71",procRhythmicity23F k g h "u71" coeffs wrs ks arr gs us vs), ("u72",procRhythmicity23F k g h "u73" coeffs wrs ks arr gs us vs), ("u74",procRhythmicity23F k g h "u74" coeffs wrs ks arr gs us vs), ("v01",procRhythmicity23F k g h "v01" coeffs wrs ks arr gs us vs), ("v02",procRhythmicity23F k g h "v02" coeffs wrs ks arr gs us vs), ("v03",procRhythmicity23F k g h "v03" coeffs wrs ks arr gs us vs), ("v04",procRhythmicity23F k g h "v04" coeffs wrs ks arr gs us vs), ("v11",procRhythmicity23F k g h "v11" coeffs wrs ks arr gs us vs), ("v12",procRhythmicity23F k g h "v12" coeffs wrs ks arr gs us vs), ("v13",procRhythmicity23F k g h "v13" coeffs wrs ks arr gs us vs), ("v14",procRhythmicity23F k g h "v14" coeffs wrs ks arr gs us vs), ("v21",procRhythmicity23F k g h "v21" coeffs wrs ks arr gs us vs), ("v22",procRhythmicity23F k g h "v22" coeffs wrs ks arr gs us vs), ("v23",procRhythmicity23F k g h "v23" coeffs wrs ks arr gs us vs), ("v24",procRhythmicity23F k g h "v24" coeffs wrs ks arr gs us vs), ("v31",procRhythmicity23F k g h "v31" coeffs wrs ks arr gs us vs), ("v32",procRhythmicity23F k g h "v32" coeffs wrs ks arr gs us vs), ("v33",procRhythmicity23F k g h "v33" coeffs wrs ks arr gs us vs), ("v34",procRhythmicity23F k g h "v34" coeffs wrs ks arr gs us vs), ("v41",procRhythmicity23F k g h "v41" coeffs wrs ks arr gs us vs), ("v42",procRhythmicity23F k g h "v42" coeffs wrs ks arr gs us vs), ("v43",procRhythmicity23F k g h "v43" coeffs wrs ks arr gs us vs), ("v44",procRhythmicity23F k g h "v44" coeffs wrs ks arr gs us vs), ("v51",procRhythmicity23F k g h "v51" coeffs wrs ks arr gs us vs), ("v52",procRhythmicity23F k g h "v52" coeffs wrs ks arr gs us vs), ("v53",procRhythmicity23F k g h "v53" coeffs wrs ks arr gs us vs), ("v54",procRhythmicity23F k g h "v54" coeffs wrs ks arr gs us vs), ("v61",procRhythmicity23F k g h "v61" coeffs wrs ks arr gs us vs), ("v62",procRhythmicity23F k g h "v62" coeffs wrs ks arr gs us vs), ("v63",procRhythmicity23F k g h "v63" coeffs wrs ks arr gs us vs), ("v64",procRhythmicity23F k g h "v64" coeffs wrs ks arr gs us vs), ("v71",procRhythmicity23F k g h "v71" coeffs wrs ks arr gs us vs), ("v72",procRhythmicity23F k g h "v73" coeffs wrs ks arr gs us vs), ("v74",procRhythmicity23F k g h "v74" coeffs wrs ks arr gs us vs), ("w01",procRhythmicity23F k g h "w01" coeffs wrs ks arr gs us vs), ("w02",procRhythmicity23F k g h "w02" coeffs wrs ks arr gs us vs), ("w03",procRhythmicity23F k g h "w03" coeffs wrs ks arr gs us vs), ("w04",procRhythmicity23F k g h "w04" coeffs wrs ks arr gs us vs), ("w11",procRhythmicity23F k g h "w11" coeffs wrs ks arr gs us vs), ("w12",procRhythmicity23F k g h "w12" coeffs wrs ks arr gs us vs), ("w13",procRhythmicity23F k g h "w13" coeffs wrs ks arr gs us vs), ("w14",procRhythmicity23F k g h "w14" coeffs wrs ks arr gs us vs), ("w21",procRhythmicity23F k g h "w21" coeffs wrs ks arr gs us vs), ("w22",procRhythmicity23F k g h "w22" coeffs wrs ks arr gs us vs), ("w23",procRhythmicity23F k g h "w23" coeffs wrs ks arr gs us vs), ("w24",procRhythmicity23F k g h "w24" coeffs wrs ks arr gs us vs), ("w31",procRhythmicity23F k g h "w31" coeffs wrs ks arr gs us vs), ("w32",procRhythmicity23F k g h "w32" coeffs wrs ks arr gs us vs), ("w33",procRhythmicity23F k g h "w33" coeffs wrs ks arr gs us vs), ("w34",procRhythmicity23F k g h "w34" coeffs wrs ks arr gs us vs), ("x01",procRhythmicity23F k g h "x01" coeffs wrs ks arr gs us vs), ("x02",procRhythmicity23F k g h "x02" coeffs wrs ks arr gs us vs), ("x03",procRhythmicity23F k g h "x03" coeffs wrs ks arr gs us vs), ("x04",procRhythmicity23F k g h "x04" coeffs wrs ks arr gs us vs), ("x11",procRhythmicity23F k g h "x11" coeffs wrs ks arr gs us vs), ("x12",procRhythmicity23F k g h "x12" coeffs wrs ks arr gs us vs), ("x13",procRhythmicity23F k g h "x13" coeffs wrs ks arr gs us vs), ("x14",procRhythmicity23F k g h "x14" coeffs wrs ks arr gs us vs), ("x21",procRhythmicity23F k g h "x21" coeffs wrs ks arr gs us vs), ("x22",procRhythmicity23F k g h "x22" coeffs wrs ks arr gs us vs), ("x23",procRhythmicity23F k g h "x23" coeffs wrs ks arr gs us vs), ("x24",procRhythmicity23F k g h "x24" coeffs wrs ks arr gs us vs), ("x31",procRhythmicity23F k g h "x31" coeffs wrs ks arr gs us vs), ("x32",procRhythmicity23F k g h "x32" coeffs wrs ks arr gs us vs), ("x33",procRhythmicity23F k g h "x33" coeffs wrs ks arr gs us vs), ("x34",procRhythmicity23F k g h "x34" coeffs wrs ks arr gs us vs), ("y",procB2F wrs ks arr gs us vs g (xs !! 0) coeffs), ("y0",procDiverse2F wrs (' ':us `mappend` vs) g), ("y2",procB2F wrs ks arr gs us vs g (xs !! 1) coeffs), ("y3",procB2F wrs ks arr gs us vs g (xs !! 2) coeffs), ("y4",procB2F wrs ks arr gs us vs g (xs !! 3) coeffs), ("yy",procB2InvF wrs ks arr gs us vs g (xs !! 0) coeffs), ("yy2",procB2InvF wrs ks arr gs us vs g (xs !! 1) coeffs), ("yy3",procB2InvF wrs ks arr gs us vs g (xs !! 2) coeffs), ("z",procB2FF wrs ks arr gs us vs k g (xs !! 0) coeffs), ("z2",procB2FF wrs ks arr gs us vs k g (xs !! 1) coeffs), ("z3",procB2FF wrs ks arr gs us vs k g (xs !! 2) coeffs), ("z4",procB2FF wrs ks arr gs us vs k g (xs !! 3) coeffs), ("zz",procB2InvFF wrs ks arr gs us vs k g (xs !! 0) coeffs), ("zz2",procB2InvFF wrs ks arr gs us vs k g (xs !! 1) coeffs), ("zz3",procB2InvFF wrs ks arr gs us vs k g (xs !! 2) coeffs), ("zz4", procB2InvFF wrs ks arr gs us vs k g (xs !! 3) coeffs)] choice -- | Allows to choose precision in the Numeric.showFDouble function being given a choice parameter. precChoice :: 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 the 0.5.0.0 version -- you can use also \"w\" and \"x\"-based lines of properties. Specifies the applied properties -- to get the result. The \"z\"-line uses \'F\' functions. -- @ since 0.6.0.0 -- There is also the possibility to use \'line growing\' that is to use the 'prepereGrowTextMN' function -- with the 'Int' arguments from the first argument tuple. This allows to rearrange the given text and then -- to rewrite it. -- Besides there are new lines of the arguments for the 'String' argument that can begin with \"c\", \"s\", \"t\", -- \"u\", \"v\" letters. For more information, please, refer to the 'Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2.rhythmicity'. -> Maybe Int precChoice = getBFstL' (Just 4) [("02y",Just 0),("02z",Just 0),("03y",Just 0),("03z",Just 0),("04y",Just 0), ("04z",Just 0),("0y",Just 0),("0z",Just 0),("y",Just 0),("y0",Just 0),("y2",Just 0),("y3",Just 0), ("y4",Just 0), ("z",Just 0),("z0",Just 0),("z2",Just 0),("z3",Just 0), ("z4",Just 0)]