{-# LANGUAGE BangPatterns #-}
module Phonetic.Languages.EmphasisG where
import Data.Phonetic.Languages.Base
import Data.Phonetic.Languages.Syllables
import GHC.Int
import Data.Maybe (fromMaybe)
import Text.Read (readMaybe)
import Data.Char (toUpper)
import GHC.Arr
import Data.List (scanl',intersperse)
import CaseBi.Arr
import Data.Foldable (foldl')
import CaseBi.Arr (getBFst',getBFstLSorted')
import Data.Lists.FLines (newLineEnding)
import Data.Traversable (traverse)
import Control.Applicative
import System.IO
data SyllWeightsG = SyG {
SyllWeightsG -> [PRS]
point :: ![PRS]
, SyllWeightsG -> Int8
order :: !Int8
, SyllWeightsG -> Double
weight :: !Double
}
showFSG :: FlowSoundG -> String
showFSG :: [PRS] -> String
showFSG = (PRS -> Char) -> [PRS] -> String
forall a b. (a -> b) -> [a] -> [b]
map PRS -> Char
charS
{-# INLINE showFSG #-}
type FlowSoundG = [PRS]
instance Show SyllWeightsG where
show :: SyllWeightsG -> String
show (SyG [PRS]
ps Int8
i Double
w) = [PRS] -> String
showFSG [PRS]
ps String -> ShowS
forall a. Monoid a => a -> a -> a
`mappend` (Char
' 'Char -> ShowS
forall a. a -> [a] -> [a]
:Int8 -> String
forall a. Show a => a -> String
show Int8
i) String -> ShowS
forall a. Monoid a => a -> a -> a
`mappend` (Char
' 'Char -> ShowS
forall a. a -> [a] -> [a]
:Double -> String
forall a. Show a => a -> String
show Double
w) String -> ShowS
forall a. Monoid a => a -> a -> a
`mappend` String
newLineEnding
weightSyllablesIO :: [FlowSoundG] -> IO [SyllWeightsG]
weightSyllablesIO :: [[PRS]] -> IO [SyllWeightsG]
weightSyllablesIO = ((Int8, [PRS]) -> IO SyllWeightsG)
-> [(Int8, [PRS])] -> IO [SyllWeightsG]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\(Int8
i,[PRS]
xs) -> (\Double
d1 -> ([PRS] -> Int8 -> Double -> SyllWeightsG
SyG [PRS]
xs Int8
i Double
d1)) (Double -> SyllWeightsG) -> IO Double -> IO SyllWeightsG
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Bool -> [PRS] -> IO Double
weightSyllAIO Bool
False [PRS]
xs) ([(Int8, [PRS])] -> IO [SyllWeightsG])
-> ([[PRS]] -> [(Int8, [PRS])]) -> [[PRS]] -> IO [SyllWeightsG]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int8] -> [[PRS]] -> [(Int8, [PRS])]
forall a b. [a] -> [b] -> [(a, b)]
zip ([-Int8
128..Int8
127]::[Int8])
weightStringIO
:: GWritingSystemPRPLX
-> [(Char,Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> IO ([[FlowSoundG]],[SyllWeightsG],[[[Int8]]])
weightStringIO :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> IO ([[[PRS]]], [SyllWeightsG], [[[Int8]]])
weightStringIO GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs String
xs = [[PRS]] -> IO [SyllWeightsG]
weightSyllablesIO [[PRS]]
fss IO [SyllWeightsG]
-> ([SyllWeightsG] -> IO ([[[PRS]]], [SyllWeightsG], [[[Int8]]]))
-> IO ([[[PRS]]], [SyllWeightsG], [[[Int8]]])
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[SyllWeightsG]
zs -> ([[[PRS]]], [SyllWeightsG], [[[Int8]]])
-> IO ([[[PRS]]], [SyllWeightsG], [[[Int8]]])
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([[[PRS]]]
tsss, [SyllWeightsG]
zs, [Int8] -> [[[Int8]]]
helper1F ([Int8] -> [[[Int8]]])
-> ([[[PRS]]] -> [Int8]) -> [[[PRS]]] -> [[[Int8]]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int8 -> Int8 -> Int8) -> Int8 -> [Int8] -> [Int8]
forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl' Int8 -> Int8 -> Int8
forall a. Num a => a -> a -> a
(+) (-Int8
128::Int8) ([Int8] -> [Int8]) -> ([[[PRS]]] -> [Int8]) -> [[[PRS]]] -> [Int8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([[PRS]] -> Int8) -> [[[PRS]]] -> [Int8]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int8) -> ([[PRS]] -> Int) -> [[PRS]] -> Int8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[PRS]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length) ([[[PRS]]] -> [[[Int8]]]) -> [[[PRS]]] -> [[[Int8]]]
forall a b. (a -> b) -> a -> b
$ [[[PRS]]]
tsss)
where tsss :: [[[PRS]]]
tsss = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [[[PRS]]]
createSyllablesPL GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs String
xs
fss :: [[PRS]]
fss = [ [PRS]
ts | [[PRS]]
tss <- [[[PRS]]]
tsss , [PRS]
ts <- [[PRS]]
tss ]
weightStringNIO
:: GWritingSystemPRPLX
-> [(Char,Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> Int
-> String
-> IO ([[FlowSoundG]],[[SyllWeightsG]],[[[Int8]]])
weightStringNIO :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> Int
-> String
-> IO ([[[PRS]]], [[SyllWeightsG]], [[[Int8]]])
weightStringNIO GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs Int
n String
xs = (Int -> IO [SyllWeightsG]) -> [Int] -> IO [[SyllWeightsG]]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\Int
_-> [[PRS]] -> IO [SyllWeightsG]
weightSyllablesIO [[PRS]]
fss) [Int
1..Int
n] IO [[SyllWeightsG]]
-> ([[SyllWeightsG]]
-> IO ([[[PRS]]], [[SyllWeightsG]], [[[Int8]]]))
-> IO ([[[PRS]]], [[SyllWeightsG]], [[[Int8]]])
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[[SyllWeightsG]]
zss -> ([[[PRS]]], [[SyllWeightsG]], [[[Int8]]])
-> IO ([[[PRS]]], [[SyllWeightsG]], [[[Int8]]])
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([[[PRS]]]
tsss, [[SyllWeightsG]]
zss, [Int8] -> [[[Int8]]]
helper1F ([Int8] -> [[[Int8]]])
-> ([[[PRS]]] -> [Int8]) -> [[[PRS]]] -> [[[Int8]]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int8 -> Int8 -> Int8) -> Int8 -> [Int8] -> [Int8]
forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl' Int8 -> Int8 -> Int8
forall a. Num a => a -> a -> a
(+) (-Int8
128::Int8) ([Int8] -> [Int8]) -> ([[[PRS]]] -> [Int8]) -> [[[PRS]]] -> [Int8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([[PRS]] -> Int8) -> [[[PRS]]] -> [Int8]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Int8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int8) -> ([[PRS]] -> Int) -> [[PRS]] -> Int8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[PRS]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length) ([[[PRS]]] -> [[[Int8]]]) -> [[[PRS]]] -> [[[Int8]]]
forall a b. (a -> b) -> a -> b
$ [[[PRS]]]
tsss)
where tsss :: [[[PRS]]]
tsss = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [[[PRS]]]
createSyllablesPL GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs String
xs
fss :: [[PRS]]
fss = [ [PRS]
ts | [[PRS]]
tss <- [[[PRS]]]
tsss , [PRS]
ts <- [[PRS]]
tss ]
weights2SyllableDurationsDArr :: [SyllWeightsG] -> Array Int (Int8,Double)
weights2SyllableDurationsDArr :: [SyllWeightsG] -> Array Int (Int8, Double)
weights2SyllableDurationsDArr [SyllWeightsG]
xs = (Int, Int) -> [(Int8, Double)] -> Array Int (Int8, Double)
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) ([(Int8, Double)] -> Array Int (Int8, Double))
-> ([SyllWeightsG] -> [(Int8, Double)])
-> [SyllWeightsG]
-> Array Int (Int8, Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SyllWeightsG -> (Int8, Double))
-> [SyllWeightsG] -> [(Int8, Double)]
forall a b. (a -> b) -> [a] -> [b]
map (\(SyG [PRS]
_ Int8
i Double
w) -> (Int8
i,Double
w)) ([SyllWeightsG] -> Array Int (Int8, Double))
-> [SyllWeightsG] -> Array Int (Int8, Double)
forall a b. (a -> b) -> a -> b
$ [SyllWeightsG]
xs
where l :: Int
l = [SyllWeightsG] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [SyllWeightsG]
xs
weights2SyllableDurationsD :: [SyllWeightsG] -> [[[Int8]]] -> [[Double]]
weights2SyllableDurationsD :: [SyllWeightsG] -> [[[Int8]]] -> [[Double]]
weights2SyllableDurationsD [SyllWeightsG]
xs = ([[Int8]] -> [Double]) -> [[[Int8]]] -> [[Double]]
forall a b. (a -> b) -> [a] -> [b]
map (([Int8] -> Double) -> [[Int8]] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map ((Int8 -> Double) -> [Int8] -> Double
forall (t :: * -> *) a t.
(Foldable t, Num a) =>
(t -> a) -> t t -> a
k ((Double, Array Int (Int8, Double)) -> Int8 -> Double
forall a b. Ord a => (b, Array Int (a, b)) -> a -> b
getBFst' (Double
4.0, [SyllWeightsG] -> Array Int (Int8, Double)
weights2SyllableDurationsDArr [SyllWeightsG]
xs))))
where k :: (t -> a) -> t t -> a
k t -> a
f = (a -> t -> a) -> a -> t t -> a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\a
y t
x -> t -> a
f t
x a -> a -> a
forall a. Num a => a -> a -> a
+ a
y) a
0
{-# INLINE weights2SyllableDurationsD #-}
helper1F :: [Int8] -> [[[Int8]]]
helper1F :: [Int8] -> [[[Int8]]]
helper1F (Int8
x:Int8
y:[Int8]
ys) = (Int8 -> [Int8]) -> [Int8] -> [[Int8]]
forall a b. (a -> b) -> [a] -> [b]
map (Int8 -> [Int8] -> [Int8]
forall a. a -> [a] -> [a]
:[]) [Int8
x..Int8
yInt8 -> Int8 -> Int8
forall a. Num a => a -> a -> a
-Int8
1][[Int8]] -> [[[Int8]]] -> [[[Int8]]]
forall a. a -> [a] -> [a]
:[Int8] -> [[[Int8]]]
helper1F (Int8
yInt8 -> [Int8] -> [Int8]
forall a. a -> [a] -> [a]
:[Int8]
ys)
helper1F [Int8]
_ = []
weightSyllAIO :: Bool -> FlowSoundG -> IO Double
weightSyllAIO :: Bool -> [PRS] -> IO Double
weightSyllAIO Bool
upper [PRS]
xs
| [PRS] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [PRS]
xs = Double -> IO Double
forall (f :: * -> *) a. Applicative f => a -> f a
pure Double
4.0
| Bool
otherwise =
(\String
d -> Double -> Maybe Double -> Double
forall a. a -> Maybe a -> a
fromMaybe Double
4.0 (String -> Maybe Double
forall a. Read a => String -> Maybe a
readMaybe String
d::Maybe Double)) (String -> Double) -> IO String -> IO Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Handle -> String -> IO ()
hPutStr Handle
stderr (String
"? " String -> ShowS
forall a. Monoid a => a -> a -> a
`mappend` ((if Bool
upper then (Char -> Char) -> ShowS
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper else ShowS
forall a. a -> a
id) ShowS -> ([PRS] -> String) -> [PRS] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [PRS] -> String
showFSG ([PRS] -> String) -> [PRS] -> String
forall a b. (a -> b) -> a -> b
$ [PRS]
xs) String -> ShowS
forall a. Monoid a => a -> a -> a
`mappend` String
" ") IO () -> IO String -> IO String
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> IO String
getLine)
data ReadyForConstructionPL = StrG String | FSLG [[[Int8]]] deriving (ReadyForConstructionPL -> ReadyForConstructionPL -> Bool
(ReadyForConstructionPL -> ReadyForConstructionPL -> Bool)
-> (ReadyForConstructionPL -> ReadyForConstructionPL -> Bool)
-> Eq ReadyForConstructionPL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReadyForConstructionPL -> ReadyForConstructionPL -> Bool
$c/= :: ReadyForConstructionPL -> ReadyForConstructionPL -> Bool
== :: ReadyForConstructionPL -> ReadyForConstructionPL -> Bool
$c== :: ReadyForConstructionPL -> ReadyForConstructionPL -> Bool
Eq,Eq ReadyForConstructionPL
Eq ReadyForConstructionPL
-> (ReadyForConstructionPL -> ReadyForConstructionPL -> Ordering)
-> (ReadyForConstructionPL -> ReadyForConstructionPL -> Bool)
-> (ReadyForConstructionPL -> ReadyForConstructionPL -> Bool)
-> (ReadyForConstructionPL -> ReadyForConstructionPL -> Bool)
-> (ReadyForConstructionPL -> ReadyForConstructionPL -> Bool)
-> (ReadyForConstructionPL
-> ReadyForConstructionPL -> ReadyForConstructionPL)
-> (ReadyForConstructionPL
-> ReadyForConstructionPL -> ReadyForConstructionPL)
-> Ord ReadyForConstructionPL
ReadyForConstructionPL -> ReadyForConstructionPL -> Bool
ReadyForConstructionPL -> ReadyForConstructionPL -> Ordering
ReadyForConstructionPL
-> ReadyForConstructionPL -> ReadyForConstructionPL
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ReadyForConstructionPL
-> ReadyForConstructionPL -> ReadyForConstructionPL
$cmin :: ReadyForConstructionPL
-> ReadyForConstructionPL -> ReadyForConstructionPL
max :: ReadyForConstructionPL
-> ReadyForConstructionPL -> ReadyForConstructionPL
$cmax :: ReadyForConstructionPL
-> ReadyForConstructionPL -> ReadyForConstructionPL
>= :: ReadyForConstructionPL -> ReadyForConstructionPL -> Bool
$c>= :: ReadyForConstructionPL -> ReadyForConstructionPL -> Bool
> :: ReadyForConstructionPL -> ReadyForConstructionPL -> Bool
$c> :: ReadyForConstructionPL -> ReadyForConstructionPL -> Bool
<= :: ReadyForConstructionPL -> ReadyForConstructionPL -> Bool
$c<= :: ReadyForConstructionPL -> ReadyForConstructionPL -> Bool
< :: ReadyForConstructionPL -> ReadyForConstructionPL -> Bool
$c< :: ReadyForConstructionPL -> ReadyForConstructionPL -> Bool
compare :: ReadyForConstructionPL -> ReadyForConstructionPL -> Ordering
$ccompare :: ReadyForConstructionPL -> ReadyForConstructionPL -> Ordering
$cp1Ord :: Eq ReadyForConstructionPL
Ord)
showR :: ReadyForConstructionPL -> String
showR :: ReadyForConstructionPL -> String
showR (StrG String
xs) = String
xs
showR (FSLG [[[Int8]]]
tsss) = [[[Int8]]] -> String
forall a. Show a => a -> String
show [[[Int8]]]
tsss
isStr :: ReadyForConstructionPL -> Bool
isStr :: ReadyForConstructionPL -> Bool
isStr (StrG String
_) = Bool
True
isStr ReadyForConstructionPL
_ = Bool
False
isFSL :: ReadyForConstructionPL -> Bool
isFSL :: ReadyForConstructionPL -> Bool
isFSL (FSLG [[[Int8]]]
_) = Bool
True
isFSL ReadyForConstructionPL
_ = Bool
False
fromReadyFCPLS :: ReadyForConstructionPL -> Maybe String
fromReadyFCPLS :: ReadyForConstructionPL -> Maybe String
fromReadyFCPLS (StrG String
xs) = String -> Maybe String
forall a. a -> Maybe a
Just String
xs
fromReadyFCPLS ReadyForConstructionPL
_ = Maybe String
forall a. Maybe a
Nothing
fromReadyFCPLF :: ReadyForConstructionPL -> Maybe [[[Int8]]]
fromReadyFCPLF :: ReadyForConstructionPL -> Maybe [[[Int8]]]
fromReadyFCPLF (FSLG [[[Int8]]]
xsss) = [[[Int8]]] -> Maybe [[[Int8]]]
forall a. a -> Maybe a
Just [[[Int8]]]
xsss
fromReadyFCPLF ReadyForConstructionPL
_ = Maybe [[[Int8]]]
forall a. Maybe a
Nothing
helper2F :: [b] -> [a] -> [c] -> [[d]] -> [([b],[a],[c])]
helper2F :: [b] -> [a] -> [c] -> [[d]] -> [([b], [a], [c])]
helper2F [b]
vs [a]
xs [c]
ys [[d]]
tss = let ([b]
us,[a]
ks,[c]
rs) = [(b, a, c)] -> ([b], [a], [c])
forall a b c. [(a, b, c)] -> ([a], [b], [c])
unzip3 ([(b, a, c)] -> ([b], [a], [c]))
-> ([c] -> [(b, a, c)]) -> [c] -> ([b], [a], [c])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [b] -> [a] -> [c] -> [(b, a, c)]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 [b]
vs [a]
xs ([c] -> ([b], [a], [c])) -> [c] -> ([b], [a], [c])
forall a b. (a -> b) -> a -> b
$ [c]
ys in
[b] -> [a] -> [c] -> [[d]] -> [([b], [a], [c])]
forall (t :: * -> *) a a a a.
Foldable t =>
[a] -> [a] -> [a] -> [t a] -> [([a], [a], [a])]
helper2F' [b]
us [a]
ks [c]
rs [[d]]
tss
where helper2F' :: [a] -> [a] -> [a] -> [t a] -> [([a], [a], [a])]
helper2F' us :: [a]
us@(a
_:[a]
_) ks :: [a]
ks@(a
_:[a]
_) rs :: [a]
rs@(a
_:[a]
_) tss :: [t a]
tss@(t a
ts:[t a]
wss) =
let l :: Int
l = t a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length t a
ts
([a]
wws,[a]
vvs) = Int -> [a] -> ([a], [a])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
l [a]
us
([a]
qs,[a]
ps) = Int -> [a] -> ([a], [a])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
l [a]
ks
([a]
ns,[a]
ms) = Int -> [a] -> ([a], [a])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
l [a]
rs
in ([a]
wws,[a]
qs,[a]
ns)([a], [a], [a]) -> [([a], [a], [a])] -> [([a], [a], [a])]
forall a. a -> [a] -> [a]
:[a] -> [a] -> [a] -> [t a] -> [([a], [a], [a])]
helper2F' [a]
vvs [a]
ps [a]
ms [t a]
wss
helper2F' [a]
_ [a]
_ [a]
_ [t a]
_ = []
convF1
:: GWritingSystemPRPLX
-> [(Char,Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [[FlowSoundG]]
convF1 :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [[[PRS]]]
convF1 GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs String
xs
| String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
xs = []
| Bool
otherwise = [ [[PRS]]
tss | [[PRS]]
tss <- GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [[[PRS]]]
createSyllablesPL GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs String
xs ]
convF3
:: GWritingSystemPRPLX
-> [(Char,Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [([String],[[Int8]],[FlowSoundG])]
convF3 :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [([String], [[Int8]], [[PRS]])]
convF3 GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs String
xs
| String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
xs = [([],[],[])]
| Bool
otherwise = [String]
-> [[Int8]]
-> [[PRS]]
-> [[[PRS]]]
-> [([String], [[Int8]], [[PRS]])]
forall b a c d. [b] -> [a] -> [c] -> [[d]] -> [([b], [a], [c])]
helper2F (([[PRS]] -> [String]) -> [[[PRS]]] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (([PRS] -> String) -> [[PRS]] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map [PRS] -> String
showFSG) [[[PRS]]]
tsss) ((Int8 -> [Int8]) -> [Int8] -> [[Int8]]
forall a b. (a -> b) -> [a] -> [b]
map (Int8 -> [Int8] -> [Int8]
forall a. a -> [a] -> [a]
:[]) ([-Int8
128..Int8
127]::[Int8])) [ [PRS]
ts | [[PRS]]
tss <- [[[PRS]]]
qss, [PRS]
ts <- [[PRS]]
tss ] [[[PRS]]]
qss
where tsss :: [[[PRS]]]
tsss = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [[[PRS]]]
createSyllablesPL GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs String
xs
qss :: [[[PRS]]]
qss = [ [[PRS]]
tss | [[PRS]]
tss <- [[[PRS]]]
tsss ]
convF3W
:: GWritingSystemPRPLX
-> [(Char,Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [(String,[[Int8]])]
convF3W :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [(String, [[Int8]])]
convF3W GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs String
xs
| String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
xs = [([],[])]
| Bool
otherwise = (([String], [[Int8]], [[PRS]]) -> String -> (String, [[Int8]]))
-> [([String], [[Int8]], [[PRS]])]
-> [String]
-> [(String, [[Int8]])]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\([String]
_,[[Int8]]
ys,[[PRS]]
_) String
ts -> (String
ts,[[Int8]]
ys)) (GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [([String], [[Int8]], [[PRS]])]
convF3 GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs String
xs) ([String] -> [(String, [[Int8]])])
-> (String -> [String]) -> String -> [(String, [[Int8]])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words (String -> [(String, [[Int8]])]) -> String -> [(String, [[Int8]])]
forall a b. (a -> b) -> a -> b
$ String
xs
convFI
:: GWritingSystemPRPLX
-> [(Char,Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> String
-> [[[Int8]]]
convFI :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> String
-> [[[Int8]]]
convFI GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs String
ts = (String -> [[Int8]]) -> [String] -> [[[Int8]]]
forall a b. (a -> b) -> [a] -> [b]
map String -> [[Int8]]
f ([String] -> [[[Int8]]])
-> (String -> [String]) -> String -> [[[Int8]]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words
where !f :: String -> [[Int8]]
f = [[Int8]] -> [(String, [[Int8]])] -> String -> [[Int8]]
forall a b. Ord a => b -> [(a, b)] -> a -> b
getBFstL' [] (GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [(String, [[Int8]])]
convF3W GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs String
ts)
convFSL
:: GWritingSystemPRPLX
-> [(Char,Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> ReadyForConstructionPL
-> String
convFSL :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> ReadyForConstructionPL
-> String
convFSL GWritingSystemPRPLX
wrs [(Char, Char)]
ps CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs String
ts r :: ReadyForConstructionPL
r@(StrG String
xs) = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String) -> (String -> [String]) -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[String]] -> [String])
-> (String -> [[String]]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [[String]] -> [[String]]
forall a. a -> [a] -> [a]
intersperse [String
" "] ([[String]] -> [[String]])
-> (String -> [[String]]) -> String -> [[String]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([String], [[Int8]], [[PRS]]) -> [String])
-> [([String], [[Int8]], [[PRS]])] -> [[String]]
forall a b. (a -> b) -> [a] -> [b]
map (\([String]
ks,[[Int8]]
_,[[PRS]]
_)-> [String]
ks) ([([String], [[Int8]], [[PRS]])] -> [[String]])
-> (String -> [([String], [[Int8]], [[PRS]])])
-> String
-> [[String]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [([String], [[Int8]], [[PRS]])]
convF3 GWritingSystemPRPLX
wrs [(Char, Char)]
ps CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String
xs
where js :: ([[[Int8]]], [[String]])
js = [([[Int8]], [String])] -> ([[[Int8]]], [[String]])
forall a b. [(a, b)] -> ([a], [b])
unzip ([([[Int8]], [String])] -> ([[[Int8]]], [[String]]))
-> (String -> [([[Int8]], [String])])
-> String
-> ([[[Int8]]], [[String]])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([String], [[Int8]], [[PRS]]) -> ([[Int8]], [String]))
-> [([String], [[Int8]], [[PRS]])] -> [([[Int8]], [String])]
forall a b. (a -> b) -> [a] -> [b]
map (\([String]
rs,[[Int8]]
ps,[[PRS]]
_) -> ([[Int8]]
ps,[String]
rs)) ([([String], [[Int8]], [[PRS]])] -> [([[Int8]], [String])])
-> (String -> [([String], [[Int8]], [[PRS]])])
-> String
-> [([[Int8]], [String])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [([String], [[Int8]], [[PRS]])]
convF3 GWritingSystemPRPLX
wrs [(Char, Char)]
ps CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs (String -> ([[[Int8]]], [[String]]))
-> String -> ([[[Int8]]], [[String]])
forall a b. (a -> b) -> a -> b
$ String
ts
convFSL GWritingSystemPRPLX
wrs [(Char, Char)]
ps CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs String
ts r :: ReadyForConstructionPL
r@(FSLG [[[Int8]]]
tsss) = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([[[Int8]]] -> [String]) -> [[[Int8]]] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[String]] -> [String])
-> ([[[Int8]]] -> [[String]]) -> [[[Int8]]] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [[String]] -> [[String]]
forall a. a -> [a] -> [a]
intersperse [String
" "] ([[String]] -> [[String]])
-> ([[[Int8]]] -> [[String]]) -> [[[Int8]]] -> [[String]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([[Int8]] -> [String]) -> [[[Int8]]] -> [[String]]
forall a b. (a -> b) -> [a] -> [b]
map (([Int8] -> String) -> [[Int8]] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String -> [([Int8], String)] -> [Int8] -> String
forall a b. Ord a => b -> [(a, b)] -> a -> b
getBFstLSorted' String
" " [([Int8], String)]
ks) ) ([[[Int8]]] -> String) -> [[[Int8]]] -> String
forall a b. (a -> b) -> a -> b
$ [[[Int8]]]
tsss
where js :: ([[[Int8]]], [[String]])
js = [([[Int8]], [String])] -> ([[[Int8]]], [[String]])
forall a b. [(a, b)] -> ([a], [b])
unzip ([([[Int8]], [String])] -> ([[[Int8]]], [[String]]))
-> (String -> [([[Int8]], [String])])
-> String
-> ([[[Int8]]], [[String]])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([String], [[Int8]], [[PRS]]) -> ([[Int8]], [String]))
-> [([String], [[Int8]], [[PRS]])] -> [([[Int8]], [String])]
forall a b. (a -> b) -> [a] -> [b]
map (\([String]
rs,[[Int8]]
ps,[[PRS]]
_) -> ([[Int8]]
ps,[String]
rs)) ([([String], [[Int8]], [[PRS]])] -> [([[Int8]], [String])])
-> (String -> [([String], [[Int8]], [[PRS]])])
-> String
-> [([[Int8]], [String])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [([String], [[Int8]], [[PRS]])]
convF3 GWritingSystemPRPLX
wrs [(Char, Char)]
ps CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs (String -> ([[[Int8]]], [[String]]))
-> String -> ([[[Int8]]], [[String]])
forall a b. (a -> b) -> a -> b
$ String
ts
ks :: [([Int8], String)]
ks = [[Int8]] -> [String] -> [([Int8], String)]
forall a b. [a] -> [b] -> [(a, b)]
zip ([[[Int8]]] -> [[Int8]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[[Int8]]] -> [[Int8]])
-> (([[[Int8]]], [[String]]) -> [[[Int8]]])
-> ([[[Int8]]], [[String]])
-> [[Int8]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([[[Int8]]], [[String]]) -> [[[Int8]]]
forall a b. (a, b) -> a
fst (([[[Int8]]], [[String]]) -> [[Int8]])
-> ([[[Int8]]], [[String]]) -> [[Int8]]
forall a b. (a -> b) -> a -> b
$ ([[[Int8]]], [[String]])
js) ([[String]] -> [String]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[String]] -> [String])
-> (([[[Int8]]], [[String]]) -> [[String]])
-> ([[[Int8]]], [[String]])
-> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([[[Int8]]], [[String]]) -> [[String]]
forall a b. (a, b) -> b
snd (([[[Int8]]], [[String]]) -> [String])
-> ([[[Int8]]], [[String]]) -> [String]
forall a b. (a -> b) -> a -> b
$ ([[[Int8]]], [[String]])
js)
weightsString3IO
:: GWritingSystemPRPLX
-> [(Char,Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> Bool
-> String
-> IO ([[FlowSoundG]],[[[[Int8]]] -> [[Double]]],ReadyForConstructionPL)
weightsString3IO :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> Bool
-> String
-> IO
([[[PRS]]], [[[[Int8]]] -> [[Double]]], ReadyForConstructionPL)
weightsString3IO GWritingSystemPRPLX
wrs [(Char, Char)]
ps CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs Bool
bool String
bs
| Bool
bool = do
([[[PRS]]]
syllDs1,[SyllWeightsG]
sylws,[[[Int8]]]
fsls0) <- GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> IO ([[[PRS]]], [SyllWeightsG], [[[Int8]]])
weightStringIO GWritingSystemPRPLX
wrs [(Char, Char)]
ps CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs String
bs
let syllableDurationsD2s :: [[[[Int8]]] -> [[Double]]]
syllableDurationsD2s = [[SyllWeightsG] -> [[[Int8]]] -> [[Double]]
weights2SyllableDurationsD [SyllWeightsG]
sylws]
([[[PRS]]], [[[[Int8]]] -> [[Double]]], ReadyForConstructionPL)
-> IO
([[[PRS]]], [[[[Int8]]] -> [[Double]]], ReadyForConstructionPL)
forall (m :: * -> *) a. Monad m => a -> m a
return ([[[PRS]]]
syllDs1,[[[[Int8]]] -> [[Double]]]
syllableDurationsD2s,[[[Int8]]] -> ReadyForConstructionPL
FSLG [[[Int8]]]
fsls0)
| Bool
otherwise = ([[[PRS]]], [[[[Int8]]] -> [[Double]]], ReadyForConstructionPL)
-> IO
([[[PRS]]], [[[[Int8]]] -> [[Double]]], ReadyForConstructionPL)
forall (m :: * -> *) a. Monad m => a -> m a
return ([],[],[[[Int8]]] -> ReadyForConstructionPL
FSLG [])
weightsString3NIO
:: GWritingSystemPRPLX
-> [(Char,Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> Int
-> Bool
-> String
-> IO ([[FlowSoundG]],[[[[Int8]]] -> [[Double]]],ReadyForConstructionPL)
weightsString3NIO :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> Int
-> Bool
-> String
-> IO
([[[PRS]]], [[[[Int8]]] -> [[Double]]], ReadyForConstructionPL)
weightsString3NIO GWritingSystemPRPLX
wrs [(Char, Char)]
ps CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs Int
n Bool
bool String
bs
| Bool
bool = (\([[[PRS]]]
syllDs1,[[SyllWeightsG]]
sylws,[[[Int8]]]
fsls0) -> ([[[PRS]]]
syllDs1,([SyllWeightsG] -> [[[Int8]]] -> [[Double]])
-> [[SyllWeightsG]] -> [[[[Int8]]] -> [[Double]]]
forall a b. (a -> b) -> [a] -> [b]
map [SyllWeightsG] -> [[[Int8]]] -> [[Double]]
weights2SyllableDurationsD [[SyllWeightsG]]
sylws,[[[Int8]]] -> ReadyForConstructionPL
FSLG [[[Int8]]]
fsls0)) (([[[PRS]]], [[SyllWeightsG]], [[[Int8]]])
-> ([[[PRS]]], [[[[Int8]]] -> [[Double]]], ReadyForConstructionPL))
-> IO ([[[PRS]]], [[SyllWeightsG]], [[[Int8]]])
-> IO
([[[PRS]]], [[[[Int8]]] -> [[Double]]], ReadyForConstructionPL)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> Int
-> String
-> IO ([[[PRS]]], [[SyllWeightsG]], [[[Int8]]])
weightStringNIO GWritingSystemPRPLX
wrs [(Char, Char)]
ps CharPhoneticClassification
arr SegmentRulesG
hs String
us String
vs Int
n String
bs
| Bool
otherwise = ([[[PRS]]], [[[[Int8]]] -> [[Double]]], ReadyForConstructionPL)
-> IO
([[[PRS]]], [[[[Int8]]] -> [[Double]]], ReadyForConstructionPL)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([],[],[[[Int8]]] -> ReadyForConstructionPL
FSLG [])