{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -funbox-strict-fields -fobject-code #-}
{-# OPTIONS_HADDOCK show-extensions #-}
module Aftovolio.General.Base (
PhoneticElement (..),
PhoneticsRepresentationPL (..),
PhoneticsRepresentationPLX (..),
Generations,
InterGenerationsString,
WritingSystemPRPLX,
GWritingSystemPRPLX,
PhoneticRepresentationXInter,
IGWritingSystemPRPLX,
fromX2PRPL,
fromPhoneticRX,
isPRC,
isPRAfterC,
isPRBeforeC,
isPREmptyC,
stringToXSG,
stringToXG,
stringToXS,
string2X,
rulesX,
fHelp4,
findSA,
findSAI,
(~=),
compareG,
) where
import Data.Char (isLetter)
import Data.Either
import Data.List (find, groupBy, intercalate, nub, partition, sortBy, words, (\\))
import Data.Maybe (fromJust, isJust)
import Data.Tuple (fst, snd)
import GHC.Arr
import GHC.Base
import GHC.Exts
import GHC.Int (Int8 (..))
import GHC.List
import GHC.Num ((-))
import Text.Show (Show (..))
data PhoneticsRepresentationPL
= PR {PhoneticsRepresentationPL -> String
string :: String, PhoneticsRepresentationPL -> String
afterString :: String, PhoneticsRepresentationPL -> String
beforeString :: String}
| PRAfter {string :: String, afterString :: String}
| PRBefore {string :: String, beforeString :: String}
| PREmpty {string :: String}
deriving (PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool
(PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool)
-> (PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool)
-> Eq PhoneticsRepresentationPL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool
== :: PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool
$c/= :: PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool
/= :: PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool
Eq, Eq PhoneticsRepresentationPL
Eq PhoneticsRepresentationPL =>
(PhoneticsRepresentationPL
-> PhoneticsRepresentationPL -> Ordering)
-> (PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool)
-> (PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool)
-> (PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool)
-> (PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool)
-> (PhoneticsRepresentationPL
-> PhoneticsRepresentationPL -> PhoneticsRepresentationPL)
-> (PhoneticsRepresentationPL
-> PhoneticsRepresentationPL -> PhoneticsRepresentationPL)
-> Ord PhoneticsRepresentationPL
PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool
PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Ordering
PhoneticsRepresentationPL
-> PhoneticsRepresentationPL -> PhoneticsRepresentationPL
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
$ccompare :: PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Ordering
compare :: PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Ordering
$c< :: PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool
< :: PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool
$c<= :: PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool
<= :: PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool
$c> :: PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool
> :: PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool
$c>= :: PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool
>= :: PhoneticsRepresentationPL -> PhoneticsRepresentationPL -> Bool
$cmax :: PhoneticsRepresentationPL
-> PhoneticsRepresentationPL -> PhoneticsRepresentationPL
max :: PhoneticsRepresentationPL
-> PhoneticsRepresentationPL -> PhoneticsRepresentationPL
$cmin :: PhoneticsRepresentationPL
-> PhoneticsRepresentationPL -> PhoneticsRepresentationPL
min :: PhoneticsRepresentationPL
-> PhoneticsRepresentationPL -> PhoneticsRepresentationPL
Ord)
instance Show PhoneticsRepresentationPL where
show :: PhoneticsRepresentationPL -> String
show (PR String
xs String
ys String
zs) = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
" " [String
"R", ShowS
forall a. Show a => a -> String
show String
zs, ShowS
forall a. Show a => a -> String
show String
xs, ShowS
forall a. Show a => a -> String
show String
ys]
show (PRAfter String
xs String
ys) = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
" " [String
"A", ShowS
forall a. Show a => a -> String
show String
xs, ShowS
forall a. Show a => a -> String
show String
ys]
show (PRBefore String
xs String
zs) = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
" " [String
"B", ShowS
forall a. Show a => a -> String
show String
zs, ShowS
forall a. Show a => a -> String
show String
xs]
show (PREmpty String
xs) = String
"E " String -> ShowS
forall a. Monoid a => a -> a -> a
`mappend` ShowS
forall a. Show a => a -> String
show String
xs
class PhoneticElement a where
readPEMaybe :: String -> Maybe a
instance PhoneticElement PhoneticsRepresentationPL where
readPEMaybe :: String -> Maybe PhoneticsRepresentationPL
readPEMaybe String
rs
| Bool -> Bool
not (Bool -> Bool) -> (String -> Bool) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> Bool
forall a. (a -> Bool) -> [a] -> Bool
any Char -> Bool
isLetter (String -> Bool) -> String -> Bool
forall a b. (a -> b) -> a -> b
$ String
rs = Maybe PhoneticsRepresentationPL
forall a. Maybe a
Nothing
| Bool
otherwise = case String
ys of
String
"R" -> case [String]
yss of
[String
zs, String
xs, String
ts] -> PhoneticsRepresentationPL -> Maybe PhoneticsRepresentationPL
forall a. a -> Maybe a
Just (String -> String -> String -> PhoneticsRepresentationPL
PR String
xs String
ts String
zs)
[String]
_ -> Maybe PhoneticsRepresentationPL
forall a. Maybe a
Nothing
String
"A" -> case [String]
yss of
[String
xs, String
ts] -> PhoneticsRepresentationPL -> Maybe PhoneticsRepresentationPL
forall a. a -> Maybe a
Just (String -> String -> PhoneticsRepresentationPL
PRAfter String
xs String
ts)
[String]
_ -> Maybe PhoneticsRepresentationPL
forall a. Maybe a
Nothing
String
"B" -> case [String]
yss of
[String
zs, String
xs] -> PhoneticsRepresentationPL -> Maybe PhoneticsRepresentationPL
forall a. a -> Maybe a
Just (String -> String -> PhoneticsRepresentationPL
PRBefore String
xs String
zs)
[String]
_ -> Maybe PhoneticsRepresentationPL
forall a. Maybe a
Nothing
String
"E" -> case [String]
yss of
[String
xs] -> PhoneticsRepresentationPL -> Maybe PhoneticsRepresentationPL
forall a. a -> Maybe a
Just (String -> PhoneticsRepresentationPL
PREmpty String
xs)
[String]
_ -> Maybe PhoneticsRepresentationPL
forall a. Maybe a
Nothing
String
_ -> Maybe PhoneticsRepresentationPL
forall a. Maybe a
Nothing
where
(String
ys : [String]
yss) = String -> [String]
words String
rs
data PhoneticsRepresentationPLX
= PRC
{ PhoneticsRepresentationPLX -> String
stringX :: String
, PhoneticsRepresentationPLX -> String
afterStringX :: String
, PhoneticsRepresentationPLX -> String
beforeStringX :: String
, PhoneticsRepresentationPLX -> Char
char :: Char
, PhoneticsRepresentationPLX -> String
string1 :: String
}
| PRAfterC
{stringX :: String, afterStringX :: String, char :: Char, string1 :: String}
| PRBeforeC
{stringX :: String, beforeStringX :: String, char :: Char, string1 :: String}
| PREmptyC {stringX :: String, char :: Char, string1 :: String}
deriving (PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX -> Bool
(PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX -> Bool)
-> (PhoneticsRepresentationPLX
-> PhoneticsRepresentationPLX -> Bool)
-> Eq PhoneticsRepresentationPLX
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX -> Bool
== :: PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX -> Bool
$c/= :: PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX -> Bool
/= :: PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX -> Bool
Eq, Eq PhoneticsRepresentationPLX
Eq PhoneticsRepresentationPLX =>
(PhoneticsRepresentationPLX
-> PhoneticsRepresentationPLX -> Ordering)
-> (PhoneticsRepresentationPLX
-> PhoneticsRepresentationPLX -> Bool)
-> (PhoneticsRepresentationPLX
-> PhoneticsRepresentationPLX -> Bool)
-> (PhoneticsRepresentationPLX
-> PhoneticsRepresentationPLX -> Bool)
-> (PhoneticsRepresentationPLX
-> PhoneticsRepresentationPLX -> Bool)
-> (PhoneticsRepresentationPLX
-> PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX)
-> (PhoneticsRepresentationPLX
-> PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX)
-> Ord PhoneticsRepresentationPLX
PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX -> Bool
PhoneticsRepresentationPLX
-> PhoneticsRepresentationPLX -> Ordering
PhoneticsRepresentationPLX
-> PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
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
$ccompare :: PhoneticsRepresentationPLX
-> PhoneticsRepresentationPLX -> Ordering
compare :: PhoneticsRepresentationPLX
-> PhoneticsRepresentationPLX -> Ordering
$c< :: PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX -> Bool
< :: PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX -> Bool
$c<= :: PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX -> Bool
<= :: PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX -> Bool
$c> :: PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX -> Bool
> :: PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX -> Bool
$c>= :: PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX -> Bool
>= :: PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX -> Bool
$cmax :: PhoneticsRepresentationPLX
-> PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
max :: PhoneticsRepresentationPLX
-> PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
$cmin :: PhoneticsRepresentationPLX
-> PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
min :: PhoneticsRepresentationPLX
-> PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
Ord)
instance Show PhoneticsRepresentationPLX where
show :: PhoneticsRepresentationPLX -> String
show (PRC String
xs String
ys String
zs Char
c String
us) = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
" " [String
"RC", ShowS
forall a. Show a => a -> String
show String
zs, ShowS
forall a. Show a => a -> String
show String
xs, ShowS
forall a. Show a => a -> String
show String
ys, Char
'\'' Char -> ShowS
forall a. a -> [a] -> [a]
: Char
c Char -> ShowS
forall a. a -> [a] -> [a]
: String
"\'", String
us]
show (PRAfterC String
xs String
ys Char
c String
us) = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
" " [String
"AC", ShowS
forall a. Show a => a -> String
show String
xs, ShowS
forall a. Show a => a -> String
show String
ys, Char
'\'' Char -> ShowS
forall a. a -> [a] -> [a]
: Char
c Char -> ShowS
forall a. a -> [a] -> [a]
: String
"\'", String
us]
show (PRBeforeC String
xs String
zs Char
c String
us) = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
" " [String
"BC", ShowS
forall a. Show a => a -> String
show String
zs, ShowS
forall a. Show a => a -> String
show String
xs, Char
'\'' Char -> ShowS
forall a. a -> [a] -> [a]
: Char
c Char -> ShowS
forall a. a -> [a] -> [a]
: String
"\'", String
us]
show (PREmptyC String
xs Char
c String
us) = String
"EC " String -> ShowS
forall a. Monoid a => a -> a -> a
`mappend` ShowS
forall a. Show a => a -> String
show String
xs String -> ShowS
forall a. Monoid a => a -> a -> a
`mappend` (Char
' ' Char -> ShowS
forall a. a -> [a] -> [a]
: Char
'\'' Char -> ShowS
forall a. a -> [a] -> [a]
: Char
c Char -> ShowS
forall a. a -> [a] -> [a]
: String
"\'") String -> ShowS
forall a. Monoid a => a -> a -> a
`mappend` String
us
instance PhoneticElement PhoneticsRepresentationPLX where
readPEMaybe :: String -> Maybe PhoneticsRepresentationPLX
readPEMaybe String
rs
| Bool -> Bool
not (Bool -> Bool) -> (String -> Bool) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> Bool
forall a. (a -> Bool) -> [a] -> Bool
any Char -> Bool
isLetter (String -> Bool) -> String -> Bool
forall a b. (a -> b) -> a -> b
$ String
rs = Maybe PhoneticsRepresentationPLX
forall a. Maybe a
Nothing
| Bool
otherwise = case String
ys of
String
"RC" -> case [String]
yss of
[String
zs, String
xs, String
ts, String
cs, String
us] -> case String
cs of
Char
'\'' : Char
c : String
"\'" -> PhoneticsRepresentationPLX -> Maybe PhoneticsRepresentationPLX
forall a. a -> Maybe a
Just (String
-> String -> String -> Char -> String -> PhoneticsRepresentationPLX
PRC String
xs String
ts String
zs Char
c String
us)
String
_ -> Maybe PhoneticsRepresentationPLX
forall a. Maybe a
Nothing
[String]
_ -> Maybe PhoneticsRepresentationPLX
forall a. Maybe a
Nothing
String
"AC" -> case [String]
yss of
[String
xs, String
ts, String
cs, String
us] -> case String
cs of
Char
'\'' : Char
c : String
"\'" -> PhoneticsRepresentationPLX -> Maybe PhoneticsRepresentationPLX
forall a. a -> Maybe a
Just (String -> String -> Char -> String -> PhoneticsRepresentationPLX
PRAfterC String
xs String
ts Char
c String
us)
String
_ -> Maybe PhoneticsRepresentationPLX
forall a. Maybe a
Nothing
[String]
_ -> Maybe PhoneticsRepresentationPLX
forall a. Maybe a
Nothing
String
"BC" -> case [String]
yss of
[String
zs, String
xs, String
cs, String
us] -> case String
cs of
Char
'\'' : Char
c : String
"\'" -> PhoneticsRepresentationPLX -> Maybe PhoneticsRepresentationPLX
forall a. a -> Maybe a
Just (String -> String -> Char -> String -> PhoneticsRepresentationPLX
PRBeforeC String
xs String
zs Char
c String
us)
String
_ -> Maybe PhoneticsRepresentationPLX
forall a. Maybe a
Nothing
[String]
_ -> Maybe PhoneticsRepresentationPLX
forall a. Maybe a
Nothing
String
"EC" -> case [String]
yss of
[String
xs, String
cs, String
us] -> case String
cs of
Char
'\'' : Char
c : String
"\'" -> PhoneticsRepresentationPLX -> Maybe PhoneticsRepresentationPLX
forall a. a -> Maybe a
Just (String -> Char -> String -> PhoneticsRepresentationPLX
PREmptyC String
xs Char
c String
us)
String
_ -> Maybe PhoneticsRepresentationPLX
forall a. Maybe a
Nothing
[String]
_ -> Maybe PhoneticsRepresentationPLX
forall a. Maybe a
Nothing
String
_ -> Maybe PhoneticsRepresentationPLX
forall a. Maybe a
Nothing
where
(String
ys : [String]
yss) = String -> [String]
words String
rs
isPRC :: PhoneticsRepresentationPLX -> Bool
isPRC :: PhoneticsRepresentationPLX -> Bool
isPRC (PRC String
_ String
_ String
_ Char
_ String
_) = Bool
True
isPRC PhoneticsRepresentationPLX
_ = Bool
False
isPRAfterC :: PhoneticsRepresentationPLX -> Bool
isPRAfterC :: PhoneticsRepresentationPLX -> Bool
isPRAfterC (PRAfterC String
_ String
_ Char
_ String
_) = Bool
True
isPRAfterC PhoneticsRepresentationPLX
_ = Bool
False
isPRBeforeC :: PhoneticsRepresentationPLX -> Bool
isPRBeforeC :: PhoneticsRepresentationPLX -> Bool
isPRBeforeC (PRBeforeC String
_ String
_ Char
_ String
_) = Bool
True
isPRBeforeC PhoneticsRepresentationPLX
_ = Bool
False
isPREmptyC :: PhoneticsRepresentationPLX -> Bool
isPREmptyC :: PhoneticsRepresentationPLX -> Bool
isPREmptyC (PREmptyC String
_ Char
_ String
_) = Bool
True
isPREmptyC PhoneticsRepresentationPLX
_ = Bool
False
fromX2PRPL :: PhoneticsRepresentationPLX -> PhoneticsRepresentationPL
fromX2PRPL :: PhoneticsRepresentationPLX -> PhoneticsRepresentationPL
fromX2PRPL (PREmptyC String
xs Char
_ String
_) = String -> PhoneticsRepresentationPL
PREmpty String
xs
fromX2PRPL (PRAfterC String
xs String
ys Char
_ String
_) = String -> String -> PhoneticsRepresentationPL
PRAfter String
xs String
ys
fromX2PRPL (PRBeforeC String
xs String
zs Char
_ String
_) = String -> String -> PhoneticsRepresentationPL
PRBefore String
xs String
zs
fromX2PRPL (PRC String
xs String
ys String
zs Char
_ String
_) = String -> String -> String -> PhoneticsRepresentationPL
PR String
xs String
ys String
zs
{-# INLINE fromX2PRPL #-}
rulesX :: PhoneticsRepresentationPLX -> Char
rulesX :: PhoneticsRepresentationPLX -> Char
rulesX = PhoneticsRepresentationPLX -> Char
char
{-# INLINE rulesX #-}
stringToXS :: WritingSystemPRPLX -> String -> [String]
stringToXS :: [PhoneticsRepresentationPLX] -> String -> [String]
stringToXS [PhoneticsRepresentationPLX]
xs String
ys = String
ks String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String] -> Int -> String -> [String]
forall {a}. Eq a => [[a]] -> Int -> [a] -> [[a]]
stringToX' [String]
zss Int
l String
ts
where
!zss :: [String]
zss = [String] -> [String]
forall a. Eq a => [a] -> [a]
nub ([String] -> [String])
-> ([PhoneticsRepresentationPLX] -> [String])
-> [PhoneticsRepresentationPLX]
-> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PhoneticsRepresentationPLX -> String)
-> [PhoneticsRepresentationPLX] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map PhoneticsRepresentationPLX -> String
stringX ([PhoneticsRepresentationPLX] -> [String])
-> [PhoneticsRepresentationPLX] -> [String]
forall a b. (a -> b) -> a -> b
$ [PhoneticsRepresentationPLX]
xs
!l :: Int
l = [Int] -> Int
forall a. (Ord a, HasCallStack) => [a] -> a
maximum ([Int] -> Int) -> ([String] -> [Int]) -> [String] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Int) -> [String] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map String -> Int
forall a. [a] -> Int
length ([String] -> Int) -> [String] -> Int
forall a b. (a -> b) -> a -> b
$ [String]
zss
f :: [a] -> Int -> [[a]] -> ([a], [a])
f [a]
ys Int
l [[a]]
zss =
Int -> [a] -> ([a], [a])
forall a. Int -> [a] -> ([a], [a])
splitAt
( (\[Int]
xs -> if [Int] -> Bool
forall a. [a] -> Bool
null [Int]
xs then Int
1 else [Int] -> Int
forall a. HasCallStack => [a] -> a
head [Int]
xs) ([Int] -> Int) -> ([Int] -> [Int]) -> [Int] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Bool) -> [Int] -> [Int]
forall a. (a -> Bool) -> [a] -> [a]
filter (\Int
n -> [a] -> [[a]] -> Bool
forall a. Eq a => a -> [a] -> Bool
elem (Int -> [a] -> [a]
forall a. Int -> [a] -> [a]
take Int
n [a]
ys) [[a]]
zss) ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$
[Int
l, Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1 .. Int
1]
)
[a]
ys
{-# INLINE f #-}
(!String
ks, !String
ts) = String -> Int -> [String] -> (String, String)
forall {a}. Eq a => [a] -> Int -> [[a]] -> ([a], [a])
f String
ys Int
l [String]
zss
stringToX' :: [[a]] -> Int -> [a] -> [[a]]
stringToX' [[a]]
rss Int
m [a]
vs = [a]
bs [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: [[a]] -> Int -> [a] -> [[a]]
stringToX' [[a]]
rss Int
m [a]
us
where
(![a]
bs, ![a]
us) = [a] -> Int -> [[a]] -> ([a], [a])
forall {a}. Eq a => [a] -> Int -> [[a]] -> ([a], [a])
f [a]
vs Int
m [[a]]
rss
string2X :: WritingSystemPRPLX -> String -> [PhoneticsRepresentationPLX]
string2X :: [PhoneticsRepresentationPLX]
-> String -> [PhoneticsRepresentationPLX]
string2X [PhoneticsRepresentationPLX]
xs = GWritingSystemPRPLX -> String -> [PhoneticsRepresentationPLX]
stringToXG [([PhoneticsRepresentationPLX]
zs, Generations
1), ([PhoneticsRepresentationPLX]
ys, Generations
0)]
where
([PhoneticsRepresentationPLX]
ys, [PhoneticsRepresentationPLX]
zs) = (PhoneticsRepresentationPLX -> Bool)
-> [PhoneticsRepresentationPLX]
-> ([PhoneticsRepresentationPLX], [PhoneticsRepresentationPLX])
forall a. (a -> Bool) -> [a] -> ([a], [a])
partition PhoneticsRepresentationPLX -> Bool
isPREmptyC [PhoneticsRepresentationPLX]
xs
{-# INLINE string2X #-}
type Generations = Int8
type InterGenerationsString = String
type WritingSystemPRPLX = [PhoneticsRepresentationPLX]
type GWritingSystemPRPLX = [([PhoneticsRepresentationPLX], Generations)]
type PhoneticRepresentationXInter =
Either PhoneticsRepresentationPLX InterGenerationsString
fromPhoneticRX ::
[PhoneticsRepresentationPLX] ->
[PhoneticRepresentationXInter] ->
[PhoneticsRepresentationPLX]
fromPhoneticRX :: [PhoneticsRepresentationPLX]
-> [PhoneticRepresentationXInter] -> [PhoneticsRepresentationPLX]
fromPhoneticRX [PhoneticsRepresentationPLX]
ts = (PhoneticRepresentationXInter -> [PhoneticsRepresentationPLX])
-> [PhoneticRepresentationXInter] -> [PhoneticsRepresentationPLX]
forall a b. (a -> [b]) -> [a] -> [b]
concatMap ([PhoneticsRepresentationPLX]
-> PhoneticRepresentationXInter -> [PhoneticsRepresentationPLX]
fromInter2X [PhoneticsRepresentationPLX]
ts)
where
fromInter2X ::
[PhoneticsRepresentationPLX] ->
PhoneticRepresentationXInter ->
[PhoneticsRepresentationPLX]
fromInter2X :: [PhoneticsRepresentationPLX]
-> PhoneticRepresentationXInter -> [PhoneticsRepresentationPLX]
fromInter2X [PhoneticsRepresentationPLX]
_ (Left PhoneticsRepresentationPLX
x) = [PhoneticsRepresentationPLX
x]
fromInter2X [PhoneticsRepresentationPLX]
ys (Right String
z) = (PhoneticsRepresentationPLX -> Bool)
-> [PhoneticsRepresentationPLX] -> [PhoneticsRepresentationPLX]
forall a. (a -> Bool) -> [a] -> [a]
filter ((String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
z) (String -> Bool)
-> (PhoneticsRepresentationPLX -> String)
-> PhoneticsRepresentationPLX
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PhoneticsRepresentationPLX -> String
stringX) [PhoneticsRepresentationPLX]
ys
type IGWritingSystemPRPLX = [(PhoneticRepresentationXInter, Generations)]
fHelp4 ::
(a -> Bool) ->
(a -> Bool) ->
(a -> Bool) ->
(a -> Bool) ->
[a] ->
([a], [a], [a], [a])
fHelp4 :: forall a.
(a -> Bool)
-> (a -> Bool)
-> (a -> Bool)
-> (a -> Bool)
-> [a]
-> ([a], [a], [a], [a])
fHelp4 a -> Bool
p1 a -> Bool
p2 a -> Bool
p3 a -> Bool
p4 = (a -> ([a], [a], [a], [a]) -> ([a], [a], [a], [a]))
-> ([a], [a], [a], [a]) -> [a] -> ([a], [a], [a], [a])
forall a b. (a -> b -> b) -> b -> [a] -> b
foldr a -> ([a], [a], [a], [a]) -> ([a], [a], [a], [a])
g ([a], [a], [a], [a])
forall {a} {a} {a} {a}. ([a], [a], [a], [a])
v
where
v :: ([a], [a], [a], [a])
v = ([], [], [], [])
g :: a -> ([a], [a], [a], [a]) -> ([a], [a], [a], [a])
g a
x ([a]
xs1, [a]
xs2, [a]
xs3, [a]
xs4)
| a -> Bool
p1 a
x = (a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
xs1, [a]
xs2, [a]
xs3, [a]
xs4)
| a -> Bool
p2 a
x = ([a]
xs1, a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
xs2, [a]
xs3, [a]
xs4)
| a -> Bool
p3 a
x = ([a]
xs1, [a]
xs2, a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
xs3, [a]
xs4)
| a -> Bool
p4 a
x = ([a]
xs1, [a]
xs2, [a]
xs3, a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a]
xs4)
| Bool
otherwise = ([a]
xs1, [a]
xs2, [a]
xs3, [a]
xs4)
{-# INLINE fHelp4 #-}
(~=) :: PhoneticsRepresentationPL -> PhoneticsRepresentationPLX -> Bool
(PR String
xs String
ys String
zs) ~= :: PhoneticsRepresentationPL -> PhoneticsRepresentationPLX -> Bool
~= (PRC String
xs1 String
ys1 String
zs1 Char
_ String
_) = String
xs String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
xs1 Bool -> Bool -> Bool
&& String
ys String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
ys1 Bool -> Bool -> Bool
&& String
zs String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
zs1
(PRAfter String
xs String
ys) ~= (PRAfterC String
xs1 String
ys1 Char
_ String
_) = String
xs String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
xs1 Bool -> Bool -> Bool
&& String
ys String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
ys1
(PRBefore String
ys String
zs) ~= (PRBeforeC String
ys1 String
zs1 Char
_ String
_) = String
ys String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
ys1 Bool -> Bool -> Bool
&& String
zs String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
zs1
(PREmpty String
xs) ~= (PREmptyC String
xs1 Char
_ String
_) = String
xs1 String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
xs1
PhoneticsRepresentationPL
_ ~= PhoneticsRepresentationPLX
_ = Bool
False
compareG :: PhoneticsRepresentationPL -> PhoneticsRepresentationPLX -> Ordering
compareG :: PhoneticsRepresentationPL -> PhoneticsRepresentationPLX -> Ordering
compareG (PR String
xs String
ys String
zs) (PRC String
xs1 String
ys1 String
zs1 Char
_ String
_)
| String
xs String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
xs1 = String -> String -> Ordering
forall a. Ord a => a -> a -> Ordering
compare String
xs String
xs1
| String
ys String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
ys1 = String -> String -> Ordering
forall a. Ord a => a -> a -> Ordering
compare String
ys String
ys1
| String
zs String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
zs1 = String -> String -> Ordering
forall a. Ord a => a -> a -> Ordering
compare String
zs String
zs1
| Bool
otherwise = Ordering
EQ
compareG (PR String
_ String
_ String
_) PhoneticsRepresentationPLX
_ = Ordering
LT
compareG (PREmpty String
xs) (PREmptyC String
xs1 Char
_ String
_)
| String
xs String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
xs1 = String -> String -> Ordering
forall a. Ord a => a -> a -> Ordering
compare String
xs String
xs1
| Bool
otherwise = Ordering
EQ
compareG (PREmpty String
_) PhoneticsRepresentationPLX
_ = Ordering
GT
compareG (PRAfter String
xs String
ys) (PRAfterC String
xs1 String
ys1 Char
_ String
_)
| String
xs String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
xs1 = String -> String -> Ordering
forall a. Ord a => a -> a -> Ordering
compare String
xs String
xs1
| String
ys String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
ys1 = String -> String -> Ordering
forall a. Ord a => a -> a -> Ordering
compare String
ys String
ys1
| Bool
otherwise = Ordering
EQ
compareG (PRAfter String
_ String
_) (PRC String
_ String
_ String
_ Char
_ String
_) = Ordering
GT
compareG (PRAfter String
_ String
_) PhoneticsRepresentationPLX
_ = Ordering
LT
compareG (PRBefore String
ys String
zs) (PRBeforeC String
ys1 String
zs1 Char
_ String
_)
| String
ys String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
ys1 = String -> String -> Ordering
forall a. Ord a => a -> a -> Ordering
compare String
ys String
ys1
| String
zs String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
zs1 = String -> String -> Ordering
forall a. Ord a => a -> a -> Ordering
compare String
zs String
zs1
| Bool
otherwise = Ordering
EQ
compareG (PRBefore String
_ String
_) (PREmptyC String
_ Char
_ String
_) = Ordering
LT
compareG (PRBefore String
_ String
_) PhoneticsRepresentationPLX
_ = Ordering
GT
gBF3 ::
(Ix i) =>
(# Int#, PhoneticsRepresentationPLX #) ->
(# Int#, PhoneticsRepresentationPLX #) ->
PhoneticsRepresentationPL ->
Array i PhoneticsRepresentationPLX ->
Maybe PhoneticsRepresentationPLX
gBF3 :: forall i.
Ix i =>
(# Int#, PhoneticsRepresentationPLX #)
-> (# Int#, PhoneticsRepresentationPLX #)
-> PhoneticsRepresentationPL
-> Array i PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
gBF3 (# !Int#
i#, PhoneticsRepresentationPLX
k #) (# !Int#
j#, PhoneticsRepresentationPLX
m #) PhoneticsRepresentationPL
repr Array i PhoneticsRepresentationPLX
arr
| Int# -> Bool
isTrue# ((Int#
j# Int# -> Int# -> Int#
-# Int#
i#) Int# -> Int# -> Int#
># Int#
1#) =
case PhoneticsRepresentationPL -> PhoneticsRepresentationPLX -> Ordering
compareG PhoneticsRepresentationPL
repr PhoneticsRepresentationPLX
p of
Ordering
GT -> (# Int#, PhoneticsRepresentationPLX #)
-> (# Int#, PhoneticsRepresentationPLX #)
-> PhoneticsRepresentationPL
-> Array i PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
forall i.
Ix i =>
(# Int#, PhoneticsRepresentationPLX #)
-> (# Int#, PhoneticsRepresentationPLX #)
-> PhoneticsRepresentationPL
-> Array i PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
gBF3 (# Int#
n#, PhoneticsRepresentationPLX
p #) (# Int#
j#, PhoneticsRepresentationPLX
m #) PhoneticsRepresentationPL
repr Array i PhoneticsRepresentationPLX
arr
Ordering
LT -> (# Int#, PhoneticsRepresentationPLX #)
-> (# Int#, PhoneticsRepresentationPLX #)
-> PhoneticsRepresentationPL
-> Array i PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
forall i.
Ix i =>
(# Int#, PhoneticsRepresentationPLX #)
-> (# Int#, PhoneticsRepresentationPLX #)
-> PhoneticsRepresentationPL
-> Array i PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
gBF3 (# Int#
i#, PhoneticsRepresentationPLX
k #) (# Int#
n#, PhoneticsRepresentationPLX
p #) PhoneticsRepresentationPL
repr Array i PhoneticsRepresentationPLX
arr
Ordering
_ -> PhoneticsRepresentationPLX -> Maybe PhoneticsRepresentationPLX
forall a. a -> Maybe a
Just PhoneticsRepresentationPLX
p
| PhoneticsRepresentationPL
repr PhoneticsRepresentationPL -> PhoneticsRepresentationPLX -> Bool
~= PhoneticsRepresentationPLX
m = PhoneticsRepresentationPLX -> Maybe PhoneticsRepresentationPLX
forall a. a -> Maybe a
Just PhoneticsRepresentationPLX
m
| PhoneticsRepresentationPL
repr PhoneticsRepresentationPL -> PhoneticsRepresentationPLX -> Bool
~= PhoneticsRepresentationPLX
k = PhoneticsRepresentationPLX -> Maybe PhoneticsRepresentationPLX
forall a. a -> Maybe a
Just PhoneticsRepresentationPLX
k
| Bool
otherwise = Maybe PhoneticsRepresentationPLX
forall a. Maybe a
Nothing
where
!n# :: Int#
n# = (Int#
i# Int# -> Int# -> Int#
+# Int#
j#) Int# -> Int# -> Int#
`quotInt#` Int#
2#
!p :: PhoneticsRepresentationPLX
p = Array i PhoneticsRepresentationPLX
-> Int -> PhoneticsRepresentationPLX
forall i e. Array i e -> Int -> e
unsafeAt Array i PhoneticsRepresentationPLX
arr (Int# -> Int
I# Int#
n#)
{-# INLINEABLE gBF3 #-}
findSA ::
PhoneticsRepresentationPL ->
Array Int PhoneticsRepresentationPLX ->
Maybe PhoneticsRepresentationPLX
findSA :: PhoneticsRepresentationPL
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
findSA PhoneticsRepresentationPL
repr Array Int PhoneticsRepresentationPLX
arr = (# Int#, PhoneticsRepresentationPLX #)
-> (# Int#, PhoneticsRepresentationPLX #)
-> PhoneticsRepresentationPL
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
forall i.
Ix i =>
(# Int#, PhoneticsRepresentationPLX #)
-> (# Int#, PhoneticsRepresentationPLX #)
-> PhoneticsRepresentationPL
-> Array i PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
gBF3 (# Int#
i#, PhoneticsRepresentationPLX
k #) (# Int#
j#, PhoneticsRepresentationPLX
m #) PhoneticsRepresentationPL
repr Array Int PhoneticsRepresentationPLX
arr
where
!(I# Int#
i#, I# Int#
j#) = Array Int PhoneticsRepresentationPLX -> (Int, Int)
forall i e. Array i e -> (i, i)
bounds Array Int PhoneticsRepresentationPLX
arr
!k :: PhoneticsRepresentationPLX
k = Array Int PhoneticsRepresentationPLX
-> Int -> PhoneticsRepresentationPLX
forall i e. Array i e -> Int -> e
unsafeAt Array Int PhoneticsRepresentationPLX
arr (Int# -> Int
I# Int#
i#)
!m :: PhoneticsRepresentationPLX
m = Array Int PhoneticsRepresentationPLX
-> Int -> PhoneticsRepresentationPLX
forall i e. Array i e -> Int -> e
unsafeAt Array Int PhoneticsRepresentationPLX
arr (Int# -> Int
I# Int#
i#)
findSAI ::
PhoneticRepresentationXInter ->
(String, String) ->
Array Int PhoneticsRepresentationPLX ->
Maybe PhoneticsRepresentationPLX
findSAI :: PhoneticRepresentationXInter
-> (String, String)
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
findSAI PhoneticRepresentationXInter
repr (String
xs, String
ys) Array Int PhoneticsRepresentationPLX
arr
| PhoneticRepresentationXInter -> Bool
forall a b. Either a b -> Bool
isLeft PhoneticRepresentationXInter
repr =
(# Int#, PhoneticsRepresentationPLX #)
-> (# Int#, PhoneticsRepresentationPLX #)
-> PhoneticsRepresentationPL
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
forall i.
Ix i =>
(# Int#, PhoneticsRepresentationPLX #)
-> (# Int#, PhoneticsRepresentationPLX #)
-> PhoneticsRepresentationPL
-> Array i PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
gBF3
(# Int#
i#, PhoneticsRepresentationPLX
k #)
(# Int#
j#, PhoneticsRepresentationPLX
m #)
(PhoneticsRepresentationPLX -> PhoneticsRepresentationPL
fromX2PRPL (PhoneticsRepresentationPLX -> PhoneticsRepresentationPL)
-> (PhoneticRepresentationXInter -> PhoneticsRepresentationPLX)
-> PhoneticRepresentationXInter
-> PhoneticsRepresentationPL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PhoneticsRepresentationPLX
-> PhoneticRepresentationXInter -> PhoneticsRepresentationPLX
forall a b. a -> Either a b -> a
fromLeft (String -> Char -> String -> PhoneticsRepresentationPLX
PREmptyC String
" " Char
' ' String
" ") (PhoneticRepresentationXInter -> PhoneticsRepresentationPL)
-> PhoneticRepresentationXInter -> PhoneticsRepresentationPL
forall a b. (a -> b) -> a -> b
$ PhoneticRepresentationXInter
repr)
Array Int PhoneticsRepresentationPLX
arr
| Bool
otherwise =
(# Int#, PhoneticsRepresentationPLX #)
-> (# Int#, PhoneticsRepresentationPLX #)
-> PhoneticsRepresentationPL
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
forall i.
Ix i =>
(# Int#, PhoneticsRepresentationPLX #)
-> (# Int#, PhoneticsRepresentationPLX #)
-> PhoneticsRepresentationPL
-> Array i PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
gBF3 (# Int#
i#, PhoneticsRepresentationPLX
k #) (# Int#
j#, PhoneticsRepresentationPLX
m #) (String -> (String, String) -> PhoneticsRepresentationPL
str2PRPL (String -> PhoneticRepresentationXInter -> String
forall b a. b -> Either a b -> b
fromRight [] PhoneticRepresentationXInter
repr) (String
xs, String
ys)) Array Int PhoneticsRepresentationPLX
arr
where
!(I# Int#
i#, I# Int#
j#) = Array Int PhoneticsRepresentationPLX -> (Int, Int)
forall i e. Array i e -> (i, i)
bounds Array Int PhoneticsRepresentationPLX
arr
!k :: PhoneticsRepresentationPLX
k = Array Int PhoneticsRepresentationPLX
-> Int -> PhoneticsRepresentationPLX
forall i e. Array i e -> Int -> e
unsafeAt Array Int PhoneticsRepresentationPLX
arr (Int# -> Int
I# Int#
i#)
!m :: PhoneticsRepresentationPLX
m = Array Int PhoneticsRepresentationPLX
-> Int -> PhoneticsRepresentationPLX
forall i e. Array i e -> Int -> e
unsafeAt Array Int PhoneticsRepresentationPLX
arr (Int# -> Int
I# Int#
i#)
str2PRPL :: String -> (String, String) -> PhoneticsRepresentationPL
str2PRPL :: String -> (String, String) -> PhoneticsRepresentationPL
str2PRPL String
ts ([], []) = String -> PhoneticsRepresentationPL
PREmpty String
ts
str2PRPL String
ts (String
ys, []) = String -> String -> PhoneticsRepresentationPL
PRBefore String
ts String
ys
str2PRPL String
ts ([], String
zs) = String -> String -> PhoneticsRepresentationPL
PRAfter String
ts String
zs
str2PRPL String
ts (String
ys, String
zs) = String -> String -> String -> PhoneticsRepresentationPL
PR String
ts String
zs String
ys
stringToXSG ::
GWritingSystemPRPLX -> Generations -> String -> IGWritingSystemPRPLX
stringToXSG :: GWritingSystemPRPLX
-> Generations -> String -> IGWritingSystemPRPLX
stringToXSG GWritingSystemPRPLX
xs Generations
n String
ys
| (([PhoneticsRepresentationPLX], Generations) -> Bool)
-> GWritingSystemPRPLX -> Bool
forall a. (a -> Bool) -> [a] -> Bool
any ((Generations -> Generations -> Bool
forall a. Eq a => a -> a -> Bool
== Generations
n) (Generations -> Bool)
-> (([PhoneticsRepresentationPLX], Generations) -> Generations)
-> ([PhoneticsRepresentationPLX], Generations)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([PhoneticsRepresentationPLX], Generations) -> Generations
forall a b. (a, b) -> b
snd) GWritingSystemPRPLX
xs Bool -> Bool -> Bool
&& Generations
n Generations -> Generations -> Bool
forall a. Ord a => a -> a -> Bool
> Generations
0 =
GWritingSystemPRPLX
-> Generations -> IGWritingSystemPRPLX -> IGWritingSystemPRPLX
stringToXSGI (GWritingSystemPRPLX
xs GWritingSystemPRPLX -> GWritingSystemPRPLX -> GWritingSystemPRPLX
forall a. Eq a => [a] -> [a] -> [a]
\\ GWritingSystemPRPLX
ts) (Generations
n Generations -> Generations -> Generations
forall a. Num a => a -> a -> a
- Generations
1) (IGWritingSystemPRPLX -> IGWritingSystemPRPLX)
-> ([String] -> IGWritingSystemPRPLX)
-> [String]
-> IGWritingSystemPRPLX
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [PhoneticsRepresentationPLX]
-> Generations -> [String] -> IGWritingSystemPRPLX
forall {t}.
Num t =>
[PhoneticsRepresentationPLX]
-> t -> [String] -> [(PhoneticRepresentationXInter, t)]
xsG [PhoneticsRepresentationPLX]
zs Generations
n ([String] -> IGWritingSystemPRPLX)
-> [String] -> IGWritingSystemPRPLX
forall a b. (a -> b) -> a -> b
$ [String]
pss
| Bool
otherwise =
String -> IGWritingSystemPRPLX
forall a. HasCallStack => String -> a
error
String
"Aftovolio.General.Base.stringToXSG: Not defined for these first two arguments. "
where
!pss :: [String]
pss = [PhoneticsRepresentationPLX] -> String -> [String]
stringToXS ((([PhoneticsRepresentationPLX], Generations)
-> [PhoneticsRepresentationPLX])
-> GWritingSystemPRPLX -> [PhoneticsRepresentationPLX]
forall a b. (a -> [b]) -> [a] -> [b]
concatMap ([PhoneticsRepresentationPLX], Generations)
-> [PhoneticsRepresentationPLX]
forall a b. (a, b) -> a
fst GWritingSystemPRPLX
xs) String
ys
!ts :: GWritingSystemPRPLX
ts = (([PhoneticsRepresentationPLX], Generations) -> Bool)
-> GWritingSystemPRPLX -> GWritingSystemPRPLX
forall a. (a -> Bool) -> [a] -> [a]
filter ((Generations -> Generations -> Bool
forall a. Eq a => a -> a -> Bool
== Generations
n) (Generations -> Bool)
-> (([PhoneticsRepresentationPLX], Generations) -> Generations)
-> ([PhoneticsRepresentationPLX], Generations)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([PhoneticsRepresentationPLX], Generations) -> Generations
forall a b. (a, b) -> b
snd) (GWritingSystemPRPLX -> GWritingSystemPRPLX)
-> GWritingSystemPRPLX -> GWritingSystemPRPLX
forall a b. (a -> b) -> a -> b
$ GWritingSystemPRPLX
xs
!zs :: [PhoneticsRepresentationPLX]
zs = if GWritingSystemPRPLX -> Bool
forall a. [a] -> Bool
null GWritingSystemPRPLX
ts then [] else ([PhoneticsRepresentationPLX], Generations)
-> [PhoneticsRepresentationPLX]
forall a b. (a, b) -> a
fst (([PhoneticsRepresentationPLX], Generations)
-> [PhoneticsRepresentationPLX])
-> (GWritingSystemPRPLX
-> ([PhoneticsRepresentationPLX], Generations))
-> GWritingSystemPRPLX
-> [PhoneticsRepresentationPLX]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GWritingSystemPRPLX -> ([PhoneticsRepresentationPLX], Generations)
forall a. HasCallStack => [a] -> a
head (GWritingSystemPRPLX -> [PhoneticsRepresentationPLX])
-> GWritingSystemPRPLX -> [PhoneticsRepresentationPLX]
forall a b. (a -> b) -> a -> b
$ GWritingSystemPRPLX
ts
xsG1 :: t
-> t
-> [String]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, t)]
xsG1 t
rs t
n (String
k1s : String
k2s : String
k3s : [String]
kss) (!Array Int PhoneticsRepresentationPLX
r2s, !Array Int PhoneticsRepresentationPLX
r3s, !Array Int PhoneticsRepresentationPLX
r4s, !Array Int PhoneticsRepresentationPLX
r5s)
| Maybe PhoneticsRepresentationPLX -> Bool
forall a. Maybe a -> Bool
isJust Maybe PhoneticsRepresentationPLX
x1 =
(String -> PhoneticRepresentationXInter
forall a b. b -> Either a b
Right String
k1s, t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
1) (PhoneticRepresentationXInter, t)
-> [(PhoneticRepresentationXInter, t)]
-> [(PhoneticRepresentationXInter, t)]
forall a. a -> [a] -> [a]
: (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. a -> Either a b
Left (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> (Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX)
-> Maybe PhoneticsRepresentationPLX
-> PhoneticRepresentationXInter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. (a -> b) -> a -> b
$ Maybe PhoneticsRepresentationPLX
x1, t
n) (PhoneticRepresentationXInter, t)
-> [(PhoneticRepresentationXInter, t)]
-> [(PhoneticRepresentationXInter, t)]
forall a. a -> [a] -> [a]
: t
-> t
-> [String]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, t)]
xsG1 t
rs t
n (String
k3s String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
kss) (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
| Maybe PhoneticsRepresentationPLX -> Bool
forall a. Maybe a -> Bool
isJust Maybe PhoneticsRepresentationPLX
x2 = (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. a -> Either a b
Left (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> (Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX)
-> Maybe PhoneticsRepresentationPLX
-> PhoneticRepresentationXInter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. (a -> b) -> a -> b
$ Maybe PhoneticsRepresentationPLX
x2, t
n) (PhoneticRepresentationXInter, t)
-> [(PhoneticRepresentationXInter, t)]
-> [(PhoneticRepresentationXInter, t)]
forall a. a -> [a] -> [a]
: t
-> t
-> [String]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, t)]
xsG1 t
rs t
n (String
k2s String -> [String] -> [String]
forall a. a -> [a] -> [a]
: String
k3s String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
kss) (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
| Maybe PhoneticsRepresentationPLX -> Bool
forall a. Maybe a -> Bool
isJust Maybe PhoneticsRepresentationPLX
x3 =
(String -> PhoneticRepresentationXInter
forall a b. b -> Either a b
Right String
k1s, t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
1) (PhoneticRepresentationXInter, t)
-> [(PhoneticRepresentationXInter, t)]
-> [(PhoneticRepresentationXInter, t)]
forall a. a -> [a] -> [a]
: (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. a -> Either a b
Left (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> (Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX)
-> Maybe PhoneticsRepresentationPLX
-> PhoneticRepresentationXInter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. (a -> b) -> a -> b
$ Maybe PhoneticsRepresentationPLX
x3, t
n) (PhoneticRepresentationXInter, t)
-> [(PhoneticRepresentationXInter, t)]
-> [(PhoneticRepresentationXInter, t)]
forall a. a -> [a] -> [a]
: t
-> t
-> [String]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, t)]
xsG1 t
rs t
n (String
k3s String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
kss) (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
| Maybe PhoneticsRepresentationPLX -> Bool
forall a. Maybe a -> Bool
isJust Maybe PhoneticsRepresentationPLX
x4 = (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. a -> Either a b
Left (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> (Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX)
-> Maybe PhoneticsRepresentationPLX
-> PhoneticRepresentationXInter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. (a -> b) -> a -> b
$ Maybe PhoneticsRepresentationPLX
x4, t
n) (PhoneticRepresentationXInter, t)
-> [(PhoneticRepresentationXInter, t)]
-> [(PhoneticRepresentationXInter, t)]
forall a. a -> [a] -> [a]
: t
-> t
-> [String]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, t)]
xsG1 t
rs t
n (String
k2s String -> [String] -> [String]
forall a. a -> [a] -> [a]
: String
k3s String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
kss) (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
| Bool
otherwise = (String -> PhoneticRepresentationXInter
forall a b. b -> Either a b
Right String
k1s, t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
1) (PhoneticRepresentationXInter, t)
-> [(PhoneticRepresentationXInter, t)]
-> [(PhoneticRepresentationXInter, t)]
forall a. a -> [a] -> [a]
: t
-> t
-> [String]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, t)]
xsG1 t
rs t
n (String
k2s String -> [String] -> [String]
forall a. a -> [a] -> [a]
: String
k3s String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
kss) (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
where
!x1 :: Maybe PhoneticsRepresentationPLX
x1 = PhoneticsRepresentationPL
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
findSA (String -> String -> String -> PhoneticsRepresentationPL
PR String
k2s String
k3s String
k1s) Array Int PhoneticsRepresentationPLX
r2s
!x2 :: Maybe PhoneticsRepresentationPLX
x2 = PhoneticsRepresentationPL
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
findSA (String -> String -> PhoneticsRepresentationPL
PRAfter String
k1s String
k2s) Array Int PhoneticsRepresentationPLX
r3s
!x3 :: Maybe PhoneticsRepresentationPLX
x3 = PhoneticsRepresentationPL
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
findSA (String -> String -> PhoneticsRepresentationPL
PRBefore String
k2s String
k1s) Array Int PhoneticsRepresentationPLX
r4s
!x4 :: Maybe PhoneticsRepresentationPLX
x4 = PhoneticsRepresentationPL
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
findSA (String -> PhoneticsRepresentationPL
PREmpty String
k1s) Array Int PhoneticsRepresentationPLX
r5s
xsG1 t
rs t
n (String
k1s : String
k2s : [String]
kss) (!Array Int PhoneticsRepresentationPLX
r2s, !Array Int PhoneticsRepresentationPLX
r3s, !Array Int PhoneticsRepresentationPLX
r4s, !Array Int PhoneticsRepresentationPLX
r5s)
| Maybe PhoneticsRepresentationPLX -> Bool
forall a. Maybe a -> Bool
isJust Maybe PhoneticsRepresentationPLX
x2 = (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. a -> Either a b
Left (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> (Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX)
-> Maybe PhoneticsRepresentationPLX
-> PhoneticRepresentationXInter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. (a -> b) -> a -> b
$ Maybe PhoneticsRepresentationPLX
x2, t
n) (PhoneticRepresentationXInter, t)
-> [(PhoneticRepresentationXInter, t)]
-> [(PhoneticRepresentationXInter, t)]
forall a. a -> [a] -> [a]
: t
-> t
-> [String]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, t)]
xsG1 t
rs t
n (String
k2s String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
kss) (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
| Maybe PhoneticsRepresentationPLX -> Bool
forall a. Maybe a -> Bool
isJust Maybe PhoneticsRepresentationPLX
x3 =
(String -> PhoneticRepresentationXInter
forall a b. b -> Either a b
Right String
k1s, t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
1) (PhoneticRepresentationXInter, t)
-> [(PhoneticRepresentationXInter, t)]
-> [(PhoneticRepresentationXInter, t)]
forall a. a -> [a] -> [a]
: (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. a -> Either a b
Left (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> (Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX)
-> Maybe PhoneticsRepresentationPLX
-> PhoneticRepresentationXInter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. (a -> b) -> a -> b
$ Maybe PhoneticsRepresentationPLX
x3, t
n) (PhoneticRepresentationXInter, t)
-> [(PhoneticRepresentationXInter, t)]
-> [(PhoneticRepresentationXInter, t)]
forall a. a -> [a] -> [a]
: t
-> t
-> [String]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, t)]
xsG1 t
rs t
n [String]
kss (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
| Maybe PhoneticsRepresentationPLX -> Bool
forall a. Maybe a -> Bool
isJust Maybe PhoneticsRepresentationPLX
x4 = (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. a -> Either a b
Left (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> (Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX)
-> Maybe PhoneticsRepresentationPLX
-> PhoneticRepresentationXInter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. (a -> b) -> a -> b
$ Maybe PhoneticsRepresentationPLX
x4, t
n) (PhoneticRepresentationXInter, t)
-> [(PhoneticRepresentationXInter, t)]
-> [(PhoneticRepresentationXInter, t)]
forall a. a -> [a] -> [a]
: t
-> t
-> [String]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, t)]
xsG1 t
rs t
n (String
k2s String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
kss) (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
| Bool
otherwise = (String -> PhoneticRepresentationXInter
forall a b. b -> Either a b
Right String
k1s, t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
1) (PhoneticRepresentationXInter, t)
-> [(PhoneticRepresentationXInter, t)]
-> [(PhoneticRepresentationXInter, t)]
forall a. a -> [a] -> [a]
: t
-> t
-> [String]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, t)]
xsG1 t
rs t
n (String
k2s String -> [String] -> [String]
forall a. a -> [a] -> [a]
: [String]
kss) (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
where
!x2 :: Maybe PhoneticsRepresentationPLX
x2 = PhoneticsRepresentationPL
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
findSA (String -> String -> PhoneticsRepresentationPL
PRAfter String
k1s String
k2s) Array Int PhoneticsRepresentationPLX
r3s
!x3 :: Maybe PhoneticsRepresentationPLX
x3 = PhoneticsRepresentationPL
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
findSA (String -> String -> PhoneticsRepresentationPL
PRBefore String
k2s String
k1s) Array Int PhoneticsRepresentationPLX
r4s
!x4 :: Maybe PhoneticsRepresentationPLX
x4 = PhoneticsRepresentationPL
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
findSA (String -> PhoneticsRepresentationPL
PREmpty String
k1s) Array Int PhoneticsRepresentationPLX
r5s
xsG1 t
rs t
n [String
k1s] (Array Int PhoneticsRepresentationPLX
_, Array Int PhoneticsRepresentationPLX
_, Array Int PhoneticsRepresentationPLX
_, Array Int PhoneticsRepresentationPLX
r5s)
| Maybe PhoneticsRepresentationPLX -> Bool
forall a. Maybe a -> Bool
isJust Maybe PhoneticsRepresentationPLX
x4 = [(PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. a -> Either a b
Left (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> (Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX)
-> Maybe PhoneticsRepresentationPLX
-> PhoneticRepresentationXInter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. (a -> b) -> a -> b
$ Maybe PhoneticsRepresentationPLX
x4, t
n)]
| Bool
otherwise = [(String -> PhoneticRepresentationXInter
forall a b. b -> Either a b
Right String
k1s, t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
1)]
where
!x4 :: Maybe PhoneticsRepresentationPLX
x4 = PhoneticsRepresentationPL
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
findSA (String -> PhoneticsRepresentationPL
PREmpty String
k1s) Array Int PhoneticsRepresentationPLX
r5s
xsG1 t
rs t
n [] (Array Int PhoneticsRepresentationPLX
_, Array Int PhoneticsRepresentationPLX
_, Array Int PhoneticsRepresentationPLX
_, Array Int PhoneticsRepresentationPLX
_) = []
xsG :: [PhoneticsRepresentationPLX]
-> t -> [String] -> [(PhoneticRepresentationXInter, t)]
xsG [PhoneticsRepresentationPLX]
rs t
n [String]
jss = [PhoneticsRepresentationPLX]
-> t
-> [String]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, t)]
forall {t} {t}.
Num t =>
t
-> t
-> [String]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, t)]
xsG1 [PhoneticsRepresentationPLX]
rs t
n [String]
jss (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
where
(![PhoneticsRepresentationPLX]
r2ls, ![PhoneticsRepresentationPLX]
r3ls, ![PhoneticsRepresentationPLX]
r4ls, ![PhoneticsRepresentationPLX]
r5ls) = (PhoneticsRepresentationPLX -> Bool)
-> (PhoneticsRepresentationPLX -> Bool)
-> (PhoneticsRepresentationPLX -> Bool)
-> (PhoneticsRepresentationPLX -> Bool)
-> [PhoneticsRepresentationPLX]
-> ([PhoneticsRepresentationPLX], [PhoneticsRepresentationPLX],
[PhoneticsRepresentationPLX], [PhoneticsRepresentationPLX])
forall a.
(a -> Bool)
-> (a -> Bool)
-> (a -> Bool)
-> (a -> Bool)
-> [a]
-> ([a], [a], [a], [a])
fHelp4 PhoneticsRepresentationPLX -> Bool
isPRC PhoneticsRepresentationPLX -> Bool
isPRAfterC PhoneticsRepresentationPLX -> Bool
isPRBeforeC PhoneticsRepresentationPLX -> Bool
isPREmptyC [PhoneticsRepresentationPLX]
rs
!r2s :: Array Int PhoneticsRepresentationPLX
r2s = (Int, Int)
-> [PhoneticsRepresentationPLX]
-> Array Int PhoneticsRepresentationPLX
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0, [PhoneticsRepresentationPLX] -> Int
forall a. [a] -> Int
length [PhoneticsRepresentationPLX]
r2ls Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [PhoneticsRepresentationPLX]
r2ls
!r3s :: Array Int PhoneticsRepresentationPLX
r3s = (Int, Int)
-> [PhoneticsRepresentationPLX]
-> Array Int PhoneticsRepresentationPLX
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0, [PhoneticsRepresentationPLX] -> Int
forall a. [a] -> Int
length [PhoneticsRepresentationPLX]
r3ls Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [PhoneticsRepresentationPLX]
r3ls
!r4s :: Array Int PhoneticsRepresentationPLX
r4s = (Int, Int)
-> [PhoneticsRepresentationPLX]
-> Array Int PhoneticsRepresentationPLX
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0, [PhoneticsRepresentationPLX] -> Int
forall a. [a] -> Int
length [PhoneticsRepresentationPLX]
r4ls Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [PhoneticsRepresentationPLX]
r4ls
!r5s :: Array Int PhoneticsRepresentationPLX
r5s = (Int, Int)
-> [PhoneticsRepresentationPLX]
-> Array Int PhoneticsRepresentationPLX
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0, [PhoneticsRepresentationPLX] -> Int
forall a. [a] -> Int
length [PhoneticsRepresentationPLX]
r5ls Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [PhoneticsRepresentationPLX]
r5ls
stringToXSGI ::
GWritingSystemPRPLX ->
Generations ->
IGWritingSystemPRPLX ->
IGWritingSystemPRPLX
stringToXSGI :: GWritingSystemPRPLX
-> Generations -> IGWritingSystemPRPLX -> IGWritingSystemPRPLX
stringToXSGI GWritingSystemPRPLX
xs Generations
n IGWritingSystemPRPLX
ys
| Generations
n Generations -> Generations -> Bool
forall a. Ord a => a -> a -> Bool
> Generations
0 = GWritingSystemPRPLX
-> Generations -> IGWritingSystemPRPLX -> IGWritingSystemPRPLX
stringToXSGI (GWritingSystemPRPLX
xs GWritingSystemPRPLX -> GWritingSystemPRPLX -> GWritingSystemPRPLX
forall a. Eq a => [a] -> [a] -> [a]
\\ GWritingSystemPRPLX
ts) (Generations
n Generations -> Generations -> Generations
forall a. Num a => a -> a -> a
- Generations
1) (IGWritingSystemPRPLX -> IGWritingSystemPRPLX)
-> (IGWritingSystemPRPLX -> IGWritingSystemPRPLX)
-> IGWritingSystemPRPLX
-> IGWritingSystemPRPLX
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [PhoneticsRepresentationPLX]
-> Generations -> IGWritingSystemPRPLX -> IGWritingSystemPRPLX
forall {b}.
(Eq b, Num b) =>
[PhoneticsRepresentationPLX]
-> b
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
xsGI [PhoneticsRepresentationPLX]
zs Generations
n (IGWritingSystemPRPLX -> IGWritingSystemPRPLX)
-> IGWritingSystemPRPLX -> IGWritingSystemPRPLX
forall a b. (a -> b) -> a -> b
$ IGWritingSystemPRPLX
ys
| Bool
otherwise = IGWritingSystemPRPLX
ys
where
!ts :: GWritingSystemPRPLX
ts = (([PhoneticsRepresentationPLX], Generations) -> Bool)
-> GWritingSystemPRPLX -> GWritingSystemPRPLX
forall a. (a -> Bool) -> [a] -> [a]
filter ((Generations -> Generations -> Bool
forall a. Eq a => a -> a -> Bool
== Generations
n) (Generations -> Bool)
-> (([PhoneticsRepresentationPLX], Generations) -> Generations)
-> ([PhoneticsRepresentationPLX], Generations)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([PhoneticsRepresentationPLX], Generations) -> Generations
forall a b. (a, b) -> b
snd) GWritingSystemPRPLX
xs
!zs :: [PhoneticsRepresentationPLX]
zs = (([PhoneticsRepresentationPLX], Generations)
-> [PhoneticsRepresentationPLX])
-> GWritingSystemPRPLX -> [PhoneticsRepresentationPLX]
forall a b. (a -> [b]) -> [a] -> [b]
concatMap ([PhoneticsRepresentationPLX], Generations)
-> [PhoneticsRepresentationPLX]
forall a b. (a, b) -> a
fst GWritingSystemPRPLX
ts
xsGI1 :: t
-> b
-> [(PhoneticRepresentationXInter, b)]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, b)]
xsGI1 t
rs b
n ((PhoneticRepresentationXInter, b)
k1s : (PhoneticRepresentationXInter, b)
k2s : (PhoneticRepresentationXInter, b)
k3s : [(PhoneticRepresentationXInter, b)]
kss) (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
| (PhoneticRepresentationXInter, b) -> b
forall a b. (a, b) -> b
snd (PhoneticRepresentationXInter, b)
k2s b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
n Bool -> Bool -> Bool
&& Maybe PhoneticsRepresentationPLX -> Bool
forall a. Maybe a -> Bool
isJust Maybe PhoneticsRepresentationPLX
x1 =
((PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst (PhoneticRepresentationXInter, b)
k1s, b
n b -> b -> b
forall a. Num a => a -> a -> a
- b
1)
(PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. a -> Either a b
Left (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> (Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX)
-> Maybe PhoneticsRepresentationPLX
-> PhoneticRepresentationXInter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. (a -> b) -> a -> b
$ Maybe PhoneticsRepresentationPLX
x1, b
n)
(PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: t
-> b
-> [(PhoneticRepresentationXInter, b)]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, b)]
xsGI1 t
rs b
n ((PhoneticRepresentationXInter, b)
k3s (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: [(PhoneticRepresentationXInter, b)]
kss) (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
| (PhoneticRepresentationXInter, b) -> b
forall a b. (a, b) -> b
snd (PhoneticRepresentationXInter, b)
k1s b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
n Bool -> Bool -> Bool
&& Maybe PhoneticsRepresentationPLX -> Bool
forall a. Maybe a -> Bool
isJust Maybe PhoneticsRepresentationPLX
x2 =
(PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. a -> Either a b
Left (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> (Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX)
-> Maybe PhoneticsRepresentationPLX
-> PhoneticRepresentationXInter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. (a -> b) -> a -> b
$ Maybe PhoneticsRepresentationPLX
x2, b
n) (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: t
-> b
-> [(PhoneticRepresentationXInter, b)]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, b)]
xsGI1 t
rs b
n ((PhoneticRepresentationXInter, b)
k2s (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: (PhoneticRepresentationXInter, b)
k3s (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: [(PhoneticRepresentationXInter, b)]
kss) (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
| (PhoneticRepresentationXInter, b) -> b
forall a b. (a, b) -> b
snd (PhoneticRepresentationXInter, b)
k2s b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
n Bool -> Bool -> Bool
&& Maybe PhoneticsRepresentationPLX -> Bool
forall a. Maybe a -> Bool
isJust Maybe PhoneticsRepresentationPLX
x3 =
((PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst (PhoneticRepresentationXInter, b)
k1s, b
n b -> b -> b
forall a. Num a => a -> a -> a
- b
1) (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. a -> Either a b
Left (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> (Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX)
-> Maybe PhoneticsRepresentationPLX
-> PhoneticRepresentationXInter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. (a -> b) -> a -> b
$ Maybe PhoneticsRepresentationPLX
x3, b
n) (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: t
-> b
-> [(PhoneticRepresentationXInter, b)]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, b)]
xsGI1 t
rs b
n ((PhoneticRepresentationXInter, b)
k3s (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: [(PhoneticRepresentationXInter, b)]
kss) (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
| (PhoneticRepresentationXInter, b) -> b
forall a b. (a, b) -> b
snd (PhoneticRepresentationXInter, b)
k1s b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
n Bool -> Bool -> Bool
&& Maybe PhoneticsRepresentationPLX -> Bool
forall a. Maybe a -> Bool
isJust Maybe PhoneticsRepresentationPLX
x4 =
(PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. a -> Either a b
Left (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> (Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX)
-> Maybe PhoneticsRepresentationPLX
-> PhoneticRepresentationXInter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. (a -> b) -> a -> b
$ Maybe PhoneticsRepresentationPLX
x4, b
n) (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: t
-> b
-> [(PhoneticRepresentationXInter, b)]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, b)]
xsGI1 t
rs b
n ((PhoneticRepresentationXInter, b)
k2s (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: (PhoneticRepresentationXInter, b)
k3s (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: [(PhoneticRepresentationXInter, b)]
kss) (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
| Bool
otherwise = ((PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst (PhoneticRepresentationXInter, b)
k1s, b
n b -> b -> b
forall a. Num a => a -> a -> a
- b
1) (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: t
-> b
-> [(PhoneticRepresentationXInter, b)]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, b)]
xsGI1 t
rs b
n ((PhoneticRepresentationXInter, b)
k2s (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: (PhoneticRepresentationXInter, b)
k3s (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: [(PhoneticRepresentationXInter, b)]
kss) (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
where
!x1 :: Maybe PhoneticsRepresentationPLX
x1 =
PhoneticRepresentationXInter
-> (String, String)
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
findSAI
((PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst (PhoneticRepresentationXInter, b)
k2s)
((PhoneticsRepresentationPLX -> String)
-> ShowS -> PhoneticRepresentationXInter -> String
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either PhoneticsRepresentationPLX -> String
stringX ShowS
forall a. a -> a
id (PhoneticRepresentationXInter -> String)
-> ((PhoneticRepresentationXInter, b)
-> PhoneticRepresentationXInter)
-> (PhoneticRepresentationXInter, b)
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst ((PhoneticRepresentationXInter, b) -> String)
-> (PhoneticRepresentationXInter, b) -> String
forall a b. (a -> b) -> a -> b
$ (PhoneticRepresentationXInter, b)
k1s, (PhoneticsRepresentationPLX -> String)
-> ShowS -> PhoneticRepresentationXInter -> String
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either PhoneticsRepresentationPLX -> String
stringX ShowS
forall a. a -> a
id (PhoneticRepresentationXInter -> String)
-> ((PhoneticRepresentationXInter, b)
-> PhoneticRepresentationXInter)
-> (PhoneticRepresentationXInter, b)
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst ((PhoneticRepresentationXInter, b) -> String)
-> (PhoneticRepresentationXInter, b) -> String
forall a b. (a -> b) -> a -> b
$ (PhoneticRepresentationXInter, b)
k3s)
Array Int PhoneticsRepresentationPLX
r2s
!x2 :: Maybe PhoneticsRepresentationPLX
x2 = PhoneticRepresentationXInter
-> (String, String)
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
findSAI ((PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst (PhoneticRepresentationXInter, b)
k1s) ([], (PhoneticsRepresentationPLX -> String)
-> ShowS -> PhoneticRepresentationXInter -> String
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either PhoneticsRepresentationPLX -> String
stringX ShowS
forall a. a -> a
id (PhoneticRepresentationXInter -> String)
-> ((PhoneticRepresentationXInter, b)
-> PhoneticRepresentationXInter)
-> (PhoneticRepresentationXInter, b)
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst ((PhoneticRepresentationXInter, b) -> String)
-> (PhoneticRepresentationXInter, b) -> String
forall a b. (a -> b) -> a -> b
$ (PhoneticRepresentationXInter, b)
k2s) Array Int PhoneticsRepresentationPLX
r3s
!x3 :: Maybe PhoneticsRepresentationPLX
x3 = PhoneticRepresentationXInter
-> (String, String)
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
findSAI ((PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst (PhoneticRepresentationXInter, b)
k2s) ((PhoneticsRepresentationPLX -> String)
-> ShowS -> PhoneticRepresentationXInter -> String
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either PhoneticsRepresentationPLX -> String
stringX ShowS
forall a. a -> a
id (PhoneticRepresentationXInter -> String)
-> ((PhoneticRepresentationXInter, b)
-> PhoneticRepresentationXInter)
-> (PhoneticRepresentationXInter, b)
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst ((PhoneticRepresentationXInter, b) -> String)
-> (PhoneticRepresentationXInter, b) -> String
forall a b. (a -> b) -> a -> b
$ (PhoneticRepresentationXInter, b)
k1s, []) Array Int PhoneticsRepresentationPLX
r4s
!x4 :: Maybe PhoneticsRepresentationPLX
x4 = PhoneticRepresentationXInter
-> (String, String)
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
findSAI ((PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst (PhoneticRepresentationXInter, b)
k1s) ([], []) Array Int PhoneticsRepresentationPLX
r5s
xsGI1 t
rs b
n ((PhoneticRepresentationXInter, b)
k1s : (PhoneticRepresentationXInter, b)
k2s : [(PhoneticRepresentationXInter, b)]
kss) (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
| (PhoneticRepresentationXInter, b) -> b
forall a b. (a, b) -> b
snd (PhoneticRepresentationXInter, b)
k1s b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
n Bool -> Bool -> Bool
&& Maybe PhoneticsRepresentationPLX -> Bool
forall a. Maybe a -> Bool
isJust Maybe PhoneticsRepresentationPLX
x2 =
(PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. a -> Either a b
Left (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> (Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX)
-> Maybe PhoneticsRepresentationPLX
-> PhoneticRepresentationXInter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. (a -> b) -> a -> b
$ Maybe PhoneticsRepresentationPLX
x2, b
n) (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: t
-> b
-> [(PhoneticRepresentationXInter, b)]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, b)]
xsGI1 t
rs b
n ((PhoneticRepresentationXInter, b)
k2s (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: [(PhoneticRepresentationXInter, b)]
kss) (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
| (PhoneticRepresentationXInter, b) -> b
forall a b. (a, b) -> b
snd (PhoneticRepresentationXInter, b)
k2s b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
n Bool -> Bool -> Bool
&& Maybe PhoneticsRepresentationPLX -> Bool
forall a. Maybe a -> Bool
isJust Maybe PhoneticsRepresentationPLX
x3 =
((PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst (PhoneticRepresentationXInter, b)
k1s, b
n b -> b -> b
forall a. Num a => a -> a -> a
- b
1) (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. a -> Either a b
Left (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> (Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX)
-> Maybe PhoneticsRepresentationPLX
-> PhoneticRepresentationXInter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. (a -> b) -> a -> b
$ Maybe PhoneticsRepresentationPLX
x3, b
n) (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: t
-> b
-> [(PhoneticRepresentationXInter, b)]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, b)]
xsGI1 t
rs b
n [(PhoneticRepresentationXInter, b)]
kss (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
| (PhoneticRepresentationXInter, b) -> b
forall a b. (a, b) -> b
snd (PhoneticRepresentationXInter, b)
k1s b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
n Bool -> Bool -> Bool
&& Maybe PhoneticsRepresentationPLX -> Bool
forall a. Maybe a -> Bool
isJust Maybe PhoneticsRepresentationPLX
x4 =
(PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. a -> Either a b
Left (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> (Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX)
-> Maybe PhoneticsRepresentationPLX
-> PhoneticRepresentationXInter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. (a -> b) -> a -> b
$ Maybe PhoneticsRepresentationPLX
x4, b
n) (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: t
-> b
-> [(PhoneticRepresentationXInter, b)]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, b)]
xsGI1 t
rs b
n ((PhoneticRepresentationXInter, b)
k2s (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: [(PhoneticRepresentationXInter, b)]
kss) (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
| Bool
otherwise = ((PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst (PhoneticRepresentationXInter, b)
k1s, b
n b -> b -> b
forall a. Num a => a -> a -> a
- b
1) (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: t
-> b
-> [(PhoneticRepresentationXInter, b)]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, b)]
xsGI1 t
rs b
n ((PhoneticRepresentationXInter, b)
k2s (PhoneticRepresentationXInter, b)
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
forall a. a -> [a] -> [a]
: [(PhoneticRepresentationXInter, b)]
kss) (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
where
!x2 :: Maybe PhoneticsRepresentationPLX
x2 = PhoneticRepresentationXInter
-> (String, String)
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
findSAI ((PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst (PhoneticRepresentationXInter, b)
k1s) ([], (PhoneticsRepresentationPLX -> String)
-> ShowS -> PhoneticRepresentationXInter -> String
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either PhoneticsRepresentationPLX -> String
stringX ShowS
forall a. a -> a
id (PhoneticRepresentationXInter -> String)
-> ((PhoneticRepresentationXInter, b)
-> PhoneticRepresentationXInter)
-> (PhoneticRepresentationXInter, b)
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst ((PhoneticRepresentationXInter, b) -> String)
-> (PhoneticRepresentationXInter, b) -> String
forall a b. (a -> b) -> a -> b
$ (PhoneticRepresentationXInter, b)
k2s) Array Int PhoneticsRepresentationPLX
r3s
!x3 :: Maybe PhoneticsRepresentationPLX
x3 = PhoneticRepresentationXInter
-> (String, String)
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
findSAI ((PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst (PhoneticRepresentationXInter, b)
k2s) ((PhoneticsRepresentationPLX -> String)
-> ShowS -> PhoneticRepresentationXInter -> String
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either PhoneticsRepresentationPLX -> String
stringX ShowS
forall a. a -> a
id (PhoneticRepresentationXInter -> String)
-> ((PhoneticRepresentationXInter, b)
-> PhoneticRepresentationXInter)
-> (PhoneticRepresentationXInter, b)
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst ((PhoneticRepresentationXInter, b) -> String)
-> (PhoneticRepresentationXInter, b) -> String
forall a b. (a -> b) -> a -> b
$ (PhoneticRepresentationXInter, b)
k1s, []) Array Int PhoneticsRepresentationPLX
r4s
!x4 :: Maybe PhoneticsRepresentationPLX
x4 = PhoneticRepresentationXInter
-> (String, String)
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
findSAI ((PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst (PhoneticRepresentationXInter, b)
k1s) ([], []) Array Int PhoneticsRepresentationPLX
r5s
xsGI1 t
rs b
n [(PhoneticRepresentationXInter, b)
k1s] (Array Int PhoneticsRepresentationPLX
_, Array Int PhoneticsRepresentationPLX
_, Array Int PhoneticsRepresentationPLX
_, Array Int PhoneticsRepresentationPLX
r5s)
| (PhoneticRepresentationXInter, b) -> b
forall a b. (a, b) -> b
snd (PhoneticRepresentationXInter, b)
k1s b -> b -> Bool
forall a. Eq a => a -> a -> Bool
== b
n Bool -> Bool -> Bool
&& Maybe PhoneticsRepresentationPLX -> Bool
forall a. Maybe a -> Bool
isJust Maybe PhoneticsRepresentationPLX
x4 = [(PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. a -> Either a b
Left (PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> (Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX)
-> Maybe PhoneticsRepresentationPLX
-> PhoneticRepresentationXInter
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe PhoneticsRepresentationPLX -> PhoneticsRepresentationPLX
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter)
-> Maybe PhoneticsRepresentationPLX -> PhoneticRepresentationXInter
forall a b. (a -> b) -> a -> b
$ Maybe PhoneticsRepresentationPLX
x4, b
n)]
| Bool
otherwise = [((PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst (PhoneticRepresentationXInter, b)
k1s, b
n b -> b -> b
forall a. Num a => a -> a -> a
- b
1)]
where
!x4 :: Maybe PhoneticsRepresentationPLX
x4 = PhoneticRepresentationXInter
-> (String, String)
-> Array Int PhoneticsRepresentationPLX
-> Maybe PhoneticsRepresentationPLX
findSAI ((PhoneticRepresentationXInter, b) -> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst (PhoneticRepresentationXInter, b)
k1s) ([], []) Array Int PhoneticsRepresentationPLX
r5s
xsGI1 t
rs b
n [] (Array Int PhoneticsRepresentationPLX
_, Array Int PhoneticsRepresentationPLX
_, Array Int PhoneticsRepresentationPLX
_, Array Int PhoneticsRepresentationPLX
_) = []
xsGI :: [PhoneticsRepresentationPLX]
-> b
-> [(PhoneticRepresentationXInter, b)]
-> [(PhoneticRepresentationXInter, b)]
xsGI [PhoneticsRepresentationPLX]
rs b
n [(PhoneticRepresentationXInter, b)]
jss = [PhoneticsRepresentationPLX]
-> b
-> [(PhoneticRepresentationXInter, b)]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, b)]
forall {b} {t}.
(Eq b, Num b) =>
t
-> b
-> [(PhoneticRepresentationXInter, b)]
-> (Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX,
Array Int PhoneticsRepresentationPLX)
-> [(PhoneticRepresentationXInter, b)]
xsGI1 [PhoneticsRepresentationPLX]
rs b
n [(PhoneticRepresentationXInter, b)]
jss (Array Int PhoneticsRepresentationPLX
r2s, Array Int PhoneticsRepresentationPLX
r3s, Array Int PhoneticsRepresentationPLX
r4s, Array Int PhoneticsRepresentationPLX
r5s)
where
(![PhoneticsRepresentationPLX]
r2ls, ![PhoneticsRepresentationPLX]
r3ls, ![PhoneticsRepresentationPLX]
r4ls, ![PhoneticsRepresentationPLX]
r5ls) = (PhoneticsRepresentationPLX -> Bool)
-> (PhoneticsRepresentationPLX -> Bool)
-> (PhoneticsRepresentationPLX -> Bool)
-> (PhoneticsRepresentationPLX -> Bool)
-> [PhoneticsRepresentationPLX]
-> ([PhoneticsRepresentationPLX], [PhoneticsRepresentationPLX],
[PhoneticsRepresentationPLX], [PhoneticsRepresentationPLX])
forall a.
(a -> Bool)
-> (a -> Bool)
-> (a -> Bool)
-> (a -> Bool)
-> [a]
-> ([a], [a], [a], [a])
fHelp4 PhoneticsRepresentationPLX -> Bool
isPRC PhoneticsRepresentationPLX -> Bool
isPRAfterC PhoneticsRepresentationPLX -> Bool
isPRBeforeC PhoneticsRepresentationPLX -> Bool
isPREmptyC [PhoneticsRepresentationPLX]
rs
!r2s :: Array Int PhoneticsRepresentationPLX
r2s = (Int, Int)
-> [PhoneticsRepresentationPLX]
-> Array Int PhoneticsRepresentationPLX
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0, [PhoneticsRepresentationPLX] -> Int
forall a. [a] -> Int
length [PhoneticsRepresentationPLX]
r2ls Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [PhoneticsRepresentationPLX]
r2ls
!r3s :: Array Int PhoneticsRepresentationPLX
r3s = (Int, Int)
-> [PhoneticsRepresentationPLX]
-> Array Int PhoneticsRepresentationPLX
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0, [PhoneticsRepresentationPLX] -> Int
forall a. [a] -> Int
length [PhoneticsRepresentationPLX]
r3ls Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [PhoneticsRepresentationPLX]
r3ls
!r4s :: Array Int PhoneticsRepresentationPLX
r4s = (Int, Int)
-> [PhoneticsRepresentationPLX]
-> Array Int PhoneticsRepresentationPLX
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0, [PhoneticsRepresentationPLX] -> Int
forall a. [a] -> Int
length [PhoneticsRepresentationPLX]
r4ls Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [PhoneticsRepresentationPLX]
r4ls
!r5s :: Array Int PhoneticsRepresentationPLX
r5s = (Int, Int)
-> [PhoneticsRepresentationPLX]
-> Array Int PhoneticsRepresentationPLX
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0, [PhoneticsRepresentationPLX] -> Int
forall a. [a] -> Int
length [PhoneticsRepresentationPLX]
r5ls Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [PhoneticsRepresentationPLX]
r5ls
stringToXG :: GWritingSystemPRPLX -> String -> [PhoneticsRepresentationPLX]
stringToXG :: GWritingSystemPRPLX -> String -> [PhoneticsRepresentationPLX]
stringToXG GWritingSystemPRPLX
xs String
ys = [PhoneticsRepresentationPLX]
-> [PhoneticRepresentationXInter] -> [PhoneticsRepresentationPLX]
fromPhoneticRX [PhoneticsRepresentationPLX]
ts ([PhoneticRepresentationXInter] -> [PhoneticsRepresentationPLX])
-> (String -> [PhoneticRepresentationXInter])
-> String
-> [PhoneticsRepresentationPLX]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((PhoneticRepresentationXInter, Generations)
-> PhoneticRepresentationXInter)
-> IGWritingSystemPRPLX -> [PhoneticRepresentationXInter]
forall a b. (a -> b) -> [a] -> [b]
map (PhoneticRepresentationXInter, Generations)
-> PhoneticRepresentationXInter
forall a b. (a, b) -> a
fst (IGWritingSystemPRPLX -> [PhoneticRepresentationXInter])
-> (String -> IGWritingSystemPRPLX)
-> String
-> [PhoneticRepresentationXInter]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GWritingSystemPRPLX
-> Generations -> String -> IGWritingSystemPRPLX
stringToXSG GWritingSystemPRPLX
xs Generations
n (String -> [PhoneticsRepresentationPLX])
-> String -> [PhoneticsRepresentationPLX]
forall a b. (a -> b) -> a -> b
$ String
ys
where
n :: Generations
n = [Generations] -> Generations
forall a. (Ord a, HasCallStack) => [a] -> a
maximum ([Generations] -> Generations)
-> (GWritingSystemPRPLX -> [Generations])
-> GWritingSystemPRPLX
-> Generations
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([PhoneticsRepresentationPLX], Generations) -> Generations)
-> GWritingSystemPRPLX -> [Generations]
forall a b. (a -> b) -> [a] -> [b]
map ([PhoneticsRepresentationPLX], Generations) -> Generations
forall a b. (a, b) -> b
snd (GWritingSystemPRPLX -> Generations)
-> GWritingSystemPRPLX -> Generations
forall a b. (a -> b) -> a -> b
$ GWritingSystemPRPLX
xs
!ts :: [PhoneticsRepresentationPLX]
ts = (([PhoneticsRepresentationPLX], Generations)
-> [PhoneticsRepresentationPLX])
-> GWritingSystemPRPLX -> [PhoneticsRepresentationPLX]
forall a b. (a -> [b]) -> [a] -> [b]
concatMap ([PhoneticsRepresentationPLX], Generations)
-> [PhoneticsRepresentationPLX]
forall a b. (a, b) -> a
fst (GWritingSystemPRPLX -> [PhoneticsRepresentationPLX])
-> (GWritingSystemPRPLX -> GWritingSystemPRPLX)
-> GWritingSystemPRPLX
-> [PhoneticsRepresentationPLX]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (([PhoneticsRepresentationPLX], Generations) -> Bool)
-> GWritingSystemPRPLX -> GWritingSystemPRPLX
forall a. (a -> Bool) -> [a] -> [a]
filter ((Generations -> Generations -> Bool
forall a. Eq a => a -> a -> Bool
== Generations
0) (Generations -> Bool)
-> (([PhoneticsRepresentationPLX], Generations) -> Generations)
-> ([PhoneticsRepresentationPLX], Generations)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([PhoneticsRepresentationPLX], Generations) -> Generations
forall a b. (a, b) -> b
snd) (GWritingSystemPRPLX -> [PhoneticsRepresentationPLX])
-> GWritingSystemPRPLX -> [PhoneticsRepresentationPLX]
forall a b. (a -> b) -> a -> b
$ GWritingSystemPRPLX
xs