{-# OPTIONS_GHC -threaded -rtsopts #-}
{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE BangPatterns, NoImplicitPrelude #-}
module Phladiprelio.General.Parsing (
isClosingCurlyBracket
, isSlash
, isOpeningCurlyBracket
, variations
, breakGroupOfStrings
, breakInSlashes
, combineVariants
, combineHeadsWithNexts
, transformToVariations
, readLangSpecs
, innerProcessmentSimple
, argsProcessment
) where
import GHC.Base
import GHC.List
import Phladiprelio.General.PrepareText
import System.Environment (getArgs)
import System.IO (FilePath, readFile)
import Data.List (sort,lines,unwords)
import GHC.Arr
import Phladiprelio.General.Base
import Phladiprelio.General.Syllables
import Text.Read (readMaybe,read)
import Data.Maybe (fromMaybe)
import Phladiprelio.General.SpecificationsRead
isClosingCurlyBracket :: String -> Bool
isClosingCurlyBracket :: String -> Bool
isClosingCurlyBracket = (forall a. Eq a => a -> a -> Bool
== String
"}")
isSlash :: String -> Bool
isSlash :: String -> Bool
isSlash (Char
x:String
xs)
| Char
x forall a. Eq a => a -> a -> Bool
/= Char
'/' = Bool
False
| forall a. [a] -> Bool
null String
xs = Bool
True
| Bool
otherwise = Bool
False
isSlash String
_ = Bool
False
isOpeningCurlyBracket :: String -> Bool
isOpeningCurlyBracket :: String -> Bool
isOpeningCurlyBracket = (forall a. Eq a => a -> a -> Bool
== String
"{")
breakGroupOfStrings :: [String] -> (([String],[[String]]),[String])
breakGroupOfStrings :: [String] -> (([String], [[String]]), [String])
breakGroupOfStrings ![String]
xss = (([String]
tss,[String] -> [[String]] -> [[String]]
breakInSlashes [String]
uss []), forall a. Int -> [a] -> [a]
drop Int
1 [String]
zss)
where (![String]
yss,![String]
zss) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break String -> Bool
isClosingCurlyBracket [String]
xss
(![String]
tss,![String]
uss) = (\([String]
t1,[String]
t2) -> ([String]
t1,forall a. Int -> [a] -> [a]
drop Int
1 [String]
t2)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> ([a], [a])
break String -> Bool
isOpeningCurlyBracket forall a b. (a -> b) -> a -> b
$ [String]
yss
breakInSlashes :: [String] -> [[String]] -> [[String]]
breakInSlashes :: [String] -> [[String]] -> [[String]]
breakInSlashes ![String]
wss ![[String]]
usss
| forall a. [a] -> Bool
null [String]
lss = [String]
kss forall a. a -> [a] -> [a]
: [[String]]
usss
| Bool
otherwise = [String] -> [[String]] -> [[String]]
breakInSlashes (forall a. Int -> [a] -> [a]
drop Int
1 [String]
lss) ([String]
kss forall a. a -> [a] -> [a]
: [[String]]
usss)
where (![String]
kss,![String]
lss) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break String -> Bool
isSlash [String]
wss
combineVariants :: ([String],[[String]]) -> [[String]]
combineVariants :: ([String], [[String]]) -> [[String]]
combineVariants (![String]
xss, (![String]
yss:[[String]]
ysss)) = ([String]
xss forall a. Monoid a => a -> a -> a
`mappend` [String]
yss) forall a. a -> [a] -> [a]
: ([String], [[String]]) -> [[String]]
combineVariants ([String]
xss, [[String]]
ysss)
combineVariants ([String], [[String]])
_ = []
combineHeadsWithNexts :: [[String]] -> [String] -> [[String]]
combineHeadsWithNexts :: [[String]] -> [String] -> [[String]]
combineHeadsWithNexts ![[String]]
xsss ![String]
yss
| forall a. [a] -> Bool
null [String]
yss = [[String]]
xsss
| Bool
otherwise = [[String]] -> [String] -> [[String]]
combineHeadsWithNexts [[String]
xss forall a. Monoid a => a -> a -> a
`mappend` [String]
zss | [String]
xss <- [[String]]
xsss, [String]
zss <- [[String]]
zsss] [String]
uss
where (!([String], [[String]])
t,![String]
uss) = [String] -> (([String], [[String]]), [String])
breakGroupOfStrings [String]
yss
!zsss :: [[String]]
zsss = ([String], [[String]]) -> [[String]]
combineVariants ([String], [[String]])
t
transformToVariations :: [String] -> [[String]]
transformToVariations :: [String] -> [[String]]
transformToVariations ![String]
yss
| forall a. [a] -> Bool
null [String]
yss = []
| Bool
otherwise = [[String]] -> [String] -> [[String]]
combineHeadsWithNexts [[String]]
xsss [String]
tss
where (!([String], [[String]])
y,![String]
tss) = [String] -> (([String], [[String]]), [String])
breakGroupOfStrings [String]
yss
!xsss :: [[String]]
xsss = ([String], [[String]]) -> [[String]]
combineVariants ([String], [[String]])
y
variations :: [String] -> Bool
variations :: [String] -> Bool
variations [String]
xss
| forall a. (a -> Bool) -> [a] -> Bool
any String -> Bool
isSlash [String]
xss = if forall a. (a -> Bool) -> [a] -> Bool
any String -> Bool
isOpeningCurlyBracket [String]
xss Bool -> Bool -> Bool
&& forall a. (a -> Bool) -> [a] -> Bool
any String -> Bool
isClosingCurlyBracket [String]
xss then Bool
True else Bool
False
| Bool
otherwise = Bool
False
innerProcessmentSimple
:: String
-> String
-> String
-> String
-> String
-> (GWritingSystemPRPLX, [(Char, Char)], CharPhoneticClassification, SegmentRulesG, String, String, Concatenations, Concatenations, String)
innerProcessmentSimple :: String
-> String
-> String
-> String
-> String
-> (GWritingSystemPRPLX, [(Char, Char)],
CharPhoneticClassification, SegmentRulesG, String, String,
[[String]], [[String]], String)
innerProcessmentSimple String
gwrsCnts String
controlConts String
segmentData String
concatenationsFileP String
concatenationsFileA =
let [[String]
allophonesGs, [String]
charClfs, [String]
jss, [String]
vss, [String]
wss] = Char -> [String] -> [[String]]
groupBetweenChars Char
'~' forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines forall a b. (a -> b) -> a -> b
$ String
controlConts
wrs :: GWritingSystemPRPLX
wrs = Char -> String -> GWritingSystemPRPLX
getGWritingSystem Char
'~' String
gwrsCnts
ks :: [(Char, Char)]
ks = forall a. Ord a => [a] -> [a]
sort forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a -> a
fromMaybe [] forall a b. (a -> b) -> a -> b
$ (forall a. Read a => String -> Maybe a
readMaybe ([String] -> String
unwords [String]
allophonesGs)::Maybe [(Char, Char)])
arr :: CharPhoneticClassification
arr = forall a. Read a => String -> a
read ([String] -> String
unwords [String]
charClfs)::Array Int PRS
gs :: SegmentRulesG
gs = forall a. Read a => String -> a
read String
segmentData::SegmentRulesG
ysss :: [[String]]
ysss = [[String]] -> [[String]]
sort2Concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a -> a
fromMaybe [] forall a b. (a -> b) -> a -> b
$ (forall a. Read a => String -> Maybe a
readMaybe String
concatenationsFileP::Maybe [[String]])
zzzsss :: [[String]]
zzzsss = [[String]] -> [[String]]
sort2Concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a -> a
fromMaybe [] forall a b. (a -> b) -> a -> b
$ (forall a. Read a => String -> Maybe a
readMaybe String
concatenationsFileA::Maybe [[String]])
js :: String
js = forall a. [[a]] -> [a]
concat [String]
jss
vs :: String
vs = forall a. [[a]] -> [a]
concat [String]
vss
ws :: String
ws = forall a. Ord a => [a] -> [a]
sort forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [[a]] -> [a]
concat forall a b. (a -> b) -> a -> b
$ [String]
wss
in (GWritingSystemPRPLX
wrs, [(Char, Char)]
ks, CharPhoneticClassification
arr, SegmentRulesG
gs, String
js, String
vs, [[String]]
ysss, [[String]]
zzzsss, String
ws)
argsProcessment
:: FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> IO [String]
argsProcessment :: String -> String -> String -> String -> String -> IO [String]
argsProcessment String
fileGWrSys String
controlFile String
segmentRulesFile String
concatenationsFileP String
concatenationsFileA = forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM String -> IO String
readFile [String
controlFile, String
fileGWrSys, String
segmentRulesFile, String
concatenationsFileP, String
concatenationsFileA]
readLangSpecs
:: FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> IO (GWritingSystemPRPLX, [(Char, Char)], CharPhoneticClassification, SegmentRulesG, String, String, Concatenations, Concatenations, String)
readLangSpecs :: String
-> String
-> String
-> String
-> String
-> IO
(GWritingSystemPRPLX, [(Char, Char)], CharPhoneticClassification,
SegmentRulesG, String, String, [[String]], [[String]], String)
readLangSpecs String
fileGWrSys String
controlFile String
segmentRulesFile String
concatenationsFileP String
concatenationsFileA =
String -> String -> String -> String -> String -> IO [String]
argsProcessment String
fileGWrSys String
controlFile String
segmentRulesFile String
concatenationsFileP String
concatenationsFileA forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \[String]
xss -> let [String
controlConts, String
gwrsCnts, String
segmentData, String
concatenationsFileP1, String
concatenationsFileA1] = [String]
xss in forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ String
-> String
-> String
-> String
-> String
-> (GWritingSystemPRPLX, [(Char, Char)],
CharPhoneticClassification, SegmentRulesG, String, String,
[[String]], [[String]], String)
innerProcessmentSimple String
gwrsCnts String
controlConts String
segmentData String
concatenationsFileP1 String
concatenationsFileA1