{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE CPP, BangPatterns #-}
module Phonetic.Languages.Array.Ukrainian.PropertiesFuncRepG2 (
procDiverse2I
, procB2FG
, procB2InvFG
, procDiverse2F
, procBothF
, procBothFF
, procBothInvF
, procBothInvFF
, procBoth2F
, procBoth2FF
, procBoth2InvF
, procBoth2InvFF
, procBoth3F
, procBoth3FF
, procBoth3InvF
, procBoth3InvFF
, procBoth4F
, procBoth4FF
, procBoth4InvF
, procBoth4InvFF
, procRhythmicity23F
, procRhythmicity23FH
) 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 Phonetic.Languages.Array.Ukrainian.PropertiesSyllablesG2
import Phonetic.Languages.Simplified.Lists.UniquenessPeriodsG.Base
import Languages.Rhythmicity
import Languages.Rhythmicity.Factor
import Phonetic.Languages.Simplified.DataG.Base
import GHC.Float (int2Double)
import Melodics.ByteString.Ukrainian.Arr
import qualified Languages.Phonetic.Ukrainian.Syllable.Double.Arr as SD
import qualified Languages.Phonetic.Ukrainian.Syllable.Arr 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) => (Double -> c)
-> FuncRep2 String Double c
procDiverse2F :: (Double -> c) -> FuncRep2 String Double c
procDiverse2F Double -> c
g = (String -> Double) -> (Double -> c) -> FuncRep2 String Double c
forall a b c. (a -> b) -> (b -> c) -> FuncRep2 a b c
D (Int -> Double
int2Double (Int -> Double) -> (String -> Int) -> String -> Double
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) Double -> c
g
{-# INLINE procDiverse2F #-}
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 #-}
procB2FG
:: (Ord c) => ([Double] -> Double)
-> (Double -> c)
-> ([[[S.UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2FG :: ([Double] -> Double)
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2FG [Double] -> Double
h1 Double -> c
h [[[UZPP2]]] -> [[Double]]
g Coeffs2
coeffs = (String -> Double) -> (Double -> c) -> FuncRep2 String Double 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 -> Double
int2Double (Int -> Double) -> (String -> Int) -> String -> Double
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 -> Double) -> String -> Double
forall a b. (a -> b) -> a -> b
$ String
ys)Double -> Double -> Double
forall a. Num a => a -> a -> a
*([Double] -> Double
h1 ([Double] -> Double) -> (String -> [Double]) -> String -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Double]] -> [Double]
forall a. Monoid a => [a] -> a
mconcat ([[Double]] -> [Double])
-> (String -> [[Double]]) -> String -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Double]]
g ([[[UZPP2]]] -> [[Double]])
-> (String -> [[[UZPP2]]]) -> String -> [[Double]]
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 -> Double) -> String -> Double
forall a b. (a -> b) -> a -> b
$ String
ys))) Double -> c
h
{-# INLINE procB2FG #-}
procB2F
:: (Ord c) => (Double -> c)
-> ([[[S.UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2F :: (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2F Double -> c
h [[[UZPP2]]] -> [[Double]]
g Coeffs2
coeffs = ([Double] -> Double)
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
([Double] -> Double)
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2FG (Coeffs2 -> [Double] -> Double
eval23Coeffs Coeffs2
coeffs) Double -> c
h [[[UZPP2]]] -> [[Double]]
g Coeffs2
coeffs
{-# INLINE procB2F #-}
procB2FF
:: (Ord c) => Double
-> (Double -> c)
-> ([[[S.UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2FF :: Double
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2FF Double
k Double -> c
h [[[UZPP2]]] -> [[Double]]
g Coeffs2
coeffs = ([Double] -> Double)
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
([Double] -> Double)
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2FG (Double -> Coeffs2 -> [Double] -> Double
eval23CoeffsF Double
k Coeffs2
coeffs) Double -> c
h [[[UZPP2]]] -> [[Double]]
g Coeffs2
coeffs
{-# INLINE procB2FF #-}
procB2InvFG
:: (Ord c) => ([Double] -> Double)
-> (Double -> c)
-> ([[[S.UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvFG :: ([Double] -> Double)
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvFG [Double] -> Double
h1 Double -> c
h [[[UZPP2]]] -> [[Double]]
g Coeffs2
coeffs = (String -> Double) -> (Double -> c) -> FuncRep2 String Double 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 ([Double] -> Double
h1 ([Double] -> Double) -> (String -> [Double]) -> String -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Double]] -> [Double]
forall a. Monoid a => [a] -> a
mconcat ([[Double]] -> [Double])
-> (String -> [[Double]]) -> String -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Double]]
g ([[[UZPP2]]] -> [[Double]])
-> (String -> [[[UZPP2]]]) -> String -> [[Double]]
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 -> Double) -> String -> Double
forall a b. (a -> b) -> a -> b
$ String
ys) Double -> Double -> Double
forall a. Floating a => a -> a -> a
** Double
2.0
else (([Double] -> Double
h1 ([Double] -> Double) -> (String -> [Double]) -> String -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Double]] -> [Double]
forall a. Monoid a => [a] -> a
mconcat ([[Double]] -> [Double])
-> (String -> [[Double]]) -> String -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[UZPP2]]] -> [[Double]]
g ([[[UZPP2]]] -> [[Double]])
-> (String -> [[[UZPP2]]]) -> String -> [[Double]]
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 -> Double) -> String -> Double
forall a b. (a -> b) -> a -> b
$ String
ys) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Int -> Double
int2Double (Int -> Double) -> (Int16 -> Int) -> Int16 -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int16 -> Int
forall a. Enum a => a -> Int
fromEnum (Int16 -> Double) -> Int16 -> Double
forall a b. (a -> b) -> a -> b
$ Int16
z))) Double -> c
h
{-# INLINE procB2InvFG #-}
procB2InvF
:: (Ord c) => (Double -> c)
-> ([[[S.UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvF :: (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvF Double -> c
h [[[UZPP2]]] -> [[Double]]
g Coeffs2
coeffs = ([Double] -> Double)
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
([Double] -> Double)
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvFG (Coeffs2 -> [Double] -> Double
eval23Coeffs Coeffs2
coeffs) Double -> c
h [[[UZPP2]]] -> [[Double]]
g Coeffs2
coeffs
{-# INLINE procB2InvF #-}
procB2InvFF
:: (Ord c) => Double
-> (Double -> c)
-> ([[[S.UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvFF :: Double
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvFF Double
k Double -> c
h [[[UZPP2]]] -> [[Double]]
g Coeffs2
coeffs = ([Double] -> Double)
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
([Double] -> Double)
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvFG (Double -> Coeffs2 -> [Double] -> Double
eval23CoeffsF Double
k Coeffs2
coeffs) Double -> c
h [[[UZPP2]]] -> [[Double]]
g Coeffs2
coeffs
{-# INLINE procB2InvFF #-}
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
D (String -> Coeffs2 -> String -> Double
g String
choice Coeffs2
coeffs) Double -> c
h
{-# INLINE procRhythm23F #-}
procRhythmicity23F
:: (Ord c) => Double
-> (Double -> c)
-> String
-> Coeffs2
-> FuncRep2 String Double c
procRhythmicity23F :: Double
-> (Double -> c) -> String -> Coeffs2 -> FuncRep2 String Double c
procRhythmicity23F Double
k Double -> c
g String
choice Coeffs2
coeffs = (Double -> c)
-> String
-> (String -> Coeffs2 -> String -> Double)
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c)
-> String
-> (String -> Coeffs2 -> String -> Double)
-> Coeffs2
-> FuncRep2 String Double c
procRhythm23F Double -> c
g String
choice (Double -> String -> Coeffs2 -> String -> Double
rhythmicity Double
k) Coeffs2
coeffs
{-# INLINE procRhythmicity23F #-}
procRhythmicity23FH
:: (Ord c) => Double
-> (Double -> c)
-> [[[[S.UZPP2]]] -> [[Double]]]
-> String
-> Coeffs2
-> FuncRep2 String Double c
procRhythmicity23FH :: Double
-> (Double -> c)
-> [[[[UZPP2]]] -> [[Double]]]
-> String
-> Coeffs2
-> FuncRep2 String Double c
procRhythmicity23FH Double
k Double -> c
g [[[[UZPP2]]] -> [[Double]]]
syllableDurationsDs String
choice Coeffs2
coeffs = (String -> Double) -> (Double -> c) -> FuncRep2 String Double c
forall a b c. (a -> b) -> (b -> c) -> FuncRep2 a b c
D (Double
-> String
-> [[[[UZPP2]]] -> [[Double]]]
-> Coeffs2
-> String
-> Double
rhythmicityH Double
k String
choice [[[[UZPP2]]] -> [[Double]]]
syllableDurationsDs Coeffs2
coeffs) Double -> c
g
{-# INLINE procRhythmicity23FH #-}
procBothF
:: (Ord c) => (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBothF :: (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBothF Double -> c
g Coeffs2
coeffs = (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2F Double -> c
g [[[UZPP2]]] -> [[Double]]
SD.syllableDurationsD Coeffs2
coeffs
{-# INLINE procBothF #-}
procBothFF
:: (Ord c) => Double
-> (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBothFF :: Double -> (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBothFF Double
k Double -> c
g Coeffs2
coeffs = Double
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
Double
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2FF Double
k Double -> c
g [[[UZPP2]]] -> [[Double]]
SD.syllableDurationsD Coeffs2
coeffs
{-# INLINE procBothFF #-}
procBothInvF
:: (Ord c) => (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBothInvF :: (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBothInvF Double -> c
g Coeffs2
coeffs = (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvF Double -> c
g [[[UZPP2]]] -> [[Double]]
SD.syllableDurationsD Coeffs2
coeffs
{-# INLINE procBothInvF #-}
procBothInvFF
:: (Ord c) => Double
-> (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBothInvFF :: Double -> (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBothInvFF Double
k Double -> c
g Coeffs2
coeffs = Double
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
Double
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvFF Double
k Double -> c
g [[[UZPP2]]] -> [[Double]]
SD.syllableDurationsD Coeffs2
coeffs
{-# INLINE procBothInvFF #-}
procBoth2F
:: (Ord c) => (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBoth2F :: (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth2F Double -> c
g Coeffs2
coeffs = (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2F Double -> c
g [[[UZPP2]]] -> [[Double]]
SD.syllableDurationsD2 Coeffs2
coeffs
{-# INLINE procBoth2F #-}
procBoth2InvF
:: (Ord c) => (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBoth2InvF :: (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth2InvF Double -> c
g Coeffs2
coeffs = (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvF Double -> c
g [[[UZPP2]]] -> [[Double]]
SD.syllableDurationsD2 Coeffs2
coeffs
{-# INLINE procBoth2InvF #-}
procBoth2FF
:: (Ord c) => Double
-> (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBoth2FF :: Double -> (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth2FF Double
k Double -> c
g Coeffs2
coeffs = Double
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
Double
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2FF Double
k Double -> c
g [[[UZPP2]]] -> [[Double]]
SD.syllableDurationsD2 Coeffs2
coeffs
{-# INLINE procBoth2FF #-}
procBoth2InvFF
:: (Ord c) => Double
-> (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBoth2InvFF :: Double -> (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth2InvFF Double
k Double -> c
g Coeffs2
coeffs = Double
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
Double
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvFF Double
k Double -> c
g [[[UZPP2]]] -> [[Double]]
SD.syllableDurationsD2 Coeffs2
coeffs
{-# INLINE procBoth2InvFF #-}
procBoth3F
:: (Ord c) => (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBoth3F :: (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth3F Double -> c
g Coeffs2
coeffs = (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2F Double -> c
g [[[UZPP2]]] -> [[Double]]
SD.syllableDurationsD3 Coeffs2
coeffs
{-# INLINE procBoth3F #-}
procBoth3InvF
:: (Ord c) => (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBoth3InvF :: (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth3InvF Double -> c
g Coeffs2
coeffs = (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvF Double -> c
g [[[UZPP2]]] -> [[Double]]
SD.syllableDurationsD3 Coeffs2
coeffs
{-# INLINE procBoth3InvF #-}
procBoth3FF
:: (Ord c) => Double
-> (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBoth3FF :: Double -> (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth3FF Double
k Double -> c
g Coeffs2
coeffs = Double
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
Double
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2FF Double
k Double -> c
g [[[UZPP2]]] -> [[Double]]
SD.syllableDurationsD3 Coeffs2
coeffs
{-# INLINE procBoth3FF #-}
procBoth3InvFF
:: (Ord c) => Double
-> (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBoth3InvFF :: Double -> (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth3InvFF Double
k Double -> c
g Coeffs2
coeffs = Double
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
Double
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvFF Double
k Double -> c
g [[[UZPP2]]] -> [[Double]]
SD.syllableDurationsD3 Coeffs2
coeffs
{-# INLINE procBoth3InvFF #-}
procBoth4F
:: (Ord c) => (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBoth4F :: (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth4F Double -> c
g Coeffs2
coeffs = (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2F Double -> c
g [[[UZPP2]]] -> [[Double]]
SD.syllableDurationsD4 Coeffs2
coeffs
{-# INLINE procBoth4F #-}
procBoth4InvF
:: (Ord c) => (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBoth4InvF :: (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth4InvF Double -> c
g Coeffs2
coeffs = (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
(Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvF Double -> c
g [[[UZPP2]]] -> [[Double]]
SD.syllableDurationsD4 Coeffs2
coeffs
{-# INLINE procBoth4InvF #-}
procBoth4FF
:: (Ord c) => Double
-> (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBoth4FF :: Double -> (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth4FF Double
k Double -> c
g Coeffs2
coeffs = Double
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
Double
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2FF Double
k Double -> c
g [[[UZPP2]]] -> [[Double]]
SD.syllableDurationsD4 Coeffs2
coeffs
{-# INLINE procBoth4FF #-}
procBoth4InvFF
:: (Ord c) => Double
-> (Double -> c)
-> Coeffs2
-> FuncRep2 String Double c
procBoth4InvFF :: Double -> (Double -> c) -> Coeffs2 -> FuncRep2 String Double c
procBoth4InvFF Double
k Double -> c
g Coeffs2
coeffs = Double
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
forall c.
Ord c =>
Double
-> (Double -> c)
-> ([[[UZPP2]]] -> [[Double]])
-> Coeffs2
-> FuncRep2 String Double c
procB2InvFF Double
k Double -> c
g [[[UZPP2]]] -> [[Double]]
SD.syllableDurationsD4 Coeffs2
coeffs
{-# INLINE procBoth4InvFF #-}
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''
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 #-}