{-# OPTIONS_HADDOCK show-extensions #-}

-- |
-- Module      :  Phonetic.Languages.Array.Ukrainian.PropertiesFuncRepG2Rhythmicity
-- Copyright   :  (c) OleksandrZhabenko 2020-2021
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  olexandr543@yahoo.com
--
-- Generalization of the functionality of the DobutokO.Poetry.Norms
-- and DobutokO.Poetry.Norms.Extended modules
-- from the @dobutokO-poetry@ package. Instead of vectors, uses arrays.

module Phonetic.Languages.Array.Ukrainian.PropertiesFuncRepG2Rhythmicity (
  -- * Basic
  -- ** Working with rhythmicity
  procRhythmicity23F
  -- *** Working with rhythmicity that can be defined by the user (using 'rhythmicityH')
  , procRhythmicity23FH
  -- * Extended
  -- ** Working with rhythmicity
  , procRhythmicity23FTup
  -- *** Working with rhythmicity that can be defined by the user (using 'rhythmicityH')
  , procRhythmicity23FHTup
) where

import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2Common
import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2H
import Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2Hprime
import Phonetic.Languages.Simplified.DataG.Base
import Melodics.Ukrainian.ArrInt8
import GHC.Arr (Array)
import GHC.Int (Int8)

procRhythm23F
  :: (Ord c) => (Double -> c)
  -> String
  -> (String -> Coeffs2 -> String -> Double)
  -> Coeffs2
  -> FuncRep2 String Double c
procRhythm23F :: (Double -> c)
-> String
-> (String -> Coeffs2 -> String -> Double)
-> Coeffs2
-> FuncRep2 String Double c
procRhythm23F Double -> c
h String
choice String -> Coeffs2 -> String -> Double
g Coeffs2
coeffs = (String -> Double) -> (Double -> c) -> FuncRep2 String Double c
forall a b c. (a -> b) -> (b -> c) -> FuncRep2 a b c
D (String -> Coeffs2 -> String -> Double
g String
choice Coeffs2
coeffs) Double -> c
h
{-# INLINE procRhythm23F #-}

procRhythmicity23F
  :: (Ord c) => Double
  -> (Double -> c)
  -> String
  -> Coeffs2
  -> FuncRep2 String Double c
procRhythmicity23F :: Double
-> (Double -> c) -> String -> Coeffs2 -> FuncRep2 String Double c
procRhythmicity23F Double
k Double -> c
g String
choice Coeffs2
coeffs = (Double -> c)
-> String
-> (String -> Coeffs2 -> String -> Double)
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c)
-> String
-> (String -> Coeffs2 -> String -> Double)
-> Coeffs2
-> FuncRep2 String Double c
procRhythm23F Double -> c
g String
choice (Double -> String -> Coeffs2 -> String -> Double
rhythmicity Double
k) Coeffs2
coeffs
{-# INLINE procRhythmicity23F #-}

procRhythmicity23FH
  :: (Ord c) => Double
  -> (Double -> c)
  -> [[[[Sound8]]] -> [[Double]]]
  -> String
  -> Coeffs2
  -> FuncRep2 String Double c
procRhythmicity23FH :: Double
-> (Double -> c)
-> [[[[Sound8]]] -> [[Double]]]
-> String
-> Coeffs2
-> FuncRep2 String Double c
procRhythmicity23FH Double
k Double -> c
g [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs String
choice Coeffs2
coeffs = (String -> Double) -> (Double -> c) -> FuncRep2 String Double c
forall a b c. (a -> b) -> (b -> c) -> FuncRep2 a b c
D (Double
-> String
-> [[[[Sound8]]] -> [[Double]]]
-> Coeffs2
-> String
-> Double
rhythmicityH Double
k String
choice [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs Coeffs2
coeffs) Double -> c
g
{-# INLINE procRhythmicity23FH #-}

-------------------------------------------------------

procRhythmicity23FTup
  :: (Ord c) => 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
  -> (Double -> c)
  -> String
  -> Coeffs2
  -> FuncRep2 String Double c
procRhythmicity23FTup :: 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
-> (Double -> c)
-> String
-> Coeffs2
-> FuncRep2 String Double c
procRhythmicity23FTup 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 Double -> c
g String
choice Coeffs2
coeffs = (Double -> c)
-> String
-> (String -> Coeffs2 -> String -> Double)
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c)
-> String
-> (String -> Coeffs2 -> String -> Double)
-> Coeffs2
-> FuncRep2 String Double c
procRhythm23F Double -> c
g 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
-> Coeffs2
-> String
-> 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) Coeffs2
coeffs
{-# INLINE procRhythmicity23FTup #-}

procRhythmicity23FHTup
  :: (Ord c) => 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
  -> (Double -> c)
  -> [[[[Sound8]]] -> [[Double]]]
  -> String
  -> Coeffs2
  -> FuncRep2 String Double c
procRhythmicity23FHTup :: 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
-> (Double -> c)
-> [[[[Sound8]]] -> [[Double]]]
-> String
-> Coeffs2
-> FuncRep2 String Double c
procRhythmicity23FHTup 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 Double -> c
g [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs String
choice Coeffs2
coeffs = (String -> Double) -> (Double -> c) -> FuncRep2 String Double c
forall a b c. (a -> b) -> (b -> c) -> FuncRep2 a b c
D (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
-> 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) Double -> c
g
{-# INLINE procRhythmicity23FHTup #-}