-- | -- Module : Languages.UniquenessPeriods.Vector.PropertiesSyllablesG -- Copyright : (c) OleksandrZhabenko 2020 -- 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. {-# LANGUAGE CPP #-} module Languages.UniquenessPeriods.Vector.PropertiesSyllablesG ( -- * Rhythmicity metrices -- ** A simple one rhythmicity0 , rhythmicityV0 -- ** With weight coefficients , rhythmicityVK , rhythmicityK ) 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 qualified Data.Vector as VB import Languages.Rhythmicity import Languages.Phonetic.Ukrainian.Syllable #ifdef __GLASGOW_HASKELL__ #if __GLASGOW_HASKELL__==708 /* code that applies only to GHC 7.8.* */ mconcat = concat #endif #endif rhythmicity0 :: String -> Float rhythmicity0 xs | null xs = 0.0 | otherwise = evalRhythmicity23 . mconcat . syllableDurations . createSyllablesUkr $ xs rhythmicityK :: Float -> Float -> String -> Float rhythmicityK k2 k3 xs | null xs = 0.0 | otherwise = evalRhythmicity23K k2 k3 . mconcat . syllableDurations . createSyllablesUkrP $ xs rhythmicityV0 :: VB.Vector Char -> Float rhythmicityV0 v | VB.null v = 0.0 | otherwise = evalRhythmicity23 . mconcat . syllableDurations . createSyllablesUkrV $ v rhythmicityVK :: Float -> Float -> VB.Vector Char -> Float rhythmicityVK k2 k3 v | VB.null v = 0.0 | otherwise = evalRhythmicity23K k2 k3 . mconcat . syllableDurations . createSyllablesUkrVP $ v