{-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Phonetic.Languages.Array.Ukrainian.PropertiesFuncRepG2RhythmicityOld -- 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. module Phonetic.Languages.Array.Ukrainian.PropertiesFuncRepG2RhythmicityOld ( -- * Basic -- ** Working with rhythmicity procRhythmicity23F -- *** Working with rhythmicity that can be defined by the user (using 'rhythmicityH') , procRhythmicity23FH ) where import Phonetic.Languages.Array.Ukrainian.Common import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2CommonOld import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2HOld import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2HprimeOld import Phonetic.Languages.Basis import Melodics.Ukrainian.ArrInt8 import GHC.Arr (Array) import GHC.Int (Int8) procRhythmicity23F :: (Ord c) => Double -> (Double -> c) -> String -> Coeffs2 -> FuncRep2 String Double c procRhythmicity23F k g choice coeffs = procRhythm23F g choice (rhythmicity k) coeffs {-# INLINE procRhythmicity23F #-} procRhythmicity23FH :: (Ord c) => Double -> (Double -> c) -> [[[[Sound8]]] -> [[Double]]] -> String -> Coeffs2 -> FuncRep2 String Double c procRhythmicity23FH k g syllableDurationsDs choice coeffs = D (rhythmicityH k choice syllableDurationsDs coeffs) g {-# INLINE procRhythmicity23FH #-}