{-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Phonetic.Languages.Array.Ukrainian.PropertiesFuncRepG2CommonOld -- Copyright : (c) OleksandrZhabenko 2020-2022 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Generalization of the functionality of the DobutokO.Poetry.Norms -- and DobutokO.Poetry.Norms.Extended modules -- from the @dobutokO-poetry@ package. Instead of vectors, uses arrays. {-# LANGUAGE CPP, BangPatterns #-} module Phonetic.Languages.Array.Ukrainian.PropertiesFuncRepG2CommonOld where #ifdef __GLASGOW_HASKELL__ #if __GLASGOW_HASKELL__>=710 /* code that applies only to GHC 7.10.* and higher versions */ import GHC.Base (mconcat) #endif #endif import Phonetic.Languages.Array.Ukrainian.Common import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2CommonOld import Phonetic.Languages.UniquenessPeriodsG import Languages.Rhythmicity import Languages.Rhythmicity.Factor import Phonetic.Languages.Basis import GHC.Float (int2Double) import qualified Languages.Phonetic.Ukrainian.Syllable.ArrInt8 as S import Melodics.Ukrainian.ArrInt8 import Data.Maybe (fromMaybe) import GHC.Arr (Array) import GHC.Int (Int8) #ifdef __GLASGOW_HASKELL__ #if __GLASGOW_HASKELL__==708 /* code that applies only to GHC 7.8.* */ mconcat = concat #endif #endif procB2FG :: (Ord c) => ([Double] -> Double) -> (Double -> c) -> ([[[Sound8]]] -> [[Double]]) -> Coeffs2 -> FuncRep2 String Double c procB2FG h1 h g coeffs = D (\xs -> let ys = convertToProperUkrainianI8 . map (\x -> if x == '-' then ' ' else x) $ xs in ((int2Double . fromEnum . diverse2GLInt8 [-1,0] $ ys)*(h1 . mconcat . g . map (S.divVwls . S.reSyllableCntnts . S.groupSnds) . words1 $ ys))) h {-# INLINE procB2FG #-} procB2InvFG :: (Ord c) => ([Double] -> Double) -> (Double -> c) -> ([[[Sound8]]] -> [[Double]]) -> Coeffs2 -> FuncRep2 String Double c procB2InvFG h1 h g coeffs = D (\xs -> let !ys = convertToProperUkrainianI8 . map (\x -> if x == '-' then ' ' else x) $ xs !z = diverse2GLInt8 [-1,0] ys in if z == 0 then (h1 . mconcat . g . map (S.divVwls . S.reSyllableCntnts . S.groupSnds) . words1 $ ys) ** 2.0 else ((h1 . mconcat . g . map (S.divVwls . S.reSyllableCntnts . S.groupSnds) . words1 $ ys) / (int2Double . fromEnum $ z))) h {-# INLINE procB2InvFG #-} procB2F :: (Ord c) => (Double -> c) -> ([[[Sound8]]] -> [[Double]]) -> Coeffs2 -> FuncRep2 String Double c procB2F h g coeffs = procB2FG (eval23Coeffs coeffs) h g coeffs {-# INLINE procB2F #-} procB2FF :: (Ord c) => Double -> (Double -> c) -> ([[[Sound8]]] -> [[Double]]) -> Coeffs2 -> FuncRep2 String Double c procB2FF k h g coeffs = procB2FG (eval23CoeffsF k coeffs) h g coeffs {-# INLINE procB2FF #-} procB2InvF :: (Ord c) => (Double -> c) -> ([[[Sound8]]] -> [[Double]]) -> Coeffs2 -> FuncRep2 String Double c procB2InvF h g coeffs = procB2InvFG (eval23Coeffs coeffs) h g coeffs {-# INLINE procB2InvF #-} procB2InvFF :: (Ord c) => Double -> (Double -> c) -> ([[[Sound8]]] -> [[Double]]) -> Coeffs2 -> FuncRep2 String Double c procB2InvFF k h g coeffs = procB2InvFG (eval23CoeffsF k coeffs) h g coeffs {-# INLINE procB2InvFF #-}