-- |
-- Module      :  Phonetic.Languages.Lists.Ukrainian.PropertiesFuncRepG
-- Copyright   :  (c) OleksandrZhabenko 2020
-- 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.

{-# LANGUAGE CPP, BangPatterns #-}

module Phonetic.Languages.Lists.Ukrainian.PropertiesFuncRepG (
  -- * Functions with 'Int16'
  procDiverse2I
  -- * Functions with 'Float'
  , procDiverse2F
  , procBothF
  , procBothInvF
  -- ** Working with generated by r-glpk-phonetic-languages-ukrainian-durations syllable durations
  , procBoth2F
  , procBoth2InvF
  -- ** NEW Working with generated by r-glpk-phonetic-languages-ukrainian-durations syllable durations
  , procBoth3F
  , procBoth3InvF
  -- * Working with rhythmicity
  , procRhythmicity23F
) 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 GHC.Int
import qualified Data.Vector as VB
import qualified Data.Vector.Unboxed as V
import Phonetic.Languages.Lists.Ukrainian.PropertiesSyllablesG
import Phonetic.Languages.Simplified.Lists.UniquenessPeriodsG
import Languages.Rhythmicity
import Phonetic.Languages.Simplified.DataG
import GHC.Float (int2Float)
import Melodics.ByteString.Ukrainian
import qualified Languages.Phonetic.Ukrainian.Syllable as S
import Data.Maybe (isNothing,fromMaybe,mapMaybe)
import Text.Read (readMaybe)

#ifdef __GLASGOW_HASKELL__
#if __GLASGOW_HASKELL__==708
/* code that applies only to GHC 7.8.* */
mconcat = concat
#endif
#endif

procDiverse2I
  :: (Ord c) => (Int16 -> c)
  -> FuncRep2 String Int16 c
procDiverse2I :: (Int16 -> c) -> FuncRep2 String Int16 c
procDiverse2I Int16 -> c
g = (String -> Int16) -> (Int16 -> c) -> FuncRep2 String Int16 c
forall a b c. (a -> b) -> (b -> c) -> FuncRep2 a b c
D (String -> String -> Int16
forall (t :: * -> *). Foldable t => String -> t Char -> Int16
diverse2GL String
" 01-" (String -> Int16) -> (String -> String) -> String -> Int16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
convertToProperUkrainianS) Int16 -> c
g
{-# INLINE procDiverse2I #-}

procDiverse2F
  :: (Ord c) => (Float -> c)
  -> FuncRep2 String Float c
procDiverse2F :: (Float -> c) -> FuncRep2 String Float c
procDiverse2F Float -> c
g = (String -> Float) -> (Float -> c) -> FuncRep2 String Float c
forall a b c. (a -> b) -> (b -> c) -> FuncRep2 a b c
D (Int -> Float
int2Float (Int -> Float) -> (String -> Int) -> String -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int16 -> Int
forall a. Enum a => a -> Int
fromEnum (Int16 -> Int) -> (String -> Int16) -> String -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> Int16
forall (t :: * -> *). Foldable t => String -> t Char -> Int16
diverse2GL String
" 01-" (String -> Int16) -> (String -> String) -> String -> Int16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
convertToProperUkrainianS) Float -> c
g
{-# INLINE procDiverse2F #-}

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

procRhythmicity23F
  :: (Ord c) => (Float -> c)
  -> String
  -> Coeffs2
  -> FuncRep2 String Float c
procRhythmicity23F :: (Float -> c) -> String -> Coeffs2 -> FuncRep2 String Float c
procRhythmicity23F Float -> c
g String
choice Coeffs2
coeffs = (Float -> c)
-> String
-> (String -> Coeffs2 -> String -> Float)
-> Coeffs2
-> FuncRep2 String Float c
forall c.
Ord c =>
(Float -> c)
-> String
-> (String -> Coeffs2 -> String -> Float)
-> Coeffs2
-> FuncRep2 String Float c
procRhythm23F Float -> c
g String
choice String -> Coeffs2 -> String -> Float
rhythmicity Coeffs2
coeffs
{-# INLINE procRhythmicity23F #-}

procBothF
  :: (Ord c) => (Float -> c)
  -> Coeffs2
  -> FuncRep2 String Float c
procBothF :: (Float -> c) -> Coeffs2 -> FuncRep2 String Float c
procBothF Float -> c
g Coeffs2
coeffs  = (Float -> c)
-> ([[[UZPP2]]] -> [[Float]]) -> Coeffs2 -> FuncRep2 String Float c
forall c.
Ord c =>
(Float -> c)
-> ([[[UZPP2]]] -> [[Float]]) -> Coeffs2 -> FuncRep2 String Float c
procB2F Float -> c
g [[[UZPP2]]] -> [[Float]]
S.syllableDurations Coeffs2
coeffs
{-# INLINE procBothF #-}

procBothInvF
  :: (Ord c) => (Float -> c)
  -> Coeffs2
  -> FuncRep2 String Float c
procBothInvF :: (Float -> c) -> Coeffs2 -> FuncRep2 String Float c
procBothInvF Float -> c
g Coeffs2
coeffs  = (Float -> c)
-> ([[[UZPP2]]] -> [[Float]]) -> Coeffs2 -> FuncRep2 String Float c
forall c.
Ord c =>
(Float -> c)
-> ([[[UZPP2]]] -> [[Float]]) -> Coeffs2 -> FuncRep2 String Float c
procB2InvF Float -> c
g [[[UZPP2]]] -> [[Float]]
S.syllableDurations Coeffs2
coeffs
{-# INLINE procBothInvF #-}

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

procBoth2F
  :: (Ord c) => (Float -> c)
  -> Coeffs2
  -> FuncRep2 String Float c
procBoth2F :: (Float -> c) -> Coeffs2 -> FuncRep2 String Float c
procBoth2F Float -> c
g Coeffs2
coeffs  = (Float -> c)
-> ([[[UZPP2]]] -> [[Float]]) -> Coeffs2 -> FuncRep2 String Float c
forall c.
Ord c =>
(Float -> c)
-> ([[[UZPP2]]] -> [[Float]]) -> Coeffs2 -> FuncRep2 String Float c
procB2F Float -> c
g [[[UZPP2]]] -> [[Float]]
S.syllableDurations2 Coeffs2
coeffs
{-# INLINE procBoth2F #-}

procBoth2InvF
  :: (Ord c) => (Float -> c)
  -> Coeffs2
  -> FuncRep2 String Float c
procBoth2InvF :: (Float -> c) -> Coeffs2 -> FuncRep2 String Float c
procBoth2InvF Float -> c
g Coeffs2
coeffs  = (Float -> c)
-> ([[[UZPP2]]] -> [[Float]]) -> Coeffs2 -> FuncRep2 String Float c
forall c.
Ord c =>
(Float -> c)
-> ([[[UZPP2]]] -> [[Float]]) -> Coeffs2 -> FuncRep2 String Float c
procB2InvF Float -> c
g [[[UZPP2]]] -> [[Float]]
S.syllableDurations2 Coeffs2
coeffs
{-# INLINE procBoth2InvF #-}

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

eval23Coeffs :: Coeffs2 -> [Float] -> Float
eval23Coeffs :: Coeffs2 -> [Float] -> Float
eval23Coeffs (CF2 Maybe Float
x Maybe Float
y) = Float -> Float -> [Float] -> Float
forall a. (RealFrac a, Floating a) => a -> a -> [a] -> a
evalRhythmicity23K (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)
eval23Coeffs Coeffs2
CF0 = [Float] -> Float
forall a. (RealFrac a, Floating a) => [a] -> a
evalRhythmicity23

procRhythm23F
  :: (Ord c) => (Float -> c)
  -> String
  -> (String -> Coeffs2 -> String -> Float)
  -> Coeffs2
  -> FuncRep2 String Float c
procRhythm23F :: (Float -> c)
-> String
-> (String -> Coeffs2 -> String -> Float)
-> Coeffs2
-> FuncRep2 String Float c
procRhythm23F Float -> c
h String
choice String -> Coeffs2 -> String -> Float
g Coeffs2
coeffs = (String -> Float) -> (Float -> c) -> FuncRep2 String Float c
forall a b c. (a -> b) -> (b -> c) -> FuncRep2 a b c
D (String -> Coeffs2 -> String -> Float
g String
choice Coeffs2
coeffs) Float -> c
h
{-# INLINE procRhythm23F #-}

procB2F
  :: (Ord c) => (Float -> c)
  -> ([[[S.UZPP2]]] -> [[Float]])
  -> Coeffs2
  -> FuncRep2 String Float c
procB2F :: (Float -> c)
-> ([[[UZPP2]]] -> [[Float]]) -> Coeffs2 -> FuncRep2 String Float c
procB2F Float -> c
h [[[UZPP2]]] -> [[Float]]
g Coeffs2
coeffs = (String -> Float) -> (Float -> c) -> FuncRep2 String Float c
forall a b c. (a -> b) -> (b -> c) -> FuncRep2 a b c
D (\String
xs -> let ys :: String
ys = String -> String
convertToProperUkrainianS (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map (\Char
x -> if Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' then Char
' ' else Char
x) (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
xs in  ((Int -> Float
int2Float (Int -> Float) -> (String -> Int) -> String -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int16 -> Int
forall a. Enum a => a -> Int
fromEnum (Int16 -> Int) -> (String -> Int16) -> String -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> Int16
forall (t :: * -> *). Foldable t => String -> t Char -> Int16
diverse2GL String
" 01-" (String -> Float) -> String -> Float
forall a b. (a -> b) -> a -> b
$ String
ys)Float -> Float -> Float
forall a. Num a => a -> a -> a
*(Coeffs2 -> [Float] -> Float
eval23Coeffs Coeffs2
coeffs ([Float] -> Float) -> (String -> [Float]) -> String -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Float]] -> [Float]
forall a. Monoid a => [a] -> a
mconcat ([[Float]] -> [Float])
-> (String -> [[Float]]) -> String -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
g ([[[UZPP2]]] -> [[Float]])
-> (String -> [[[UZPP2]]]) -> String -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> [[UZPP2]]) -> [String] -> [[[UZPP2]]]
forall a b. (a -> b) -> [a] -> [b]
map ([[UZPP2]] -> [[UZPP2]]
S.divVwls ([[UZPP2]] -> [[UZPP2]])
-> (String -> [[UZPP2]]) -> String -> [[UZPP2]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[UZPP2]] -> [[UZPP2]]
S.reSyllableCntnts ([[UZPP2]] -> [[UZPP2]])
-> (String -> [[UZPP2]]) -> String -> [[UZPP2]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [UZPP2] -> [[UZPP2]]
S.groupSnds ([UZPP2] -> [[UZPP2]])
-> (String -> [UZPP2]) -> String -> [[UZPP2]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [UZPP2]
S.str2UZPP2s) ([String] -> [[[UZPP2]]])
-> (String -> [String]) -> String -> [[[UZPP2]]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words1 (String -> [String]) -> (String -> String) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Maybe Char) -> String -> String
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Char -> Maybe Char
f (String -> Float) -> String -> Float
forall a b. (a -> b) -> a -> b
$ String
ys))) Float -> c
h
{-# INLINE procB2F #-}

procB2InvF
  :: (Ord c) => (Float -> c)
  -> ([[[S.UZPP2]]] -> [[Float]])
  -> Coeffs2
  -> FuncRep2 String Float c
procB2InvF :: (Float -> c)
-> ([[[UZPP2]]] -> [[Float]]) -> Coeffs2 -> FuncRep2 String Float c
procB2InvF Float -> c
h [[[UZPP2]]] -> [[Float]]
g Coeffs2
coeffs = (String -> Float) -> (Float -> c) -> FuncRep2 String Float c
forall a b c. (a -> b) -> (b -> c) -> FuncRep2 a b c
D (\String
xs ->
  let !ys :: String
ys = String -> String
convertToProperUkrainianS (String -> String) -> (String -> String) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map (\Char
x -> if Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-' then Char
' ' else Char
x) (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
xs
      !z :: Int16
z = String -> String -> Int16
forall (t :: * -> *). Foldable t => String -> t Char -> Int16
diverse2GL String
" 01-" String
ys in if Int16
z Int16 -> Int16 -> Bool
forall a. Eq a => a -> a -> Bool
== Int16
0 then  (Coeffs2 -> [Float] -> Float
eval23Coeffs Coeffs2
coeffs ([Float] -> Float) -> (String -> [Float]) -> String -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Float]] -> [Float]
forall a. Monoid a => [a] -> a
mconcat ([[Float]] -> [Float])
-> (String -> [[Float]]) -> String -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
g ([[[UZPP2]]] -> [[Float]])
-> (String -> [[[UZPP2]]]) -> String -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> [[UZPP2]]) -> [String] -> [[[UZPP2]]]
forall a b. (a -> b) -> [a] -> [b]
map ([[UZPP2]] -> [[UZPP2]]
S.divVwls ([[UZPP2]] -> [[UZPP2]])
-> (String -> [[UZPP2]]) -> String -> [[UZPP2]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[UZPP2]] -> [[UZPP2]]
S.reSyllableCntnts ([[UZPP2]] -> [[UZPP2]])
-> (String -> [[UZPP2]]) -> String -> [[UZPP2]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [UZPP2] -> [[UZPP2]]
S.groupSnds ([UZPP2] -> [[UZPP2]])
-> (String -> [UZPP2]) -> String -> [[UZPP2]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
         String -> [UZPP2]
S.str2UZPP2s) ([String] -> [[[UZPP2]]])
-> (String -> [String]) -> String -> [[[UZPP2]]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words1 (String -> [String]) -> (String -> String) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Maybe Char) -> String -> String
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Char -> Maybe Char
f (String -> Float) -> String -> Float
forall a b. (a -> b) -> a -> b
$ String
ys) Float -> Float -> Float
forall a. Floating a => a -> a -> a
** Float
2.0
        else  ((Coeffs2 -> [Float] -> Float
eval23Coeffs Coeffs2
coeffs ([Float] -> Float) -> (String -> [Float]) -> String -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Float]] -> [Float]
forall a. Monoid a => [a] -> a
mconcat ([[Float]] -> [Float])
-> (String -> [[Float]]) -> String -> [Float]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Float]]
g ([[[UZPP2]]] -> [[Float]])
-> (String -> [[[UZPP2]]]) -> String -> [[Float]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> [[UZPP2]]) -> [String] -> [[[UZPP2]]]
forall a b. (a -> b) -> [a] -> [b]
map ([[UZPP2]] -> [[UZPP2]]
S.divVwls ([[UZPP2]] -> [[UZPP2]])
-> (String -> [[UZPP2]]) -> String -> [[UZPP2]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[UZPP2]] -> [[UZPP2]]
S.reSyllableCntnts ([[UZPP2]] -> [[UZPP2]])
-> (String -> [[UZPP2]]) -> String -> [[UZPP2]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [UZPP2] -> [[UZPP2]]
S.groupSnds ([UZPP2] -> [[UZPP2]])
-> (String -> [UZPP2]) -> String -> [[UZPP2]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [UZPP2]
S.str2UZPP2s) ([String] -> [[[UZPP2]]])
-> (String -> [String]) -> String -> [[[UZPP2]]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words1 (String -> [String]) -> (String -> String) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Maybe Char) -> String -> String
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Char -> Maybe Char
f (String -> Float) -> String -> Float
forall a b. (a -> b) -> a -> b
$ String
ys) Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ (Int -> Float
int2Float (Int -> Float) -> (Int16 -> Int) -> Int16 -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int16 -> Int
forall a. Enum a => a -> Int
fromEnum (Int16 -> Float) -> Int16 -> Float
forall a b. (a -> b) -> a -> b
$ Int16
z))) Float -> c
h
{-# INLINE procB2InvF #-}

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

procBoth3F
  :: (Ord c) => (Float -> c)
  -> Coeffs2
  -> FuncRep2 String Float c
procBoth3F :: (Float -> c) -> Coeffs2 -> FuncRep2 String Float c
procBoth3F Float -> c
g Coeffs2
coeffs  = (Float -> c)
-> ([[[UZPP2]]] -> [[Float]]) -> Coeffs2 -> FuncRep2 String Float c
forall c.
Ord c =>
(Float -> c)
-> ([[[UZPP2]]] -> [[Float]]) -> Coeffs2 -> FuncRep2 String Float c
procB2F Float -> c
g [[[UZPP2]]] -> [[Float]]
S.syllableDurations3 Coeffs2
coeffs
{-# INLINE procBoth3F #-}

procBoth3InvF
  :: (Ord c) => (Float -> c)
  -> Coeffs2
  -> FuncRep2 String Float c
procBoth3InvF :: (Float -> c) -> Coeffs2 -> FuncRep2 String Float c
procBoth3InvF Float -> c
g Coeffs2
coeffs  = (Float -> c)
-> ([[[UZPP2]]] -> [[Float]]) -> Coeffs2 -> FuncRep2 String Float c
forall c.
Ord c =>
(Float -> c)
-> ([[[UZPP2]]] -> [[Float]]) -> Coeffs2 -> FuncRep2 String Float c
procB2InvF Float -> c
g [[[UZPP2]]] -> [[Float]]
S.syllableDurations3 Coeffs2
coeffs
{-# INLINE procBoth3InvF #-}

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

f :: Char -> Maybe Char
f Char
x
  | Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'0' = Maybe Char
forall a. Maybe a
Nothing
  | Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'1' Bool -> Bool -> Bool
&& Char
x Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'-' = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
x
  | Bool
otherwise = Char -> Maybe Char
forall a. a -> Maybe a
Just Char
' '
{-# INLINE f #-}

words1 :: String -> [String]
words1 String
xs = if String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
ts then [] else String
w String -> [String] -> [String]
forall a. a -> [a] -> [a]
: String -> [String]
words1 String
s'' -- Practically this is an optimized version for this case 'words' function from Prelude.
  where ts :: String
ts = (Char -> Bool) -> String -> String
forall a. (a -> Bool) -> [a] -> [a]
dropWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' ') String
xs
        (String
w, String
s'') = (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
span (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
' ') String
ts
{-# NOINLINE words1 #-}