{-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Phladiprelio.Ukrainian.PropertiesSyllablesG2Hprime -- 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, MultiWayIf #-} module Phladiprelio.Ukrainian.PropertiesSyllablesG2Hprime ( -- * Extended rhythmicityHTup , rhythmicityH'Tup , rhythmicitya'Tup ) where import Data.Tuple (uncurry) import GHC.Base import GHC.List import GHC.Real (rem) import GHC.Num ((-)) import Phladiprelio.Ukrainian.Common import Phladiprelio.Ukrainian.SyllableDouble import Phladiprelio.Ukrainian.Melodics (Sound8,FlowSound) import Phladiprelio.Ukrainian.Syllable import Data.Maybe (fromMaybe) import Text.Read (readMaybe) import Phladiprelio.Rhythmicity.TwoFourth import Phladiprelio.Rhythmicity.PolyRhythm import Phladiprelio.Ukrainian.PropertiesSyllablesG201 import GHC.Arr (Array) import GHC.Int (Int8) import Phladiprelio.Ukrainian.Emphasis import Phladiprelio.Coeffs import Phladiprelio.Rhythmicity.Factor import Phladiprelio.Ukrainian.PropertiesSyllablesG2H import qualified Logical.OrdConstraints as L helperHG :: Bool -> Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]] helperHG bool n xs | null xs = if bool then syllableDurationsD4 else (\_ -> []) | (n `rem` length xs) == 0 = head xs | otherwise = xs !! ((n `rem` length xs) - 1) helperHF4 :: Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]] helperHF4 = helperHG True {-# INLINE helperHF4 #-} helperHF1 :: Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]] helperHF1 = helperHG False {-# INLINE helperHF1 #-} ----------------------------------------------------------- -- | Partially defined auxiliary function to reduce code duplication. helpF1 bool choice@(c1:_) syllableDurationsDs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt = let just_probe = readRhythmicity choice in (case just_probe of Just (P1 ch rh n) -> rhythmicityABC 1.0 2.0 0.125 ch rh . rhythmicityGTup (helperHG bool n syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 Just (P2 ch rh r n) -> (case c1 of 'A' -> rhythmicityPolyWeightedLEF2 'D' -> rhythmicityPolyWeightedLF2 'E' -> rhythmicityPolyWeightedLEF3 'F' -> rhythmicityPolyWeightedLF3 'B' -> rhythmicityPolyWeightedEF2 'C' -> rhythmicityPolyWeightedF2 'M' -> rhythmicityPolyWeightedEF3 'N' -> rhythmicityPolyWeightedF3 'c' -> rhythmicityPoly) 1.0 r ch rh . rhythmicityGTup (helperHG bool n syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 _ -> rhythmicity0HTup (helperHG bool 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17) tttt -- | Partially defined auxiliary function to reduce code duplication. helpG1 choice@(c1:c2@(c3:c4@(c5:cs))) syllableDurationsDs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt = (case c1 of 'b' -> g rhythmicityPolyWeightedLEF3 5 1 'd' -> g rhythmicityPolyWeightedLEF30 5 1 'e' -> g rhythmicityPolyWeightedLEF3 6 2 'g' -> g rhythmicityPolyWeightedLEF2 5 1 'h' -> g rhythmicityPolyWeightedLEF20 5 1 'i' -> g rhythmicityPolyWeightedLEF2 6 2 'j' -> g rhythmicityPolyWeightedLEF20 6 2 'k' -> g rhythmicityPolyWeightedLF3 5 1 'l' -> g rhythmicityPolyWeightedLF30 5 1 'm' -> g rhythmicityPolyWeightedLF3 6 2 'n' -> g rhythmicityPolyWeightedLF30 6 2 'o' -> g rhythmicityPolyWeightedLF2 5 1 'p' -> g rhythmicityPolyWeightedLF20 5 1 'q' -> g rhythmicityPolyWeightedLF2 6 2 'r' -> g rhythmicityPolyWeightedLF20 6 2 'I' -> g rhythmicityPolyWeightedEF3 5 1 'J' -> g rhythmicityPolyWeightedEF30 5 1 'K' -> g rhythmicityPolyWeightedEF3 6 2 'L' -> g rhythmicityPolyWeightedEF30 6 2 'O' -> g rhythmicityPolyWeightedEF2 5 1 'P' -> g rhythmicityPolyWeightedEF20 5 1 'Q' -> g rhythmicityPolyWeightedEF2 6 2 'R' -> g rhythmicityPolyWeightedEF20 6 2 'W' -> g rhythmicityPolyWeightedF3 5 1 'X' -> g rhythmicityPolyWeightedF30 5 1 'Y' -> g rhythmicityPolyWeightedF3 6 2 'Z' -> g rhythmicityPolyWeightedF30 6 2 'U' -> g rhythmicityPolyWeightedF2 5 1 'V' -> g rhythmicityPolyWeightedF20 5 1 'S' -> g rhythmicityPolyWeightedF2 6 2 'T' -> g rhythmicityPolyWeightedF20 6 2 'u' -> g rhythmicityPoly 5 1 'v' -> g rhythmicityPoly0 5 1 's' -> g rhythmicityPoly 6 2 't' -> g rhythmicityPoly0 6 2 'z' -> g rhythmicityPolyWeightedLEF30 6 2) where h1 f ts xs m n = f 1.0 4 (PolyCh xs m) (PolyRhythm [1,2,1,n]) . mconcat . (let q = readMaybe c4::Maybe Int in case q of {Just q' -> helperHF1 q' syllableDurationsDs; ~Nothing -> (\_ -> [[-1.0]]) }) h2 f ts xs m n = f 1.0 4 (PolyCh xs m) (PolyRhythm [2,1,1,n]) . mconcat . (let q = readMaybe c4::Maybe Int in case q of {Just q' -> helperHF1 q' syllableDurationsDs; ~Nothing -> (\_ -> [[-1.0]]) }) g f m n | c3 == '0' = h1 f [c5] [True,True,True] m n | c3 == '1' = h1 f [c5] [True,True,False] m n | c3 == '2' = h1 f [c5] [True,False,True] m n | c3 == '3' = h1 f [c5] [True,False,False] m n | c3 == '4' = h2 f [c5] [False,False,True] m n | c3 == '5' = h2 f [c5] [False,True,False] m n | c3 == '6' = h2 f [c5] [False,True,True] m n | c3 == '7' = h2 f [c5] [False,False,False] m n | otherwise = \_ -> rhythmicity0HTup (helperHF1 n syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt {-| -} rhythmicityHTup :: Factors -> Double -> String -> [[[[Sound8]]] -> [[Double]]] -> 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) -> ReadyForConstructionUkr -> Double rhythmicityHTup ff k choice syllableDurationsDs coeffs bbs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 | any (== 'a') choice = rhythmicitya'Tup ff k (filter (\c -> c /='a' && c /= 'H') choice) syllableDurationsDs coeffs bbs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 | any (== 'H') choice = rhythmicityH'Tup ff k (filter (/= 'H') choice) syllableDurationsDs coeffs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 | otherwise = rhythmicityTup ff k choice coeffs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 rhythmicityH'Tup :: Factors -> Double -> String -> [[[[Sound8]]] -> [[Double]]] -> 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) -> ReadyForConstructionUkr -> Double rhythmicityH'Tup ff k choice@(c1:c2@(c3:c4@(c5:cs))) syllableDurationsDs CF0 tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt@(Str tttts) | L.ordCs2HPred1 [L.O "cMN", L.C "AF"] c1 = helpF1 True choice syllableDurationsDs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | c1 == '0' && c4 == "y" = let n2 = readMaybe [c3]::Maybe Int in rhythmicity0HTup (helperHF4 (case n2 of { Just n3 -> n3; Nothing -> 1}) syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | c1 == '0' && c4 == "f" = let n2 = readMaybe [c3]::Maybe Int in rhythmicity0FHTup (helperHF4 (case n2 of { Just n3 -> n3; Nothing -> 1}) syllableDurationsDs) ff k tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | c1 == '0' = rhythmicity0HTup (helperHF4 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | c1 `elem` "wx" = if | c4 >= "1" && c4 <= "4" -> if c3 >= '0' && c3 <= '3' then uncurry (wwF c4 tttts) (case c3 of '0' -> (Ch 1 1 4, Rhythm 1 1 2) '1' -> (Ch 1 0 4, Rhythm 2 1 1) '2' -> (Ch 0 1 4, Rhythm 1 2 1) '3' -> (Ch 0 0 4, Rhythm 1 1 2)) else rhythmicity0HTup (helperHF4 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | otherwise -> rhythmicity0HTup (helperHF4 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | L.ordCs2HPred1 [L.O "bz", L.C "degvIZ"] c1 && c4 >= "1" && c4 <= "9" = (case c1 of 'b' -> g rhythmicityPolyWeightedLEF3 5 1 'd' -> g rhythmicityPolyWeightedLEF30 5 1 'e' -> g rhythmicityPolyWeightedLEF3 6 2 'g' -> g rhythmicityPolyWeightedLEF2 5 1 'h' -> g rhythmicityPolyWeightedLEF20 5 1 'i' -> g rhythmicityPolyWeightedLEF2 6 2 'j' -> g rhythmicityPolyWeightedLEF20 6 2 'k' -> g rhythmicityPolyWeightedLF3 5 1 'l' -> g rhythmicityPolyWeightedLF30 5 1 'm' -> g rhythmicityPolyWeightedLF3 6 2 'n' -> g rhythmicityPolyWeightedLF30 6 2 'o' -> g rhythmicityPolyWeightedLF2 5 1 'p' -> g rhythmicityPolyWeightedLF20 5 1 'q' -> g rhythmicityPolyWeightedLF2 6 2 'r' -> g rhythmicityPolyWeightedLF20 6 2 'I' -> g rhythmicityPolyWeightedEF3 5 1 'J' -> g rhythmicityPolyWeightedEF30 5 1 'K' -> g rhythmicityPolyWeightedEF3 6 2 'L' -> g rhythmicityPolyWeightedEF30 6 2 'O' -> g rhythmicityPolyWeightedEF2 5 1 'P' -> g rhythmicityPolyWeightedEF20 5 1 'Q' -> g rhythmicityPolyWeightedEF2 6 2 'R' -> g rhythmicityPolyWeightedEF20 6 2 'W' -> g rhythmicityPolyWeightedF3 5 1 'X' -> g rhythmicityPolyWeightedF30 5 1 'Y' -> g rhythmicityPolyWeightedF3 6 2 'Z' -> g rhythmicityPolyWeightedF30 6 2 'U' -> g rhythmicityPolyWeightedF2 5 1 'V' -> g rhythmicityPolyWeightedF20 5 1 'S' -> g rhythmicityPolyWeightedF2 6 2 'T' -> g rhythmicityPolyWeightedF20 6 2 'u' -> g rhythmicityPoly 5 1 'v' -> g rhythmicityPoly0 5 1 's' -> g rhythmicityPoly 6 2 't' -> g rhythmicityPoly0 6 2 'z' -> g rhythmicityPolyWeightedLEF30 6 2) tttts | otherwise = rhythmicity0HTup (let q = readMaybe c4::Maybe Int in case q of {Just q' -> helperHF4 q' syllableDurationsDs; ~Nothing -> syllableDurationsD4 }) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt where h1 f ts xs m n = f 1.0 4 (PolyCh xs m) (PolyRhythm [1,2,1,n]) . mconcat . (let q = readMaybe c4::Maybe Int in case q of {Just q' -> helperHF4 q' syllableDurationsDs; ~Nothing -> syllableDurationsD4 }) . createSyllablesUkrSTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 h2 f ts xs m n = f 1.0 4 (PolyCh xs m) (PolyRhythm [2,1,1,n]) . mconcat . (let q = readMaybe c4::Maybe Int in case q of {Just q' -> helperHF4 q' syllableDurationsDs; ~Nothing -> syllableDurationsD4 }) . createSyllablesUkrSTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 g f m n | c3 == '0' = h1 f c4 [True,True,True] m n | c3 == '1' = h1 f c4 [True,True,False] m n | c3 == '2' = h1 f c4 [True,False,True] m n | c3 == '3' = h1 f c4 [True,False,False] m n | c3 == '4' = h2 f c4 [False,False,True] m n | c3 == '5' = h2 f c4 [False,True,False] m n | c3 == '6' = h2 f c4 [False,True,True] m n | c3 == '7' = h2 f c4 [False,False,False] m n | otherwise = \_ -> rhythmicity0HTup (helperHF4 n syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt w1F f tttts ch rh = (if c1 == 'w' then rhythmicityABC else rhythmicityABC0) 1.0 2.0 0.125 ch rh . mconcat . f . createSyllablesUkrSTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 $ tttts wwF2 g2 xs = let n1 = readMaybe xs::Maybe Int in case n1 of Just n2 -> g2 (helperHF4 n2 syllableDurationsDs) Nothing -> g2 syllableDurationsD4 wwF = wwF2 w1F {-# INLINE w1F #-} {-# INLINE wwF2 #-} {-# INLINE wwF #-} rhythmicityH'Tup ff k choice@(c1:c2@(c3:c4@(c5:cs))) syllableDurationsDs (CF2 x y) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt@(Str tttts) | c1 `elem` "wx" = if | c5 >= '1' && c5 <= '4' -> if c3 >= '0' && c3 <= '3' then uncurry (wwF c4 tttts) (case c3 of '0' -> (Ch 1 1 4, Rhythm 1 1 2) '1' -> (Ch 1 0 4, Rhythm 2 1 1) '2' -> (Ch 0 1 4, Rhythm 1 2 1) '3' -> (Ch 0 0 4, Rhythm 1 1 2)) else rhythmicity0HTup (helperHF4 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | otherwise -> rhythmicity0HTup (helperHF4 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | c1 == '0' = if c2 `elem` ["2f","3f","4f"] then rhythmicityKFHTup (helperHF4 (case c5 of {'2' -> 2; '3' -> 3; '4' -> 4; ~rrrrr -> 1}) syllableDurationsDs) ff k (fromMaybe 1.0 x) (fromMaybe 1.0 y) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt else rhythmicityKHTup (helperHF4 (case c5 of {'2' -> 2; '3' -> 3; '4' -> 4; ~rrrrr -> 1}) syllableDurationsDs) (fromMaybe 1.0 x) (fromMaybe 1.0 y) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | L.ordCs2HPred1 [L.O "z", L.C "begvAFIZ"] c1 = rhythmicityH'Tup ff k choice syllableDurationsDs CF0 tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | otherwise = rhythmicityKHTup (let q = readMaybe c4::Maybe Int in case q of {Just q' -> helperHF4 q' syllableDurationsDs; ~Nothing -> syllableDurationsD4 }) (fromMaybe 1.0 x) (fromMaybe 1.0 y) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt where w1F f tttts ch rh = (if c1 == 'w' then rhythmicityABC else rhythmicityABC0) 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) ch rh . mconcat . f . createSyllablesUkrSTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 $ tttts wwF xs = let n1 = readMaybe xs::Maybe Int in case n1 of Just n2 -> w1F (helperHF4 n2 syllableDurationsDs) Nothing -> w1F syllableDurationsD4 {-# INLINE w1F #-} {-# INLINE wwF #-} rhythmicityH'Tup ff k choice@(c1:c2@(c3:cs)) syllableDurationsDs CF0 tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt@(Str tttts) | choice == "0y" = rhythmicity0HTup (helperHF4 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | choice == "0f" = rhythmicity0FHTup (helperHF4 1 syllableDurationsDs) ff k tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | otherwise = rhythmicity0HTup (helperHF4 4 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt rhythmicityH'Tup ff k choice@(c1:c2@(c3:cs)) syllableDurationsDs (CF2 x y) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt@(Str tttts) | choice == "0f" = rhythmicityKFHTup (helperHF4 1 syllableDurationsDs) ff k (fromMaybe 1.0 x) (fromMaybe 1.0 y) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | choice == "0y" = rhythmicityKHTup (helperHF4 1 syllableDurationsDs) (fromMaybe 1.0 x) (fromMaybe 1.0 y) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | otherwise = rhythmicity0HTup (helperHF4 4 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt rhythmicityH'Tup _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ = -3.0 rhythmicitya'Tup :: Factors -> Double -> String -> [[[[Sound8]]] -> [[Double]]] -> 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) -> ReadyForConstructionUkr -> Double rhythmicitya'Tup ff k choice@(c1:c2@(c3:c4@(c5:cs))) syllableDurationsDs CF0 bbs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt@(FSL tttts) | L.ordCs2HPred1 [L.O "cMN", L.C "AF"] c1 = helpF1 False choice syllableDurationsDs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | c1 == '0' && c5 == 'y' = let n2 = readMaybe [c3]::Maybe Int in rhythmicity0HTup (helperHF1 (case n2 of {Just n3 -> n3; Nothing -> 1}) syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | c1 == '0' && c5 == 'f' = let n2 = readMaybe [c3]::Maybe Int in rhythmicity0FHTup (helperHF1 (case n2 of {Just n3 -> n3; Nothing -> 1}) syllableDurationsDs) ff k tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | c1 == '0' = rhythmicity0HTup (helperHF1 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | c1 `elem` "wx" = if | c5 >= '1' && c5 <= '4' -> if c3 >= '0' && c3 <= '3' then uncurry (wwF c4 tttts) (case c3 of '0' -> (Ch 1 1 4, Rhythm 1 1 2) '1' -> (Ch 1 0 4, Rhythm 2 1 1) '2' -> (Ch 0 1 4, Rhythm 1 2 1) '3' -> (Ch 0 0 4, Rhythm 1 1 2)) else rhythmicity0HTup (helperHF1 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | otherwise -> rhythmicity0HTup (helperHF1 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | (L.ordCs2HPred1 [L.O "z", L.C "begvIZ"] c1) && c5 >= '1' && c5 <= '9' = (helpG1 choice syllableDurationsDs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt) tttts | otherwise = rhythmicity0HTup (let q = readMaybe c4::Maybe Int in case q of {Just q' -> helperHF1 q' syllableDurationsDs; ~Nothing -> (\_ -> [[-1.0]]) }) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt where w1F f tttts ch rh = (if c1 == 'w' then rhythmicityABC else rhythmicityABC0) 1.0 2.0 0.125 ch rh . mconcat . f $ tttts wwF2 g2 xs = let n1 = readMaybe xs::Maybe Int in case n1 of Just n2 -> g2 (helperHF1 n2 syllableDurationsDs) Nothing -> g2 (\_ -> [[-1.0]]) wwF = wwF2 w1F {-# INLINE w1F #-} {-# INLINE wwF2 #-} {-# INLINE wwF #-} rhythmicitya'Tup ff k choice@(c1:c2@(c3:c4@(c5:cs))) syllableDurationsDs (CF2 x y) bbs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt@(FSL tttts) | c1 `elem` "wx" = if | c5 >= '1' && c5 <= '4' -> if c3 >= '0' && c3 <= '3' then uncurry (wwF c4 tttts) (case c3 of '0' -> (Ch 1 1 4, Rhythm 1 1 2) '1' -> (Ch 1 0 4, Rhythm 2 1 1) '2' -> (Ch 0 1 4, Rhythm 1 2 1) '3' -> (Ch 0 0 4, Rhythm 1 1 2)) else rhythmicity0HTup (helperHF1 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | otherwise -> rhythmicity0HTup (helperHF1 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | c1 == '0' = if c2 `elem` ["2f","3f","4f"] then rhythmicityKFHTup (helperHF1 (case c5 of {'2' -> 2; '3' -> 3; '4' -> 4; ~rrrrr -> 1}) syllableDurationsDs) ff k (fromMaybe 1.0 x) (fromMaybe 1.0 y)tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt else rhythmicityKHTup (helperHF1 (case c5 of {'2' -> 2; '3' -> 3; '4' -> 4; ~rrrrr -> 1}) syllableDurationsDs) (fromMaybe 1.0 x) (fromMaybe 1.0 y) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | L.ordCs2HPred1 [L.O "z",L.C "begvAFIZ"] c1 = rhythmicityH'Tup ff k choice syllableDurationsDs CF0 tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | otherwise = rhythmicityKHTup (let q = readMaybe c4::Maybe Int in case q of {Just q' -> helperHF1 q' syllableDurationsDs; ~Nothing -> (\_ -> [[-1.0]]) }) (fromMaybe 1.0 x) (fromMaybe 1.0 y) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt where w1F f tttts ch rh = (if c1 == 'w' then rhythmicityABC else rhythmicityABC0) 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) ch rh . mconcat . f $ tttts wwF xs = let n1 = readMaybe xs::Maybe Int in case n1 of Just n2 -> w1F (helperHF1 n2 syllableDurationsDs) Nothing -> w1F (\_ -> [[-1.0]]) {-# INLINE w1F #-} {-# INLINE wwF #-} rhythmicitya'Tup ff k choice@(c1:c2@(c3:c4@(c5:cs))) syllableDurationsDs CF0 bbs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt@(Str tttts@(_:_)) | c1 `elem` "cMN" || (c1 >= 'A' && c1 <= 'F') = helpF1 False choice syllableDurationsDs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | c1 == '0' && c5 == 'y' = let n2 = readMaybe [c3]::Maybe Int in rhythmicity0HTup (helperHF1 (case n2 of {Just n3 -> n3; Nothing -> 1}) syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | c1 == '0' && c5 == 'f' = let n2 = readMaybe [c3]::Maybe Int in rhythmicity0FHTup (helperHF1 (case n2 of {Just n3 -> n3; Nothing -> 1}) syllableDurationsDs) ff k tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | c1 == '0' = rhythmicity0HTup (helperHF1 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | c1 `elem` "wx" = if | c5 >= '1' && c5 <= '4' -> if c3 >= '0' && c3 <= '3' then uncurry (wwF c4 tttts) (case c3 of '0' -> (Ch 1 1 4, Rhythm 1 1 2) '1' -> (Ch 1 0 4, Rhythm 2 1 1) '2' -> (Ch 0 1 4, Rhythm 1 2 1) '3' -> (Ch 0 0 4, Rhythm 1 1 2)) else rhythmicity0HTup (helperHF1 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | otherwise -> rhythmicity0HTup (helperHF1 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | L.ordCs2HPred1 [L.O "bz", L.C "degvIZ"] c1 && c5 >= '1' && c5 <= '9' = (helpG1 choice syllableDurationsDs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt) . convFI bbs $ tttts | otherwise = rhythmicity0HTup (let q = readMaybe c4::Maybe Int in case q of {Just q' -> helperHF1 q' syllableDurationsDs; ~Nothing -> (\_ -> [[-1.0]]) }) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt where w1F f tttts ch rh = (if c1 == 'w' then rhythmicityABC else rhythmicityABC0) 1.0 2.0 0.125 ch rh . mconcat . f $ tttts wwF2 g2 xs = let n1 = readMaybe xs::Maybe Int in case n1 of Just n2 -> g2 (helperHF1 n2 syllableDurationsDs . convFI bbs) Nothing -> g2 (\_ -> [[-1.0]]) wwF = wwF2 w1F {-# INLINE w1F #-} {-# INLINE wwF2 #-} {-# INLINE wwF #-} rhythmicitya'Tup ff k choice@(c1:c2@(c3:c4@(c5:cs))) syllableDurationsDs (CF2 x y) bbs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt@(Str tttts@(_:_)) | c1 `elem` "wx" = if | c5 >= '1' && c5 <= '4' -> if c3 >= '0' && c3 <= '3' then uncurry (wwF c4 tttts) (case c3 of '0' -> (Ch 1 1 4, Rhythm 1 1 2) '1' -> (Ch 1 0 4, Rhythm 2 1 1) '2' -> (Ch 0 1 4, Rhythm 1 2 1) '3' -> (Ch 0 0 4, Rhythm 1 1 2)) else rhythmicity0HTup (helperHF1 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | otherwise -> rhythmicity0HTup (helperHF1 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | c1 == '0' = if c2 `elem` ["2f","3f","4f"] then rhythmicityKFHTup (helperHF1 (case c5 of {'2' -> 2; '3' -> 3; '4' -> 4; ~rrrrr -> 1}) syllableDurationsDs) ff k (fromMaybe 1.0 x) (fromMaybe 1.0 y) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt else rhythmicityKHTup (helperHF1 (case c5 of {'2' -> 2; '3' -> 3; '4' -> 4; ~rrrrr -> 1}) syllableDurationsDs) (fromMaybe 1.0 x) (fromMaybe 1.0 y) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | L.ordCs2HPred1 [L.O "z", L.C "begvAFIZ"] c1 = rhythmicityH'Tup ff k choice syllableDurationsDs CF0 tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | otherwise = rhythmicityKHTup (let q = readMaybe c4::Maybe Int in case q of {Just q' -> helperHF1 q' syllableDurationsDs; ~Nothing -> (\_ -> [[-1.0]]) }) (fromMaybe 1.0 x) (fromMaybe 1.0 y) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt where w1F f tttts ch rh = (if c1 == 'w' then rhythmicityABC else rhythmicityABC0) 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) ch rh . mconcat . f $ tttts wwF xs = let n1 = readMaybe xs::Maybe Int in case n1 of Just n2 -> w1F (helperHF1 n2 syllableDurationsDs . convFI bbs) Nothing -> w1F (\_ -> [[-1.0]]) {-# INLINE w1F #-} {-# INLINE wwF #-} rhythmicitya'Tup ff k choice@(c1:c2@(c3:cs)) syllableDurationsDs CF0 bbs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt@(FSL tttts) | choice == "0y" = rhythmicity0HTup (helperHF1 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | choice == "0f" = rhythmicity0FHTup (helperHF1 1 syllableDurationsDs) ff k tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | otherwise = rhythmicity0HTup (helperHF1 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt rhythmicitya'Tup ff k choice@(c1:c2@(c3:cs)) syllableDurationsDs (CF2 x y) bbs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt@(FSL tttts) | choice == "0f" = rhythmicityKFHTup (helperHF1 1 syllableDurationsDs) ff k (fromMaybe 1.0 x) (fromMaybe 1.0 y) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | choice == "0y" = rhythmicityKHTup (helperHF1 1 syllableDurationsDs) (fromMaybe 1.0 x) (fromMaybe 1.0 y) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | otherwise = rhythmicity0HTup (helperHF1 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt rhythmicitya'Tup ff k choice@(c1:c2@(c3:cs)) syllableDurationsDs CF0 bbs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt@(Str tttts@(_:_)) | choice == "0y" = rhythmicity0HTup (helperHF1 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | choice == "0f" = rhythmicity0FHTup (helperHF1 1 syllableDurationsDs) ff k tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | otherwise = rhythmicity0HTup (helperHF1 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt rhythmicitya'Tup ff k choice@(c1:c2@(c3:cs)) syllableDurationsDs (CF2 x y) bbs tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt@(Str tttts@(_:_)) | choice == "0f" = rhythmicityKFHTup (helperHF1 1 syllableDurationsDs) ff k (fromMaybe 1.0 x) (fromMaybe 1.0 y) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | choice == "0y" = rhythmicityKHTup (helperHF1 1 syllableDurationsDs) (fromMaybe 1.0 x) (fromMaybe 1.0 y) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt | otherwise = rhythmicity0HTup (helperHF1 1 syllableDurationsDs) tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 tttt rhythmicitya'Tup _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ _ = -2.0