{-# LANGUAGE BangPatterns #-} {-# LANGUAGE MultiWayIf #-} {-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Rhythmicity.PolyRhythm -- Copyright : (c) OleksandrZhabenko 2021 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- The module is highly experimental approach to estimate further the rhythmicity (using some extent of the -- music concept of polyrhythm) of the not very long lists (well, not longer than e. g. 30 elements). -- Is rather computationally expensive, so must be used with caution. If the period -- of rhythm is less than 5 or even 6 it is not effective. module Rhythmicity.PolyRhythm where import Data.List (sort) import Data.Maybe (fromJust,fromMaybe) import Data.Char (toLower,isDigit) import GHC.Float (int2Double) import qualified Rhythmicity.TwoFourth as TF import Text.Read (readMaybe) data Marker4s = D | E | F | G deriving (Eq,Ord,Show) newtype PolyMarkers = PolyMs Char deriving (Eq,Ord) instance Show PolyMarkers where show (PolyMs c) = 'P':' ':[toLower c] data PolyMrks = R4 Marker4s | RP PolyMarkers deriving (Eq,Ord,Show) is4s :: PolyMrks -> Bool is4s (R4 _) = True is4s _ = False isPoly :: PolyMrks -> Bool isPoly (RP _) = True isPoly _ = False {-| Data to specify some quantitative information of the structure of rhythmicity. -} data PolyRhythmBasis = PolyRhythm [Int] deriving (Eq,Show) vals :: PolyRhythmBasis -> [Int] vals (PolyRhythm xs) = xs {-| Data to specify (mostly) the qualitative information of the structure of rhythmicity. -} data PolyChoices = PolyCh { xn :: [Bool], -- ^ the 'True' corresponds to maximums, 'False' -- to minimums pqty :: Int -- ^ general quantity of the elements to be taken as one period. Must be not less than the sum of 'cheis' and 'chbis'. Symbolically, it must be 'sum' . 'vals' . 'PolyRhythm' $ ['Int'] = 'PolyCh' 'pqty'. } deriving Eq {-| The predicate to check whether the two given arguments can be used together to get meaningful results. -} validPolyChRhPair :: PolyChoices -> PolyRhythmBasis -> Bool validPolyChRhPair (PolyCh xs n) (PolyRhythm ys) | ks <= [0] = False | any (<0) rs = False | length xs < n && drop l ys > [0] && l == length xs = n == sum ys | otherwise = False where (ks,rs) = splitAt 1 ys l = length ys - 1 data Intermediate a = J a | I PolyMarkers deriving (Eq, Ord) isJI :: Intermediate a -> Bool isJI (J _) = True isJI _ = False fromIntermediate :: Intermediate a -> Maybe PolyMrks fromIntermediate (I k) = Just (RP k) fromIntermediate _ = Nothing getPolyChRhData :: (Ord a) => Char -- ^ The start of the 'RP' 'PolyMarkers' count in case of 'PolyMrks' with 'Char's. The usual one can be \'a\' or \'h\'. -> Int -- ^ If the argument is less or equal to 4, then 'Marker4s' is used, if it is greater than 4, then 'PolyMarkers' is used. -> PolyChoices -> PolyRhythmBasis -> [a] -> [[PolyMrks]] getPolyChRhData c r choice@(PolyCh ts l1) rhythm@(PolyRhythm ys) xs | r <= 4 && validPolyChRhPair choice rhythm = map (g4 choice rhythm) . f choice $ xs | r > 4 && validPolyChRhPair choice rhythm = map (\ks -> map (fromJust . fromIntermediate) . gPoly [c..] choice rhythm ks . map J $ ks) . f choice $ xs | otherwise = error "Rhythmicity.PolyRhythm.getPolyChRhData: the first two arguments cannot be used together to get some meaningful result. " where g4 (PolyCh js l) (PolyRhythm ys) us = let ws = sort us in case (ys,js) of (x1:x2:x3:zs,[False,False,False]) -> let !k1 = ws !! (x1 - 1) !k2 = ws !! (x1 + x2 - 1) !k3 = ws !! (x1 + x2 + x3 - 1) in map (\t -> if | t <= k1 -> R4 D | x2 == 0 -> R4 G | t <= k2 -> R4 E | x3 == 0 -> R4 G | t <= k3 -> R4 F | otherwise -> R4 G) us (x1:x2:x3:zs,[True,False,False]) -> let !k1 = ws !! (length ws - x1) !k2 | x2 < 2 = head ws | otherwise = ws !! (x2 - 1) !k3 | x2 == 0 = head ws | otherwise = ws !! (x2 + x3 - 1) in map (\t -> if | t >= k1 -> R4 D | x2 == 0 -> R4 G | t <= k2 -> R4 E | x3 == 0 -> R4 G | t <= k3 -> R4 F | otherwise -> R4 G) us (x1:x2:x3:zs,[False,True,False]) -> let !k1 = ws !! (x1 - 1) !k2 | x2 == 0 = last ws | otherwise = ws !! (length ws - x2) !k3 = ws !! (x1 + x3 - 1) in map (\t -> if | t <= k1 -> R4 D | x2 == 0 -> R4 G | t >= k2 -> R4 E | x3 == 0 -> R4 G | t <= k3 -> R4 F | otherwise -> R4 G) us (x1:x2:x3:zs,[False,False,True]) -> let !k1 = ws !! (x1 - 1) !k2 = ws !! (x1 + x2 - 1) !k3 | x3 == 0 = last ws | otherwise = ws !! (length ws - x3) in map (\t -> if | t <= k1 -> R4 D | x2 == 0 -> R4 G | t <= k2 -> R4 E | x3 == 0 -> R4 G | t >= k3 -> R4 F | otherwise -> R4 G) us (x1:x2:x3:zs,[True,True,False]) -> let !k1 = ws !! (length ws - x1) !k2 = ws !! (length ws - x1 - x2 - 1) !k3 | x3 == 0 = head ws | otherwise = ws !! (x3 - 1) in map (\t -> if | t >= k1 -> R4 D | x2 == 0 -> R4 G | t >= k2 -> R4 E | x3 == 0 -> R4 G | t <= k3 -> R4 F | otherwise -> R4 G) us (x1:x2:x3:zs,[True,False,True]) -> let !k1 = ws !! (length ws - x1) !k2 | x2 == 0 = head ws | otherwise = ws !! (x2 - 1) !k3 = ws !! (length ws - x1 - x3) in map (\t -> if | t >= k1 -> R4 D | x2 == 0 -> R4 G | t <= k2 -> R4 E | x3 == 0 -> R4 G | t >= k3 -> R4 F | otherwise -> R4 G) us (x1:x2:x3:zs,[False,True,True]) -> let !k1 = ws !! (x1 - 1) !k2 | x2 == 0 = last ws | otherwise = ws !! (length ws - x2) !k3 | x2 == 0 = last ws | otherwise = ws !! (length ws - x2 - x3) in map (\t -> if | t <= k1 -> R4 D | x2 == 0 -> R4 G | t >= k2 -> R4 E | x3 == 0 -> R4 G | t >= k3 -> R4 F | otherwise -> R4 G) us (x1:x2:x3:zs,[_,_,_]) -> let !k1 = ws !! (length ws - x1) !k2 = ws !! (length ws - x1 - x2) !k3 = ws !! (length ws - x1 - x2 - x3) in map (\t -> if | t >= k1 -> R4 D | x2 == 0 -> R4 G | t >= k2 -> R4 E | x3 == 0 -> R4 G | t >= k3 -> R4 F | otherwise -> R4 G) us gPoly wws (PolyCh (j:js) l) (PolyRhythm (y:ys)) vs us | null vs = map (\r -> if | isJI r -> (\q@(J rr) -> I (PolyMs (head wws))) r | otherwise -> r) us | y == 0 = map (\r -> if | isJI r -> (\q@(J rr) -> I (PolyMs (head wws))) r | otherwise -> r) us | otherwise = let ws = sort vs in case j of False -> let !k = ws !! (y - 1) in gPoly (drop 1 wws) (PolyCh js l) (PolyRhythm ys) (filter (> k) vs) (map (\r -> if | isJI r -> (\q@(J rr) -> if | rr <= k -> I (PolyMs (head wws)) | otherwise -> q) r | otherwise -> r) us) _ -> let !k = ws !! (length ws - y) in gPoly (drop 1 wws) (PolyCh js l) (PolyRhythm ys) (filter (< k) vs) (map (\r -> if | isJI r -> (\q@(J rr) -> if | rr >= k -> I (PolyMs (head wws)) | otherwise -> q) r | otherwise -> r) us) gPoly wws (PolyCh [] l) _ vs us = map (\r -> if isJI r then I (PolyMs (head wws)) else r) us f ch@(PolyCh _ l1) ys@(_:_) = let !q = length ys `quot` l1 rs = take (q * l1) ys in f' ch rs f' ch@(PolyCh _ l1) qs@(_:_) = let (ts,zs) = splitAt l1 qs in ts : f' ch zs f' _ [] = [] increasingF :: Int -> Double -> Double increasingF n x | n <= 0 || x < 0 = error $ "Rhythmicity.PolyRhythm.increasingF: not defined for the arguments. " ++ show n ++ " " ++ show x | x == 0.0 = 0.001 | n == 1 = x + min (x * 0.25) 0.125 | x < 1 = x ** (1.0 / int2Double n) | x <= 1.1 = x + 1.0 / int2Double n | otherwise = x ^ n {-# INLINE increasingF #-} increasingF1 :: Int -> Double -> Double increasingF1 n x | n <= 0 = error $ "Rhythmicity.PolyRhythm.increasingF1: not defined for the argument. " ++ show n | otherwise = x + int2Double n {-# INLINE increasingF1 #-} increasingFG :: Int -> Double -> (Int -> Double -> Double -> Double) -> Double -> Double increasingFG n k f x | n <= 0 = error $ "Rhythmicity.PolyRhythm.increasingFG: not defined for the argument. " ++ show n | otherwise = x + abs (f n k x) {-# INLINE increasingFG #-} decreasingF1 :: Int -> Double -> Double decreasingF1 n x | n <= 0 = error $ "Rhythmicity.PolyRhythm.decreasingF1: not defined for the argument. " ++ show n | otherwise = x - int2Double n {-# INLINE decreasingF1 #-} decreasingFG :: Int -> Double -> (Int -> Double -> Double -> Double) -> Double -> Double decreasingFG n k f x | n <= 0 = error $ "Rhythmicity.PolyRhythm.decreasingFG: not defined for the argument. " ++ show n | otherwise = x - abs (f n k x) {-# INLINE decreasingFG #-} decreasingFG2 :: Int -> Double -> (Double -> Double -> Double) -> Double -> Double decreasingFG2 n k f x | n <= 0 = error $ "Rhythmicity.PolyRhythm.decreasingFG2: not defined for the argument. " ++ show n | otherwise = x - int2Double n * abs (f k x) {-# INLINE decreasingFG2 #-} increasingFG2 :: Int -> Double -> (Double -> Double -> Double) -> Double -> Double increasingFG2 n k f x | n <= 0 = error $ "Rhythmicity.PolyRhythm.increasingFG2: not defined for the argument. " ++ show n | otherwise = x + int2Double n * abs (f k x) {-# INLINE increasingFG2 #-} decreasingF :: Int -> Double -> Double decreasingF n x | n <= 0 || x < 0 = error $ "Rhythmicity.PolyRhythm.decreasingF: not defined for the arguments. " ++ show n ++ " " ++ show x | x == 0.0 = 0.000000000001 | n == 1 = x - min (x * 0.25) 0.125 | x < 1 = x ** int2Double n | x <= 1.1 = 1.0 / (x + 1.0 / int2Double n) | otherwise = x ** (1.0 / int2Double n) {-# INLINE decreasingF #-} similarityF1 :: Char -- ^ The start of the counting. -> PolyMrks -> PolyMrks -> Double -- ^ The initial value. -> Double similarityF1 c m1 m2 x0 | is4s m1 = if | m1 == m2 -> case (\(R4 t0) -> t0) m1 of D -> increasingF1 4 x0 E -> increasingF1 3 x0 F -> increasingF1 2 x0 _ -> increasingF1 1 x0 | otherwise -> case (\(R4 t0) -> t0) . min m1 $ m2 of D -> decreasingF1 4 x0 E -> decreasingF1 3 x0 F -> decreasingF1 2 x0 _ -> decreasingF1 1 x0 | otherwise = let n = length [c..(\(RP (PolyMs t0)) -> t0) (min m1 m2)] in if | m1 == m2 -> increasingF1 n x0 | otherwise -> decreasingF1 n x0 {-# INLINE similarityF1 #-} {-| The more straightforward variant of the 'similarityF1' function. -} similarityF0 :: Char -- ^ The start of the counting. -> PolyMrks -> PolyMrks -> Double -- ^ The initial value. -> Double similarityF0 c m1 m2 x0 | is4s m1 = if | m1 == m2 -> case (\(R4 t0) -> t0) m1 of D -> increasingF1 4 x0 E -> increasingF1 3 x0 F -> increasingF1 2 x0 _ -> increasingF1 1 x0 | otherwise -> x0 | otherwise = let n = length [c..(\(RP (PolyMs t0)) -> t0) (min m1 m2)] in if | m1 == m2 -> increasingF1 n x0 | otherwise -> x0 {-# INLINE similarityF0 #-} {-| The function that uses a simple arithmetic logics to calculate the similarity of the two equal by length (if not they are truncated to the least one) lists of 'PolyMrks'. Uses both increasing and decreasing functions. -} similarityLogics :: Char -- ^ The start of the counting. -> Double -- ^ An initial value. -> [PolyMrks] -> [PolyMrks] -> Double -- ^ In case of positive previous 'Double' arguments this is a positive value. The greater one corresponds to (probably) more rhythmic list. similarityLogics c x0 (x:xs) (y:ys) = similarityLogics c (similarityF1 c x y x0) xs ys similarityLogics c x0 _ _ = x0 {-| The more straightforward variant of the 'similarityLogics' function. -} similarityLogics0 :: Char -- ^ The start of the counting. -> Double -- ^ An initial value. -> [PolyMrks] -> [PolyMrks] -> Double -- ^ In case of positive previous 'Double' arguments this is a positive value. The greater one corresponds to (probably) more rhythmic list. similarityLogics0 c x0 (x:xs) (y:ys) = similarityLogics0 c (similarityF0 c x y x0) xs ys similarityLogics0 c x0 _ _ = x0 {-| The function that uses a simple arithmetic logics to calculate the similarity of the two equal by length (if not they are truncated to the least one) lists of 'PolyMrks'. Uses 'similarityLogics' inside. -} similarityPoly :: Char -- ^ The start of the counting. -> Double -- ^ The initial value starting from which it counts. Usually, equals to 1.0. -> [[PolyMrks]] -> Double -- ^ In case of positive previous 'Double' arguments this is a positive value. The greater one corresponds to (probably) more rhythmic list. similarityPoly c z (xs:ys:xss) = similarityPoly c (z * similarityLogics c z xs ys) (ys:xss) similarityPoly _ z _ = z {-| The function that uses a simple arithmetic logics to calculate the similarity of the two equal by length (if not they are truncated to the least one) lists of 'PolyMrks'. Uses 'similarityLogics0' inside. The more straightforward variant of the 'similarityPoly' function. -} similarityPoly0 :: Char -- ^ The start of the counting. -> Double -- ^ The initial value starting from which it counts. Usually, equals to 1.0. -> [[PolyMrks]] -> Double -- ^ In case of positive previous 'Double' arguments this is a positive value. The greater one corresponds to (probably) more rhythmic list. similarityPoly0 c z (xs:ys:xss) = similarityPoly0 c (z * similarityLogics0 c z xs ys) (ys:xss) similarityPoly0 _ z _ = z {-| General function to estimate the inner rhythmicity of the 'Ord'ered list of values. For many cases its arguments can be guessed or approximated by some reasonable values. Nevertheless, it is a highly experimental one. -} rhythmicityPoly :: (Ord a) => Double -- ^ The initial value starting from which it counts. Usually, equals to 1.0. -> Int -- ^ If the argument is less or equal to 4, then 'Marker4s' is used, if it is greater than 4, then 'PolyMarkers' is used. -> PolyChoices -> PolyRhythmBasis -> [a] -> Double -- ^ In case of positive previous 'Double' arguments this is a positive value. The greater one corresponds to (probably) more rhythmic list. rhythmicityPoly x0 r choices rhythm = similarityPoly 'a' x0 . getPolyChRhData 'a' r choices rhythm {-# INLINE rhythmicityPoly #-} {-| General function to estimate the inner rhythmicity of the 'Ord'ered list of values. For many cases its arguments can be guessed or approximated by some reasonable values. Nevertheless, it is a highly experimental one. The more straightforward variant of the 'rhythmicityPoly' function. -} rhythmicityPoly0 :: (Ord a) => Double -- ^ The initial value starting from which it counts. Usually, equals to 1.0. -> Int -- ^ If the argument is less or equal to 4, then 'Marker4s' is used, if it is greater than 4, then 'PolyMarkers' is used. -> PolyChoices -> PolyRhythmBasis -> [a] -> Double -- ^ In case of positive previous 'Double' arguments this is a positive value. The greater one corresponds to (probably) more rhythmic list. rhythmicityPoly0 x0 r choices rhythm = similarityPoly0 'a' x0 . getPolyChRhData 'a' r choices rhythm {-# INLINE rhythmicityPoly0 #-} ------------------------------------------------------------------- {-| Data type that is used to implement some parameter language to encode in the 'String' argument information that is sufficient to transform the 'String' into 'Double' using the needed additional information provided by some other means. -} data ParseChRh = P0 String | P1 TF.Choices TF.RhythmBasis Int -- ^ The number of the one of the functions to convert the phonetic languages elements into 'Double' values (usually, durations). | P2 PolyChoices PolyRhythmBasis Int -- ^ The value for the 'Int' parameter in the 'getPolyChRhData' function that uses two previous arguments. Int -- ^ The number of the one of the functions to convert the phonetic languages elements into 'Double' values (usually, durations). deriving Eq isChRhString :: ParseChRh -> Bool isChRhString (P0 _) = True isChRhString _ = False isChRh3 :: ParseChRh -> Bool isChRh3 (P1 _ _ _) = True isChRh3 _ = False isChRhPoly :: ParseChRh -> Bool isChRhPoly (P2 _ _ _ _) = True isChRhPoly _ = False {-| A parser function to get the 'ParseChRh' data. In case of success returns 'Just' 'ParseChRh' value. Nevertheless, the further checks (e. g. 'validPolyChRhPair' or 'validChRhPair') is not applied by it, so they must be applied further during the usage. Examples of the usage: \"c114+112=2\" returns 'Just' @P1 (Ch 1 1 4) (Rhythm 1 1 2) 2@ \"ctttff7+112111=7*3\" returns 'Just' @P2 (PolyCh [True,True,True,False,False] 7) (PolyRhythm [1,1,2,1,1,1]) 7 3@. -} readRhythmicity :: String -> Maybe ParseChRh readRhythmicity ys@(x:xs) | x == 'c' && not (null xs) = if | isDigit . head $ xs -> let x = readMaybe (take 1 ts)::Maybe Int y = readMaybe (drop 1 . take 2 $ ts)::Maybe Int z = readMaybe (drop 2 ts)::Maybe Int ch = case (x,y,z) of (Just x1, Just y1, Just z1) -> Just (TF.Ch x1 y1 z1) _ -> Nothing x2 = readMaybe (take 1 ws)::Maybe Int y2 = readMaybe (drop 1 . take 2 $ ws)::Maybe Int z2 = readMaybe (drop 2 ws)::Maybe Int rh = case (x2,y2,z2) of (Just x3, Just y3, Just z3) -> Just (TF.Rhythm x3 y3 z3) _ -> Nothing n = readMaybe ks::Maybe Int in case (ch,rh,n) of (Just ch1,Just rh1,Just n1) -> Just . P1 ch1 rh1 $ f n1 _ -> Just . P0 $ ys | head xs == 't' || head xs == 'f' -> let z = readMaybe qs::Maybe Int ch = case z of Just z1 -> Just (PolyCh rs z1) _ -> Nothing n = readMaybe ps::Maybe Int m = readMaybe ms::Maybe Int in case (ch,n,m) of (Just ch1,Just n1,Just m1) -> Just . P2 ch1 (PolyRhythm vs) n1 $ f m1 _ -> Just . P0 $ ys | otherwise -> Just . P0 $ ys | otherwise = Just . P0 $ ys where (ts, us) = break (== '+') xs (ws,zs) = break (== '=') . drop 1 $ us ks = drop 1 zs (ps,ns) = break (== '*') ks ms = drop 1 ns vs = map (fromMaybe 0 . (\t -> readMaybe t::Maybe Int) . (:[])) ws (ls,qs) = break isDigit ts rs = map (\t -> if t == 't' then True else False) ls f k | k `rem` 4 < 0 = 5 + (k `rem` 4) | otherwise = 1 + (k `rem` 4)