-- | -- Module : Phonetic.Languages.Simplified.Array.General.FuncRep2RelatedG2 -- Copyright : (c) OleksandrZhabenko 2020-2022 -- 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.Basis 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 import Phonetic.Languages.EmphasisG import Data.Char (isDigit) import Data.Maybe (fromJust) import Text.Read (readMaybe) -- | 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 -> MappingFunctionPL) -- ^ 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 -> [MappingFunctionPL] -- ^ A list of either 'PhoPaaW'-based or 'SaaW'-based (and not both ones) different functions that specifies the syllables durations in the PhoPaaW or SaaW mode respectively (the former one has been introduced earlier), analogues of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The first one in case of 'PhoPaaW'-based ones 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. -> String -- ^ The starting 'String' which creates the order for the 'FSLG' representation -> FuncRep2 ReadyForConstructionPL 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 -> MappingFunctionPL) -- ^ 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 -> [MappingFunctionPL] -- ^ A list of either 'PhoPaaW'-based or 'SaaW'-based (and not both ones) different functions that specifies the syllables durations in the PhoPaaW or SaaW mode respectively (the former one has been introduced earlier), analogues of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The first one in case of 'PhoPaaW'-based ones 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\", or some other letters. For more information, please, refer to the 'Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2.rhythmicity'. -> String -- ^ The starting 'String' which creates the order for the 'FSLG' representation -> FuncRep2 ReadyForConstructionPL Double c chooseMaxG k wrs ks arr gs us vs g h coeffs xs choice bbs | any (== 'G') choice = chooseMaxG k wrs ks arr gs us vs g h coeffs xs (filter (/= 'G') choice) bbs | any (=='a') choice = procRhythmicity23F k g (\_ _ -> if null (filter isDigit choice) then (xs !! 0) else (xs !! ((\z -> if z == -1 then 0 else z) $ fromJust (readMaybe [last . filter isDigit $ choice]::Maybe Int) - 1))) (filter (/='a') choice) coeffs wrs ks arr gs us vs bbs | take 1 choice `elem` ["c","C","N"] || (take 1 choice >= "A" && take 1 choice <= "F") || getBFstL' False (zip ["02y","02z","03y","03z","04y","04z","0y","0z","I01","I02","I03","I04","I11", "I12","I12","I13","I14","I21","I22","I23","I24","I31","I32","I33","I34","I41","I42","I43","I44", "I51","I52","I53","I54","I61","I62","I63","I64","I71","I72","I74","J01","J02","J03","J04","J11", "J12","J13","J14","J21","J22","J23","J24","J31","J32","J33","J34","J41","J42","J43","J44","J51", "J52","J53","J54","J61","J62","J63","J64","J71","J72","J73","J74","K01","K02","K03","K04","K11", "K12","K13","K14","K21","K21","K22","K23","K24","K31","K32","K33","K34","K41","K42","K43","K44", "K51","K52","K53","K54","K61","K62","K63","K64","K71","K72","K73","K74","L01","L02","L03","L04", "L11","L12","L13","L14","L21","L22","L23","L24","L31","L32","L33","L34","L41","L42","L43","L44", "L51","L52","L53","L54","L61","L62","L63","L64","L71","L72","L74","O01","O02","O03","O04","O11", "O12","O13","O14","O21","O22","O23","O24","O31","O32","O33","O34","O41","O42","O43","O44","O51", "O52","O53","O54","O61","O62","O63","O64","O71","O72","O73","O74","P01","P02","P03","P04","P11", "P12","P13","P14","P21","P22","P23","P24","P31","P32","P33","P34","P41","P42","P43","P44","P51", "P52","P53","P54","P61","P62","P63","P64","P71","P72","P73","P74","Q01","Q02","Q03","Q04", "Q11","Q12","Q13","Q14","Q21","Q22","Q23","Q24","Q31","Q32","Q33","Q34","Q41","Q42","Q43","Q44", "Q51","Q52","Q53","Q54","Q61","Q62","Q63","Q64","Q71","Q72","Q74","R01","R02","R03","R04","R11", "R12","R13","R14","R21","R22","R23","R24","R31","R32","R33","R34","R41","R42","R43","R44","R51", "R52","R53","R54","R61","R62","R63","R64","R71","R72","R73","R74","S01","S02","S03","S04","S11", "S12","S12","S13","S14","S21","S22","S23","S24","S31","S32","S33","S34","S41","S42","S43","S44", "S51","S52","S53","S54","S61","S62","S63","S64","S71","S72","S74","T01","T02","T03","T04","T11", "T12","T13","T14","T21","T22","T23","T24","T31","T32","T33","T34","T41","T42","T43","T44","T51", "T52","T53","T54","T61","T62","T63","T64","T71","T72","T73","T74","U01","U02","U03","U04","U11", "U12","U13","U14","U21","U21","U22","U23","U24","U31","U32","U33","U34","U41","U42","U43","U44", "U51","U52","U53","U54","U61","U62","U63","U64","U71","U72","U73","U74","V01","V02","V03","V04", "V11","V12","V13","V14","V21","V22","V23","V24","V31","V32","V33","V34","V41","V42","V43","V44", "V51","V52","V53","V54","V61","V62","V63","V64","V71","V72","V74","W01","W02","W03","W04","W11", "W12","W13","W14","W21","W22","W23","W24","W31","W32","W33","W34","W41","W42","W43","W44","W51", "W52","W53","W54","W61","W62","W63","W64","W71","W72","W73","W74","X01","X02","X03","X04","X11", "X12","X13","X14","X21","X22","X23","X24","X31","X32","X33","X34","X41","X42","X43","X44","X51", "X52","X53","X54","X61","X62","X63","X64","X71","X72","X73","X74","Y01","Y02","Y03","Y04", "Y11","Y12","Y13","Y14","Y21","Y22","Y23","Y24","Y31","Y32","Y33","Y34","Y41","Y42","Y43","Y44", "Y51","Y52","Y53","Y54","Y61","Y62","Y63","Y64","Y71","Y72","Y74","Z01","Z02","Z03","Z04","Z11", "Z12","Z13","Z14","Z21","Z22","Z23","Z24","Z31","Z32","Z33","Z34","Z41","Z42","Z43","Z44","Z51", "Z52","Z53","Z54","Z61","Z62","Z63","Z64","Z71","Z72","Z73","Z74","b01","b02","b03","b04","b11", "b12","b12","b13","b14","b21","b22","b23","b24","b31","b32","b33","b34","b41","b42","b43","b44", "b51","b52","b53","b54","b61","b62","b63","b64","b71","b72","b74","d01","d02","d03","d04","d11", "d12","d13","d14","d21","d22","d23","d24","d31","d32","d33","d34","d41","d42","d43","d44","d51", "d52","d53","d54","d61","d62","d63","d64","d71","d72","d73","d74","e01","e02","e03","e04","e11", "e12","e13","e14","e21","e21","e22","e23","e24","e31","e32","e33","e34","e41","e42","e43","e44", "e51","e52","e53","e54","e61","e62","e63","e64","e71","e72","e73","e74","f01","f02","f03","f04", "f11","f12","f13","f14","f21","f22","f23","f24","f31","f32","f33","f34","f41","f42","f43","f44", "f51","f52","f53","f54","f61","f62","f63","f64","f71","f72","f74","g01","g02","g03","g04","g11", "g12","g13","g14","g21","g22","g23","g24","g31","g32","g33","g34","g41","g42","g43","g44","g51", "g52","g53","g54","g61","g62","g63","g64","g71","g72","g73","g74","h01","h02","h03","h04","h11", "h12","h13","h14","h21","h22","h23","h24","h31","h32","h33","h34","h41","h42","h43","h44","h51", "h52","h53","h54","h61","h62","h63","h64","h71","h72","h73","h74","i01","i02","i03","i04", "i11","i12","i13","i14","i21","i22","i23","i24","i31","i32","i33","i34","i41","i42","i43","i44", "i51","i52","i53","i54","i61","i62","i63","i64","i71","i72","i74","j01","j02","j03","j04","j11", "j12","j13","j14","j21","j22","j23","j24","j31","j32","j33","j34","j41","j42","j43","j44","j51", "j52","j53","j54","j61","j62","j63","j64","j71","j72","j73","j74","k01","k02","k03","k04","k11", "k12","k12","k13","k14","k21","k22","k23","k24","k31","k32","k33","k34","k41","k42","k43","k44", "k51","k52","k53","k54","k61","k62","k63","k64","k71","k72","k74","l01","l02","l03","l04","l11", "l12","l13","l14","l21","l22","l23","l24","l31","l32","l33","l34","l41","l42","l43","l44","l51", "l52","l53","l54","l61","l62","l63","l64","l71","l72","l73","l74","m01","m02","m03","m04","m11", "m12","m13","m14","m21","m21","m22","m23","m24","m31","m32","m33","m34","m41","m42","m43","m44", "m51","m52","m53","m54","m61","m62","m63","m64","m71","m72","m73","m74","n01","n02","n03","n04", "n11","n12","n13","n14","n21","n22","n23","n24","n31","n32","n33","n34","n41","n42","n43","n44", "n51","n52","n53","n54","n61","n62","n63","n64","n71","n72","n74","o01","o02","o03","o04","o11", "o12","o13","o14","o21","o22","o23","o24","o31","o32","o33","o34","o41","o42","o43","o44","o51", "o52","o53","o54","o61","o62","o63","o64","o71","o72","o73","o74","p01","p02","p03","p04","p11", "p12","p13","p14","p21","p22","p23","p24","p31","p32","p33","p34","p41","p42","p43","p44","p51", "p52","p53","p54","p61","p62","p63","p64","p71","p72","p73","p74","q01","q02","q03","q04", "q11","q12","q13","q14","q21","q22","q23","q24","q31","q32","q33","q34","q41","q42","q43","q44", "q51","q52","q53","q54","q61","q62","q63","q64","q71","q72","q74","r01","r02","r03","r04","r11", "r12","r13","r14","r21","r22","r23","r24","r31","r32","r33","r34","r41","r42","r43","r44","r51", "r52","r53","r54","r61","r62","r63","r64","r71","r72","r73","r74","s01","s02","s03","s04", "s11","s12","s13","s14","s21","s22","s23","s24","s31","s32","s33","s34","s41","s42","s43","s44", "s51","s52","s53","s54","s61","s62","s63","s64","s71","s72","s74","t01","t02","t03","t04","t11", "t12","t13","t14","t21","t22","t23","t24","t31","t32","t33","t34","t41","t42","t43","t44","t51", "t52","t53","t54","t61","t62","t63","t64","t71","t72","t74","u01","u02","u03","u04","u11","u12", "u13","u14","u21","u22","u23","u24","u31","u32","u33","u34","u41","u42","u43","u44","u51","u52", "u53","u54","u61","u62","u63","u64","u71","u72","u74","v01","v02","v03","v04","v11","v12","v13", "v14","v21","v22","v23","v24","v31","v32","v33","v34","v41","v42","v43","v44","v51","v52","v53", "v54","v61","v62","v63","v64","v71","v72","v74","w01","w02","w03","w04","w11","w12","w13","w14", "w21","w22","w23","w24","w31","w32","w33","w34","x01","x02","x03","x04","x11","x12","x13","x14", "x21","x22","x23","x24","x31","x32","x33","x34"] . replicate 2000 $ True) choice = procRhythmicity23F k g h choice coeffs wrs ks arr gs us vs bbs | otherwise = getBFstL' (procB2F wrs ks arr gs us vs g (xs !! 0) coeffs) [("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\", or some other letters. For more information, please, refer to the 'Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2.rhythmicity'. -> Maybe Int precChoice choice | any (\t -> t =='G' || t == 'a') choice = precChoice . filter (\t -> t/='G' && t /= 'a') $ choice | otherwise = 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)] choice