{-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Phonetic.Languages.Array.Ukrainian.Common -- Copyright : (c) OleksandrZhabenko 2020-2022 -- 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. {-# LANGUAGE CPP, BangPatterns #-} module Phonetic.Languages.Array.Ukrainian.Common 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 Phonetic.Languages.Basis import Languages.Rhythmicity import Languages.Rhythmicity.Factor import Data.Maybe (fromMaybe,isNothing) import Rhythmicity.PolyRhythm import Text.Read (readMaybe) #ifdef __GLASGOW_HASKELL__ #if __GLASGOW_HASKELL__==708 /* code that applies only to GHC 7.8.* */ mconcat = concat #endif #endif procRhythm23F :: (Ord c) => (Double -> c) -> String -> (String -> Coeffs2 -> String -> Double) -> Coeffs2 -> FuncRep2 String Double c procRhythm23F h choice g coeffs = Phonetic.Languages.Basis.D (g choice coeffs) h {-# INLINE procRhythm23F #-} parseChRhEndMaybe :: ParseChRh -> Maybe Int parseChRhEndMaybe (P0 _) = Nothing parseChRhEndMaybe (P1 _ _ n) = Just n parseChRhEndMaybe (P2 _ _ _ n) = Just n eval23Coeffs :: Coeffs2 -> [Double] -> Double eval23Coeffs (CF2 x y) = evalRhythmicity23K (fromMaybe 1.0 x) (fromMaybe 1.0 y) eval23Coeffs CF0 = evalRhythmicity23 {-# INLINE eval23Coeffs #-} eval23CoeffsF :: Double -> Coeffs2 -> [Double] -> Double eval23CoeffsF k (CF2 x y) = evalRhythmicity23KF k (fromMaybe 1.0 x) (fromMaybe 1.0 y) eval23CoeffsF k CF0 = evalRhythmicity23F k {-# INLINE eval23CoeffsF #-} 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 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 #-} words1 xs = if null ts then [] else w : words1 s'' -- Practically this is an optimized versio> where ts = dropWhile (< 1) xs (w, s'') = span (> 0) ts {-# NOINLINE words1 #-}