{-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2H -- Copyright : (c) OleksandrZhabenko 2020-2021 -- 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.PropertiesSyllablesG2H ( -- * General rhythmicity , parseChRhEndMaybe -- * Extended general , rhythmicityTup ) 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 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 rhythmicity :: Double -> String -> Coeffs2 -> String -> Double rhythmicity k choice 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 . mconcat . (helperF4 n) . createSyllablesUkrS Just (P2 ch rh r n) -> case take 1 choice of "A" -> rhythmicityPolyWeightedLEF2 1.0 r ch rh . mconcat . (helperF4 n) . createSyllablesUkrS "D" -> rhythmicityPolyWeightedLF2 1.0 r ch rh . mconcat . (helperF4 n) . createSyllablesUkrS "E" -> rhythmicityPolyWeightedLEF3 1.0 r ch rh . mconcat . (helperF4 n) . createSyllablesUkrS "F" -> rhythmicityPolyWeightedLF3 1.0 r ch rh . mconcat . (helperF4 n) . createSyllablesUkrS "B" -> rhythmicityPolyWeightedEF2 1.0 r ch rh . mconcat . (helperF4 n) . createSyllablesUkrS "C" -> rhythmicityPolyWeightedF2 1.0 r ch rh . mconcat . (helperF4 n) . createSyllablesUkrS "M" -> rhythmicityPolyWeightedEF3 1.0 r ch rh . mconcat . (helperF4 n) . createSyllablesUkrS "N" -> rhythmicityPolyWeightedF3 1.0 r ch rh . mconcat . (helperF4 n) . createSyllablesUkrS "c" -> rhythmicityPoly 1.0 r ch rh . mconcat . (helperF4 n) . createSyllablesUkrS _ -> rhythmicity04 | choice == "0y" -> rhythmicity0 | choice == "02y" -> rhythmicity02 | choice == "03y" -> rhythmicity03 | choice == "0z" -> rhythmicity0F k | choice == "02z" -> rhythmicity02F k | choice == "03z" -> rhythmicity03F k | choice == "04z" -> rhythmicity04F k | take 1 choice == "0" -> rhythmicity04 | 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) _ -> rhythmicity04 | otherwise -> rhythmicity04 | 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) _ -> rhythmicity04 | otherwise -> rhythmicity04 | 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) <= "4" -> 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 -> rhythmicity04 where h1 f ts xs m n = f 1.0 4 (PolyCh xs m) (PolyRhythm [1,2,1,n]) . mconcat . (case readMaybe ts::Maybe Int of { Just 1 -> syllableDurationsD ; Just 2 -> syllableDurationsD2 ; Just 3 -> syllableDurationsD3 ; Just 4 -> syllableDurationsD4 }) . createSyllablesUkrS h2 f ts xs m n = f 1.0 4 (PolyCh xs m) (PolyRhythm [2,1,1,n]) . mconcat . (case readMaybe ts::Maybe Int of { Just 1 -> syllableDurationsD ; Just 2 -> syllableDurationsD2 ; Just 3 -> syllableDurationsD3 ; Just 4 -> syllableDurationsD4 }) . createSyllablesUkrS g f m n | drop 1 choice `elem` ["01","02","03","04"] = h1 f (drop 2 . take 3 $ choice) [True,True,True] m n | drop 1 choice `elem` ["11","12","13","14"] = h1 f (drop 2 . take 3 $ choice) [True,True,False] m n | drop 1 choice `elem` ["21","22","23","24"] = h1 f (drop 2 . take 3 $ choice) [True,False,True] m n | drop 1 choice `elem` ["31","32","33","34"] = h1 f (drop 2 . take 3 $ choice) [True,False,False] m n | drop 1 choice `elem` ["41","42","43","44"] = h2 f (drop 2 . take 3 $ choice) [True,True,True] m n | drop 1 choice `elem` ["51","52","53","54"] = h2 f (drop 2 . take 3 $ choice) [True,True,False] m n | drop 1 choice `elem` ["61","62","63","64"] = h2 f (drop 2 . take 3 $ choice) [True,False,True] m n | drop 1 choice `elem` ["71","72","73","74"] = h2 f (drop 2 . take 3 $ choice) [True,False,False] m n | otherwise = rhythmicity04 w1F f ch rh = rhythmicityABC 1.0 2.0 0.125 ch rh . mconcat . f . createSyllablesUkrS wwF2 g2 xs = let (Just n) = readMaybe xs::Maybe Int in case n `rem` 4 of 1 -> g2 syllableDurationsD 2 -> g2 syllableDurationsD2 3 -> g2 syllableDurationsD3 _ -> 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 #-} rhythmicity k choice (CF2 x y) = case take 1 choice of "0" -> case choice of "0y" -> rhythmicityK (fromMaybe 1.0 x) (fromMaybe 1.0 y) "02y" -> rhythmicityK2 (fromMaybe 1.0 x) (fromMaybe 1.0 y) "03y" -> rhythmicityK3 (fromMaybe 1.0 x) (fromMaybe 1.0 y) "0z" -> rhythmicityKF k (fromMaybe 1.0 x) (fromMaybe 1.0 y) "02z" -> rhythmicityKF2 k (fromMaybe 1.0 x) (fromMaybe 1.0 y) "03z" -> rhythmicityKF3 k (fromMaybe 1.0 x) (fromMaybe 1.0 y) "04z" -> rhythmicityKF4 k (fromMaybe 1.0 x) (fromMaybe 1.0 y) _ -> rhythmicityK4 (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) _ -> rhythmicity04 | otherwise -> rhythmicity04 where w1F f ch rh = rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) ch rh . mconcat . f . createSyllablesUkrS wwF xs = let (Just n) = readMaybe xs::Maybe Int in case n `rem` 4 of 1 -> w1F syllableDurationsD 2 -> w1F syllableDurationsD2 3 -> w1F syllableDurationsD3 _ -> 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) _ -> rhythmicity04 | otherwise -> rhythmicity04 where x1F f ch rh = rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) ch rh . mconcat . f . createSyllablesUkrS xxF xs = let (Just n) = readMaybe xs::Maybe Int in case n `rem` 4 of 1 -> x1F syllableDurationsD 2 -> x1F syllableDurationsD2 3 -> x1F syllableDurationsD3 _ -> 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"])) -> rhythmicity k choice CF0 | otherwise -> rhythmicityK4 (fromMaybe 1.0 x) (fromMaybe 1.0 y) helperF4 :: Int -> [[[Sound8]]] -> [[Double]] helperF4 n | n == 1 = syllableDurationsD | n == 2 = syllableDurationsD2 | n == 3 = syllableDurationsD3 | otherwise = syllableDurationsD4 parseChRhEndMaybe :: ParseChRh -> Maybe Int parseChRhEndMaybe (P0 _) = Nothing parseChRhEndMaybe (P1 _ _ n) = Just n parseChRhEndMaybe (P2 _ _ _ n) = Just n ---------------------------------------------------------------- rhythmicityTup :: 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 -> Coeffs2 -> String -> Double rhythmicityTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k choice 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 . mconcat . (helperF4 n) . createSyllablesUkrSTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 Just (P2 ch rh r n) -> case take 1 choice of "A" -> rhythmicityPolyWeightedLEF2 1.0 r ch rh . mconcat . (helperF4 n) . createSyllablesUkrSTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 "D" -> rhythmicityPolyWeightedLF2 1.0 r ch rh . mconcat . (helperF4 n) . createSyllablesUkrSTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 "E" -> rhythmicityPolyWeightedLEF3 1.0 r ch rh . mconcat . (helperF4 n) . createSyllablesUkrSTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 "F" -> rhythmicityPolyWeightedLF3 1.0 r ch rh . mconcat . (helperF4 n) . createSyllablesUkrSTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 "B" -> rhythmicityPolyWeightedEF2 1.0 r ch rh . mconcat . (helperF4 n) . createSyllablesUkrSTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 "C" -> rhythmicityPolyWeightedF2 1.0 r ch rh . mconcat . (helperF4 n) . createSyllablesUkrSTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 "M" -> rhythmicityPolyWeightedEF3 1.0 r ch rh . mconcat . (helperF4 n) . createSyllablesUkrSTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 "N" -> rhythmicityPolyWeightedF3 1.0 r ch rh . mconcat . (helperF4 n) . createSyllablesUkrSTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 "c" -> rhythmicityPoly 1.0 r ch rh . mconcat . (helperF4 n) . createSyllablesUkrSTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 _ -> rhythmicity04Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 | choice == "0y" -> rhythmicity0Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 | choice == "02y" -> rhythmicity02Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 | choice == "03y" -> rhythmicity03Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 | choice == "0z" -> rhythmicity0FTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k | choice == "02z" -> rhythmicity02FTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k | choice == "03z" -> rhythmicity03FTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k | choice == "04z" -> rhythmicity04FTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k | take 1 choice == "0" -> rhythmicity04Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 | 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) _ -> rhythmicity04Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 | otherwise -> rhythmicity04Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 | 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) _ -> rhythmicity04Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 | otherwise -> rhythmicity04Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 | 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) <= "4" -> 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 -> rhythmicity04Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 where h1 f ts xs m n = f 1.0 4 (PolyCh xs m) (PolyRhythm [1,2,1,n]) . mconcat . (case readMaybe ts::Maybe Int of { Just 1 -> syllableDurationsD ; Just 2 -> syllableDurationsD2 ; Just 3 -> syllableDurationsD3 ; Just 4 -> 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 readMaybe ts::Maybe Int of { Just 1 -> syllableDurationsD ; Just 2 -> syllableDurationsD2 ; Just 3 -> syllableDurationsD3 ; Just 4 -> 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 choice `elem` ["01","02","03","04"] = h1 f (drop 2 . take 3 $ choice) [True,True,True] m n | drop 1 choice `elem` ["11","12","13","14"] = h1 f (drop 2 . take 3 $ choice) [True,True,False] m n | drop 1 choice `elem` ["21","22","23","24"] = h1 f (drop 2 . take 3 $ choice) [True,False,True] m n | drop 1 choice `elem` ["31","32","33","34"] = h1 f (drop 2 . take 3 $ choice) [True,False,False] m n | drop 1 choice `elem` ["41","42","43","44"] = h2 f (drop 2 . take 3 $ choice) [True,True,True] m n | drop 1 choice `elem` ["51","52","53","54"] = h2 f (drop 2 . take 3 $ choice) [True,True,False] m n | drop 1 choice `elem` ["61","62","63","64"] = h2 f (drop 2 . take 3 $ choice) [True,False,True] m n | drop 1 choice `elem` ["71","72","73","74"] = h2 f (drop 2 . take 3 $ choice) [True,False,False] m n | otherwise = rhythmicity04 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 (Just n) = readMaybe xs::Maybe Int in case n `rem` 4 of 1 -> g2 syllableDurationsD 2 -> g2 syllableDurationsD2 3 -> g2 syllableDurationsD3 _ -> 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 #-} rhythmicityTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k choice (CF2 x y) = case take 1 choice of "0" -> case choice of "0y" -> rhythmicityKTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (fromMaybe 1.0 x) (fromMaybe 1.0 y) "02y" -> rhythmicityK2Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (fromMaybe 1.0 x) (fromMaybe 1.0 y) "03y" -> rhythmicityK3Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (fromMaybe 1.0 x) (fromMaybe 1.0 y) "0z" -> rhythmicityKFTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k (fromMaybe 1.0 x) (fromMaybe 1.0 y) "02z" -> rhythmicityKF2Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k (fromMaybe 1.0 x) (fromMaybe 1.0 y) "03z" -> rhythmicityKF3Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k (fromMaybe 1.0 x) (fromMaybe 1.0 y) "04z" -> rhythmicityKF4Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k (fromMaybe 1.0 x) (fromMaybe 1.0 y) _ -> rhythmicityK4Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (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) _ -> rhythmicity04Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 | otherwise -> rhythmicity04Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 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 (Just n) = readMaybe xs::Maybe Int in case n `rem` 4 of 1 -> w1F syllableDurationsD 2 -> w1F syllableDurationsD2 3 -> w1F syllableDurationsD3 _ -> 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) _ -> rhythmicity04Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 | otherwise -> rhythmicity04Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 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 (Just n) = readMaybe xs::Maybe Int in case n `rem` 4 of 1 -> x1F syllableDurationsD 2 -> x1F syllableDurationsD2 3 -> x1F syllableDurationsD3 _ -> 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"])) -> rhythmicityTup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 k choice CF0 | otherwise -> rhythmicityK4Tup tup1 tup2 tup3 tup4 tup5 tup6 tup7 tup8 tup9 tup10 tup11 tup12 tup13 tup14 tup15 tup16 tup17 (fromMaybe 1.0 x) (fromMaybe 1.0 y)