{-# 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 (
  -- * Extended
  rhythmicityHTup
  , rhythmicityH'Tup
  , rhythmicitya'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 Phonetic.Languages.Array.Ukrainian.Common
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.PropertiesSyllablesG201
import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2H
import GHC.Arr (Array)
import GHC.Int (Int8)
import Phonetic.Languages.Emphasis

#ifdef __GLASGOW_HASKELL__
#if __GLASGOW_HASKELL__==708
/* code that applies only to GHC 7.8.* */
mconcat = concat
#endif
#endif

helperHF4 :: Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 :: Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
n [[[[Sound8]]] -> [[Double]]]
xs
  | [[[[Sound8]]] -> [[Double]]] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [[[[Sound8]]] -> [[Double]]]
xs = [[[Sound8]]] -> [[Double]]
syllableDurationsD4
  | (Int
n Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` [[[[Sound8]]] -> [[Double]]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[[[Sound8]]] -> [[Double]]]
xs) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
forall a. [a] -> a
head [[[[Sound8]]] -> [[Double]]]
xs
  | Bool
otherwise = [[[[Sound8]]] -> [[Double]]]
xs [[[[Sound8]]] -> [[Double]]] -> Int -> [[[Sound8]]] -> [[Double]]
forall a. [a] -> Int -> a
!! ((Int
n Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` [[[[Sound8]]] -> [[Double]]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[[[Sound8]]] -> [[Double]]]
xs) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)

helperHF1 :: Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 :: Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
n [[[[Sound8]]] -> [[Double]]]
xs
  | [[[[Sound8]]] -> [[Double]]] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [[[[Sound8]]] -> [[Double]]]
xs = \[[[Sound8]]]
_ -> []
  | (Int
n Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` [[[[Sound8]]] -> [[Double]]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[[[Sound8]]] -> [[Double]]]
xs) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
forall a. [a] -> a
head [[[[Sound8]]] -> [[Double]]]
xs
  | Bool
otherwise = [[[[Sound8]]] -> [[Double]]]
xs [[[[Sound8]]] -> [[Double]]] -> Int -> [[[Sound8]]] -> [[Double]]
forall a. [a] -> Int -> a
!! ((Int
n Int -> Int -> Int
forall a. Integral a => a -> a -> a
`rem` [[[[Sound8]]] -> [[Double]]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[[[Sound8]]] -> [[Double]]]
xs) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
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
  -> ReadyForConstructionUkr
  -> Double
rhythmicityHTup :: Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> Double
-> String
-> [[[[Sound8]]] -> [[Double]]]
-> Coeffs2
-> String
-> ReadyForConstructionUkr
-> Double
rhythmicityHTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double
k String
choice [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs Coeffs2
coeffs String
bbs
  | (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'a') String
choice = Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> Double
-> String
-> [[[[Sound8]]] -> [[Double]]]
-> Coeffs2
-> String
-> ReadyForConstructionUkr
-> Double
rhythmicitya'Tup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double
k ((Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
filter (\Char
c -> Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=Char
'a' Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/=  Char
'H') String
choice) [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs Coeffs2
coeffs String
bbs
  | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"H" = Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> Double
-> String
-> [[[[Sound8]]] -> [[Double]]]
-> Coeffs2
-> ReadyForConstructionUkr
-> Double
rhythmicityH'Tup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double
k (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 String
choice) [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs Coeffs2
coeffs
  | Bool
otherwise = Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> Double
-> String
-> Coeffs2
-> ReadyForConstructionUkr
-> Double
rhythmicityTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double
k String
choice Coeffs2
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
  -> ReadyForConstructionUkr
  -> Double
rhythmicityH'Tup :: Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> Double
-> String
-> [[[[Sound8]]] -> [[Double]]]
-> Coeffs2
-> ReadyForConstructionUkr
-> Double
rhythmicityH'Tup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double
k String
choice [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs Coeffs2
CF0 tttt :: ReadyForConstructionUkr
tttt@(Str String
tttts) = if
 | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"c",String
"M",String
"N"] Bool -> Bool -> Bool
|| (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"A" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"F") -> let just_probe :: Maybe ParseChRh
just_probe = String -> Maybe ParseChRh
readRhythmicity String
choice in
           (case Maybe ParseChRh
just_probe of
             Just (P1 Choices
ch RhythmBasis
rh Int
n) -> Double
-> Double -> Double -> Choices -> RhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
rhythmicityABC Double
1.0 Double
2.0 Double
0.125 Choices
ch RhythmBasis
rh ([Double] -> Double)
-> (ReadyForConstructionUkr -> [Double])
-> ReadyForConstructionUkr
-> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> [Double]
rhythmicityGTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
n [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs)
             Just (P2 PolyChoices
ch PolyRhythmBasis
rh Int
r Int
n) -> (case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice of
                   String
"A" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF2 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"D" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF2 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"E" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF3 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"F" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF3 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"B" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF2 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"C" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF2 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"M" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF3 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"N" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF3 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"c" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPoly Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh) ([Double] -> Double)
-> (ReadyForConstructionUkr -> [Double])
-> ReadyForConstructionUkr
-> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> [Double]
rhythmicityGTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
n [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs)
             Maybe ParseChRh
_ -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs)) ReadyForConstructionUkr
tttt
 | String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0y" -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
 | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"y" ->
    let n2 :: Maybe Int
n2 = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice)::Maybe Int in
      Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
        (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 (case Maybe Int
n2 of { Just Int
n3 -> Int
n3; Maybe Int
Nothing -> Int
1}) [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
 | String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0z" -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> Double
-> ReadyForConstructionUkr
-> Double
rhythmicity0FHTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) Double
k ReadyForConstructionUkr
tttt
 | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"z" ->
    let n2 :: Maybe Int
n2 = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice)::Maybe Int in
      Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> Double
-> ReadyForConstructionUkr
-> Double
rhythmicity0FHTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
          (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 (case Maybe Int
n2 of { Just Int
n3 -> Int
n3; Maybe Int
Nothing -> Int
1}) [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) Double
k ReadyForConstructionUkr
tttt
 | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0" -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
 | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"w" -> if
          | (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"1" Bool -> Bool -> Bool
&& (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"4" ->
             case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice of
              String
"w0" -> String -> Choices -> RhythmBasis -> String -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) String
tttts
              String
"w1" -> String -> Choices -> RhythmBasis -> String -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
2 Int
1 Int
1) String
tttts
              String
"w2" -> String -> Choices -> RhythmBasis -> String -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
2 Int
1) String
tttts
              String
"w3" -> String -> Choices -> RhythmBasis -> String -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) String
tttts
              String
_ -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
          | Bool
otherwise -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
 | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"x" -> if
          | (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"1" Bool -> Bool -> Bool
&& (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"4" ->
             case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice of
              String
"x0" -> String -> Choices -> RhythmBasis -> String -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) String
tttts
              String
"x1" -> String -> Choices -> RhythmBasis -> String -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
2 Int
1 Int
1) String
tttts
              String
"x2" -> String -> Choices -> RhythmBasis -> String -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
2 Int
1) String
tttts
              String
"x3" -> String -> Choices -> RhythmBasis -> String -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) String
tttts
              String
_ -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
          | Bool
otherwise -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
 | Bool
otherwise -> if
    | (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"b" Bool -> Bool -> Bool
|| ((Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"d" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"v") Bool -> Bool -> Bool
|| (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"I" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"Z"))) Bool -> Bool -> Bool
&& (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"1" Bool -> Bool -> Bool
&& (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"9" ->
        (case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice of
          String
"b" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF3 Int
5 Int
1
          String
"d" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF30 Int
5 Int
1
          String
"e" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF3 Int
6 Int
2
          String
"f" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF30 Int
6 Int
2
          String
"g" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF2 Int
5 Int
1
          String
"h" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF20 Int
5 Int
1
          String
"i" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF2 Int
6 Int
2
          String
"j" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF20 Int
6 Int
2
          String
"k" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF3 Int
5 Int
1
          String
"l" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF30 Int
5 Int
1
          String
"m" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF3 Int
6 Int
2
          String
"n" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF30 Int
6 Int
2
          String
"o" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF2 Int
5 Int
1
          String
"p" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF20 Int
5 Int
1
          String
"q" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF2 Int
6 Int
2
          String
"r" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF20 Int
6 Int
2
          String
"I" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF3 Int
5 Int
1
          String
"J" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF30 Int
5 Int
1
          String
"K" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF3 Int
6 Int
2
          String
"L" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF30 Int
6 Int
2
          String
"O" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF2 Int
5 Int
1
          String
"P" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF20 Int
5 Int
1
          String
"Q" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF2 Int
6 Int
2
          String
"R" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF20 Int
6 Int
2
          String
"W" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF3 Int
5 Int
1
          String
"X" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF30 Int
5 Int
1
          String
"Y" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF3 Int
6 Int
2
          String
"Z" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF30 Int
6 Int
2
          String
"U" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF2 Int
5 Int
1
          String
"V" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF20 Int
5 Int
1
          String
"S" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF2 Int
6 Int
2
          String
"T" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF20 Int
6 Int
2
          String
"u" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPoly Int
5 Int
1
          String
"v" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPoly0 Int
5 Int
1
          String
"s" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPoly Int
6 Int
2
          String
"t" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPoly0 Int
6 Int
2) String
tttts
    | Bool
otherwise -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
       (let ts :: String
ts = Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice in
          case String
ts of { [] -> [[[Sound8]]] -> [[Double]]
syllableDurationsD4 ; String
ks ->
            let q :: Maybe Int
q = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
ks::Maybe Int in
              case Maybe Int
q of {Just Int
q' -> Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
q' [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs; ~Maybe Int
Nothing -> [[[Sound8]]] -> [[Double]]
syllableDurationsD4 }}) ReadyForConstructionUkr
tttt
        where h1 :: (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> String -> c
h1 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c
f String
ts [Bool]
xs Int
m Int
n = t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c
f t
1.0 t
4 ([Bool] -> Int -> PolyChoices
PolyCh [Bool]
xs Int
m) ([Int] -> PolyRhythmBasis
PolyRhythm [Int
1,Int
2,Int
1,Int
n]) ([Double] -> c) -> (String -> [Double]) -> String -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Double]] -> [Double]
forall a. Monoid a => [a] -> a
mconcat ([[Double]] -> [Double])
-> (String -> [[Double]]) -> String -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                  (case String
ts of { [] -> [[[Sound8]]] -> [[Double]]
syllableDurationsD4 ; String
ks -> let q :: Maybe Int
q = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
ks::Maybe Int in
                      case Maybe Int
q of {Just Int
q' -> Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
q' [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs; ~Maybe Int
Nothing -> [[[Sound8]]] -> [[Double]]
syllableDurationsD4 }}) ([[[Sound8]]] -> [[Double]])
-> (String -> [[[Sound8]]]) -> String -> [[Double]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                        Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> String
-> [[[Sound8]]]
createSyllablesUkrSTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
              h2 :: (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> String -> c
h2 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c
f String
ts [Bool]
xs Int
m Int
n = t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c
f t
1.0 t
4 ([Bool] -> Int -> PolyChoices
PolyCh [Bool]
xs Int
m) ([Int] -> PolyRhythmBasis
PolyRhythm [Int
2,Int
1,Int
1,Int
n]) ([Double] -> c) -> (String -> [Double]) -> String -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Double]] -> [Double]
forall a. Monoid a => [a] -> a
mconcat ([[Double]] -> [Double])
-> (String -> [[Double]]) -> String -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                  (case String
ts of { [] -> [[[Sound8]]] -> [[Double]]
syllableDurationsD4 ; String
ks -> let q :: Maybe Int
q = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
ks::Maybe Int in
                      case Maybe Int
q of {Just Int
q' -> Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
q' [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs; ~Maybe Int
Nothing -> [[[Sound8]]] -> [[Double]]
syllableDurationsD4 }}) ([[[Sound8]]] -> [[Double]])
-> (String -> [[[Sound8]]]) -> String -> [[Double]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                        Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> String
-> [[[Sound8]]]
createSyllablesUkrSTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
              g :: (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> String -> Double
g t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> String -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> String -> c
h1 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
True,Bool
True] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"1" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> String -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> String -> c
h1 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
True,Bool
False] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"2" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> String -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> String -> c
h1 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
False,Bool
True] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"3" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> String -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> String -> c
h1 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
False,Bool
False] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"4" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> String -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> String -> c
h2 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
True,Bool
True] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"5" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> String -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> String -> c
h2 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
True,Bool
False] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"6" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> String -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> String -> c
h2 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
False,Bool
True] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"7" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> String -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> String -> c
h2 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
False,Bool
False] Int
m Int
n
                | Bool
otherwise = \String
_ -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
n [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
              w1F :: ([[[Sound8]]] -> [[a]])
-> Choices -> RhythmBasis -> String -> Double
w1F [[[Sound8]]] -> [[a]]
f Choices
ch RhythmBasis
rh = Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
forall a.
Ord a =>
Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
rhythmicityABC Double
1.0 Double
2.0 Double
0.125 Choices
ch RhythmBasis
rh ([a] -> Double) -> (String -> [a]) -> String -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[a]] -> [a]
forall a. Monoid a => [a] -> a
mconcat ([[a]] -> [a]) -> (String -> [[a]]) -> String -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[Sound8]]] -> [[a]]
f ([[[Sound8]]] -> [[a]])
-> (String -> [[[Sound8]]]) -> String -> [[a]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> String
-> [[[Sound8]]]
createSyllablesUkrSTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
              wwF2 :: (([[[Sound8]]] -> [[Double]]) -> p) -> String -> p
wwF2 ([[[Sound8]]] -> [[Double]]) -> p
g2 String
xs =
                let n1 :: Maybe Int
n1 = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
xs::Maybe Int in
                   case Maybe Int
n1 of
                     Just Int
n2 -> ([[[Sound8]]] -> [[Double]]) -> p
g2 (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
n2 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs)
                     Maybe Int
Nothing -> ([[[Sound8]]] -> [[Double]]) -> p
g2 [[[Sound8]]] -> [[Double]]
syllableDurationsD4
              x1F :: ([[[Sound8]]] -> [[a]])
-> Choices -> RhythmBasis -> String -> Double
x1F [[[Sound8]]] -> [[a]]
f Choices
ch RhythmBasis
rh = Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
forall a.
Ord a =>
Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
rhythmicityABC0 Double
1.0 Double
2.0 Double
0.125 Choices
ch RhythmBasis
rh ([a] -> Double) -> (String -> [a]) -> String -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[a]] -> [a]
forall a. Monoid a => [a] -> a
mconcat ([[a]] -> [a]) -> (String -> [[a]]) -> String -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[Sound8]]] -> [[a]]
f ([[[Sound8]]] -> [[a]])
-> (String -> [[[Sound8]]]) -> String -> [[a]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> String
-> [[[Sound8]]]
createSyllablesUkrSTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
              xxF :: String -> Choices -> RhythmBasis -> String -> Double
xxF = (([[[Sound8]]] -> [[Double]])
 -> Choices -> RhythmBasis -> String -> Double)
-> String -> Choices -> RhythmBasis -> String -> Double
forall p. (([[[Sound8]]] -> [[Double]]) -> p) -> String -> p
wwF2 ([[[Sound8]]] -> [[Double]])
-> Choices -> RhythmBasis -> String -> Double
forall a.
Ord a =>
([[[Sound8]]] -> [[a]])
-> Choices -> RhythmBasis -> String -> Double
x1F
              wwF :: String -> Choices -> RhythmBasis -> String -> Double
wwF = (([[[Sound8]]] -> [[Double]])
 -> Choices -> RhythmBasis -> String -> Double)
-> String -> Choices -> RhythmBasis -> String -> Double
forall p. (([[[Sound8]]] -> [[Double]]) -> p) -> String -> p
wwF2 ([[[Sound8]]] -> [[Double]])
-> Choices -> RhythmBasis -> String -> Double
forall a.
Ord a =>
([[[Sound8]]] -> [[a]])
-> Choices -> RhythmBasis -> String -> Double
w1F
              {-# INLINE w1F #-}
              {-# INLINE wwF2 #-}
              {-# INLINE x1F #-}
              {-# INLINE xxF #-}
              {-# INLINE wwF #-}
rhythmicityH'Tup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double
k String
choice [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs (CF2 Maybe Double
x Maybe Double
y) tttt :: ReadyForConstructionUkr
tttt@(Str String
tttts) =
 case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice of
  String
"0" -> if String
choice String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"0z",String
"02z",String
"03z",String
"04z"] then Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> Double
-> Double
-> Double
-> ReadyForConstructionUkr
-> Double
rhythmicityKFHTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13
           Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 (case String -> Char
forall a. [a] -> a
last String
choice of {Char
'2' -> Int
2; Char
'3' -> Int
3; Char
'4' -> Int
4; ~Char
rrrrr -> Int
1}) [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) Double
k
             (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
x) (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
y) ReadyForConstructionUkr
tttt
          else Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> Double
-> Double
-> ReadyForConstructionUkr
-> Double
rhythmicityKHTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
            (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 (case String -> Char
forall a. [a] -> a
last String
choice of {Char
'2' -> Int
2; Char
'3' -> Int
3; Char
'4' -> Int
4; ~Char
rrrrr -> Int
1}) [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
x) (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
y) ReadyForConstructionUkr
tttt
  String
"w" -> if
          | (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"1" Bool -> Bool -> Bool
&& (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"4" ->
             case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice of
              String
"w0" -> String -> Choices -> RhythmBasis -> String -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) String
tttts
              String
"w1" -> String -> Choices -> RhythmBasis -> String -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
2 Int
1 Int
1) String
tttts
              String
"w2" -> String -> Choices -> RhythmBasis -> String -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
2 Int
1) String
tttts
              String
"w3" -> String -> Choices -> RhythmBasis -> String -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) String
tttts
              String
_ -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
          | Bool
otherwise -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
              where w1F :: ([[[Sound8]]] -> [[a]])
-> Choices -> RhythmBasis -> String -> Double
w1F [[[Sound8]]] -> [[a]]
f Choices
ch RhythmBasis
rh = Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
forall a.
Ord a =>
Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
rhythmicityABC Double
1.0 (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
2.0 Maybe Double
x) (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
0.125 Maybe Double
y) Choices
ch RhythmBasis
rh ([a] -> Double) -> (String -> [a]) -> String -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[a]] -> [a]
forall a. Monoid a => [a] -> a
mconcat ([[a]] -> [a]) -> (String -> [[a]]) -> String -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[Sound8]]] -> [[a]]
f ([[[Sound8]]] -> [[a]])
-> (String -> [[[Sound8]]]) -> String -> [[a]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> String
-> [[[Sound8]]]
createSyllablesUkrSTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
                    wwF :: String -> Choices -> RhythmBasis -> String -> Double
wwF String
xs =
                      let n1 :: Maybe Int
n1 = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
xs::Maybe Int in
                        case Maybe Int
n1 of
                         Just Int
n2 -> ([[[Sound8]]] -> [[Double]])
-> Choices -> RhythmBasis -> String -> Double
forall a.
Ord a =>
([[[Sound8]]] -> [[a]])
-> Choices -> RhythmBasis -> String -> Double
w1F (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
n2 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs)
                         Maybe Int
Nothing -> ([[[Sound8]]] -> [[Double]])
-> Choices -> RhythmBasis -> String -> Double
forall a.
Ord a =>
([[[Sound8]]] -> [[a]])
-> Choices -> RhythmBasis -> String -> Double
w1F [[[Sound8]]] -> [[Double]]
syllableDurationsD4
                    {-# INLINE w1F #-}
                    {-# INLINE wwF #-}
  String
"x" -> if
          | (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"1" Bool -> Bool -> Bool
&& (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"4" ->
             case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice of
              String
"x0" -> String -> Choices -> RhythmBasis -> String -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) String
tttts
              String
"x1" -> String -> Choices -> RhythmBasis -> String -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
2 Int
1 Int
1) String
tttts
              String
"x2" -> String -> Choices -> RhythmBasis -> String -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
2 Int
1) String
tttts
              String
"x3" -> String -> Choices -> RhythmBasis -> String -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) String
tttts
              String
_ -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
          | Bool
otherwise -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
              where x1F :: ([[[Sound8]]] -> [[a]])
-> Choices -> RhythmBasis -> String -> Double
x1F [[[Sound8]]] -> [[a]]
f Choices
ch RhythmBasis
rh = Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
forall a.
Ord a =>
Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
rhythmicityABC0 Double
1.0 (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
2.0 Maybe Double
x) (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
0.125 Maybe Double
y) Choices
ch RhythmBasis
rh ([a] -> Double) -> (String -> [a]) -> String -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[a]] -> [a]
forall a. Monoid a => [a] -> a
mconcat ([[a]] -> [a]) -> (String -> [[a]]) -> String -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[Sound8]]] -> [[a]]
f ([[[Sound8]]] -> [[a]])
-> (String -> [[[Sound8]]]) -> String -> [[a]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> String
-> [[[Sound8]]]
createSyllablesUkrSTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
                    xxF :: String -> Choices -> RhythmBasis -> String -> Double
xxF String
xs =
                      let n1 :: Maybe Int
n1 = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
xs::Maybe Int in
                        case Maybe Int
n1 of
                         Just Int
n2 -> ([[[Sound8]]] -> [[Double]])
-> Choices -> RhythmBasis -> String -> Double
forall a.
Ord a =>
([[[Sound8]]] -> [[a]])
-> Choices -> RhythmBasis -> String -> Double
x1F (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
n2 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs)
                         Maybe Int
Nothing -> ([[[Sound8]]] -> [[Double]])
-> Choices -> RhythmBasis -> String -> Double
forall a.
Ord a =>
([[[Sound8]]] -> [[a]])
-> Choices -> RhythmBasis -> String -> Double
x1F [[[Sound8]]] -> [[Double]]
syllableDurationsD4
                    {-# INLINE x1F #-}
                    {-# INLINE xxF #-}
  String
_ -> if
     | ((Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"b" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"v") Bool -> Bool -> Bool
|| (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"A" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"Z" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [String
"G",String
"H"])) -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> Double
-> String
-> [[[[Sound8]]] -> [[Double]]]
-> Coeffs2
-> ReadyForConstructionUkr
-> Double
rhythmicityH'Tup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double
k String
choice [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs Coeffs2
forall a. CoeffTwo a
CF0 ReadyForConstructionUkr
tttt
     | Bool
otherwise -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> Double
-> Double
-> ReadyForConstructionUkr
-> Double
rhythmicityKHTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 
        (let ts :: String
ts = Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice in
          case String
ts of { [] -> [[[Sound8]]] -> [[Double]]
syllableDurationsD4 ; String
ks ->
            let q :: Maybe Int
q = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
ks::Maybe Int in
              case Maybe Int
q of {Just Int
q' -> Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF4 Int
q' [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs; ~Maybe Int
Nothing -> [[[Sound8]]] -> [[Double]]
syllableDurationsD4 }})
                (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
x) (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
y) ReadyForConstructionUkr
tttt
rhythmicityH'Tup Array Int (Sound8, Bool)
_ Array Int (Sound8, Bool)
_ Array Int (Sound8, Bool)
_ Array Int (Sound8, Bool)
_ Array Int ([Sound8], Bool)
_ Array Int ([Sound8], Sound8)
_ Array Int (Sound8, [Sound8] -> Sound8)
_ Array Int (Sound8, Bool)
_ Array Int ([Sound8], Bool)
_ Array Int ([Sound8], Bool)
_ Array Int ([Sound8], Bool)
_ Array Int (Sound8, [Sound8])
_ Array Int (Char, Sound8)
_ Array Int (Sound8, [Sound8])
_ Array Int (Char, Bool)
_ Array Int (Char, Bool)
_ Array Int (Sound8, Bool)
_ Double
_ String
_ [[[[Sound8]]] -> [[Double]]]
_ Coeffs2
_ ReadyForConstructionUkr
_ = -Double
3.0

rhythmicitya'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
  -> ReadyForConstructionUkr
  -> Double
rhythmicitya'Tup :: Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> Double
-> String
-> [[[[Sound8]]] -> [[Double]]]
-> Coeffs2
-> String
-> ReadyForConstructionUkr
-> Double
rhythmicitya'Tup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double
k String
choice [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs Coeffs2
CF0 String
bbs tttt :: ReadyForConstructionUkr
tttt@(FSL [[[Sound8]]]
tttts)= if
 | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"c",String
"M",String
"N"] Bool -> Bool -> Bool
|| (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"A" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"F") -> let just_probe :: Maybe ParseChRh
just_probe = String -> Maybe ParseChRh
readRhythmicity String
choice in
           (case Maybe ParseChRh
just_probe of
             Just (P1 Choices
ch RhythmBasis
rh Int
n) -> Double
-> Double -> Double -> Choices -> RhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
rhythmicityABC Double
1.0 Double
2.0 Double
0.125 Choices
ch RhythmBasis
rh ([Double] -> Double)
-> (ReadyForConstructionUkr -> [Double])
-> ReadyForConstructionUkr
-> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> [Double]
rhythmicityGTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
n [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs)
             Just (P2 PolyChoices
ch PolyRhythmBasis
rh Int
r Int
n) -> (case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice of
                   String
"A" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF2 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"D" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF2 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"E" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF3 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"F" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF3 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"B" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF2 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"C" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF2 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"M" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF3 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"N" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF3 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"c" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPoly Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh) ([Double] -> Double)
-> (ReadyForConstructionUkr -> [Double])
-> ReadyForConstructionUkr
-> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> [Double]
rhythmicityGTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
n [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs)
             Maybe ParseChRh
_ -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs))  ReadyForConstructionUkr
tttt
 | String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0y" -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
 | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"y" ->
    let n2 :: Maybe Int
n2 = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice)::Maybe Int in
      Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
          (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 (case Maybe Int
n2 of {Just Int
n3 -> Int
n3; Maybe Int
Nothing -> Int
1}) [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
 | String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0z" -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> Double
-> ReadyForConstructionUkr
-> Double
rhythmicity0FHTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) Double
k ReadyForConstructionUkr
tttt
 | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"z" ->
    let n2 :: Maybe Int
n2 = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice)::Maybe Int in
      Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> Double
-> ReadyForConstructionUkr
-> Double
rhythmicity0FHTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
          (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 (case Maybe Int
n2 of {Just Int
n3 -> Int
n3; Maybe Int
Nothing -> Int
1}) [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) Double
k ReadyForConstructionUkr
tttt
 | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0" -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
 | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"w" -> if
          | (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"1" Bool -> Bool -> Bool
&& (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"4" ->
             (case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice of
              String
"w0" -> String -> Choices -> RhythmBasis -> [[[Sound8]]] -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) 
              String
"w1" -> String -> Choices -> RhythmBasis -> [[[Sound8]]] -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
2 Int
1 Int
1) 
              String
"w2" -> String -> Choices -> RhythmBasis -> [[[Sound8]]] -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
2 Int
1) 
              String
"w3" -> String -> Choices -> RhythmBasis -> [[[Sound8]]] -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) 
              String
_ -> \[[[Sound8]]]
_ -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt) [[[Sound8]]]
tttts
          | Bool
otherwise -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
 | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"x" -> if
          | (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"1" Bool -> Bool -> Bool
&& (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"4" ->
             (case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice of
              String
"x0" -> String -> Choices -> RhythmBasis -> [[[Sound8]]] -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2)
              String
"x1" -> String -> Choices -> RhythmBasis -> [[[Sound8]]] -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
2 Int
1 Int
1)
              String
"x2" -> String -> Choices -> RhythmBasis -> [[[Sound8]]] -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
2 Int
1)
              String
"x3" -> String -> Choices -> RhythmBasis -> [[[Sound8]]] -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2)
              String
_ -> \[[[Sound8]]]
_ -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt) [[[Sound8]]]
tttts
          | Bool
otherwise -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
 | Bool
otherwise -> if
    | (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"b" Bool -> Bool -> Bool
|| ((Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"d" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"v") Bool -> Bool -> Bool
|| (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"I" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"Z"))) Bool -> Bool -> Bool
&& (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"1" Bool -> Bool -> Bool
&& (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"9" ->
        (case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice of
          String
"b" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF3 Int
5 Int
1
          String
"d" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF30 Int
5 Int
1
          String
"e" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF3 Int
6 Int
2
          String
"f" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF30 Int
6 Int
2
          String
"g" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF2 Int
5 Int
1
          String
"h" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF20 Int
5 Int
1
          String
"i" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF2 Int
6 Int
2
          String
"j" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF20 Int
6 Int
2
          String
"k" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF3 Int
5 Int
1
          String
"l" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF30 Int
5 Int
1
          String
"m" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF3 Int
6 Int
2
          String
"n" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF30 Int
6 Int
2
          String
"o" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF2 Int
5 Int
1
          String
"p" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF20 Int
5 Int
1
          String
"q" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF2 Int
6 Int
2
          String
"r" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF20 Int
6 Int
2
          String
"I" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF3 Int
5 Int
1
          String
"J" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF30 Int
5 Int
1
          String
"K" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF3 Int
6 Int
2
          String
"L" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF30 Int
6 Int
2
          String
"O" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF2 Int
5 Int
1
          String
"P" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF20 Int
5 Int
1
          String
"Q" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF2 Int
6 Int
2
          String
"R" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF20 Int
6 Int
2
          String
"W" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF3 Int
5 Int
1
          String
"X" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF30 Int
5 Int
1
          String
"Y" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF3 Int
6 Int
2
          String
"Z" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF30 Int
6 Int
2
          String
"U" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF2 Int
5 Int
1
          String
"V" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF20 Int
5 Int
1
          String
"S" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF2 Int
6 Int
2
          String
"T" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF20 Int
6 Int
2
          String
"u" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPoly Int
5 Int
1
          String
"v" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPoly0 Int
5 Int
1
          String
"s" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPoly Int
6 Int
2
          String
"t" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPoly0 Int
6 Int
2) [[[Sound8]]]
tttts
    | Bool
otherwise -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
       (let ts :: String
ts = Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice in
          case String
ts of { [] -> (\[[[Sound8]]]
_ -> [[-Double
1.0]]) ; String
ks ->
            let q :: Maybe Int
q = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
ks::Maybe Int in
              case Maybe Int
q of {Just Int
q' -> Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
q' [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs; ~Maybe Int
Nothing -> (\[[[Sound8]]]
_ -> [[-Double
1.0]]) }}) ReadyForConstructionUkr
tttt
        where h1 :: (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h1 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c
f String
ts [Bool]
xs Int
m Int
n = t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c
f t
1.0 t
4 ([Bool] -> Int -> PolyChoices
PolyCh [Bool]
xs Int
m) ([Int] -> PolyRhythmBasis
PolyRhythm [Int
1,Int
2,Int
1,Int
n]) ([Double] -> c) -> ([[[Sound8]]] -> [Double]) -> [[[Sound8]]] -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Double]] -> [Double]
forall a. Monoid a => [a] -> a
mconcat ([[Double]] -> [Double])
-> ([[[Sound8]]] -> [[Double]]) -> [[[Sound8]]] -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                  (case String
ts of { [] -> (\[[[Sound8]]]
_ -> [[-Double
1.0]]) ; String
ks -> let q :: Maybe Int
q = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
ks::Maybe Int in
                      case Maybe Int
q of {Just Int
q' -> Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
q' [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs; ~Maybe Int
Nothing -> (\[[[Sound8]]]
_ -> [[-Double
1.0]]) }})
              h2 :: (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h2 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c
f String
ts [Bool]
xs Int
m Int
n = t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c
f t
1.0 t
4 ([Bool] -> Int -> PolyChoices
PolyCh [Bool]
xs Int
m) ([Int] -> PolyRhythmBasis
PolyRhythm [Int
2,Int
1,Int
1,Int
n]) ([Double] -> c) -> ([[[Sound8]]] -> [Double]) -> [[[Sound8]]] -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Double]] -> [Double]
forall a. Monoid a => [a] -> a
mconcat ([[Double]] -> [Double])
-> ([[[Sound8]]] -> [[Double]]) -> [[[Sound8]]] -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                  (case String
ts of { [] -> (\[[[Sound8]]]
_ -> [[-Double
1.0]]) ; String
ks -> let q :: Maybe Int
q = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
ks::Maybe Int in
                      case Maybe Int
q of {Just Int
q' -> Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
q' [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs; ~Maybe Int
Nothing -> (\[[[Sound8]]]
_ -> [[-Double
1.0]]) }})
              g :: (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h1 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
True,Bool
True] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"1" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h1 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
True,Bool
False] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"2" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h1 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
False,Bool
True] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"3" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h1 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
False,Bool
False] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"4" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h2 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
True,Bool
True] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"5" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h2 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
True,Bool
False] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"6" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h2 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
False,Bool
True] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"7" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h2 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
False,Bool
False] Int
m Int
n
                | Bool
otherwise = \[[[Sound8]]]
_ -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
n [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
              w1F :: ([[[Sound8]]] -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
w1F [[[Sound8]]] -> [[a]]
f Choices
ch RhythmBasis
rh = Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
forall a.
Ord a =>
Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
rhythmicityABC Double
1.0 Double
2.0 Double
0.125 Choices
ch RhythmBasis
rh ([a] -> Double) -> (a -> [a]) -> a -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[a]] -> [a]
forall a. Monoid a => [a] -> a
mconcat ([[a]] -> [a]) -> (a -> [[a]]) -> a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[Sound8]]] -> [[a]]
f ([[[Sound8]]] -> [[a]]) -> (a -> [[[Sound8]]]) -> a -> [[a]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\a
_ -> [[[Sound8]]]
tttts)
              wwF2 :: (([[[Sound8]]] -> [[Double]]) -> p) -> String -> p
wwF2 ([[[Sound8]]] -> [[Double]]) -> p
g2 String
xs =
                let n1 :: Maybe Int
n1 = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
xs::Maybe Int in
                   case Maybe Int
n1 of
                     Just Int
n2 -> ([[[Sound8]]] -> [[Double]]) -> p
g2 (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
n2 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs)
                     Maybe Int
Nothing -> ([[[Sound8]]] -> [[Double]]) -> p
g2 (\[[[Sound8]]]
_ -> [[-Double
1.0]])
              x1F :: ([[[Sound8]]] -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
x1F [[[Sound8]]] -> [[a]]
f Choices
ch RhythmBasis
rh = Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
forall a.
Ord a =>
Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
rhythmicityABC0 Double
1.0 Double
2.0 Double
0.125 Choices
ch RhythmBasis
rh ([a] -> Double) -> (a -> [a]) -> a -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[a]] -> [a]
forall a. Monoid a => [a] -> a
mconcat ([[a]] -> [a]) -> (a -> [[a]]) -> a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[Sound8]]] -> [[a]]
f ([[[Sound8]]] -> [[a]]) -> (a -> [[[Sound8]]]) -> a -> [[a]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\a
_ -> [[[Sound8]]]
tttts)
              xxF :: String -> Choices -> RhythmBasis -> a -> Double
xxF = (([[[Sound8]]] -> [[Double]])
 -> Choices -> RhythmBasis -> a -> Double)
-> String -> Choices -> RhythmBasis -> a -> Double
forall p. (([[[Sound8]]] -> [[Double]]) -> p) -> String -> p
wwF2 ([[[Sound8]]] -> [[Double]])
-> Choices -> RhythmBasis -> a -> Double
forall a a.
Ord a =>
([[[Sound8]]] -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
x1F
              wwF :: String -> Choices -> RhythmBasis -> a -> Double
wwF = (([[[Sound8]]] -> [[Double]])
 -> Choices -> RhythmBasis -> a -> Double)
-> String -> Choices -> RhythmBasis -> a -> Double
forall p. (([[[Sound8]]] -> [[Double]]) -> p) -> String -> p
wwF2 ([[[Sound8]]] -> [[Double]])
-> Choices -> RhythmBasis -> a -> Double
forall a a.
Ord a =>
([[[Sound8]]] -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
w1F
              {-# INLINE w1F #-}
              {-# INLINE wwF2 #-}
              {-# INLINE x1F #-}
              {-# INLINE xxF #-}
              {-# INLINE wwF #-}
rhythmicitya'Tup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double
k String
choice [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs (CF2 Maybe Double
x Maybe Double
y) String
bbs tttt :: ReadyForConstructionUkr
tttt@(FSL [[[Sound8]]]
tttts) =
 case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice of
  String
"0" -> if String
choice String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"0z",String
"02z",String
"03z",String
"04z"] then Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> Double
-> Double
-> Double
-> ReadyForConstructionUkr
-> Double
rhythmicityKFHTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14
           Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 (case String -> Char
forall a. [a] -> a
last String
choice of {Char
'2' -> Int
2; Char
'3' -> Int
3; Char
'4' -> Int
4; ~Char
rrrrr -> Int
1}) [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) Double
k (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
x)
             (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
y) ReadyForConstructionUkr
tttt
         else Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> Double
-> Double
-> ReadyForConstructionUkr
-> Double
rhythmicityKHTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
           (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 (case String -> Char
forall a. [a] -> a
last String
choice of {Char
'2' -> Int
2; Char
'3' -> Int
3; Char
'4' -> Int
4; ~Char
rrrrr -> Int
1}) [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
x) (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
y) ReadyForConstructionUkr
tttt
  String
"w" -> if
          | (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"1" Bool -> Bool -> Bool
&& (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"4" ->
             (case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice of
              String
"w0" -> String -> Choices -> RhythmBasis -> [[[Sound8]]] -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) 
              String
"w1" -> String -> Choices -> RhythmBasis -> [[[Sound8]]] -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
2 Int
1 Int
1) 
              String
"w2" -> String -> Choices -> RhythmBasis -> [[[Sound8]]] -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
2 Int
1) 
              String
"w3" -> String -> Choices -> RhythmBasis -> [[[Sound8]]] -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) 
              String
_ -> \[[[Sound8]]]
_ -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs)  ReadyForConstructionUkr
tttt) [[[Sound8]]]
tttts
          | Bool
otherwise -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
              where w1F :: ([[[Sound8]]] -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
w1F [[[Sound8]]] -> [[a]]
f Choices
ch RhythmBasis
rh = Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
forall a.
Ord a =>
Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
rhythmicityABC Double
1.0 (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
2.0 Maybe Double
x) (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
0.125 Maybe Double
y) Choices
ch RhythmBasis
rh ([a] -> Double) -> (a -> [a]) -> a -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[a]] -> [a]
forall a. Monoid a => [a] -> a
mconcat ([[a]] -> [a]) -> (a -> [[a]]) -> a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[Sound8]]] -> [[a]]
f ([[[Sound8]]] -> [[a]]) -> (a -> [[[Sound8]]]) -> a -> [[a]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\a
_ -> [[[Sound8]]]
tttts)
                    wwF :: String -> Choices -> RhythmBasis -> a -> Double
wwF String
xs =
                      let n1 :: Maybe Int
n1 = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
xs::Maybe Int in
                        case Maybe Int
n1 of
                         Just Int
n2 -> ([[[Sound8]]] -> [[Double]])
-> Choices -> RhythmBasis -> a -> Double
forall a a.
Ord a =>
([[[Sound8]]] -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
w1F (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
n2 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs)
                         Maybe Int
Nothing -> ([[[Sound8]]] -> [[Double]])
-> Choices -> RhythmBasis -> a -> Double
forall a a.
Ord a =>
([[[Sound8]]] -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
w1F (\[[[Sound8]]]
_ -> [[-Double
1.0]])
                    {-# INLINE w1F #-}
                    {-# INLINE wwF #-}
  String
"x" -> if
          | (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"1" Bool -> Bool -> Bool
&& (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"4" ->
             (case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice of
              String
"x0" -> String -> Choices -> RhythmBasis -> [[[Sound8]]] -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) 
              String
"x1" -> String -> Choices -> RhythmBasis -> [[[Sound8]]] -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
2 Int
1 Int
1) 
              String
"x2" -> String -> Choices -> RhythmBasis -> [[[Sound8]]] -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
2 Int
1) 
              String
"x3" -> String -> Choices -> RhythmBasis -> [[[Sound8]]] -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) 
              String
_ -> \[[[Sound8]]]
_ -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt) [[[Sound8]]]
tttts
          | Bool
otherwise -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
              where x1F :: ([[[Sound8]]] -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
x1F [[[Sound8]]] -> [[a]]
f Choices
ch RhythmBasis
rh = Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
forall a.
Ord a =>
Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
rhythmicityABC0 Double
1.0 (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
2.0 Maybe Double
x) (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
0.125 Maybe Double
y) Choices
ch RhythmBasis
rh ([a] -> Double) -> (a -> [a]) -> a -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[a]] -> [a]
forall a. Monoid a => [a] -> a
mconcat ([[a]] -> [a]) -> (a -> [[a]]) -> a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[Sound8]]] -> [[a]]
f ([[[Sound8]]] -> [[a]]) -> (a -> [[[Sound8]]]) -> a -> [[a]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\a
_ -> [[[Sound8]]]
tttts)
                    xxF :: String -> Choices -> RhythmBasis -> a -> Double
xxF String
xs =
                      let n1 :: Maybe Int
n1 = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
xs::Maybe Int in
                        case Maybe Int
n1 of
                         Just Int
n2 -> ([[[Sound8]]] -> [[Double]])
-> Choices -> RhythmBasis -> a -> Double
forall a a.
Ord a =>
([[[Sound8]]] -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
x1F (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
n2 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs)
                         Maybe Int
Nothing -> ([[[Sound8]]] -> [[Double]])
-> Choices -> RhythmBasis -> a -> Double
forall a a.
Ord a =>
([[[Sound8]]] -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
x1F (\[[[Sound8]]]
_ -> [[-Double
1.0]])
                    {-# INLINE x1F #-}
                    {-# INLINE xxF #-}
  String
_ -> if
     | ((Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"b" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"v") Bool -> Bool -> Bool
|| (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"A" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"Z" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [String
"G",String
"H"])) -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> Double
-> String
-> [[[[Sound8]]] -> [[Double]]]
-> Coeffs2
-> ReadyForConstructionUkr
-> Double
rhythmicityH'Tup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double
k String
choice [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs Coeffs2
forall a. CoeffTwo a
CF0 ReadyForConstructionUkr
tttt
     | Bool
otherwise -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> Double
-> Double
-> ReadyForConstructionUkr
-> Double
rhythmicityKHTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
        (let ts :: String
ts = Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice in
          case String
ts of { [] -> (\[[[Sound8]]]
_ -> [[-Double
1.0]]) ; String
ks ->
            let q :: Maybe Int
q = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
ks::Maybe Int in
              case Maybe Int
q of {Just Int
q' -> Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
q' [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs; ~Maybe Int
Nothing -> (\[[[Sound8]]]
_ -> [[-Double
1.0]]) }})
                (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
x) (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
y) ReadyForConstructionUkr
tttt
rhythmicitya'Tup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double
k String
choice [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs Coeffs2
CF0 String
bbs tttt :: ReadyForConstructionUkr
tttt@(Str tttts :: String
tttts@(Char
_:String
_))= if
 | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"c",String
"M",String
"N"] Bool -> Bool -> Bool
|| (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"A" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"F") -> let just_probe :: Maybe ParseChRh
just_probe = String -> Maybe ParseChRh
readRhythmicity String
choice in
           (case Maybe ParseChRh
just_probe of
             Just (P1 Choices
ch RhythmBasis
rh Int
n) -> Double
-> Double -> Double -> Choices -> RhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
rhythmicityABC Double
1.0 Double
2.0 Double
0.125 Choices
ch RhythmBasis
rh ([Double] -> Double)
-> (ReadyForConstructionUkr -> [Double])
-> ReadyForConstructionUkr
-> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> [Double]
rhythmicityGTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
n [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs)
             Just (P2 PolyChoices
ch PolyRhythmBasis
rh Int
r Int
n) -> (case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice of
                   String
"A" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF2 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"D" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF2 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"E" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF3 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"F" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF3 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"B" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF2 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"C" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF2 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"M" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF3 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"N" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF3 Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh
                   String
"c" -> Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPoly Double
1.0 Int
r PolyChoices
ch PolyRhythmBasis
rh) ([Double] -> Double)
-> (ReadyForConstructionUkr -> [Double])
-> ReadyForConstructionUkr
-> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> [Double]
rhythmicityGTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
n [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs)
             Maybe ParseChRh
_ -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs))  ReadyForConstructionUkr
tttt
 | String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0y" -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
 | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"y" ->
    let n2 :: Maybe Int
n2 = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice)::Maybe Int in
      Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
          (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 (case Maybe Int
n2 of {Just Int
n3 -> Int
n3; Maybe Int
Nothing -> Int
1}) [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
 | String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0z" -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> Double
-> ReadyForConstructionUkr
-> Double
rhythmicity0FHTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) Double
k ReadyForConstructionUkr
tttt
 | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"z" ->
    let n2 :: Maybe Int
n2 = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice)::Maybe Int in
      Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> Double
-> ReadyForConstructionUkr
-> Double
rhythmicity0FHTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
          (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 (case Maybe Int
n2 of {Just Int
n3 -> Int
n3; Maybe Int
Nothing -> Int
1}) [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) Double
k ReadyForConstructionUkr
tttt
 | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0" -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
 | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"w" -> if
          | (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"1" Bool -> Bool -> Bool
&& (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"4" ->
             (case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice of
              String
"w0" -> String -> Choices -> RhythmBasis -> String -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) 
              String
"w1" -> String -> Choices -> RhythmBasis -> String -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
2 Int
1 Int
1) 
              String
"w2" -> String -> Choices -> RhythmBasis -> String -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
2 Int
1) 
              String
"w3" -> String -> Choices -> RhythmBasis -> String -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) 
              String
_ -> \String
_ -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt) String
tttts
          | Bool
otherwise -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
 | Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"x" -> if
          | (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"1" Bool -> Bool -> Bool
&& (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"4" ->
             (case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice of
              String
"x0" -> String -> Choices -> RhythmBasis -> String -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2)
              String
"x1" -> String -> Choices -> RhythmBasis -> String -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
2 Int
1 Int
1)
              String
"x2" -> String -> Choices -> RhythmBasis -> String -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
2 Int
1)
              String
"x3" -> String -> Choices -> RhythmBasis -> String -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2)
              String
_ -> \String
_ -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt) String
tttts
          | Bool
otherwise -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
 | Bool
otherwise -> if
    | (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"b" Bool -> Bool -> Bool
|| ((Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"d" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"v") Bool -> Bool -> Bool
|| (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"I" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"Z"))) Bool -> Bool -> Bool
&& (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"1" Bool -> Bool -> Bool
&& (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"9" ->
        (case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice of
          String
"b" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF3 Int
5 Int
1
          String
"d" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF30 Int
5 Int
1
          String
"e" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF3 Int
6 Int
2
          String
"f" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF30 Int
6 Int
2
          String
"g" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF2 Int
5 Int
1
          String
"h" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF20 Int
5 Int
1
          String
"i" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF2 Int
6 Int
2
          String
"j" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLEF20 Int
6 Int
2
          String
"k" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF3 Int
5 Int
1
          String
"l" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF30 Int
5 Int
1
          String
"m" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF3 Int
6 Int
2
          String
"n" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF30 Int
6 Int
2
          String
"o" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF2 Int
5 Int
1
          String
"p" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF20 Int
5 Int
1
          String
"q" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF2 Int
6 Int
2
          String
"r" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedLF20 Int
6 Int
2
          String
"I" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF3 Int
5 Int
1
          String
"J" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF30 Int
5 Int
1
          String
"K" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF3 Int
6 Int
2
          String
"L" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF30 Int
6 Int
2
          String
"O" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF2 Int
5 Int
1
          String
"P" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF20 Int
5 Int
1
          String
"Q" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF2 Int
6 Int
2
          String
"R" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedEF20 Int
6 Int
2
          String
"W" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF3 Int
5 Int
1
          String
"X" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF30 Int
5 Int
1
          String
"Y" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF3 Int
6 Int
2
          String
"Z" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF30 Int
6 Int
2
          String
"U" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF2 Int
5 Int
1
          String
"V" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF20 Int
5 Int
1
          String
"S" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF2 Int
6 Int
2
          String
"T" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPolyWeightedF20 Int
6 Int
2
          String
"u" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPoly Int
5 Int
1
          String
"v" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPoly0 Int
5 Int
1
          String
"s" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPoly Int
6 Int
2
          String
"t" -> (Double
 -> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
forall t t.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g Double
-> Int -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
forall a.
Ord a =>
Double -> Int -> PolyChoices -> PolyRhythmBasis -> [a] -> Double
rhythmicityPoly0 Int
6 Int
2) ([[[Sound8]]] -> Double)
-> (String -> [[[Sound8]]]) -> String -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> [[[Sound8]]]
convFI String
bbs (String -> Double) -> String -> Double
forall a b. (a -> b) -> a -> b
$  String
tttts
    | Bool
otherwise -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
       (let ts :: String
ts = Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice in
          case String
ts of { [] -> (\[[[Sound8]]]
_ -> [[-Double
1.0]]) ; String
ks ->
            let q :: Maybe Int
q = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
ks::Maybe Int in
              case Maybe Int
q of {Just Int
q' -> Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
q' [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs; ~Maybe Int
Nothing -> (\[[[Sound8]]]
_ -> [[-Double
1.0]]) }}) ReadyForConstructionUkr
tttt
        where h1 :: (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h1 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c
f String
ts [Bool]
xs Int
m Int
n = t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c
f t
1.0 t
4 ([Bool] -> Int -> PolyChoices
PolyCh [Bool]
xs Int
m) ([Int] -> PolyRhythmBasis
PolyRhythm [Int
1,Int
2,Int
1,Int
n]) ([Double] -> c) -> ([[[Sound8]]] -> [Double]) -> [[[Sound8]]] -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Double]] -> [Double]
forall a. Monoid a => [a] -> a
mconcat ([[Double]] -> [Double])
-> ([[[Sound8]]] -> [[Double]]) -> [[[Sound8]]] -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                  (case String
ts of { [] -> (\[[[Sound8]]]
_ -> [[-Double
1.0]]) ; String
ks -> let q :: Maybe Int
q = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
ks::Maybe Int in
                      case Maybe Int
q of {Just Int
q' -> Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
q' [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs; ~Maybe Int
Nothing -> (\[[[Sound8]]]
_ -> [[-Double
1.0]]) }})
              h2 :: (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h2 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c
f String
ts [Bool]
xs Int
m Int
n = t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c
f t
1.0 t
4 ([Bool] -> Int -> PolyChoices
PolyCh [Bool]
xs Int
m) ([Int] -> PolyRhythmBasis
PolyRhythm [Int
2,Int
1,Int
1,Int
n]) ([Double] -> c) -> ([[[Sound8]]] -> [Double]) -> [[[Sound8]]] -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Double]] -> [Double]
forall a. Monoid a => [a] -> a
mconcat ([[Double]] -> [Double])
-> ([[[Sound8]]] -> [[Double]]) -> [[[Sound8]]] -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                  (case String
ts of { [] -> (\[[[Sound8]]]
_ -> [[-Double
1.0]]) ; String
ks -> let q :: Maybe Int
q = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
ks::Maybe Int in
                      case Maybe Int
q of {Just Int
q' -> Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
q' [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs; ~Maybe Int
Nothing -> (\[[[Sound8]]]
_ -> [[-Double
1.0]]) }})
              g :: (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> Int -> Int -> [[[Sound8]]] -> Double
g t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h1 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
True,Bool
True] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"1" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h1 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
True,Bool
False] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"2" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h1 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
False,Bool
True] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"3" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h1 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
False,Bool
False] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"4" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h2 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
True,Bool
True] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"5" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h2 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
True,Bool
False] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"6" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h2 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
False,Bool
True] Int
m Int
n
                | Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice) String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"7" = (t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> Double
forall t t c.
(Fractional t, Num t) =>
(t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> c)
-> String -> [Bool] -> Int -> Int -> [[[Sound8]]] -> c
h2 t -> t -> PolyChoices -> PolyRhythmBasis -> [Double] -> Double
f (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) [Bool
True,Bool
False,Bool
False] Int
m Int
n
                | Bool
otherwise = \[[[Sound8]]]
_ -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
n [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
              w1F :: (String -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
w1F String -> [[a]]
f Choices
ch RhythmBasis
rh = Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
forall a.
Ord a =>
Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
rhythmicityABC Double
1.0 Double
2.0 Double
0.125 Choices
ch RhythmBasis
rh ([a] -> Double) -> (a -> [a]) -> a -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[a]] -> [a]
forall a. Monoid a => [a] -> a
mconcat ([[a]] -> [a]) -> (a -> [[a]]) -> a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [[a]]
f (String -> [[a]]) -> (a -> String) -> a -> [[a]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\a
_ -> String
tttts)
              wwF2 :: ((String -> [[Double]]) -> p) -> String -> p
wwF2 (String -> [[Double]]) -> p
g2 String
xs =
                let n1 :: Maybe Int
n1 = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
xs::Maybe Int in
                   case Maybe Int
n1 of
                     Just Int
n2 -> (String -> [[Double]]) -> p
g2 (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
n2 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs ([[[Sound8]]] -> [[Double]])
-> (String -> [[[Sound8]]]) -> String -> [[Double]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> [[[Sound8]]]
convFI String
bbs)
                     Maybe Int
Nothing -> (String -> [[Double]]) -> p
g2 (\String
_ -> [[-Double
1.0]])
              x1F :: (String -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
x1F String -> [[a]]
f Choices
ch RhythmBasis
rh = Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
forall a.
Ord a =>
Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
rhythmicityABC0 Double
1.0 Double
2.0 Double
0.125 Choices
ch RhythmBasis
rh ([a] -> Double) -> (a -> [a]) -> a -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[a]] -> [a]
forall a. Monoid a => [a] -> a
mconcat ([[a]] -> [a]) -> (a -> [[a]]) -> a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [[a]]
f (String -> [[a]]) -> (a -> String) -> a -> [[a]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\a
_ -> String
tttts)
              xxF :: String -> Choices -> RhythmBasis -> a -> Double
xxF = ((String -> [[Double]]) -> Choices -> RhythmBasis -> a -> Double)
-> String -> Choices -> RhythmBasis -> a -> Double
forall p. ((String -> [[Double]]) -> p) -> String -> p
wwF2 (String -> [[Double]]) -> Choices -> RhythmBasis -> a -> Double
forall a a.
Ord a =>
(String -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
x1F
              wwF :: String -> Choices -> RhythmBasis -> a -> Double
wwF = ((String -> [[Double]]) -> Choices -> RhythmBasis -> a -> Double)
-> String -> Choices -> RhythmBasis -> a -> Double
forall p. ((String -> [[Double]]) -> p) -> String -> p
wwF2 (String -> [[Double]]) -> Choices -> RhythmBasis -> a -> Double
forall a a.
Ord a =>
(String -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
w1F
              {-# INLINE w1F #-}
              {-# INLINE wwF2 #-}
              {-# INLINE x1F #-}
              {-# INLINE xxF #-}
              {-# INLINE wwF #-}
rhythmicitya'Tup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double
k String
choice [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs (CF2 Maybe Double
x Maybe Double
y) String
bbs tttt :: ReadyForConstructionUkr
tttt@(Str tttts :: String
tttts@(Char
_:String
_)) =
 case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice of
  String
"0" -> if String
choice String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
"0z",String
"02z",String
"03z",String
"04z"] then Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> Double
-> Double
-> Double
-> ReadyForConstructionUkr
-> Double
rhythmicityKFHTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14
           Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 (case String -> Char
forall a. [a] -> a
last String
choice of {Char
'2' -> Int
2; Char
'3' -> Int
3; Char
'4' -> Int
4; ~Char
rrrrr -> Int
1}) [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) Double
k (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
x)
             (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
y) ReadyForConstructionUkr
tttt
         else Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> Double
-> Double
-> ReadyForConstructionUkr
-> Double
rhythmicityKHTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
           (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 (case String -> Char
forall a. [a] -> a
last String
choice of {Char
'2' -> Int
2; Char
'3' -> Int
3; Char
'4' -> Int
4; ~Char
rrrrr -> Int
1}) [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
x) (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
y) ReadyForConstructionUkr
tttt
  String
"w" -> if
          | (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"1" Bool -> Bool -> Bool
&& (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"4" ->
             (case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice of
              String
"w0" -> String -> Choices -> RhythmBasis -> String -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) 
              String
"w1" -> String -> Choices -> RhythmBasis -> String -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
2 Int
1 Int
1) 
              String
"w2" -> String -> Choices -> RhythmBasis -> String -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
2 Int
1) 
              String
"w3" -> String -> Choices -> RhythmBasis -> String -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
wwF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) 
              String
_ -> \String
_ -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs)  ReadyForConstructionUkr
tttt) String
tttts
          | Bool
otherwise -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
              where w1F :: (String -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
w1F String -> [[a]]
f Choices
ch RhythmBasis
rh = Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
forall a.
Ord a =>
Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
rhythmicityABC Double
1.0 (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
2.0 Maybe Double
x) (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
0.125 Maybe Double
y) Choices
ch RhythmBasis
rh ([a] -> Double) -> (a -> [a]) -> a -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[a]] -> [a]
forall a. Monoid a => [a] -> a
mconcat ([[a]] -> [a]) -> (a -> [[a]]) -> a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [[a]]
f (String -> [[a]]) -> (a -> String) -> a -> [[a]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\a
_ -> String
tttts)
                    wwF :: String -> Choices -> RhythmBasis -> a -> Double
wwF String
xs =
                      let n1 :: Maybe Int
n1 = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
xs::Maybe Int in
                        case Maybe Int
n1 of
                         Just Int
n2 -> (String -> [[Double]]) -> Choices -> RhythmBasis -> a -> Double
forall a a.
Ord a =>
(String -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
w1F (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
n2 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs ([[[Sound8]]] -> [[Double]])
-> (String -> [[[Sound8]]]) -> String -> [[Double]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> [[[Sound8]]]
convFI String
bbs) 
                         Maybe Int
Nothing -> (String -> [[Double]]) -> Choices -> RhythmBasis -> a -> Double
forall a a.
Ord a =>
(String -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
w1F (\String
_ -> [[-Double
1.0]])
                    {-# INLINE w1F #-}
                    {-# INLINE wwF #-}
  String
"x" -> if
          | (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"1" Bool -> Bool -> Bool
&& (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"4" ->
             (case Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
2 String
choice of
              String
"x0" -> String -> Choices -> RhythmBasis -> String -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) 
              String
"x1" -> String -> Choices -> RhythmBasis -> String -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
1 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
2 Int
1 Int
1) 
              String
"x2" -> String -> Choices -> RhythmBasis -> String -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
1 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
2 Int
1) 
              String
"x3" -> String -> Choices -> RhythmBasis -> String -> Double
forall a. String -> Choices -> RhythmBasis -> a -> Double
xxF (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice) (Int -> Int -> Int -> Choices
Ch Int
0 Int
0 Int
4) (Int -> Int -> Int -> RhythmBasis
Rhythm Int
1 Int
1 Int
2) 
              String
_ -> \String
_ -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt) String
tttts
          | Bool
otherwise -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> ReadyForConstructionUkr
-> Double
rhythmicity0HTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17  (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
1 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs) ReadyForConstructionUkr
tttt
              where x1F :: (String -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
x1F String -> [[a]]
f Choices
ch RhythmBasis
rh = Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
forall a.
Ord a =>
Double
-> Double -> Double -> Choices -> RhythmBasis -> [a] -> Double
rhythmicityABC0 Double
1.0 (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
2.0 Maybe Double
x) (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
0.125 Maybe Double
y) Choices
ch RhythmBasis
rh ([a] -> Double) -> (a -> [a]) -> a -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[a]] -> [a]
forall a. Monoid a => [a] -> a
mconcat ([[a]] -> [a]) -> (a -> [[a]]) -> a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [[a]]
f (String -> [[a]]) -> (a -> String) -> a -> [[a]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (\a
_ -> String
tttts)
                    xxF :: String -> Choices -> RhythmBasis -> a -> Double
xxF String
xs =
                      let n1 :: Maybe Int
n1 = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
xs::Maybe Int in
                        case Maybe Int
n1 of
                         Just Int
n2 -> (String -> [[Double]]) -> Choices -> RhythmBasis -> a -> Double
forall a a.
Ord a =>
(String -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
x1F (Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
n2 [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs ([[[Sound8]]] -> [[Double]])
-> (String -> [[[Sound8]]]) -> String -> [[Double]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> [[[Sound8]]]
convFI String
bbs)
                         Maybe Int
Nothing -> (String -> [[Double]]) -> Choices -> RhythmBasis -> a -> Double
forall a a.
Ord a =>
(String -> [[a]]) -> Choices -> RhythmBasis -> a -> Double
x1F (\String
_ -> [[-Double
1.0]])
                    {-# INLINE x1F #-}
                    {-# INLINE xxF #-}
  String
_ -> if
     | ((Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"b" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"v") Bool -> Bool -> Bool
|| (Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
>= String
"A" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> String -> Bool
forall a. Ord a => a -> a -> Bool
<= String
"Z" Bool -> Bool -> Bool
&& Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
1 String
choice String -> [String] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [String
"G",String
"H"])) -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> Double
-> String
-> [[[[Sound8]]] -> [[Double]]]
-> Coeffs2
-> ReadyForConstructionUkr
-> Double
rhythmicityH'Tup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17 Double
k String
choice [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs Coeffs2
forall a. CoeffTwo a
CF0 ReadyForConstructionUkr
tttt
     | Bool
otherwise -> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Sound8)
-> Array Int (Sound8, [Sound8] -> Sound8)
-> Array Int (Sound8, Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int ([Sound8], Bool)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Sound8)
-> Array Int (Sound8, [Sound8])
-> Array Int (Char, Bool)
-> Array Int (Char, Bool)
-> Array Int (Sound8, Bool)
-> ([[[Sound8]]] -> [[Double]])
-> Double
-> Double
-> ReadyForConstructionUkr
-> Double
rhythmicityKHTup Array Int (Sound8, Bool)
tup1 Array Int (Sound8, Bool)
tup2 Array Int (Sound8, Bool)
tup3 Array Int (Sound8, Bool)
tup4 Array Int ([Sound8], Bool)
tup5 Array Int ([Sound8], Sound8)
tup6 Array Int (Sound8, [Sound8] -> Sound8)
tup7 Array Int (Sound8, Bool)
tup8 Array Int ([Sound8], Bool)
tup9 Array Int ([Sound8], Bool)
tup10 Array Int ([Sound8], Bool)
tup11 Array Int (Sound8, [Sound8])
tup12 Array Int (Char, Sound8)
tup13 Array Int (Sound8, [Sound8])
tup14 Array Int (Char, Bool)
tup15 Array Int (Char, Bool)
tup16 Array Int (Sound8, Bool)
tup17
        (let ts :: String
ts = Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
2 (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> String
forall a. Int -> [a] -> [a]
take Int
3 (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
choice in
          case String
ts of { [] -> (\[[[Sound8]]]
_ -> [[-Double
1.0]]) ; String
ks ->
            let q :: Maybe Int
q = String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
ks::Maybe Int in
              case Maybe Int
q of {Just Int
q' -> Int -> [[[[Sound8]]] -> [[Double]]] -> [[[Sound8]]] -> [[Double]]
helperHF1 Int
q' [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs; ~Maybe Int
Nothing -> (\[[[Sound8]]]
_ -> [[-Double
1.0]]) }})
                (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
x) (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
y) ReadyForConstructionUkr
tttt

rhythmicitya'Tup Array Int (Sound8, Bool)
_ Array Int (Sound8, Bool)
_ Array Int (Sound8, Bool)
_ Array Int (Sound8, Bool)
_ Array Int ([Sound8], Bool)
_ Array Int ([Sound8], Sound8)
_ Array Int (Sound8, [Sound8] -> Sound8)
_ Array Int (Sound8, Bool)
_ Array Int ([Sound8], Bool)
_ Array Int ([Sound8], Bool)
_ Array Int ([Sound8], Bool)
_ Array Int (Sound8, [Sound8])
_ Array Int (Char, Sound8)
_ Array Int (Sound8, [Sound8])
_ Array Int (Char, Bool)
_ Array Int (Char, Bool)
_ Array Int (Sound8, Bool)
_ Double
_ String
_ [[[[Sound8]]] -> [[Double]]]
_ Coeffs2
_ String
_ ReadyForConstructionUkr
_ = -Double
2.0