-- | -- Module : Phonetic.Languages.Simplified.Array.Ukrainian.FuncRep2RelatedG2 -- Copyright : (c) OleksandrZhabenko 2020 -- 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 = getBFstL' (procBoth4InvF g coeffs) [("02y",procRhythmicity23F 1.3 g "02y" coeffs), ("02z",procRhythmicity23F 1.3 g "02z" coeffs), ("03y",procRhythmicity23F 1.3 g "03y" coeffs), ("03z",procRhythmicity23F 1.3 g "03z" coeffs), ("04y",procRhythmicity23F 1.3 g "04y" coeffs), ("04z",procRhythmicity23F 1.3 g "04z" coeffs), ("0y",procRhythmicity23F 1.3 g "0y" coeffs), ("0z",procRhythmicity23F 1.3 g "0z" 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)]