-- |
-- Module      :  Languages.UniquenessPeriods.Vector.PropertiesSyllables
-- 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.PropertiesSyllables (
  -- * Rhythmicity metrices
  -- ** A simple one
  rhythmicity0
  -- ** With weight coefficients
  , rhythmicityK
) 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 V
import Languages.Rhythmicity
import MMSyn7.Syllable

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

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
forall a. (RealFrac a, Floating a) => [a] -> a
evalRhythmicity23 ([Float] -> Float) -> (String -> [Float]) -> String -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Float]] -> [Float]
forall a. Monoid a => [a] -> a
mconcat ([[Float]] -> [Float])
-> (String -> [[Float]]) -> String -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZP]]] -> [[Float]]
syllableDurations ([[[UZP]]] -> [[Float]])
-> (String -> [[[UZP]]]) -> String -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [[[UZP]]]
syllablesUkrP (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 a. (RealFrac a, Floating a) => a -> a -> [a] -> a
evalRhythmicity23K Float
k2 Float
k3 ([Float] -> Float) -> (String -> [Float]) -> String -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Float]] -> [Float]
forall a. Monoid a => [a] -> a
mconcat ([[Float]] -> [Float])
-> (String -> [[Float]]) -> String -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZP]]] -> [[Float]]
syllableDurations ([[[UZP]]] -> [[Float]])
-> (String -> [[[UZP]]]) -> String -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [[[UZP]]]
syllablesUkrP (String -> Float) -> String -> Float
forall a b. (a -> b) -> a -> b
$ String
xs