{-# OPTIONS_GHC -threaded #-}
{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE BangPatterns #-}
module Phonetic.Languages.General.Simple.Parsing where
import Phonetic.Languages.Array.General.PropertiesSyllablesG2
import Data.Phonetic.Languages.PrepareText
import System.Environment (getArgs)
import Phonetic.Languages.General.Simple
import Data.List (sort)
import GHC.Arr
import Data.Phonetic.Languages.Base
import Data.Phonetic.Languages.Syllables
import Text.Read (readMaybe)
import Data.Maybe (fromMaybe)
import Data.Phonetic.Languages.SpecificationsRead
import Interpreter.StringConversion (readFileIfAny)
import CLI.Arguments
import CLI.Arguments.Parsing
import CLI.Arguments.Get
import qualified Phonetic.Languages.Permutations.Represent as R
import Phonetic.Languages.EmphasisG
import Phonetic.Languages.Coeffs
argsToSimplePrepare
:: (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> (String -> Bool)
-> (String -> String)
-> IO ()
argsToSimplePrepare :: (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> (String -> Bool)
-> (String -> String)
-> IO ()
argsToSimplePrepare Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
qs String -> Bool
p String -> String
g1 = do
[String]
args50 <- IO [String]
getArgs
let (Args
argsA,Args
argsB,Args
argsC1,[String]
argss) = FirstChars
-> CLSpecifications -> [String] -> (Args, Args, Args, [String])
args2Args31R FirstChars
fstCharsMA CLSpecifications
specs1 [String]
args50
args00000 :: [String]
args00000 = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+p",GQtyArgs
1)] forall a b. (a -> b) -> a -> b
$ [String]
args50
pairwisePermutations :: PermutationsType
pairwisePermutations = [String] -> PermutationsType
R.bTransform2Perms forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getB String
"+p" forall a b. (a -> b) -> a -> b
$ Args
argsB
(Args
txtPFs,[String]
args0000F) = FirstChars -> CLSpecifications -> [String] -> (Args, [String])
takeCs1R FirstChars
fstCharsT CLSpecifications
cSpecs1T [String]
args00000
textProcessmentFssFs :: [String]
textProcessmentFssFs = forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getC String
"+t" Args
txtPFs
textProcessment0 :: String
textProcessment0
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getB String
"+t" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+t",GQtyArgs
1)] forall a b. (a -> b) -> a -> b
$ [String]
args00000 = []
| Bool
otherwise = String
"+t" forall a. Monoid a => a -> a -> a
`mappend` (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getB String
"+t" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+t",GQtyArgs
1)] forall a b. (a -> b) -> a -> b
$ [String]
args00000)
textProcessment1 :: GQtyArgs
textProcessment1 = forall a. a -> Maybe a -> a
fromMaybe GQtyArgs
70 (forall a. Read a => String -> Maybe a
readMaybe (forall a. GQtyArgs -> [a] -> [a]
drop GQtyArgs
2 String
textProcessment0)::Maybe Int)
(Args
rcrs,[String]
args000) = CLSpecifications -> [String] -> (Args, [String])
takeAsR [(String
"+r",GQtyArgs
0)] forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null) forall a b. (a -> b) -> a -> b
$ [String]
args0000F
recursiveMode :: Bool
recursiveMode = forall (t :: * -> *). Foldable t => String -> t Arguments -> Bool
oneA String
"+r" Args
rcrs
(![String]
args15,![String]
args00) = forall a. GQtyArgs -> [a] -> ([a], [a])
splitAt GQtyArgs
5 [String]
args000
[String
fileGWrSys, String
controlFile, String
segmentRulesFile, String
concatenationsFileP,String
concatenationsFileA] = [String]
args15
(String
gwrsCnts, String
controlConts, String
segmentData, String
concatenationsFileP1, String
concatenationsFileA1, String
toFileMode1, Bool
interactiveP, Bool
jstL0, [String]
args0, Coeffs2
coeffs, Coeffs2
coeffsWX, [String]
args, Bool
lstW,Bool
syllables,GQtyArgs
syllablesVs,GQtyArgs
verbose) <- String
-> String
-> String
-> String
-> String
-> [String]
-> IO
(String, String, String, String, String, String, Bool, Bool,
[String], Coeffs2, Coeffs2, [String], Bool, Bool, GQtyArgs,
GQtyArgs)
argsProcessment String
fileGWrSys String
controlFile String
segmentRulesFile String
concatenationsFileP String
concatenationsFileA [String]
args00
let (GWritingSystemPRPLX
wrs, [FirstChars]
ks, CharPhoneticClassification
arr, SegmentRulesG
gs, String
js, String
vs, Concatenations
ysss, Concatenations
zzzsss, String
ws) = String
-> String
-> String
-> String
-> String
-> (GWritingSystemPRPLX, [FirstChars], CharPhoneticClassification,
SegmentRulesG, String, String, Concatenations, Concatenations,
String)
innerProcessmentSimple String
gwrsCnts String
controlConts String
segmentData String
concatenationsFileP1 String
concatenationsFileA1
[String]
textProcessmentFss0 <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (String -> IO String
readFileIfAny) [String]
textProcessmentFssFs
let textProcessmentFss :: [String]
textProcessmentFss = forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null) [String]
textProcessmentFss0
if forall a. CoeffTwo a -> Bool
isPair Coeffs2
coeffs then PermutationsType
-> (String -> Bool)
-> [String]
-> String
-> GQtyArgs
-> GWritingSystemPRPLX
-> [FirstChars]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Concatenations
-> Concatenations
-> String
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> [String]
-> Bool
-> Bool
-> GQtyArgs
-> GQtyArgs
-> (String -> String)
-> IO ()
generalProc3G PermutationsType
pairwisePermutations String -> Bool
p [String]
textProcessmentFss String
textProcessment0 GQtyArgs
textProcessment1 GWritingSystemPRPLX
wrs [FirstChars]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
qs Concatenations
ysss Concatenations
zzzsss String
ws String
toFileMode1 Bool
recursiveMode Bool
interactiveP Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX (forall a. GQtyArgs -> [a] -> [a]
drop GQtyArgs
1 [String]
args) Bool
lstW Bool
syllables GQtyArgs
syllablesVs GQtyArgs
verbose String -> String
g1
else PermutationsType
-> (String -> Bool)
-> [String]
-> String
-> GQtyArgs
-> GWritingSystemPRPLX
-> [FirstChars]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Concatenations
-> Concatenations
-> String
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> [String]
-> Bool
-> Bool
-> GQtyArgs
-> GQtyArgs
-> (String -> String)
-> IO ()
generalProc3G PermutationsType
pairwisePermutations String -> Bool
p [String]
textProcessmentFss String
textProcessment0 GQtyArgs
textProcessment1 GWritingSystemPRPLX
wrs [FirstChars]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
qs Concatenations
ysss Concatenations
zzzsss String
ws String
toFileMode1 Bool
recursiveMode Bool
interactiveP Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX [String]
args Bool
lstW Bool
syllables GQtyArgs
syllablesVs GQtyArgs
verbose String -> String
g1
argsToSimplePrepare4Files
:: R.PermutationsType
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> String
-> (String -> Bool)
-> [String]
-> String
-> Int
-> (String -> String)
-> IO ()
argsToSimplePrepare4Files :: PermutationsType
-> String
-> String
-> String
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> String
-> (String -> Bool)
-> [String]
-> String
-> GQtyArgs
-> (String -> String)
-> IO ()
argsToSimplePrepare4Files PermutationsType
pairwisePermutations String
fileGWrSys String
controlFile String
segmentRulesFile String
concatenationsFileP String
concatenationsFileA Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
qs String
other_args String -> Bool
p [String]
textProcessmentFss String
textProcessment0 GQtyArgs
textProcessment1 String -> String
g1 = do
let args000 :: [String]
args000 = forall a. GQtyArgs -> [a] -> [a]
drop GQtyArgs
5 forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words forall a b. (a -> b) -> a -> b
$ String
other_args
(Args
rcs,[String]
args00) = CLSpecifications -> [String] -> (Args, [String])
takeAsR [(String
"+r",GQtyArgs
0)] [String]
args000
recursiveMode :: Bool
recursiveMode = forall (t :: * -> *). Foldable t => String -> t Arguments -> Bool
oneA String
"+r" Args
rcs
(String
gwrsCnts, String
controlConts, String
segmentData, String
concatenationsFileP1, String
concatenationsFileA1, String
toFileMode1, Bool
interactiveP, Bool
jstL0, [String]
args0, Coeffs2
coeffs, Coeffs2
coeffsWX, [String]
args, Bool
lstW,Bool
syllables,GQtyArgs
syllablesVs,GQtyArgs
verbose) <- String
-> String
-> String
-> String
-> String
-> [String]
-> IO
(String, String, String, String, String, String, Bool, Bool,
[String], Coeffs2, Coeffs2, [String], Bool, Bool, GQtyArgs,
GQtyArgs)
argsProcessment String
fileGWrSys String
controlFile String
segmentRulesFile String
concatenationsFileP String
concatenationsFileA [String]
args00
let (GWritingSystemPRPLX
wrs, [FirstChars]
ks, CharPhoneticClassification
arr, SegmentRulesG
gs, String
js, String
vs, Concatenations
ysss, Concatenations
zzzsss, String
ws) = String
-> String
-> String
-> String
-> String
-> (GWritingSystemPRPLX, [FirstChars], CharPhoneticClassification,
SegmentRulesG, String, String, Concatenations, Concatenations,
String)
innerProcessmentSimple String
gwrsCnts String
controlConts String
segmentData String
concatenationsFileP1 String
concatenationsFileA1
if forall a. CoeffTwo a -> Bool
isPair Coeffs2
coeffs then PermutationsType
-> (String -> Bool)
-> [String]
-> String
-> GQtyArgs
-> GWritingSystemPRPLX
-> [FirstChars]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Concatenations
-> Concatenations
-> String
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> [String]
-> Bool
-> Bool
-> GQtyArgs
-> GQtyArgs
-> (String -> String)
-> IO ()
generalProc3G PermutationsType
pairwisePermutations String -> Bool
p [String]
textProcessmentFss String
textProcessment0 GQtyArgs
textProcessment1 GWritingSystemPRPLX
wrs [FirstChars]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
qs Concatenations
ysss Concatenations
zzzsss String
ws String
toFileMode1 Bool
recursiveMode Bool
interactiveP Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX (forall a. GQtyArgs -> [a] -> [a]
drop GQtyArgs
1 [String]
args) Bool
lstW Bool
syllables GQtyArgs
syllablesVs GQtyArgs
verbose String -> String
g1
else PermutationsType
-> (String -> Bool)
-> [String]
-> String
-> GQtyArgs
-> GWritingSystemPRPLX
-> [FirstChars]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Concatenations
-> Concatenations
-> String
-> String
-> Bool
-> Bool
-> Bool
-> [String]
-> Coeffs2
-> Coeffs2
-> [String]
-> Bool
-> Bool
-> GQtyArgs
-> GQtyArgs
-> (String -> String)
-> IO ()
generalProc3G PermutationsType
pairwisePermutations String -> Bool
p [String]
textProcessmentFss String
textProcessment0 GQtyArgs
textProcessment1 GWritingSystemPRPLX
wrs [FirstChars]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
qs Concatenations
ysss Concatenations
zzzsss String
ws String
toFileMode1 Bool
recursiveMode Bool
interactiveP Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX [String]
args Bool
lstW Bool
syllables GQtyArgs
syllablesVs GQtyArgs
verbose String -> String
g1
innerProcessmentSimple
:: String
-> String
-> String
-> String
-> String
-> (GWritingSystemPRPLX, [(Char, Char)], CharPhoneticClassification, SegmentRulesG, String, String, Concatenations, Concatenations, String)
innerProcessmentSimple :: String
-> String
-> String
-> String
-> String
-> (GWritingSystemPRPLX, [FirstChars], CharPhoneticClassification,
SegmentRulesG, String, String, Concatenations, Concatenations,
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] -> Concatenations
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 :: [FirstChars]
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 :: Concatenations
ysss = Concatenations -> Concatenations
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 :: Concatenations
zzzsss = Concatenations -> Concatenations
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 (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String]
jss
vs :: String
vs = forall (t :: * -> *) a. Foldable t => t [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 (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ [String]
wss
in (GWritingSystemPRPLX
wrs, [FirstChars]
ks, CharPhoneticClassification
arr, SegmentRulesG
gs, String
js, String
vs, Concatenations
ysss, Concatenations
zzzsss, String
ws)
argsProcessment
:: FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> [String]
-> IO (String, String, String, String, String, String, Bool, Bool, [String], Coeffs2, Coeffs2, [String], Bool, Bool,Int,Int)
argsProcessment :: String
-> String
-> String
-> String
-> String
-> [String]
-> IO
(String, String, String, String, String, String, Bool, Bool,
[String], Coeffs2, Coeffs2, [String], Bool, Bool, GQtyArgs,
GQtyArgs)
argsProcessment String
fileGWrSys String
controlFile String
segmentRulesFile String
concatenationsFileP String
concatenationsFileA [String]
args00 = do
let args0 :: [String]
args0 = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+x",GQtyArgs
1)] forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeAsR (forall a b. [a] -> [b] -> [(a, b)]
zip [String
"+b",String
"+l",String
"+bl",String
"+i"] forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
cycle forall a b. (a -> b) -> a -> b
$ [GQtyArgs
0]) forall a b. (a -> b) -> a -> b
$ [String]
args00
lstW :: Bool
lstW = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\String
x -> String
x forall a. Eq a => a -> a -> Bool
== String
"+b" Bool -> Bool -> Bool
|| String
x forall a. Eq a => a -> a -> Bool
== String
"+bl") [String]
args00
jstL0 :: Bool
jstL0 = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\String
x -> String
x forall a. Eq a => a -> a -> Bool
== String
"+l" Bool -> Bool -> Bool
|| String
x forall a. Eq a => a -> a -> Bool
== String
"+bl") [String]
args00
toFileMode1 :: String
toFileMode1 = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getB String
"+f" forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> Args
bSpcs forall a b. (a -> b) -> a -> b
$ [String]
args0
interactiveP :: Bool
interactiveP = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall a. Eq a => a -> a -> Bool
== String
"+i") [String]
args00 Bool -> Bool -> Bool
|| Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
toFileMode1)
args01 :: [String]
args01 = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. FirstChars -> CLSpecifications -> [String] -> (Args, [String])
takeCs1R FirstChars
fstCharsMA [(String
"+a",-GQtyArgs
1)] forall a b. (a -> b) -> a -> b
$ [String]
args0
syllables :: Bool
syllables = forall (t :: * -> *). Foldable t => String -> t Arguments -> Bool
oneB String
"+s" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+s",GQtyArgs
1)] forall a b. (a -> b) -> a -> b
$ [String]
args00
syllablesVs :: GQtyArgs
syllablesVs = if Bool
syllables then forall a. a -> Maybe a -> a
fromMaybe GQtyArgs
1 (forall a. Read a => String -> Maybe a
readMaybe (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getB String
"+s" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+s",GQtyArgs
1)] forall a b. (a -> b) -> a -> b
$ [String]
args00)::Maybe Int) else GQtyArgs
0
verbose :: GQtyArgs
verbose = if (forall (t :: * -> *). Foldable t => String -> t Arguments -> Bool
oneB String
"+v" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+v",GQtyArgs
1)] forall a b. (a -> b) -> a -> b
$ [String]
args00) then forall a. a -> Maybe a -> a
fromMaybe GQtyArgs
1 (forall a. Read a => String -> Maybe a
readMaybe (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getB String
"+v" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+v",GQtyArgs
1)] forall a b. (a -> b) -> a -> b
$ [String]
args00)::Maybe Int) else GQtyArgs
0
args02 :: [String]
args02
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
toFileMode1 = forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
/= String
"+f") [String]
args01
| Bool
otherwise = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+f",GQtyArgs
1)] forall a b. (a -> b) -> a -> b
$ [String]
args01
args :: [String]
args = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. FirstChars -> CLSpecifications -> [String] -> (Args, [String])
takeCs1R FirstChars
fstCharsMA [(String
"+m",-GQtyArgs
1)] forall a b. (a -> b) -> a -> b
$ [String]
args02
coeffs :: Coeffs2
coeffs = String -> Coeffs2
readCF forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. GQtyArgs -> [a] -> [a]
take GQtyArgs
1 forall a b. (a -> b) -> a -> b
$ [String]
args
coeffsWX :: Coeffs2
coeffsWX = String -> Coeffs2
readCF forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getB String
"+x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+x",GQtyArgs
1)] forall a b. (a -> b) -> a -> b
$ [String]
args00
[String
controlConts, String
gwrsCnts, String
segmentData, String
concatenationsFileP1, String
concatenationsFileA1] <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> IO String
readFile [String
controlFile, String
fileGWrSys, String
segmentRulesFile, String
concatenationsFileP, String
concatenationsFileA]
forall (m :: * -> *) a. Monad m => a -> m a
return (String
gwrsCnts, String
controlConts, String
segmentData, String
concatenationsFileP1, String
concatenationsFileA1, String
toFileMode1, Bool
interactiveP, Bool
jstL0, [String]
args0, Coeffs2
coeffs, Coeffs2
coeffsWX, [String]
args, Bool
lstW,Bool
syllables,GQtyArgs
syllablesVs,GQtyArgs
verbose)
aSpecs :: CLSpecifications
aSpecs :: CLSpecifications
aSpecs = forall a b. [a] -> [b] -> [(a, b)]
zip [String
"+r",String
"+b",String
"+l",String
"+bl",String
"+i"] forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
cycle forall a b. (a -> b) -> a -> b
$ [GQtyArgs
0]
aSpcs :: [String] -> Args
aSpcs :: [String] -> Args
aSpcs = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeAsR CLSpecifications
aSpecs
cSpecs1MA :: CLSpecifications
cSpecs1MA :: CLSpecifications
cSpecs1MA = forall a b. [a] -> [b] -> [(a, b)]
zip [String
"+m",String
"+a"] forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
cycle forall a b. (a -> b) -> a -> b
$ [-GQtyArgs
1]
fstCharsMA :: FirstChars
fstCharsMA :: FirstChars
fstCharsMA = (Char
'+',Char
'-')
cSpecs1T :: CLSpecifications
cSpecs1T :: CLSpecifications
cSpecs1T = [(String
"+t",-GQtyArgs
1)]
fstCharsT :: FirstChars
fstCharsT :: FirstChars
fstCharsT = (Char
'+',Char
'^')
bSpecs :: CLSpecifications
bSpecs :: CLSpecifications
bSpecs = forall a b. [a] -> [b] -> [(a, b)]
zip [String
"+d",String
"+f",String
"+p",String
"+s",String
"+v"] forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
cycle forall a b. (a -> b) -> a -> b
$ [GQtyArgs
1]
bSpcs :: [String] -> Args
bSpcs :: [String] -> Args
bSpcs = forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR CLSpecifications
bSpecs
specs1 :: CLSpecifications
specs1 :: CLSpecifications
specs1 = CLSpecifications
aSpecs forall a. Monoid a => a -> a -> a
`mappend` CLSpecifications
bSpecs forall a. Monoid a => a -> a -> a
`mappend` CLSpecifications
cSpecs1MA