{-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Phladiprelio.Ukrainian.PropertiesFuncRepG2Rhythmicity -- Copyright : (c) Oleksandr Zhabenko 2020-2023 -- License : MIT -- Stability : Experimental -- Maintainer : oleksandr.zhabenko@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. {-# LANGUAGE NoImplicitPrelude #-} module Phladiprelio.Ukrainian.PropertiesFuncRepG2Rhythmicity ( -- * Extended -- ** Working with rhythmicity procRhythmicity23FTup -- *** Working with rhythmicity that can be defined by the user (using 'rhythmicityH') , procRhythmicity23FHTup ) where import GHC.Base import Phladiprelio.Ukrainian.Common hiding (procRhythm23F) import Phladiprelio.Ukrainian.PropertiesSyllablesG2H import Phladiprelio.Ukrainian.PropertiesSyllablesG2Hprime import qualified Phladiprelio.Basis as B import Phladiprelio.Ukrainian.Melodics import GHC.Arr (Array) import GHC.Int (Int8) import Phladiprelio.Ukrainian.Emphasis import Phladiprelio.Coeffs import Phladiprelio.Rhythmicity.Factor procRhythmicity23FTup :: (Ord c) => Factors -> Double -> (Double -> c) -> String -> Coeffs2 -> 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) -> B.FuncRep2 ReadyForConstructionUkr Double c procRhythmicity23FTup ff k g choice coeffs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 = B.D (rhythmicityTup ff k choice coeffs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17) g {-# INLINE procRhythmicity23FTup #-} procRhythmicity23FHTup :: (Ord c) => Factors -> Double -> (Double -> c) -> [[[[Sound8]]] -> [[Double]]] -> String -> Coeffs2 -> String -> 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) -> B.FuncRep2 ReadyForConstructionUkr Double c procRhythmicity23FHTup ff k g syllableDurationsDs choice coeffs bbs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 = B.D (rhythmicityHTup ff k choice syllableDurationsDs coeffs bbs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17) g {-# INLINE procRhythmicity23FHTup #-}