{-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Phonetic.Languages.Array.General.PropertiesSyllablesG2 -- Copyright : (c) OleksandrZhabenko 2020-2021 -- 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 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 Phonetic.Languages.Array.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 CPP, BangPatterns #-} module Phonetic.Languages.Array.General.PropertiesSyllablesG2 ( -- * Newtype to work with CoeffTwo(..) , Coeffs2 , isEmpty , isPair , fstCF , sndCF , readCF -- * Rhythmicity properties (semi-empirical) -- ** Simple one , rhythmicity0i , rhythmicity0Fi -- ** With weight coefficients , rhythmicityKi , rhythmicityKFi -- * General , rhythmicityG , rhythmicity ) 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 Languages.Rhythmicity import Languages.Rhythmicity.Factor import Rhythmicity.TwoFourth import Data.Phonetic.Languages.Base import Data.Phonetic.Languages.Syllables import Data.Maybe (isNothing,fromMaybe) import Text.Read (readMaybe) #ifdef __GLASGOW_HASKELL__ #if __GLASGOW_HASKELL__==708 /* code that applies only to GHC 7.8.* */ mconcat = concat #endif #endif data CoeffTwo a = CF0 | CF2 (Maybe a) (Maybe a) deriving (Eq) isEmpty :: CoeffTwo a -> Bool isEmpty CF0 = True isEmpty _ = False isPair :: CoeffTwo a -> Bool isPair CF0 = False isPair _ = True fstCF :: CoeffTwo a -> Maybe a fstCF (CF2 x _) = x fstCF _ = Nothing sndCF :: CoeffTwo a -> Maybe a sndCF (CF2 _ y) = y sndCF _ = Nothing readCF :: String -> Coeffs2 readCF xs | any (== '_') xs = let (!ys,!zs) = (\(ks,ts) -> (readMaybe ks::Maybe Double,readMaybe (drop 1 ts)::Maybe Double)) . break (== '_') $ xs in if (isNothing ys && isNothing zs) then CF0 else CF2 ys zs | otherwise = CF0 -- | A data type that is used to represent the coefficients of the rhythmicity functions as a one argument value. type Coeffs2 = CoeffTwo Double -------------------------------------------------------------------------------------------- eval23 = evalRhythmicity23 . mconcat {-# INLINE eval23 #-} eval23K k2 k3 = evalRhythmicity23K k2 k3 . mconcat {-# INLINE eval23K #-} eval23F k = evalRhythmicity23F k . mconcat {-# INLINE eval23F #-} eval23KF k k2 k3 = evalRhythmicity23KF k k2 k3 . mconcat {-# INLINE eval23KF #-} rhythmicityG :: ([[[PRS]]] -> [[Double]])-- ^ 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. -> 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 \'0\' symbol delimiter in the @ukrainian-phonetics-basic-array@ package. -> String -- ^ Corresponds to the \'1\' and \'-\' symbol delimiters in the @ukrainian-phonetics-basic-array@ package. -> String -> Double rhythmicityG f g wrs ks arr hs us vs xs | null xs = 0.0 | otherwise = g . f . createSyllablesPL wrs ks arr hs us vs $ xs {-# INLINE rhythmicityG #-} ------------------------------------------------------- rhythmicity0i :: ([[[PRS]]] -> [[Double]]) -- ^ A function that specifies the syllables durations, analogue of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. -> 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 \'0\' symbol delimiter in the @ukrainian-phonetics-basic-array@ package. -> String -- ^ Corresponds to the \'1\' and \'-\' symbol delimiters in the @ukrainian-phonetics-basic-array@ package. -> String -> Double rhythmicity0i f = rhythmicityG f eval23 {-# INLINE rhythmicity0i #-} ------------------------------------------------------- rhythmicityKi :: ([[[PRS]]] -> [[Double]]) -- ^ A function that specifies the syllables durations, analogue of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. -> Double -> Double -> 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 \'0\' symbol delimiter in the @ukrainian-phonetics-basic-array@ package. -> String -- ^ Corresponds to the \'1\' and \'-\' symbol delimiters in the @ukrainian-phonetics-basic-array@ package. -> String -> Double rhythmicityKi f k2 k3 = rhythmicityG f (eval23K k2 k3) {-# INLINE rhythmicityKi #-} -------------------------------------------------------- rhythmicity0Fi :: ([[[PRS]]] -> [[Double]]) -- ^ A function that specifies the syllables durations, analogue of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. -> Double -> 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 \'0\' symbol delimiter in the @ukrainian-phonetics-basic-array@ package. -> String -- ^ Corresponds to the \'1\' and \'-\' symbol delimiters in the @ukrainian-phonetics-basic-array@ package. -> String -> Double rhythmicity0Fi f k = rhythmicityG f (eval23F k) {-# INLINE rhythmicity0Fi #-} -------------------------------------------------------- rhythmicityKFi :: ([[[PRS]]] -> [[Double]]) -- ^ A function that specifies the syllables durations, analogue of the -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. -> Double -> Double -> Double -> 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 \'0\' symbol delimiter in the @ukrainian-phonetics-basic-array@ package. -> String -- ^ Corresponds to the \'1\' and \'-\' symbol delimiters in the @ukrainian-phonetics-basic-array@ package. -> String -> Double rhythmicityKFi f k k2 k3 = rhythmicityG f (eval23KF k k2 k3) {-# INLINE rhythmicityKFi #-} -------------------------------------------------------- -- | It is intended to provide different functions :: 'Double' -> 'String' -> ([[['PRS']]] -> [['Double']]) for at least the -- following values: \"0z\", \"02z\", \"03z\", \"04z\", \"0y\", \"02y\", \"03y\" and the default one for other variants. -- The \"z\"-line uses \'F\' functions. rhythmicity :: Double -> String -- ^ Is intended to be one of the following strings: \"02y\", \"02z\", \"03y\", \"03z\", \"04y\", \"04z\", -- \"0y\", \"0z\", \"y\", \"y0\", \"y2\", \"y3\", \"y4\", \"yy\", \"yy2\", \"yy3\", \"z\", \"z2\", \"z3\", \"z4\", -- \"zz\", \"zz2\", \"zz3\", \"zz4\" or some other one (that is the default one). Since the version 0.3.0.0 you -- can also use \"w\" or \"x\"-based lines. Specifies the applied properties -- to get the result. The \"z\"-line uses \'F\' functions. -> (Double -> String -> ([[[PRS]]] -> [[Double]]))-- ^ 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 -> 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 -> String -> Double rhythmicity k choice h CF0 | choice `elem` ["0z","02z","03z","04z"] = rhythmicity0Fi f k | take 1 choice == "w" = case choice of "w01" -> rhythmicityG f (rhythmicityABC0 1.0 2.0 0.125 (Ch 1 1 4) (Rhythm 1 1 2) . mconcat) "w02" -> rhythmicityG f (rhythmicityABC0 1.0 2.0 0.125 (Ch 1 1 4) (Rhythm 1 1 2) . mconcat) "w03" -> rhythmicityG f (rhythmicityABC0 1.0 2.0 0.125 (Ch 1 1 4) (Rhythm 1 1 2) . mconcat) "w04" -> rhythmicityG f (rhythmicityABC0 1.0 2.0 0.125 (Ch 1 1 4) (Rhythm 1 1 2) . mconcat) "w11" -> rhythmicityG f (rhythmicityABC0 1.0 2.0 0.125 (Ch 1 0 4) (Rhythm 2 1 1) . mconcat) "w12" -> rhythmicityG f (rhythmicityABC0 1.0 2.0 0.125 (Ch 1 0 4) (Rhythm 2 1 1) . mconcat) "w13" -> rhythmicityG f (rhythmicityABC0 1.0 2.0 0.125 (Ch 1 0 4) (Rhythm 2 1 1) . mconcat) "w14" -> rhythmicityG f (rhythmicityABC0 1.0 2.0 0.125 (Ch 1 0 4) (Rhythm 2 1 1) . mconcat) "w21" -> rhythmicityG f (rhythmicityABC0 1.0 2.0 0.125 (Ch 0 1 4) (Rhythm 1 2 1) . mconcat) "w22" -> rhythmicityG f (rhythmicityABC0 1.0 2.0 0.125 (Ch 0 1 4) (Rhythm 1 2 1) . mconcat) "w23" -> rhythmicityG f (rhythmicityABC0 1.0 2.0 0.125 (Ch 0 1 4) (Rhythm 1 2 1) . mconcat) "w24" -> rhythmicityG f (rhythmicityABC0 1.0 2.0 0.125 (Ch 0 1 4) (Rhythm 1 2 1) . mconcat) "w31" -> rhythmicityG f (rhythmicityABC0 1.0 2.0 0.125 (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) "w32" -> rhythmicityG f (rhythmicityABC0 1.0 2.0 0.125 (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) "w33" -> rhythmicityG f (rhythmicityABC0 1.0 2.0 0.125 (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) "w34" -> rhythmicityG f (rhythmicityABC0 1.0 2.0 0.125 (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) _ -> rhythmicityG f (rhythmicityABC0 1.0 2.0 0.125 (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) | take 1 choice == "x" = case choice of "x01" -> rhythmicityG f (rhythmicityABC 1.0 2.0 0.125 (Ch 1 1 4) (Rhythm 1 1 2) . mconcat) "x02" -> rhythmicityG f (rhythmicityABC 1.0 2.0 0.125 (Ch 1 1 4) (Rhythm 1 1 2) . mconcat) "x03" -> rhythmicityG f (rhythmicityABC 1.0 2.0 0.125 (Ch 1 1 4) (Rhythm 1 1 2) . mconcat) "x04" -> rhythmicityG f (rhythmicityABC 1.0 2.0 0.125 (Ch 1 1 4) (Rhythm 1 1 2) . mconcat) "x11" -> rhythmicityG f (rhythmicityABC 1.0 2.0 0.125 (Ch 1 0 4) (Rhythm 2 1 1) . mconcat) "x12" -> rhythmicityG f (rhythmicityABC 1.0 2.0 0.125 (Ch 1 0 4) (Rhythm 2 1 1) . mconcat) "x13" -> rhythmicityG f (rhythmicityABC 1.0 2.0 0.125 (Ch 1 0 4) (Rhythm 2 1 1) . mconcat) "x14" -> rhythmicityG f (rhythmicityABC 1.0 2.0 0.125 (Ch 1 0 4) (Rhythm 2 1 1) . mconcat) "x21" -> rhythmicityG f (rhythmicityABC 1.0 2.0 0.125 (Ch 0 1 4) (Rhythm 1 2 1) . mconcat) "x22" -> rhythmicityG f (rhythmicityABC 1.0 2.0 0.125 (Ch 0 1 4) (Rhythm 1 2 1) . mconcat) "x23" -> rhythmicityG f (rhythmicityABC 1.0 2.0 0.125 (Ch 0 1 4) (Rhythm 1 2 1) . mconcat) "x24" -> rhythmicityG f (rhythmicityABC 1.0 2.0 0.125 (Ch 0 1 4) (Rhythm 1 2 1) . mconcat) "x31" -> rhythmicityG f (rhythmicityABC 1.0 2.0 0.125 (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) "x32" -> rhythmicityG f (rhythmicityABC 1.0 2.0 0.125 (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) "x33" -> rhythmicityG f (rhythmicityABC 1.0 2.0 0.125 (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) "x34" -> rhythmicityG f (rhythmicityABC 1.0 2.0 0.125 (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) _ -> rhythmicityG f (rhythmicityABC 1.0 2.0 0.125 (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) | otherwise = rhythmicity0i f where f = h k choice rhythmicity k choice h (CF2 x y) | choice `elem` ["0z","02z","03z","04z"] = rhythmicityKFi f k (fromMaybe 1.0 x) (fromMaybe 1.0 y) | take 1 choice == "w" = case choice of "w01" -> rhythmicityG f (rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 1 1 4) (Rhythm 1 1 2) . mconcat) "w02" -> rhythmicityG f (rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 1 1 4) (Rhythm 1 1 2) . mconcat) "w03" -> rhythmicityG f (rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 1 1 4) (Rhythm 1 1 2) . mconcat) "w04" -> rhythmicityG f (rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 1 1 4) (Rhythm 1 1 2) . mconcat) "w11" -> rhythmicityG f (rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 1 0 4) (Rhythm 2 1 1) . mconcat) "w12" -> rhythmicityG f (rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 1 0 4) (Rhythm 2 1 1) . mconcat) "w13" -> rhythmicityG f (rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 1 0 4) (Rhythm 2 1 1) . mconcat) "w14" -> rhythmicityG f (rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 1 0 4) (Rhythm 2 1 1) . mconcat) "w21" -> rhythmicityG f (rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 0 1 4) (Rhythm 1 2 1) . mconcat) "w22" -> rhythmicityG f (rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 0 1 4) (Rhythm 1 2 1) . mconcat) "w23" -> rhythmicityG f (rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 0 1 4) (Rhythm 1 2 1) . mconcat) "w24" -> rhythmicityG f (rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 0 1 4) (Rhythm 1 2 1) . mconcat) "w31" -> rhythmicityG f (rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) "w32" -> rhythmicityG f (rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) "w33" -> rhythmicityG f (rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) "w34" -> rhythmicityG f (rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) _ -> rhythmicityG f (rhythmicityABC0 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) | take 1 choice == "x" = case choice of "x01" -> rhythmicityG f (rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 1 1 4) (Rhythm 1 1 2) . mconcat) "x02" -> rhythmicityG f (rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 1 1 4) (Rhythm 1 1 2) . mconcat) "x03" -> rhythmicityG f (rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 1 1 4) (Rhythm 1 1 2) . mconcat) "x04" -> rhythmicityG f (rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 1 1 4) (Rhythm 1 1 2) . mconcat) "x11" -> rhythmicityG f (rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 1 0 4) (Rhythm 2 1 1) . mconcat) "x12" -> rhythmicityG f (rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 1 0 4) (Rhythm 2 1 1) . mconcat) "x13" -> rhythmicityG f (rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 1 0 4) (Rhythm 2 1 1) . mconcat) "x14" -> rhythmicityG f (rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 1 0 4) (Rhythm 2 1 1) . mconcat) "x21" -> rhythmicityG f (rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 0 1 4) (Rhythm 1 2 1) . mconcat) "x22" -> rhythmicityG f (rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 0 1 4) (Rhythm 1 2 1) . mconcat) "x23" -> rhythmicityG f (rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 0 1 4) (Rhythm 1 2 1) . mconcat) "x24" -> rhythmicityG f (rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 0 1 4) (Rhythm 1 2 1) . mconcat) "x31" -> rhythmicityG f (rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) "x32" -> rhythmicityG f (rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) "x33" -> rhythmicityG f (rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) "x34" -> rhythmicityG f (rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) _ -> rhythmicityG f (rhythmicityABC 1.0 (fromMaybe 2.0 x) (fromMaybe 0.125 y) (Ch 0 0 4) (Rhythm 1 1 2) . mconcat) | otherwise = rhythmicityKi f (fromMaybe 1.0 x) (fromMaybe 1.0 y) where f = h k choice