{-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Phladiprelio.Ukrainian.Common -- Copyright : (c) Oleksandr Zhabenko 2020-2023 -- License : MIT -- Stability : Experimental -- Maintainer : oleksandr.zhabenko@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 NoImplicitPrelude, BangPatterns #-} module Phladiprelio.Ukrainian.Common where import GHC.Base import GHC.List import Phladiprelio.Basis import Phladiprelio.Rhythmicity.Simple import Phladiprelio.Rhythmicity.Factor import Data.Maybe (fromMaybe,isNothing) import Phladiprelio.Rhythmicity.PolyRhythm import Text.Read (readMaybe) import Phladiprelio.Coeffs procRhythm23F :: (Ord c) => (Double -> c) -> String -> (String -> Coeffs2 -> String -> Double) -> Coeffs2 -> FuncRep2 String Double c procRhythm23F h choice g coeffs = Phladiprelio.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 :: Factors -> Double -> Coeffs2 -> [Double] -> Double eval23CoeffsF ff k (CF2 x y) = evalRhythmicity23KF ff k (fromMaybe 1.0 x) (fromMaybe 1.0 y) eval23CoeffsF ff k CF0 = evalRhythmicity23F ff k {-# INLINE eval23CoeffsF #-} -------------------------------------------------------------------------------------------- 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 #-} words1 xs = if null ts then [] else w : words1 s'' -- Is inspired by Data.List.words function. where ts = dropWhile (> 99) xs (w, s'') = span (< 100) ts {-# NOINLINE words1 #-}