{-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2CommonOld -- 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 #-} module Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2CommonOld 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.Rhythmicity import Languages.Rhythmicity.Factor import Melodics.Ukrainian.ArrInt8 (Sound8,FlowSound) import Languages.Phonetic.Ukrainian.Syllable.ArrInt8 import Data.Maybe (isNothing) import Text.Read (readMaybe) import GHC.Arr import GHC.Int #ifdef __GLASGOW_HASKELL__ #if __GLASGOW_HASKELL__==708 /* code that applies only to GHC 7.8.* */ mconcat = concat #endif #endif rhythmicityGH :: ([[[Sound8]]] -> [[Double]]) -> ([[Double]] -> Double) -> String -> Double rhythmicityGH f g xs | null xs = 0.0 | otherwise = g . f . createSyllablesUkrS $ xs {-# INLINE rhythmicityGH #-}