-- |
-- Module      :  Languages.UniquenessPeriods.Vector.PropertiesSyllablesG
-- Copyright   :  (c) OleksandrZhabenko 2020
-- 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.

{-# LANGUAGE CPP #-}

module Languages.UniquenessPeriods.Vector.PropertiesSyllablesG (
  -- * Rhythmicity metrices (semi-empirical)
  -- ** Simple ones
  rhythmicity0
  , rhythmicityV0
  -- ** With weight coefficients
  , rhythmicityVK
  , rhythmicityK
  -- * Rhythmicity metrices from generated with r-glpk-phonetic-languages-ukrainian-durations package (since 0.2.0.0 version)
  -- ** Simple ones
  , rhythmicity02
  , rhythmicityV02
  -- ** With weight coefficients
  , rhythmicityVK2
  , rhythmicityK2
) 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 qualified Data.Vector as VB
import Languages.Rhythmicity
import Languages.Phonetic.Ukrainian.Syllable

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

eval23 :: [[Float]] -> Float
eval23 = [Float] -> Float
forall a. (RealFrac a, Floating a) => [a] -> a
evalRhythmicity23 ([Float] -> Float) -> ([[Float]] -> [Float]) -> [[Float]] -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Float]] -> [Float]
forall a. Monoid a => [a] -> a
mconcat
{-# INLINE eval23 #-}

eval23K :: c -> c -> [[c]] -> c
eval23K c
k2 c
k3 = c -> c -> [c] -> c
forall a. (RealFrac a, Floating a) => a -> a -> [a] -> a
evalRhythmicity23K c
k2 c
k3 ([c] -> c) -> ([[c]] -> [c]) -> [[c]] -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[c]] -> [c]
forall a. Monoid a => [a] -> a
mconcat
{-# INLINE eval23K #-}

rhythmicity0 :: String -> Float
rhythmicity0 :: String -> Float
rhythmicity0 String
xs
 | String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
xs = Float
0.0
 | Bool
otherwise = [[Float]] -> Float
eval23 ([[Float]] -> Float) -> (String -> [[Float]]) -> String -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
syllableDurations ([[[UZPP2]]] -> [[Float]])
-> (String -> [[[UZPP2]]]) -> String -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [[[UZPP2]]]
createSyllablesUkr (String -> Float) -> String -> Float
forall a b. (a -> b) -> a -> b
$ String
xs

rhythmicityK :: Float -> Float -> String -> Float
rhythmicityK :: Float -> Float -> String -> Float
rhythmicityK Float
k2 Float
k3 String
xs
 | String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
xs = Float
0.0
 | Bool
otherwise = Float -> Float -> [[Float]] -> Float
forall c. (RealFrac c, Floating c) => c -> c -> [[c]] -> c
eval23K Float
k2 Float
k3 ([[Float]] -> Float) -> (String -> [[Float]]) -> String -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
syllableDurations ([[[UZPP2]]] -> [[Float]])
-> (String -> [[[UZPP2]]]) -> String -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [[[UZPP2]]]
createSyllablesUkrP (String -> Float) -> String -> Float
forall a b. (a -> b) -> a -> b
$ String
xs

rhythmicityV0 :: VB.Vector Char -> Float
rhythmicityV0 :: Vector Char -> Float
rhythmicityV0 Vector Char
v
 | Vector Char -> Bool
forall a. Vector a -> Bool
VB.null Vector Char
v = Float
0.0
 | Bool
otherwise = [[Float]] -> Float
eval23 ([[Float]] -> Float)
-> (Vector Char -> [[Float]]) -> Vector Char -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
syllableDurations ([[[UZPP2]]] -> [[Float]])
-> (Vector Char -> [[[UZPP2]]]) -> Vector Char -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Char -> [[[UZPP2]]]
createSyllablesUkrV (Vector Char -> Float) -> Vector Char -> Float
forall a b. (a -> b) -> a -> b
$ Vector Char
v

rhythmicityVK :: Float -> Float -> VB.Vector Char -> Float
rhythmicityVK :: Float -> Float -> Vector Char -> Float
rhythmicityVK Float
k2 Float
k3 Vector Char
v
 | Vector Char -> Bool
forall a. Vector a -> Bool
VB.null Vector Char
v = Float
0.0
 | Bool
otherwise = Float -> Float -> [[Float]] -> Float
forall c. (RealFrac c, Floating c) => c -> c -> [[c]] -> c
eval23K Float
k2 Float
k3 ([[Float]] -> Float)
-> (Vector Char -> [[Float]]) -> Vector Char -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
syllableDurations ([[[UZPP2]]] -> [[Float]])
-> (Vector Char -> [[[UZPP2]]]) -> Vector Char -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Char -> [[[UZPP2]]]
createSyllablesUkrVP (Vector Char -> Float) -> Vector Char -> Float
forall a b. (a -> b) -> a -> b
$ Vector Char
v

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

rhythmicity02 :: String -> Float
rhythmicity02 :: String -> Float
rhythmicity02 String
xs
 | String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
xs = Float
0.0
 | Bool
otherwise = [[Float]] -> Float
eval23 ([[Float]] -> Float) -> (String -> [[Float]]) -> String -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
syllableDurations2 ([[[UZPP2]]] -> [[Float]])
-> (String -> [[[UZPP2]]]) -> String -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [[[UZPP2]]]
createSyllablesUkr (String -> Float) -> String -> Float
forall a b. (a -> b) -> a -> b
$ String
xs

rhythmicityK2 :: Float -> Float -> String -> Float
rhythmicityK2 :: Float -> Float -> String -> Float
rhythmicityK2 Float
k2 Float
k3 String
xs
 | String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
xs = Float
0.0
 | Bool
otherwise = Float -> Float -> [[Float]] -> Float
forall c. (RealFrac c, Floating c) => c -> c -> [[c]] -> c
eval23K Float
k2 Float
k3 ([[Float]] -> Float) -> (String -> [[Float]]) -> String -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
syllableDurations2 ([[[UZPP2]]] -> [[Float]])
-> (String -> [[[UZPP2]]]) -> String -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [[[UZPP2]]]
createSyllablesUkrP (String -> Float) -> String -> Float
forall a b. (a -> b) -> a -> b
$ String
xs

rhythmicityV02 :: VB.Vector Char -> Float
rhythmicityV02 :: Vector Char -> Float
rhythmicityV02 Vector Char
v
 | Vector Char -> Bool
forall a. Vector a -> Bool
VB.null Vector Char
v = Float
0.0
 | Bool
otherwise = [[Float]] -> Float
eval23 ([[Float]] -> Float)
-> (Vector Char -> [[Float]]) -> Vector Char -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
syllableDurations2 ([[[UZPP2]]] -> [[Float]])
-> (Vector Char -> [[[UZPP2]]]) -> Vector Char -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Char -> [[[UZPP2]]]
createSyllablesUkrV (Vector Char -> Float) -> Vector Char -> Float
forall a b. (a -> b) -> a -> b
$ Vector Char
v

rhythmicityVK2 :: Float -> Float -> VB.Vector Char -> Float
rhythmicityVK2 :: Float -> Float -> Vector Char -> Float
rhythmicityVK2 Float
k2 Float
k3 Vector Char
v
 | Vector Char -> Bool
forall a. Vector a -> Bool
VB.null Vector Char
v = Float
0.0
 | Bool
otherwise = Float -> Float -> [[Float]] -> Float
forall c. (RealFrac c, Floating c) => c -> c -> [[c]] -> c
eval23K Float
k2 Float
k3 ([[Float]] -> Float)
-> (Vector Char -> [[Float]]) -> Vector Char -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
syllableDurations2 ([[[UZPP2]]] -> [[Float]])
-> (Vector Char -> [[[UZPP2]]]) -> Vector Char -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Char -> [[[UZPP2]]]
createSyllablesUkrVP (Vector Char -> Float) -> Vector Char -> Float
forall a b. (a -> b) -> a -> b
$ Vector Char
v