{-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Phladiprelio.General.PropertiesSyllablesG2 -- Copyright : (c) Oleksandr Zhabenko 2020-2023 -- License : MIT -- Stability : Experimental -- Maintainer : oleksandr.zhabenko@yahoo.com -- -- Generalization and extension of the functionality of the DobutokO.Poetry.Norms -- and DobutokO.Poetry.Norms.Extended modules -- from the @dobutokO-poetry@ package and more recent package @phonetic-languages-simplified-properties-array@. -- Uses syllables information. -- Instead of the vector-related, uses arrays. -- If you use the functionality of the Phladiprelio.Ukrainian.PropertiesSyllablesG2 module, -- then import it qualified (or this module) because they have many common data. Is provided as a standalone one -- to reduce dependencies list in general case. {-# LANGUAGE BangPatterns, MultiWayIf, NoImplicitPrelude #-} module Phladiprelio.General.PropertiesSyllablesG2 ( -- * Mapping function data type MappingFunctionPL(..) , isPhoPaaW , isSaaW , fromPhoPaaW , fromSaaW -- * Rhythmicity properties (semi-empirical) -- ** Simple one , rhythmicity0i , rhythmicity0Fi -- ** With weight coefficients , rhythmicityKi , rhythmicityKFi -- * General , rhythmicityG , rhythmicity ) where import GHC.Base import GHC.List import Phladiprelio.Rhythmicity.Simple import Phladiprelio.Rhythmicity.Factor import Phladiprelio.Rhythmicity.TwoFourth import Phladiprelio.Rhythmicity.PolyRhythm import Phladiprelio.General.Base import Phladiprelio.General.Syllables import Data.Maybe (isNothing,fromMaybe,fromJust) import Text.Read (readMaybe) import Phladiprelio.General.EmphasisG import GHC.Int (Int8) import Phladiprelio.Coeffs import qualified Logical.OrdConstraints as L eval23 = evalRhythmicity23 . mconcat {-# INLINE eval23 #-} eval23K k2 k3 = evalRhythmicity23K k2 k3 . mconcat {-# INLINE eval23K #-} eval23F ff k = evalRhythmicity23F ff k . mconcat {-# INLINE eval23F #-} eval23KF ff k k2 k3 = evalRhythmicity23KF ff k k2 k3 . mconcat {-# INLINE eval23KF #-} -------------------------------------------------------------------------------------------- data MappingFunctionPL = PhoPaaW ([[[PRS]]] -> [[Double]]) | SaaW ([[[Int8]]] -> [[Double]]) isPhoPaaW :: MappingFunctionPL -> Bool isPhoPaaW (PhoPaaW _) = True isPhoPaaW _ = False isSaaW :: MappingFunctionPL -> Bool isSaaW (SaaW _) = True isSaaW _ = False fromPhoPaaW :: MappingFunctionPL -> Maybe ([[[PRS]]] -> [[Double]]) fromPhoPaaW (PhoPaaW f) = Just f fromPhoPaaW _ = Nothing fromSaaW :: MappingFunctionPL -> Maybe ([[[Int8]]] -> [[Double]]) fromSaaW (SaaW f) = Just f fromSaaW _ = Nothing rhythmicityG :: MappingFunctionPL-- ^ A function that specifies the syllables durations, analogue of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. -> ([[Double]] -> Double) -- ^ Usually some kind of flattening of the double list into a single value. -> String -- ^ The starting 'String' which creates the order for the 'FSLG' representation -> GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text. -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon -- (e. g. allophones). Must be sorted in the ascending order to be used correctly. -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly. -> SegmentRulesG -> String -- ^ Corresponds to the 100 delimiter in the @ukrainian-phonetics-basic-array@ package. -> String -- ^ Corresponds to the 101 delimiter in the @ukrainian-phonetics-basic-array@ package. -> ReadyForConstructionPL -> Double rhythmicityG f g bbs wrs ks arr hs us vs xs@(FSLG tsss) | null tsss = -1.0 | isSaaW f = g . (fromJust (fromSaaW f)) $ tsss | otherwise = -3.0 rhythmicityG f g bbs wrs ks arr hs us vs xs@(StrG ys) | null ys = -2.0 | isPhoPaaW f = g . (fromJust (fromPhoPaaW f)) . createSyllablesPL wrs ks arr hs us vs $ ys | otherwise = g . (fromJust (fromSaaW f)) . convFI wrs ks arr hs us vs bbs $ ys {-# INLINE rhythmicityG #-} ------------------------------------------------------- rhythmicity0i :: MappingFunctionPL -- ^ A function that specifies the syllables durations, analogue of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. -> String -> GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text. -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon -- (e. g. allophones). Must be sorted in the ascending order to be used correctly. -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly. -> SegmentRulesG -> String -- ^ Corresponds to the 100 delimiter in the @ukrainian-phonetics-basic-array@ package. -> String -- ^ Corresponds to the 101 delimiter in the @ukrainian-phonetics-basic-array@ package. -> ReadyForConstructionPL -> Double rhythmicity0i f = rhythmicityG f eval23 {-# INLINE rhythmicity0i #-} ------------------------------------------------------- rhythmicityKi :: MappingFunctionPL -- ^ A function that specifies the syllables durations, analogue of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. -> Double -> Double -> String -> GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text. -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon -- (e. g. allophones). Must be sorted in the ascending order to be used correctly. -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly. -> SegmentRulesG -> String -- ^ Corresponds to the 100 delimiter in the @ukrainian-phonetics-basic-array@ package. -> String -- ^ Corresponds to the 101 delimiter in the @ukrainian-phonetics-basic-array@ package. -> ReadyForConstructionPL -> Double rhythmicityKi f k2 k3 = rhythmicityG f (eval23K k2 k3) {-# INLINE rhythmicityKi #-} -------------------------------------------------------- rhythmicity0Fi :: Factors -> MappingFunctionPL -- ^ A function that specifies the syllables durations, analogue of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. -> Double -> String -> GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text. -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon -- (e. g. allophones). Must be sorted in the ascending order to be used correctly. -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly. -> SegmentRulesG -> String -- ^ Corresponds to the 100 delimiter in the @ukrainian-phonetics-basic-array@ package. -> String -- ^ Corresponds to the 101 delimiter in the @ukrainian-phonetics-basic-array@ package. -> ReadyForConstructionPL -> Double rhythmicity0Fi ff f k = rhythmicityG f (eval23F ff k) {-# INLINE rhythmicity0Fi #-} -------------------------------------------------------- rhythmicityKFi :: Factors -> MappingFunctionPL -- ^ A function that specifies the syllables durations, analogue of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. -> Double -> Double -> Double -> String -> GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text. -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon -- (e. g. allophones). Must be sorted in the ascending order to be used correctly. -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly. -> SegmentRulesG -> String -- ^ Corresponds to the 100 delimiter in the @ukrainian-phonetics-basic-array@ package. -> String -- ^ Corresponds to the 101 delimiter in the @ukrainian-phonetics-basic-array@ package. -> ReadyForConstructionPL -> Double rhythmicityKFi ff f k k2 k3 = rhythmicityG f (eval23KF ff k k2 k3) {-# INLINE rhythmicityKFi #-} -------------------------------------------------------- -- | It is intended to provide different functions :: 'Double' -> 'String' -> ([[['PRS']]] -> [['Double']]). -- The \"z\"-line uses \'F\' functions. rhythmicity :: Factors -> Double -> String -- ^ The \"f\"-line uses \'F\' functions since the version 0.13.0.0. -> (Double -> String -> MappingFunctionPL) -- ^ The function that is needed in the 'procRhythmicity23F' function. -- Specifies a way how the syllables represented in the phonetic language approach transforms into their durations and -- depends on two parameters. -> Coeffs2 -> String -> GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text. -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon -- (e. g. allophones). Must be sorted in the ascending order to be used correctly. -> CharPhoneticClassification -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly. -> SegmentRulesG -> String -> String -> ReadyForConstructionPL -> Double rhythmicity ff k choice@(c1:c2@(c3:c4@(c5:cs))) h CF0 | c1 == '0' && c2 `elem` ["2f","3f","4f"] = rhythmicity0Fi ff f k | c1 == '0' && c2 `elem` ["2y","3y","4y"] = rhythmicity0i f | c1 `elem` "wx" = case c3 of '0' -> w0F (Ch 1 1 4) (Rhythm 1 1 2) '1' -> w0F (Ch 1 0 4) (Rhythm 2 1 1) '2' -> w0F (Ch 0 1 4) (Rhythm 1 2 1) '3' -> w0F (Ch 0 0 4) (Rhythm 1 1 2) _ -> w0F (Ch 0 0 4) (Rhythm 1 1 2) | L.ordCs2HPred1 [L.O "cMN", L.C "AF"] c1 = let just_probe = readRhythmicity choice in case just_probe of Just (P1 ch rh _) -> rhythmicityG f (rhythmicityABC 1.0 2.0 0.125 ch rh . mconcat) Just (P2 ch rh r _) -> rhythmicityG f ((helperF5 c1) 1.0 r ch rh . mconcat) _ -> rhythmicity0i f | L.ordCs2HPred1 [L.O "z", L.C "begvIZ"] c1 && c3 >= '0' && c3 <= '7' = let u0F rs = rhythmicityG f ((helperF6 c1) 1.0 4 (PolyCh rs 5) (PolyRhythm (if c3 < '4' then [1,2,1,1] else [2,1,1,1])) . mconcat) in u0F (case c3 of '0' -> [True,True,True] '1' -> [True,True,False] '2' -> [True,False,True] '3' -> [True,False,False] '4' -> [False,False,True] '5' -> [False,True,False] '6' -> [False,True,True] '7' -> [False,False,False]) | otherwise = rhythmicity0i f where f = h k choice w0F ch rh = rhythmicityG f ((if c1 == 'w' then rhythmicityABC else rhythmicityABC0) 1.0 2.0 0.125 ch rh . mconcat) {-# INLINE w0F #-} rhythmicity ff k choice@(c1:c2@(c3:c4@(c5:cs))) h (CF2 x y) | c1 == '0' && c2 `elem` ["2f","3f","4f"] = rhythmicityKFi ff f k (fromMaybe 1.0 x) (fromMaybe 1.0 y) | c1 == '0' && c2 `elem` ["2y","3y","4y"] = rhythmicityKi f (fromMaybe 1.0 x) (fromMaybe 1.0 y) | c1 `elem` "wx" = if | c3 == '0' && (c5 >= '1' && c5 <= '4') -> w0F (Ch 1 1 4) (Rhythm 1 1 2) | c3 == '1' && (c5 >= '1' && c5 <= '4') -> w0F (Ch 1 0 4) (Rhythm 2 1 1) | c3 == '2' && (c5 >= '1' && c5 <= '4') -> w0F (Ch 0 1 4) (Rhythm 1 2 1) | c3 == '3' && (c5 >= '1' && c5 <= '4') -> w0F (Ch 0 0 4) (Rhythm 1 1 2) | otherwise -> w0F (Ch 1 0 4) (Rhythm 1 1 2) | L.ordCs2HPred1 [L.O "cz",L.C "begvAFIZ"] c1 = rhythmicity ff k choice h CF0 | otherwise = rhythmicityKi f (fromMaybe 1.0 x) (fromMaybe 1.0 y) where f = h k choice w0F ch rh = rhythmicityG f ((if c1 == 'w' then rhythmicityABC else rhythmicityABC0) 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) ch rh . mconcat) {-# INLINE w0F #-} rhythmicity ff k choice@(c1:c2@(c3:cs)) h CF0 | choice == "0f" = rhythmicity0Fi ff f k | otherwise = rhythmicity0i f where f = h k choice rhythmicity ff k choice@(c1:c2@(c3:cs)) h (CF2 x y) | choice == "0f" = rhythmicityKFi ff f k (fromMaybe 1.0 x) (fromMaybe 1.0 y) | otherwise = rhythmicityKi f (fromMaybe 1.0 x) (fromMaybe 1.0 y) where f = h k choice rhythmicity ff k choice h _ = rhythmicity0i (h k choice) helperF5 c | c == 'A' = rhythmicityPolyWeightedLEF2 | c == 'D' = rhythmicityPolyWeightedLF2 | c == 'E' = rhythmicityPolyWeightedLEF3 | c == 'F' = rhythmicityPolyWeightedLF3 | c == 'B' = rhythmicityPolyWeightedEF2 | c == 'C' = rhythmicityPolyWeightedF2 | c == 'M' = rhythmicityPolyWeightedEF3 | c == 'N' = rhythmicityPolyWeightedF3 | otherwise = rhythmicityPoly helperF6 c | c == 's' || c == 'u' = rhythmicityPoly | c == 't' || c == 'v' = rhythmicityPoly0 | c == 'S' || c == 'U' = rhythmicityPolyWeightedF2 | c == 'T' || c == 'V' = rhythmicityPolyWeightedF20 | c == 'Y' || c == 'W' = rhythmicityPolyWeightedF3 | c == 'X' || c == 'Z' = rhythmicityPolyWeightedF30 | c == 'O' || c == 'Q' = rhythmicityPolyWeightedEF2 | c == 'P' || c == 'R' = rhythmicityPolyWeightedEF20 | c == 'I' || c == 'K' = rhythmicityPolyWeightedEF3 | c == 'J' || c == 'L' = rhythmicityPolyWeightedEF30 | c == 'o' || c == 'q' = rhythmicityPolyWeightedLF2 | c == 'p' || c == 'r' = rhythmicityPolyWeightedLF20 | c == 'k' || c == 'm' = rhythmicityPolyWeightedLF3 | c == 'l' || c == 'n' = rhythmicityPolyWeightedLF30 | c == 'g' || c == 'i' = rhythmicityPolyWeightedLEF2 | c == 'h' || c == 'j' = rhythmicityPolyWeightedLEF20 | c == 'b' || c == 'e' = rhythmicityPolyWeightedLEF3 | c == 'd' || c == 'z' = rhythmicityPolyWeightedLEF30 | otherwise = rhythmicityPoly