-- | -- 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). 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). Specifies the applied properties -- to get the result. The \"z\"-line uses \'F\' functions. -> FuncRep2 String Double c chooseMaxG k wrs ks arr gs us vs g h coeffs xs choice = 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), ("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). Specifies the applied properties -- to get the result. The \"z\"-line uses \'F\' functions. -> 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)]