{-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG201Old -- Copyright : (c) OleksandrZhabenko 2020-2022 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Generalization and extension of the functionality of the DobutokO.Poetry.Norms -- and DobutokO.Poetry.Norms.Extended modules -- from the @dobutokO-poetry@ package. Uses syllables information. -- Instead of the vector-related, uses just arrays. {-# LANGUAGE CPP, BangPatterns, MultiWayIf #-} module Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG201Old ( -- * Rhythmicity properties -- ** Rhythmicity properties (semi-empirical) -- *** General ones rhythmicity0H , rhythmicity0FH , rhythmicityKH , rhythmicityKFH -- *** Simple one , rhythmicity0 , rhythmicity0F -- *** With weight coefficients , rhythmicityK , rhythmicityKF -- ** Rhythmicity properties from generated with r-glpk-phonetic-languages-ukrainian-durations package (since 0.2.0.0 version) -- *** Simple one , rhythmicity02 , rhythmicity02F -- *** With weight coefficients , rhythmicityK2 , rhythmicityKF2 -- ** NEW Rhythmicity properties from generated with r-glpk-phonetic-languages-ukrainian-durations package -- *** Simple ones , rhythmicity03 , rhythmicity03F , rhythmicity04 , rhythmicity04F -- *** With weight coefficients , rhythmicityK3 , rhythmicityKF3 , rhythmicityK4 , rhythmicityKF4 -- ** General , rhythmicityG ) 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 Languages.Phonetic.Ukrainian.Syllable.Double.ArrInt8 import Melodics.Ukrainian.ArrInt8 (Sound8,FlowSound) import Languages.Phonetic.Ukrainian.Syllable.ArrInt8 import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2CommonOld 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 rhythmicity0H :: ([[[Sound8]]] -> [[Double]]) -> String -> Double rhythmicity0H f = rhythmicityGH f eval23 {-# INLINE rhythmicity0H #-} rhythmicity0 :: String -> Double rhythmicity0 = rhythmicity0H syllableDurationsD {-# INLINE rhythmicity0 #-} rhythmicity02 :: String -> Double rhythmicity02 = rhythmicity0H syllableDurationsD2 {-# INLINE rhythmicity02 #-} rhythmicity03 :: String -> Double rhythmicity03 = rhythmicity0H syllableDurationsD3 {-# INLINE rhythmicity03 #-} rhythmicity04 :: String -> Double rhythmicity04 = rhythmicity0H syllableDurationsD4 {-# INLINE rhythmicity04 #-} ------------------------------------------------------- rhythmicityKH :: ([[[Sound8]]] -> [[Double]]) -> Double -> Double -> String -> Double rhythmicityKH f k2 k3 = rhythmicityGH f (eval23K k2 k3) {-# INLINE rhythmicityKH #-} rhythmicityK :: Double -> Double -> String -> Double rhythmicityK k2 k3 = rhythmicityKH syllableDurationsD k2 k3 {-# INLINE rhythmicityK #-} rhythmicityK2 :: Double -> Double -> String -> Double rhythmicityK2 k2 k3 = rhythmicityKH syllableDurationsD2 k2 k3 {-# INLINE rhythmicityK2 #-} rhythmicityK3 :: Double -> Double -> String -> Double rhythmicityK3 k2 k3 = rhythmicityKH syllableDurationsD3 k2 k3 {-# INLINE rhythmicityK3 #-} rhythmicityK4 :: Double -> Double -> String -> Double rhythmicityK4 k2 k3 = rhythmicityKH syllableDurationsD4 k2 k3 {-# INLINE rhythmicityK4 #-} -------------------------------------------------------- rhythmicity0FH :: ([[[Sound8]]] -> [[Double]]) -> Double -> String -> Double rhythmicity0FH f k = rhythmicityGH f (eval23F k) {-# INLINE rhythmicity0FH #-} rhythmicity0F :: Double -> String -> Double rhythmicity0F k = rhythmicity0FH syllableDurationsD k {-# INLINE rhythmicity0F #-} rhythmicity02F :: Double -> String -> Double rhythmicity02F k = rhythmicity0FH syllableDurationsD2 k {-# INLINE rhythmicity02F #-} rhythmicity03F :: Double -> String -> Double rhythmicity03F k = rhythmicity0FH syllableDurationsD3 k {-# INLINE rhythmicity03F #-} rhythmicity04F :: Double -> String -> Double rhythmicity04F k = rhythmicity0FH syllableDurationsD4 k {-# INLINE rhythmicity04F #-} -------------------------------------------------------- rhythmicityKFH :: ([[[Sound8]]] -> [[Double]]) -> Double -> Double -> Double -> String -> Double rhythmicityKFH f k k2 k3 = rhythmicityGH f (eval23KF k k2 k3) {-# INLINE rhythmicityKFH #-} rhythmicityKF :: Double -> Double -> Double -> String -> Double rhythmicityKF k k2 k3 = rhythmicityKFH syllableDurationsD k k2 k3 {-# INLINE rhythmicityKF #-} rhythmicityKF2 :: Double -> Double -> Double -> String -> Double rhythmicityKF2 k k2 k3 = rhythmicityKFH syllableDurationsD2 k k2 k3 {-# INLINE rhythmicityKF2 #-} rhythmicityKF3 :: Double -> Double -> Double -> String -> Double rhythmicityKF3 k k2 k3 = rhythmicityKFH syllableDurationsD3 k k2 k3 {-# INLINE rhythmicityKF3 #-} rhythmicityKF4 :: Double -> Double -> Double -> String -> Double rhythmicityKF4 k k2 k3 = rhythmicityKFH syllableDurationsD4 k k2 k3 {-# INLINE rhythmicityKF4 #-} ----------------------------------------- rhythmicityG :: ([[[Sound8]]] -> [[Double]])-- ^ A function that specifies the syllables durations, analogue of (or one of) the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. -> String -> [Double] rhythmicityG f xs | null xs = [] | otherwise = mconcat . f . createSyllablesUkrS $ xs {-# INLINE rhythmicityG #-}