{-# LANGUAGE CPP, BangPatterns #-}
module Languages.UniquenessPeriods.Vector.PropertiesSyllablesG (
CoeffTwo(..)
, Coeffs2
, isEmpty
, isPair
, fstCF
, sndCF
, readCF
, rhythmicity0
, rhythmicityV0
, rhythmicityVK
, rhythmicityK
, rhythmicity02
, rhythmicityV02
, rhythmicityVK2
, rhythmicityK2
, rhythmicity
, rhythmicityV
) 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 qualified Data.Vector as VB
import Languages.Rhythmicity
import Languages.Phonetic.Ukrainian.Syllable
import Data.Maybe (isNothing,fromMaybe)
import Text.Read (readMaybe)
#ifdef __GLASGOW_HASKELL__
#if __GLASGOW_HASKELL__==708
/* code that applies only to GHC 7.8.* */
mconcat = concat
#endif
#endif
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 Float
ys,!Maybe Float
zs) = (\(String
ks,String
ts) -> (String -> Maybe Float
forall a. Read a => String -> Maybe a
readMaybe String
ks::Maybe Float,String -> Maybe Float
forall a. Read a => String -> Maybe a
readMaybe (Int -> String -> String
forall a. Int -> [a] -> [a]
drop Int
1 String
ts)::Maybe Float)) ((String, String) -> (Maybe Float, Maybe Float))
-> (String -> (String, String))
-> String
-> (Maybe Float, Maybe Float)
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 Float, Maybe Float))
-> String -> (Maybe Float, Maybe Float)
forall a b. (a -> b) -> a -> b
$ String
xs in
if (Maybe Float -> Bool
forall a. Maybe a -> Bool
isNothing Maybe Float
ys Bool -> Bool -> Bool
&& Maybe Float -> Bool
forall a. Maybe a -> Bool
isNothing Maybe Float
zs) then Coeffs2
forall a. CoeffTwo a
CF0 else Maybe Float -> Maybe Float -> Coeffs2
forall a. Maybe a -> Maybe a -> CoeffTwo a
CF2 Maybe Float
ys Maybe Float
zs
| Bool
otherwise = Coeffs2
forall a. CoeffTwo a
CF0
type Coeffs2 = CoeffTwo Float
eval23 :: [[Float]] -> Float
eval23 = [Float] -> Float
forall a. (RealFrac a, Floating a) => [a] -> a
evalRhythmicity23 ([Float] -> Float) -> ([[Float]] -> [Float]) -> [[Float]] -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Float]] -> [Float]
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 #-}
rhythmicity0 :: String -> Float
rhythmicity0 :: String -> Float
rhythmicity0 String
xs
| String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
xs = Float
0.0
| Bool
otherwise = [[Float]] -> Float
eval23 ([[Float]] -> Float) -> (String -> [[Float]]) -> String -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
syllableDurations ([[[UZPP2]]] -> [[Float]])
-> (String -> [[[UZPP2]]]) -> String -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [[[UZPP2]]]
createSyllablesUkr (String -> Float) -> String -> Float
forall a b. (a -> b) -> a -> b
$ String
xs
rhythmicityK :: Float -> Float -> String -> Float
rhythmicityK :: Float -> Float -> String -> Float
rhythmicityK Float
k2 Float
k3 String
xs
| String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
xs = Float
0.0
| Bool
otherwise = Float -> Float -> [[Float]] -> Float
forall c. (RealFrac c, Floating c) => c -> c -> [[c]] -> c
eval23K Float
k2 Float
k3 ([[Float]] -> Float) -> (String -> [[Float]]) -> String -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
syllableDurations ([[[UZPP2]]] -> [[Float]])
-> (String -> [[[UZPP2]]]) -> String -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [[[UZPP2]]]
createSyllablesUkrP (String -> Float) -> String -> Float
forall a b. (a -> b) -> a -> b
$ String
xs
rhythmicityV0 :: VB.Vector Char -> Float
rhythmicityV0 :: Vector Char -> Float
rhythmicityV0 Vector Char
v
| Vector Char -> Bool
forall a. Vector a -> Bool
VB.null Vector Char
v = Float
0.0
| Bool
otherwise = [[Float]] -> Float
eval23 ([[Float]] -> Float)
-> (Vector Char -> [[Float]]) -> Vector Char -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
syllableDurations ([[[UZPP2]]] -> [[Float]])
-> (Vector Char -> [[[UZPP2]]]) -> Vector Char -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Char -> [[[UZPP2]]]
createSyllablesUkrV (Vector Char -> Float) -> Vector Char -> Float
forall a b. (a -> b) -> a -> b
$ Vector Char
v
rhythmicityVK :: Float -> Float -> VB.Vector Char -> Float
rhythmicityVK :: Float -> Float -> Vector Char -> Float
rhythmicityVK Float
k2 Float
k3 Vector Char
v
| Vector Char -> Bool
forall a. Vector a -> Bool
VB.null Vector Char
v = Float
0.0
| Bool
otherwise = Float -> Float -> [[Float]] -> Float
forall c. (RealFrac c, Floating c) => c -> c -> [[c]] -> c
eval23K Float
k2 Float
k3 ([[Float]] -> Float)
-> (Vector Char -> [[Float]]) -> Vector Char -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
syllableDurations ([[[UZPP2]]] -> [[Float]])
-> (Vector Char -> [[[UZPP2]]]) -> Vector Char -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Char -> [[[UZPP2]]]
createSyllablesUkrVP (Vector Char -> Float) -> Vector Char -> Float
forall a b. (a -> b) -> a -> b
$ Vector Char
v
rhythmicity02 :: String -> Float
rhythmicity02 :: String -> Float
rhythmicity02 String
xs
| String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
xs = Float
0.0
| Bool
otherwise = [[Float]] -> Float
eval23 ([[Float]] -> Float) -> (String -> [[Float]]) -> String -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
syllableDurations2 ([[[UZPP2]]] -> [[Float]])
-> (String -> [[[UZPP2]]]) -> String -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [[[UZPP2]]]
createSyllablesUkr (String -> Float) -> String -> Float
forall a b. (a -> b) -> a -> b
$ String
xs
rhythmicityK2 :: Float -> Float -> String -> Float
rhythmicityK2 :: Float -> Float -> String -> Float
rhythmicityK2 Float
k2 Float
k3 String
xs
| String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
xs = Float
0.0
| Bool
otherwise = Float -> Float -> [[Float]] -> Float
forall c. (RealFrac c, Floating c) => c -> c -> [[c]] -> c
eval23K Float
k2 Float
k3 ([[Float]] -> Float) -> (String -> [[Float]]) -> String -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
syllableDurations2 ([[[UZPP2]]] -> [[Float]])
-> (String -> [[[UZPP2]]]) -> String -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [[[UZPP2]]]
createSyllablesUkrP (String -> Float) -> String -> Float
forall a b. (a -> b) -> a -> b
$ String
xs
rhythmicityV02 :: VB.Vector Char -> Float
rhythmicityV02 :: Vector Char -> Float
rhythmicityV02 Vector Char
v
| Vector Char -> Bool
forall a. Vector a -> Bool
VB.null Vector Char
v = Float
0.0
| Bool
otherwise = [[Float]] -> Float
eval23 ([[Float]] -> Float)
-> (Vector Char -> [[Float]]) -> Vector Char -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
syllableDurations2 ([[[UZPP2]]] -> [[Float]])
-> (Vector Char -> [[[UZPP2]]]) -> Vector Char -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Char -> [[[UZPP2]]]
createSyllablesUkrV (Vector Char -> Float) -> Vector Char -> Float
forall a b. (a -> b) -> a -> b
$ Vector Char
v
rhythmicityVK2 :: Float -> Float -> VB.Vector Char -> Float
rhythmicityVK2 :: Float -> Float -> Vector Char -> Float
rhythmicityVK2 Float
k2 Float
k3 Vector Char
v
| Vector Char -> Bool
forall a. Vector a -> Bool
VB.null Vector Char
v = Float
0.0
| Bool
otherwise = Float -> Float -> [[Float]] -> Float
forall c. (RealFrac c, Floating c) => c -> c -> [[c]] -> c
eval23K Float
k2 Float
k3 ([[Float]] -> Float)
-> (Vector Char -> [[Float]]) -> Vector Char -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
syllableDurations2 ([[[UZPP2]]] -> [[Float]])
-> (Vector Char -> [[[UZPP2]]]) -> Vector Char -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Vector Char -> [[[UZPP2]]]
createSyllablesUkrVP (Vector Char -> Float) -> Vector Char -> Float
forall a b. (a -> b) -> a -> b
$ Vector Char
v
rhythmicity :: String -> Coeffs2 -> String -> Float
rhythmicity :: String -> Coeffs2 -> String -> Float
rhythmicity String
choice Coeffs2
CF0
| String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0y" = String -> Float
rhythmicity0
| Bool
otherwise = String -> Float
rhythmicity02
rhythmicity String
choice (CF2 Maybe Float
x Maybe Float
y)
| String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0y" = Float -> Float -> String -> Float
rhythmicityK (Float -> Maybe Float -> Float
forall a. a -> Maybe a -> a
fromMaybe Float
1.0 Maybe Float
x) (Float -> Maybe Float -> Float
forall a. a -> Maybe a -> a
fromMaybe Float
1.0 Maybe Float
y)
| Bool
otherwise = Float -> Float -> String -> Float
rhythmicityK2 (Float -> Maybe Float -> Float
forall a. a -> Maybe a -> a
fromMaybe Float
1.0 Maybe Float
x) (Float -> Maybe Float -> Float
forall a. a -> Maybe a -> a
fromMaybe Float
1.0 Maybe Float
y)
rhythmicityV :: String -> Coeffs2 -> VB.Vector Char -> Float
rhythmicityV :: String -> Coeffs2 -> Vector Char -> Float
rhythmicityV String
choice Coeffs2
CF0
| String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0y" = Vector Char -> Float
rhythmicityV0
| Bool
otherwise = Vector Char -> Float
rhythmicityV02
rhythmicityV String
choice (CF2 Maybe Float
x Maybe Float
y)
| String
choice String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"0y" = Float -> Float -> Vector Char -> Float
rhythmicityVK (Float -> Maybe Float -> Float
forall a. a -> Maybe a -> a
fromMaybe Float
1.0 Maybe Float
x) (Float -> Maybe Float -> Float
forall a. a -> Maybe a -> a
fromMaybe Float
1.0 Maybe Float
y)
| Bool
otherwise = Float -> Float -> Vector Char -> Float
rhythmicityVK2 (Float -> Maybe Float -> Float
forall a. a -> Maybe a -> a
fromMaybe Float
1.0 Maybe Float
x) (Float -> Maybe Float -> Float
forall a. a -> Maybe a -> a
fromMaybe Float
1.0 Maybe Float
y)