{-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Phonetic.Languages.Array.Ukrainian.PropertiesFuncRepG2Rhythmicity -- Copyright : (c) OleksandrZhabenko 2020-2021 -- 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.PropertiesFuncRepG2Rhythmicity ( -- * Basic -- ** Working with rhythmicity procRhythmicity23F -- *** Working with rhythmicity that can be defined by the user (using 'rhythmicityH') , procRhythmicity23FH -- * Extended -- ** Working with rhythmicity , procRhythmicity23FTup -- *** Working with rhythmicity that can be defined by the user (using 'rhythmicityH') , procRhythmicity23FHTup ) where import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2Common import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2H import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2Hprime import Phonetic.Languages.Simplified.DataG.Base import Melodics.Ukrainian.ArrInt8 import GHC.Arr (Array) import GHC.Int (Int8) procRhythm23F :: (Ord c) => (Double -> c) -> String -> (String -> Coeffs2 -> String -> Double) -> Coeffs2 -> FuncRep2 String Double c procRhythm23F h choice g coeffs = D (g choice coeffs) h {-# INLINE procRhythm23F #-} 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 #-} ------------------------------------------------------- procRhythmicity23FTup :: (Ord c) => Array Int (Int8, Bool) -> Array Int (Int8, Bool) -> Array Int (Int8, Bool) -> Array Int (Int8, Bool) -> Array Int ([Int8], Bool) -> Array Int ([Int8], Int8) -> Array Int (Int8, FlowSound -> Sound8) -> Array Int (Int8, Bool) -> Array Int ([Int8], Bool) -> Array Int ([Int8], Bool) -> Array Int ([Int8], Bool) -> Array Int (Int8, [Int8]) -> Array Int (Char,Int8) -> Array Int (Int8,[Int8]) -> Array Int (Char, Bool) -> Array Int (Char, Bool) -> Array Int (Int8,Bool) -> Double -> (Double -> c) -> String -> Coeffs2 -> FuncRep2 String Double c procRhythmicity23FTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k g choice coeffs = procRhythm23F g choice (rhythmicityTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k) coeffs {-# INLINE procRhythmicity23FTup #-} procRhythmicity23FHTup :: (Ord c) => Array Int (Int8, Bool) -> Array Int (Int8, Bool) -> Array Int (Int8, Bool) -> Array Int (Int8, Bool) -> Array Int ([Int8], Bool) -> Array Int ([Int8], Int8) -> Array Int (Int8, FlowSound -> Sound8) -> Array Int (Int8, Bool) -> Array Int ([Int8], Bool) -> Array Int ([Int8], Bool) -> Array Int ([Int8], Bool) -> Array Int (Int8, [Int8]) -> Array Int (Char,Int8) -> Array Int (Int8,[Int8]) -> Array Int (Char, Bool) -> Array Int (Char, Bool) -> Array Int (Int8,Bool) -> Double -> (Double -> c) -> [[[[Sound8]]] -> [[Double]]] -> String -> Coeffs2 -> FuncRep2 String Double c procRhythmicity23FHTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k g syllableDurationsDs choice coeffs = D (rhythmicityHTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k choice syllableDurationsDs coeffs) g {-# INLINE procRhythmicity23FHTup #-}