-- |
-- 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 :: (Double -> c) -> Coeffs2 -> String -> FuncRep2 String Double c
chooseMax Double -> c
g Coeffs2
coeffs String
choice
 | Coeffs2 -> Bool
forall a. CoeffTwo a -> Bool
isPair Coeffs2
coeffs = FuncRep2 String Double c
-> [(String, FuncRep2 String Double c)]
-> String
-> FuncRep2 String Double c
forall a b. Ord a => b -> [(a, b)] -> a -> b
getBFstL' ((Double -> c) -> Coeffs2 -> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth3InvF Double -> c
g Coeffs2
coeffs) [(String
"02y",(Double -> c) -> String -> Coeffs2 -> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c) -> String -> Coeffs2 -> FuncRep2 String Double c
procRhythmicity23F Double -> c
g String
"02y" Coeffs2
coeffs),
    (String
"03y",(Double -> c) -> String -> Coeffs2 -> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c) -> String -> Coeffs2 -> FuncRep2 String Double c
procRhythmicity23F Double -> c
g String
"03y" Coeffs2
coeffs), (String
"0y",(Double -> c) -> String -> Coeffs2 -> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c) -> String -> Coeffs2 -> FuncRep2 String Double c
procRhythmicity23F Double -> c
g String
"0y" Coeffs2
coeffs),
     (String
"y",(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBothF Double -> c
g Coeffs2
coeffs),(String
"y0",(Double -> c) -> FuncRep2 String Double c
forall c. Ord c => (Double -> c) -> FuncRep2 String Double c
procDiverse2F Double -> c
g),(String
"y2",(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth2F Double -> c
g Coeffs2
coeffs),(String
"y3",(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth3F Double -> c
g Coeffs2
coeffs),
       (String
"yy",(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBothInvF Double -> c
g Coeffs2
coeffs),(String
"yy2",(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth2InvF Double -> c
g Coeffs2
coeffs)] String
choice
 | Bool
otherwise = FuncRep2 String Double c
-> [(String, FuncRep2 String Double c)]
-> String
-> FuncRep2 String Double c
forall a b. Ord a => b -> [(a, b)] -> a -> b
getBFstL' ((Double -> c) -> Coeffs2 -> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth3InvF Double -> c
g Coeffs2
coeffs) [(String
"02y",(Double -> c) -> String -> Coeffs2 -> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c) -> String -> Coeffs2 -> FuncRep2 String Double c
procRhythmicity23F Double -> c
g String
"02y" Coeffs2
coeffs),
    (String
"03y",(Double -> c) -> String -> Coeffs2 -> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c) -> String -> Coeffs2 -> FuncRep2 String Double c
procRhythmicity23F Double -> c
g String
"03y" Coeffs2
coeffs),(String
"0y",(Double -> c) -> String -> Coeffs2 -> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c) -> String -> Coeffs2 -> FuncRep2 String Double c
procRhythmicity23F Double -> c
g String
"0y" Coeffs2
coeffs),
     (String
"y",(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBothF Double -> c
g Coeffs2
coeffs),(String
"y0",(Double -> c) -> FuncRep2 String Double c
forall c. Ord c => (Double -> c) -> FuncRep2 String Double c
procDiverse2F Double -> c
g),(String
"y2",(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth2F Double -> c
g Coeffs2
coeffs),(String
"y3",(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth3F Double -> c
g Coeffs2
coeffs),
       (String
"yy",(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBothInvF Double -> c
g Coeffs2
coeffs),(String
"yy2",(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth2InvF Double -> c
g Coeffs2
coeffs)] String
choice

-- | Allows to choose precision in the Numeric.showFDouble function being given a choice parameter.
precChoice :: String -> Maybe Int
precChoice :: String -> Maybe Int
precChoice = Maybe Int -> [(String, Maybe Int)] -> String -> Maybe Int
forall a b. Ord a => b -> [(a, b)] -> a -> b
getBFstL' (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
4) [(String
"02y",Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0),(String
"03y",Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0),(String
"0y",Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0),(String
"y",Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0),(String
"y0",Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0),(String
"y2",Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0),(String
"y3",Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0)]