-- | -- Module : Phonetic.Languages.Simplified.Array.Ukrainian.FuncRep2RelatedG2 -- Copyright : (c) OleksandrZhabenko 2020-2021 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Functions to choose from the 'FuncRep2' variants. {-# LANGUAGE BangPatterns #-} module Phonetic.Languages.Simplified.Array.Ukrainian.FuncRep2RelatedG2 where import CaseBi.Arr (getBFstL') import Phonetic.Languages.Simplified.DataG.Base import Phonetic.Languages.Array.Ukrainian.PropertiesFuncRepG2 import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2 -- | Allows to choose the variant of the computations in case of usual processment. chooseMax :: (Ord c) => (Double -> c) -> Coeffs2 -> String -> FuncRep2 String Double c chooseMax g coeffs choice | take 1 choice == "c" = procRhythmicity23F 1.3 g choice coeffs | getBFstL' False (zip ["02y","02z","03y","03z","04y","04z","0y","0z","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","x01","x02","x03","x04","x11", "x12","x13","x14","x21","x22","x23","x24","x31","x32","x33","x34"] . replicate 1000 $ True) choice = procRhythmicity23F 1.3 g choice coeffs | otherwise = getBFstL' (procBoth4InvF g coeffs) [("y",procBothF g coeffs),("y0",procDiverse2F g), ("y2",procBoth2F g coeffs),("y3",procBoth3F g coeffs), ("y4",procBoth4F g coeffs), ("yy",procBothInvF g coeffs),("yy2",procBoth2InvF g coeffs),("yy3",procBoth3InvF g coeffs), ("z",procBothFF 1.3 g coeffs),("z2",procBoth2FF 1.3 g coeffs), ("z3",procBoth3FF 1.3 g coeffs), ("z4",procBoth4FF 1.3 g coeffs), ("zz",procBothInvFF 1.3 g coeffs),("zz2",procBoth2InvFF 1.3 g coeffs), ("zz3",procBoth3InvFF 1.3 g coeffs),("zz4", procBoth4InvFF 1.3 g coeffs)] choice -- | Allows to choose precision in the Numeric.showFDouble function being given a choice parameter. precChoice :: String -> 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)]