-- | -- Module : Languages.UniquenessPeriods.Vector.FuncRepRelatedG -- Copyright : (c) OleksandrZhabenko 2020 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Functions to choose from the 'FuncRep' variants. module Languages.UniquenessPeriods.Vector.FuncRepRelatedG where import CaseBi (getBFst') import qualified Data.Vector as VB import Languages.UniquenessPeriods.Vector.DataG import String.Languages.UniquenessPeriods.VectorG import Languages.UniquenessPeriods.Vector.PropertiesFuncRepG -- | Allows to choose the variant of the computations in case of usual processment. chooseMax :: String -> FuncRep (VB.Vector Char) (UniquenessGeneral2 Char) [Float] chooseMax = getBFst' (procBoth2InvF, VB.fromList [("02y",procRhythmicity232F),("0y",procRhythmicity23F),("y",procBothF),("y0",procDiverse2F),("y2",procBoth2F)]) -- | Allows to choose the variant of the computations in case of minimum lookup. Uses @-neg@ variants. chooseMin :: String -> FuncRep (VB.Vector Char) (UniquenessGeneral2 Char) [Float] chooseMin = getBFst' (procBoth2InvFneg, VB.fromList [("02y",procRhythmicity232Fneg),("0y",procRhythmicity23Fneg),("y",procBothFneg), ("y0",procDiverse2Fneg),("y2",procBoth2Fneg)]) -- | Allows to choose precision in the Numeric.showFFloat function being given a choice parameter. precChoice :: String -> Maybe Int precChoice = getBFst' (Just 4, VB.fromList [("02y",Just 0),("0y",Just 0),("y",Just 0),("y0",Just 0),("y2",Just 0)])