{-# LANGUAGE BangPatterns, NoImplicitPrelude #-} {-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Phladiprelio.Rhythmicity.Simple -- Copyright : (c) Oleksandr Zhabenko 2020-2023 -- License : MIT -- Stability : Experimental -- Maintainer : oleksandr.zhabenko@yahoo.com -- -- Allows to evaluate (approximately, so better to say, to estimate) the -- rhythmicity properties for the text (usually, the poetic one). module Phladiprelio.Rhythmicity.Simple where import GHC.Base import GHC.Int import GHC.Num ((+),(-),(*),abs) import GHC.Real import GHC.Float import GHC.List -- | Is well defined just for positive values in the list. maxPosition2 :: (RealFrac a) => [a] -> a maxPosition2 xs | null xs = 0.0 | otherwise = maxP21 xs 0 where maxP21 (x:ks@(y:t:ys)) !acc1 | (x - y) * (t - y) <= 0 = maxP21 ks (acc1::Int16) | otherwise = maxP21 ks ((acc1 + 1)::Int16) maxP21 _ !acc1 = fromIntegral acc1 posMaxIn3 :: (Ord a) => a -> a -> a -> Int16 posMaxIn3 x y z | x < y = if y < z then 3 else 2 | x < z = 3 | otherwise = 1 maxPosition3 :: RealFrac a => [a] -> a maxPosition3 xs | null xs = 0.0 | otherwise = fromIntegral (go (h xs) ((0, 0, 0)::(Int16,Int16,Int16))) where h (x:y:z:ys) = posMaxIn3 x y z:h ys h _ = [] go (x:zs) (!acc21,!acc22,!acc23) = go zs (h1 x (acc21,acc22,acc23)) go _ (!acc21,!acc22,!acc23) | acc21 > acc22 = if acc21 > acc23 then acc21 else acc23 | acc22 > acc23 = acc22 | otherwise = acc23 h1 !x (!t,!u,!w) | x == 1 = (t + (1::Int16), u, w) | x == 2 = (t, u + (1::Int16), w) | otherwise = (t,u,w + (1::Int16)) evalRhythmicity23 :: (RealFrac a, Floating a) => [a] -> a evalRhythmicity23 xs = maxPosition2 xs + maxPosition3 xs evalRhythmicity23K :: (RealFrac a, Floating a) => a -> a -> [a] -> a evalRhythmicity23K k2 k3 xs = k2 * maxPosition2 xs + k3 * maxPosition3 xs