{-# 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 :: (Double -> c)
-> String
-> (String -> Coeffs2 -> String -> Double)
-> Coeffs2
-> FuncRep2 String Double c
procRhythm23F Double -> c
h String
choice String -> Coeffs2 -> String -> Double
g Coeffs2
coeffs = (String -> Double) -> (Double -> c) -> FuncRep2 String Double c
forall a b c. (a -> b) -> (b -> c) -> FuncRep2 a b c
Phonetic.Languages.Basis.D (String -> Coeffs2 -> String -> Double
g String
choice Coeffs2
coeffs) Double -> c
h
{-# INLINE procRhythm23F #-}

parseChRhEndMaybe :: ParseChRh -> Maybe Int
parseChRhEndMaybe :: ParseChRh -> Maybe Int
parseChRhEndMaybe (P0 String
_) = Maybe Int
forall a. Maybe a
Nothing
parseChRhEndMaybe (P1 Choices
_ RhythmBasis
_ Int
n) = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
n
parseChRhEndMaybe (P2 PolyChoices
_ PolyRhythmBasis
_ Int
_ Int
n) = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
n

eval23Coeffs :: Coeffs2 -> [Double] -> Double
eval23Coeffs :: Coeffs2 -> [Double] -> Double
eval23Coeffs (CF2 Maybe Double
x Maybe Double
y) = Double -> Double -> [Double] -> Double
forall a. (RealFrac a, Floating a) => a -> a -> [a] -> a
evalRhythmicity23K (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
x) (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
y)
eval23Coeffs Coeffs2
CF0 = [Double] -> Double
forall a. (RealFrac a, Floating a) => [a] -> a
evalRhythmicity23
{-# INLINE eval23Coeffs #-}

eval23CoeffsF :: Double -> Coeffs2 -> [Double] -> Double
eval23CoeffsF :: Double -> Coeffs2 -> [Double] -> Double
eval23CoeffsF Double
k (CF2 Maybe Double
x Maybe Double
y) = Double -> Double -> Double -> [Double] -> Double
forall a. (RealFrac a, Floating a) => a -> a -> a -> [a] -> a
evalRhythmicity23KF Double
k (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
x) (Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
1.0 Maybe Double
y)
eval23CoeffsF Double
k Coeffs2
CF0 = Double -> [Double] -> Double
forall a. (RealFrac a, Floating a) => a -> [a] -> a
evalRhythmicity23F Double
k
{-# INLINE eval23CoeffsF #-}

data CoeffTwo a = CF0 | CF2 (Maybe a) (Maybe a) deriving (CoeffTwo a -> CoeffTwo a -> Bool
(CoeffTwo a -> CoeffTwo a -> Bool)
-> (CoeffTwo a -> CoeffTwo a -> Bool) -> Eq (CoeffTwo a)
forall a. Eq a => CoeffTwo a -> CoeffTwo a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CoeffTwo a -> CoeffTwo a -> Bool
$c/= :: forall a. Eq a => CoeffTwo a -> CoeffTwo a -> Bool
== :: CoeffTwo a -> CoeffTwo a -> Bool
$c== :: forall a. Eq a => CoeffTwo a -> CoeffTwo a -> Bool
Eq)

isEmpty :: CoeffTwo a -> Bool
isEmpty :: CoeffTwo a -> Bool
isEmpty CoeffTwo a
CF0 = Bool
True
isEmpty CoeffTwo a
_ = Bool
False

isPair :: CoeffTwo a -> Bool
isPair :: CoeffTwo a -> Bool
isPair CoeffTwo a
CF0 = Bool
False
isPair CoeffTwo a
_ = Bool
True

fstCF :: CoeffTwo a -> Maybe a
fstCF :: CoeffTwo a -> Maybe a
fstCF (CF2 Maybe a
x Maybe a
_) = Maybe a
x
fstCF CoeffTwo a
_ = Maybe a
forall a. Maybe a
Nothing

sndCF :: CoeffTwo a -> Maybe a
sndCF :: CoeffTwo a -> Maybe a
sndCF (CF2 Maybe a
_ Maybe a
y) = Maybe a
y
sndCF CoeffTwo a
_ = Maybe a
forall a. Maybe a
Nothing

readCF :: String -> Coeffs2
readCF :: String -> Coeffs2
readCF String
xs
  | (Char -> Bool) -> String -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_') String
xs = let (!Maybe Double
ys,!Maybe Double
zs) = (\(String
ks,String
ts) -> (String -> Maybe Double
forall a. Read a => String -> Maybe a
readMaybe String
ks::Maybe Double,String -> Maybe Double
forall a. Read a => String -> Maybe a
readMaybe (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 String
ts)::Maybe Double)) ((String, String) -> (Maybe Double, Maybe Double))
-> (String -> (String, String))
-> String
-> (Maybe Double, Maybe Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_') (String -> (Maybe Double, Maybe Double))
-> String -> (Maybe Double, Maybe Double)
forall a b. (a -> b) -> a -> b
$ String
xs in
     if (Maybe Double -> Bool
forall a. Maybe a -> Bool
isNothing Maybe Double
ys Bool -> Bool -> Bool
&& Maybe Double -> Bool
forall a. Maybe a -> Bool
isNothing Maybe Double
zs) then Coeffs2
forall a. CoeffTwo a
CF0 else Maybe Double -> Maybe Double -> Coeffs2
forall a. Maybe a -> Maybe a -> CoeffTwo a
CF2 Maybe Double
ys Maybe Double
zs
  | Bool
otherwise = Coeffs2
forall a. CoeffTwo a
CF0

type Coeffs2 = CoeffTwo Double

--------------------------------------------------------------------------------------------

eval23 :: [[Double]] -> Double
eval23 = [Double] -> Double
forall a. (RealFrac a, Floating a) => [a] -> a
evalRhythmicity23 ([Double] -> Double)
-> ([[Double]] -> [Double]) -> [[Double]] -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Double]] -> [Double]
forall a. Monoid a => [a] -> a
mconcat
{-# INLINE eval23 #-}

eval23K :: c -> c -> [[c]] -> c
eval23K c
k2 c
k3 = c -> c -> [c] -> c
forall a. (RealFrac a, Floating a) => a -> a -> [a] -> a
evalRhythmicity23K c
k2 c
k3 ([c] -> c) -> ([[c]] -> [c]) -> [[c]] -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[c]] -> [c]
forall a. Monoid a => [a] -> a
mconcat
{-# INLINE eval23K #-}

eval23F :: c -> [[c]] -> c
eval23F c
k = c -> [c] -> c
forall a. (RealFrac a, Floating a) => a -> [a] -> a
evalRhythmicity23F c
k ([c] -> c) -> ([[c]] -> [c]) -> [[c]] -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[c]] -> [c]
forall a. Monoid a => [a] -> a
mconcat
{-# INLINE eval23F #-}

eval23KF :: c -> c -> c -> [[c]] -> c
eval23KF c
k c
k2 c
k3 = c -> c -> c -> [c] -> c
forall a. (RealFrac a, Floating a) => a -> a -> a -> [a] -> a
evalRhythmicity23KF c
k c
k2 c
k3 ([c] -> c) -> ([[c]] -> [c]) -> [[c]] -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[c]] -> [c]
forall a. Monoid a => [a] -> a
mconcat
{-# INLINE eval23KF #-}

words1 :: [a] -> [[a]]
words1 [a]
xs = if [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
ts then [] else [a]
w [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: [a] -> [[a]]
words1 [a]
s'' -- Practically this is an optimized versio>
  where ts :: [a]
ts = (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
1) [a]
xs
        ([a]
w, [a]
s'') = (a -> Bool) -> [a] -> ([a], [a])
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
0) [a]
ts
{-# NOINLINE words1 #-}