{-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Phladiprelio.Ukrainian.PropertiesSyllablesG2Common -- Copyright : (c) Oleksandr Zhabenko 2020-2023 -- License : MIT -- Stability : Experimental -- Maintainer : oleksandr.zhabenko@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 NoImplicitPrelude, BangPatterns #-} module Phladiprelio.Ukrainian.PropertiesSyllablesG2Common where import GHC.Base import Phladiprelio.Ukrainian.Melodics (Sound8,FlowSound) import Phladiprelio.Ukrainian.Syllable import GHC.Arr import GHC.Int import Phladiprelio.Ukrainian.Emphasis rhythmicityGHTup :: ([[[Sound8]]] -> [[Double]]) -> ([[Double]] -> Double) -> 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) -> ReadyForConstructionUkr -> Double rhythmicityGHTup f g tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (Str xs@(_:_)) = g . f . createSyllablesUkrSTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 $ xs rhythmicityGHTup f g _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ (FSL xsss@(_:_)) = g . f $ xsss rhythmicityGHTup _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ = 0.0 {-# INLINE rhythmicityGHTup #-}