{-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2Hprime -- Copyright : (c) OleksandrZhabenko 2020-2022 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@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 CPP, BangPatterns, MultiWayIf #-} module Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2Hprime ( -- * General rhythmicityH , rhythmicityH' -- * Extended , rhythmicityHTup , rhythmicityH'Tup ) where #ifdef __GLASGOW_HASKELL__ #if __GLASGOW_HASKELL__>=710 /* code that applies only to GHC 7.10.* and higher versions */ import GHC.Base (mconcat) #endif #endif import Languages.Phonetic.Ukrainian.Syllable.Double.ArrInt8 import Melodics.Ukrainian.ArrInt8 (Sound8, FlowSound) import Languages.Phonetic.Ukrainian.Syllable.ArrInt8 import Data.Maybe (fromMaybe) import Text.Read (readMaybe) import Rhythmicity.TwoFourth import Rhythmicity.PolyRhythm import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2Common import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG201 import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2H import GHC.Arr (Array) import GHC.Int (Int8) #ifdef __GLASGOW_HASKELL__ #if __GLASGOW_HASKELL__==708 /* code that applies only to GHC 7.8.* */ mconcat = concat #endif #endif {-| Allows to use the user-defined custom 'Sound8' durations. This is used when the first character in the second argument is \'H\'. -} rhythmicityH :: Double -> String -> [[[[Sound8]]] -> [[Double]]] -> Coeffs2 -> String -> Double rhythmicityH k choice syllableDurationsDs coeffs | take 1 choice == "H" = rhythmicityH' k (drop 1 choice) syllableDurationsDs coeffs | otherwise = rhythmicity k choice coeffs rhythmicityH' :: Double -> String -> [[[[Sound8]]] -> [[Double]]] -> Coeffs2 -> String -> Double rhythmicityH' k choice syllableDurationsDs CF0 = if | take 1 choice `elem` ["c","M","N"] || (take 1 choice >= "A" && take 1 choice <= "F") -> let just_probe = readRhythmicity choice in case just_probe of Just (P1 ch rh n) -> rhythmicityABC 1.0 2.0 0.125 ch rh . rhythmicityG (helperHF4 n syllableDurationsDs) Just (P2 ch rh r n) -> case take 1 choice of "A" -> rhythmicityPolyWeightedLEF2 1.0 r ch rh . rhythmicityG (helperHF4 n syllableDurationsDs) "D" -> rhythmicityPolyWeightedLF2 1.0 r ch rh . rhythmicityG (helperHF4 n syllableDurationsDs) "E" -> rhythmicityPolyWeightedLEF3 1.0 r ch rh . rhythmicityG (helperHF4 n syllableDurationsDs) "F" -> rhythmicityPolyWeightedLF3 1.0 r ch rh . rhythmicityG (helperHF4 n syllableDurationsDs) "B" -> rhythmicityPolyWeightedEF2 1.0 r ch rh . rhythmicityG (helperHF4 n syllableDurationsDs) "C" -> rhythmicityPolyWeightedF2 1.0 r ch rh . rhythmicityG (helperHF4 n syllableDurationsDs) "M" -> rhythmicityPolyWeightedEF3 1.0 r ch rh . rhythmicityG (helperHF4 n syllableDurationsDs) "N" -> rhythmicityPolyWeightedF3 1.0 r ch rh . rhythmicityG (helperHF4 n syllableDurationsDs) "c" -> rhythmicityPoly 1.0 r ch rh . rhythmicityG (helperHF4 n syllableDurationsDs) _ -> rhythmicity0H (helperHF4 1 syllableDurationsDs) | choice == "0y" -> rhythmicity0H (helperHF4 1 syllableDurationsDs) | take 1 choice == "0" && drop 2 (take 3 choice) == "y" -> let n2 = readMaybe (drop 1 . take 2 $ choice)::Maybe Int in case n2 of Just n3 -> rhythmicity0H (helperHF4 n3 syllableDurationsDs) Nothing -> rhythmicity0H (helperHF4 1 syllableDurationsDs) | choice == "0z" -> rhythmicity0FH (helperHF4 1 syllableDurationsDs) k | take 1 choice == "0" && drop 2 (take 3 choice) == "z" -> let n2 = readMaybe (drop 1 . take 2 $ choice)::Maybe Int in case n2 of Just n3 -> rhythmicity0FH (helperHF4 n3 syllableDurationsDs) k Nothing -> rhythmicity0FH (helperHF4 1 syllableDurationsDs) k | take 1 choice == "0" -> rhythmicity0H (helperHF4 1 syllableDurationsDs) | take 1 choice == "w" -> if | (drop 2 . take 3 $ choice) >= "1" && (drop 2 . take 3 $ choice) <= "4" -> case take 2 choice of "w0" -> wwF (drop 2 . take 3 $ choice) (Ch 1 1 4) (Rhythm 1 1 2) "w1" -> wwF (drop 2 . take 3 $ choice) (Ch 1 0 4) (Rhythm 2 1 1) "w2" -> wwF (drop 2 . take 3 $ choice) (Ch 0 1 4) (Rhythm 1 2 1) "w3" -> wwF (drop 2 . take 3 $ choice) (Ch 0 0 4) (Rhythm 1 1 2) _ -> rhythmicity0H (helperHF4 1 syllableDurationsDs) | otherwise -> rhythmicity0H (helperHF4 1 syllableDurationsDs) | take 1 choice == "x" -> if | (drop 2 . take 3 $ choice) >= "1" && (drop 2 . take 3 $ choice) <= "4" -> case take 2 choice of "x0" -> xxF (drop 2 . take 3 $ choice) (Ch 1 1 4) (Rhythm 1 1 2) "x1" -> xxF (drop 2 . take 3 $ choice) (Ch 1 0 4) (Rhythm 2 1 1) "x2" -> xxF (drop 2 . take 3 $ choice) (Ch 0 1 4) (Rhythm 1 2 1) "x3" -> xxF (drop 2 . take 3 $ choice) (Ch 0 0 4) (Rhythm 1 1 2) _ -> rhythmicity0H (helperHF4 1 syllableDurationsDs) | otherwise -> rhythmicity0H (helperHF4 1 syllableDurationsDs) | otherwise -> if | (take 1 choice == "b" || ((take 1 choice >= "d" && take 1 choice <= "v") || (take 1 choice >= "I" && take 1 choice <= "Z"))) && (drop 2 . take 3 $ choice) >= "1" && (drop 2 . take 3 $ choice) <= "9" -> case take 1 choice of "b" -> g rhythmicityPolyWeightedLEF3 5 1 "d" -> g rhythmicityPolyWeightedLEF30 5 1 "e" -> g rhythmicityPolyWeightedLEF3 6 2 "f" -> g rhythmicityPolyWeightedLEF30 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 | otherwise -> rhythmicity0H (let ts = drop 2 . take 3 $ choice in case ts of { [] -> syllableDurationsD4 ; ks -> let q = readMaybe ks::Maybe Int in case q of {Just q' -> helperHF4 q' syllableDurationsDs; ~Nothing -> syllableDurationsD4 }}) where h1 f ts xs m n = f 1.0 4 (PolyCh xs m) (PolyRhythm [1,2,1,n]) . mconcat . (case ts of { [] -> syllableDurationsD4 ; ks -> let q = readMaybe ks::Maybe Int in case q of {Just q' -> helperHF4 q' syllableDurationsDs; ~Nothing -> syllableDurationsD4 }}) . createSyllablesUkrS h2 f ts xs m n = f 1.0 4 (PolyCh xs m) (PolyRhythm [2,1,1,n]) . mconcat . (case ts of { [] -> syllableDurationsD4 ; ks -> let q = readMaybe ks::Maybe Int in case q of {Just q' -> helperHF4 q' syllableDurationsDs; ~Nothing -> syllableDurationsD4 }}) . createSyllablesUkrS g f m n | drop 1 (take 2 choice) == "0" = h1 f (drop 2 . take 3 $ choice) [True,True,True] m n | drop 1 (take 2 choice) == "1" = h1 f (drop 2 . take 3 $ choice) [True,True,False] m n | drop 1 (take 2 choice) == "2" = h1 f (drop 2 . take 3 $ choice) [True,False,True] m n | drop 1 (take 2 choice) == "3" = h1 f (drop 2 . take 3 $ choice) [True,False,False] m n | drop 1 (take 2 choice) == "4" = h2 f (drop 2 . take 3 $ choice) [True,True,True] m n | drop 1 (take 2 choice) == "5" = h2 f (drop 2 . take 3 $ choice) [True,True,False] m n | drop 1 (take 2 choice) == "6" = h2 f (drop 2 . take 3 $ choice) [True,False,True] m n | drop 1 (take 2 choice) == "7" = h2 f (drop 2 . take 3 $ choice) [True,False,False] m n | otherwise = rhythmicity0H (helperHF4 n syllableDurationsDs) w1F f ch rh = rhythmicityABC 1.0 2.0 0.125 ch rh . mconcat . f . createSyllablesUkrS wwF2 g2 xs = let n1 = readMaybe xs::Maybe Int in case n1 of Just n2 -> g2 (helperHF4 n2 syllableDurationsDs) Nothing -> g2 syllableDurationsD4 x1F f ch rh = rhythmicityABC0 1.0 2.0 0.125 ch rh . mconcat . f . createSyllablesUkrS xxF = wwF2 x1F wwF = wwF2 w1F {-# INLINE w1F #-} {-# INLINE wwF2 #-} {-# INLINE x1F #-} {-# INLINE xxF #-} {-# INLINE wwF #-} rhythmicityH' k choice syllableDurationsDs (CF2 x y) = case take 1 choice of "0" -> case choice of "0y" -> rhythmicityKH (helperHF4 1 syllableDurationsDs) (fromMaybe 1.0 x) (fromMaybe 1.0 y) "02y" -> rhythmicityKH (helperHF4 2 syllableDurationsDs) (fromMaybe 1.0 x) (fromMaybe 1.0 y) "03y" -> rhythmicityKH (helperHF4 3 syllableDurationsDs) (fromMaybe 1.0 x) (fromMaybe 1.0 y) "0z" -> rhythmicityKFH (helperHF4 1 syllableDurationsDs) k (fromMaybe 1.0 x) (fromMaybe 1.0 y) "02z" -> rhythmicityKFH (helperHF4 2 syllableDurationsDs) k (fromMaybe 1.0 x) (fromMaybe 1.0 y) "03z" -> rhythmicityKFH (helperHF4 3 syllableDurationsDs) k (fromMaybe 1.0 x) (fromMaybe 1.0 y) "04z" -> rhythmicityKFH (helperHF4 4 syllableDurationsDs) k (fromMaybe 1.0 x) (fromMaybe 1.0 y) _ -> rhythmicityKH (helperHF4 1 syllableDurationsDs) (fromMaybe 1.0 x) (fromMaybe 1.0 y) "w" -> if | (drop 2 . take 3 $ choice) >= "1" && (drop 2 . take 3 $ choice) <= "4" -> case take 2 choice of "w0" -> wwF (drop 2 . take 3 $ choice) (Ch 1 1 4) (Rhythm 1 1 2) "w1" -> wwF (drop 2 . take 3 $ choice) (Ch 1 0 4) (Rhythm 2 1 1) "w2" -> wwF (drop 2 . take 3 $ choice) (Ch 0 1 4) (Rhythm 1 2 1) "w3" -> wwF (drop 2 . take 3 $ choice) (Ch 0 0 4) (Rhythm 1 1 2) _ -> rhythmicity0H (helperHF4 1 syllableDurationsDs) | otherwise -> rhythmicity0H (helperHF4 1 syllableDurationsDs) where w1F f ch rh = rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) ch rh . mconcat . f . createSyllablesUkrS 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 #-} "x" -> if | (drop 2 . take 3 $ choice) >= "1" && (drop 2 . take 3 $ choice) <= "4" -> case take 2 choice of "x0" -> xxF (drop 2 . take 3 $ choice) (Ch 1 1 4) (Rhythm 1 1 2) "x1" -> xxF (drop 2 . take 3 $ choice) (Ch 1 0 4) (Rhythm 2 1 1) "x2" -> xxF (drop 2 . take 3 $ choice) (Ch 0 1 4) (Rhythm 1 2 1) "x3" -> xxF (drop 2 . take 3 $ choice) (Ch 0 0 4) (Rhythm 1 1 2) _ -> rhythmicity0H (helperHF4 1 syllableDurationsDs) | otherwise -> rhythmicity0H (helperHF4 1 syllableDurationsDs) where x1F f ch rh = rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) ch rh . mconcat . f . createSyllablesUkrS xxF xs = let n1 = readMaybe xs::Maybe Int in case n1 of Just n2 -> x1F (helperHF4 n2 syllableDurationsDs) Nothing -> x1F syllableDurationsD4 {-# INLINE x1F #-} {-# INLINE xxF #-} _ -> if | ((take 1 choice >= "b" && take 1 choice <= "v") || (take 1 choice >= "A" && take 1 choice <= "Z" && take 1 choice `notElem` ["G","H"])) -> rhythmicityH' k choice syllableDurationsDs CF0 | otherwise -> rhythmicityKH (let ts = drop 2 . take 3 $ choice in case ts of { [] -> syllableDurationsD4 ; ks -> let q = readMaybe ks::Maybe Int in case q of {Just q' -> helperHF4 q' syllableDurationsDs; ~Nothing -> syllableDurationsD4 }}) (fromMaybe 1.0 x) (fromMaybe 1.0 y) helperHF4 :: Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]] helperHF4 n xs | null xs = syllableDurationsD4 | (n `rem` length xs) == 0 = head xs | otherwise = xs !! ((n `rem` length xs) - 1) ----------------------------------------------------------- {-| -} rhythmicityHTup :: 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 -> String -> [[[[Sound8]]] -> [[Double]]] -> Coeffs2 -> String -> Double rhythmicityHTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k choice syllableDurationsDs coeffs | take 1 choice == "H" = rhythmicityH'Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k (drop 1 choice) syllableDurationsDs coeffs | otherwise = rhythmicityTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k choice coeffs rhythmicityH'Tup :: 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 -> String -> [[[[Sound8]]] -> [[Double]]] -> Coeffs2 -> String -> Double rhythmicityH'Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k choice syllableDurationsDs CF0 = if | take 1 choice `elem` ["c","M","N"] || (take 1 choice >= "A" && take 1 choice <= "F") -> 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 tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 n syllableDurationsDs) Just (P2 ch rh r n) -> case take 1 choice of "A" -> rhythmicityPolyWeightedLEF2 1.0 r ch rh . rhythmicityGTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 n syllableDurationsDs) "D" -> rhythmicityPolyWeightedLF2 1.0 r ch rh . rhythmicityGTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 n syllableDurationsDs) "E" -> rhythmicityPolyWeightedLEF3 1.0 r ch rh . rhythmicityGTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 n syllableDurationsDs) "F" -> rhythmicityPolyWeightedLF3 1.0 r ch rh . rhythmicityGTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 n syllableDurationsDs) "B" -> rhythmicityPolyWeightedEF2 1.0 r ch rh . rhythmicityGTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 n syllableDurationsDs) "C" -> rhythmicityPolyWeightedF2 1.0 r ch rh . rhythmicityGTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 n syllableDurationsDs) "M" -> rhythmicityPolyWeightedEF3 1.0 r ch rh . rhythmicityGTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 n syllableDurationsDs) "N" -> rhythmicityPolyWeightedF3 1.0 r ch rh . rhythmicityGTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 n syllableDurationsDs) "c" -> rhythmicityPoly 1.0 r ch rh . rhythmicityGTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 n syllableDurationsDs) _ -> rhythmicity0HTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 1 syllableDurationsDs) | choice == "0y" -> rhythmicity0HTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 1 syllableDurationsDs) | take 1 choice == "0" && drop 2 (take 3 choice) == "y" -> let n2 = readMaybe (drop 1 . take 2 $ choice)::Maybe Int in case n2 of Just n3 -> rhythmicity0HTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 n3 syllableDurationsDs) Nothing -> rhythmicity0HTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 1 syllableDurationsDs) | choice == "0z" -> rhythmicity0FHTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 1 syllableDurationsDs) k | take 1 choice == "0" && drop 2 (take 3 choice) == "z" -> let n2 = readMaybe (drop 1 . take 2 $ choice)::Maybe Int in case n2 of Just n3 -> rhythmicity0FHTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 n3 syllableDurationsDs) k Nothing -> rhythmicity0FHTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 1 syllableDurationsDs) k | take 1 choice == "0" -> rhythmicity0HTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 1 syllableDurationsDs) | take 1 choice == "w" -> if | (drop 2 . take 3 $ choice) >= "1" && (drop 2 . take 3 $ choice) <= "4" -> case take 2 choice of "w0" -> wwF (drop 2 . take 3 $ choice) (Ch 1 1 4) (Rhythm 1 1 2) "w1" -> wwF (drop 2 . take 3 $ choice) (Ch 1 0 4) (Rhythm 2 1 1) "w2" -> wwF (drop 2 . take 3 $ choice) (Ch 0 1 4) (Rhythm 1 2 1) "w3" -> wwF (drop 2 . take 3 $ choice) (Ch 0 0 4) (Rhythm 1 1 2) _ -> rhythmicity0HTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 1 syllableDurationsDs) | otherwise -> rhythmicity0HTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 1 syllableDurationsDs) | take 1 choice == "x" -> if | (drop 2 . take 3 $ choice) >= "1" && (drop 2 . take 3 $ choice) <= "4" -> case take 2 choice of "x0" -> xxF (drop 2 . take 3 $ choice) (Ch 1 1 4) (Rhythm 1 1 2) "x1" -> xxF (drop 2 . take 3 $ choice) (Ch 1 0 4) (Rhythm 2 1 1) "x2" -> xxF (drop 2 . take 3 $ choice) (Ch 0 1 4) (Rhythm 1 2 1) "x3" -> xxF (drop 2 . take 3 $ choice) (Ch 0 0 4) (Rhythm 1 1 2) _ -> rhythmicity0HTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 1 syllableDurationsDs) | otherwise -> rhythmicity0HTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 1 syllableDurationsDs) | otherwise -> if | (take 1 choice == "b" || ((take 1 choice >= "d" && take 1 choice <= "v") || (take 1 choice >= "I" && take 1 choice <= "Z"))) && (drop 2 . take 3 $ choice) >= "1" && (drop 2 . take 3 $ choice) <= "9" -> case take 1 choice of "b" -> g rhythmicityPolyWeightedLEF3 5 1 "d" -> g rhythmicityPolyWeightedLEF30 5 1 "e" -> g rhythmicityPolyWeightedLEF3 6 2 "f" -> g rhythmicityPolyWeightedLEF30 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 | otherwise -> rhythmicity0HTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (let ts = drop 2 . take 3 $ choice in case ts of { [] -> syllableDurationsD4 ; ks -> let q = readMaybe ks::Maybe Int in case q of {Just q' -> helperHF4 q' syllableDurationsDs; ~Nothing -> syllableDurationsD4 }}) where h1 f ts xs m n = f 1.0 4 (PolyCh xs m) (PolyRhythm [1,2,1,n]) . mconcat . (case ts of { [] -> syllableDurationsD4 ; ks -> let q = readMaybe ks::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 . (case ts of { [] -> syllableDurationsD4 ; ks -> let q = readMaybe ks::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 | drop 1 (take 2 choice) == "0" = h1 f (drop 2 . take 3 $ choice) [True,True,True] m n | drop 1 (take 2 choice) == "1" = h1 f (drop 2 . take 3 $ choice) [True,True,False] m n | drop 1 (take 2 choice) == "2" = h1 f (drop 2 . take 3 $ choice) [True,False,True] m n | drop 1 (take 2 choice) == "3" = h1 f (drop 2 . take 3 $ choice) [True,False,False] m n | drop 1 (take 2 choice) == "4" = h2 f (drop 2 . take 3 $ choice) [True,True,True] m n | drop 1 (take 2 choice) == "5" = h2 f (drop 2 . take 3 $ choice) [True,True,False] m n | drop 1 (take 2 choice) == "6" = h2 f (drop 2 . take 3 $ choice) [True,False,True] m n | drop 1 (take 2 choice) == "7" = h2 f (drop 2 . take 3 $ choice) [True,False,False] m n | otherwise = rhythmicity0HTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 n syllableDurationsDs) w1F f ch rh = rhythmicityABC 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 wwF2 g2 xs = let n1 = readMaybe xs::Maybe Int in case n1 of Just n2 -> g2 (helperHF4 n2 syllableDurationsDs) Nothing -> g2 syllableDurationsD4 x1F f ch rh = 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 xxF = wwF2 x1F wwF = wwF2 w1F {-# INLINE w1F #-} {-# INLINE wwF2 #-} {-# INLINE x1F #-} {-# INLINE xxF #-} {-# INLINE wwF #-} rhythmicityH'Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k choice syllableDurationsDs (CF2 x y) = case take 1 choice of "0" -> case choice of "0y" -> rhythmicityKHTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 1 syllableDurationsDs) (fromMaybe 1.0 x) (fromMaybe 1.0 y) "02y" -> rhythmicityKHTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 2 syllableDurationsDs) (fromMaybe 1.0 x) (fromMaybe 1.0 y) "03y" -> rhythmicityKHTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 3 syllableDurationsDs) (fromMaybe 1.0 x) (fromMaybe 1.0 y) "0z" -> rhythmicityKFHTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 1 syllableDurationsDs) k (fromMaybe 1.0 x) (fromMaybe 1.0 y) "02z" -> rhythmicityKFHTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 2 syllableDurationsDs) k (fromMaybe 1.0 x) (fromMaybe 1.0 y) "03z" -> rhythmicityKFHTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 3 syllableDurationsDs) k (fromMaybe 1.0 x) (fromMaybe 1.0 y) "04z" -> rhythmicityKFHTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 4 syllableDurationsDs) k (fromMaybe 1.0 x) (fromMaybe 1.0 y) _ -> rhythmicityKHTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 1 syllableDurationsDs) (fromMaybe 1.0 x) (fromMaybe 1.0 y) "w" -> if | (drop 2 . take 3 $ choice) >= "1" && (drop 2 . take 3 $ choice) <= "4" -> case take 2 choice of "w0" -> wwF (drop 2 . take 3 $ choice) (Ch 1 1 4) (Rhythm 1 1 2) "w1" -> wwF (drop 2 . take 3 $ choice) (Ch 1 0 4) (Rhythm 2 1 1) "w2" -> wwF (drop 2 . take 3 $ choice) (Ch 0 1 4) (Rhythm 1 2 1) "w3" -> wwF (drop 2 . take 3 $ choice) (Ch 0 0 4) (Rhythm 1 1 2) _ -> rhythmicity0HTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 1 syllableDurationsDs) | otherwise -> rhythmicity0HTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 1 syllableDurationsDs) where w1F f ch rh = rhythmicityABC 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 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 #-} "x" -> if | (drop 2 . take 3 $ choice) >= "1" && (drop 2 . take 3 $ choice) <= "4" -> case take 2 choice of "x0" -> xxF (drop 2 . take 3 $ choice) (Ch 1 1 4) (Rhythm 1 1 2) "x1" -> xxF (drop 2 . take 3 $ choice) (Ch 1 0 4) (Rhythm 2 1 1) "x2" -> xxF (drop 2 . take 3 $ choice) (Ch 0 1 4) (Rhythm 1 2 1) "x3" -> xxF (drop 2 . take 3 $ choice) (Ch 0 0 4) (Rhythm 1 1 2) _ -> rhythmicity0HTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 1 syllableDurationsDs) | otherwise -> rhythmicity0HTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (helperHF4 1 syllableDurationsDs) where x1F f ch rh = 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 xxF xs = let n1 = readMaybe xs::Maybe Int in case n1 of Just n2 -> x1F (helperHF4 n2 syllableDurationsDs) Nothing -> x1F syllableDurationsD4 {-# INLINE x1F #-} {-# INLINE xxF #-} _ -> if | ((take 1 choice >= "b" && take 1 choice <= "v") || (take 1 choice >= "A" && take 1 choice <= "Z" && take 1 choice `notElem` ["G","H"])) -> rhythmicityH'Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k choice syllableDurationsDs CF0 | otherwise -> rhythmicityKHTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (let ts = drop 2 . take 3 $ choice in case ts of { [] -> syllableDurationsD4 ; ks -> let q = readMaybe ks::Maybe Int in case q of {Just q' -> helperHF4 q' syllableDurationsDs; ~Nothing -> syllableDurationsD4 }}) (fromMaybe 1.0 x) (fromMaybe 1.0 y)