-- |
-- Module      :  Phonetic.Languages.General.Simple.Parsing
-- Copyright   :  (c) OleksandrZhabenko 2020-2022
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  olexandr543@yahoo.com
--
-- Prints the rearrangements with the \"property\" information for the phonetic language text. Is used for the
-- Phonetic.Languages.General.Simple module functionality.

{-# 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

-- | Prints the rearrangements with the \"property\" information for the phonetic language text.
-- Most of the arguments are obtained from the 'getArgs' function.
-- While used, it distinguishes between two groups of command line arguments: the first four ones and the others afterwards.
-- The first 5 arguments are the file names with the specifications.
-- 1) with the 'GWritingSystemPRPLX' specifications only (see the gwrsysExample.txt file in the @phonetic-languages-phonetics-basics@ package as a schema);
--
-- 2) with the 5 meaningful lines that are delimited with the \'~\' line one from another with the specifications for the possible allophones (if any), 'CharPhoneticClassification', white spaces information (two 'String's) and the 'String' of all the possible 'PLL' 'Char's;
--
-- 3) with the 'SegmentRulesG' specifications only;
--
-- 4) with the 'Concatenations' specifications only (see the data in the EnglishConcatenated.txt file in the @phonetic-languages-phonetics-basics@ package as a list of English equivalents of the needed 'String's). These are to be prepended to the next word.
--
-- 5) with the 'Concatenations' specifications only (see the data in the EnglishConcatenated.txt file in the @phonetic-languages-phonetics-basics@ package as a list of English equivalents of the needed 'String's). These are to be appended to the previous word.
--
-- Afterwards, the meaning of the command line arguments are as follows (from the left to the right).
--
-- The first next command line argument must be a
-- positive 'Int' number and is a number of printed variants for the line (if they are present, otherwise just all possible variants are printed).
-- The second one is the number of the intervals into which the all range of possible metrics values are divided. The next numeric arguments that must be
-- sequenced without interruptions further are treated as the numbers of the intervals (counting is started from 1) which values are moved to the maximum
-- values of the metrics interval using the 'unsafeSwapVecIWithMaxI' function. The first textual command line argument should be in the form either \"y0\",
-- or \"0y\", or \"yy\", or \"y\", or \"02y\", or \"y2\", or \"03y\", or \"yy2\", or \"y3\", or some other variant and specifies, which property or properties is or are evaluated.
-- The rest of the command line arguments is the phonetic text. Besides, you can use multiple metrices (no more than 5 different ones) together by
-- using \"+m\" ... \"-m\" command line arguments.
--
-- You can specify constraints according to the 'decodeLConstraints' function between +A and -A next command line arguments. If so, the program will
-- ask you additional question before proceeding. The \"+m\" ... \"-m\" and \"+a\" ... \"-a\" groups must not mutually intersect one another.
argsToSimplePrepare
 :: (Double -> String -> MappingFunctionPL) -- ^ The function that is needed in the 'procRhythmicity23F' function.
 -- Specifies a way how the syllables represented in the phonetic language approach transforms into their durations and
 -- depends on two parameters. Is specific for every phonetic language and every representation, so must be provided
 -- by the user in every case. The example of the function can be found in the package @phonetic-languages-simplified-properties-array@.
 -> [MappingFunctionPL] -- ^ A list of 'PhoPaaW'-based different functions that specifies the syllables durations in the PhoPaaW mode, analogues of the
   -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The first one must be probably the most
   --   -- exact one and, therefore, the default one.
 -> (String -> Bool) -- ^ The predicate that checks whether the given argument is not a phonetic language word in the representation.
 -> IO ()
argsToSimplePrepare :: (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL] -> (String -> Bool) -> IO ()
argsToSimplePrepare Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
qs String -> Bool
p = 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 = (Args, [String]) -> [String]
forall a b. (a, b) -> b
snd ((Args, [String]) -> [String])
-> ([String] -> (Args, [String])) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+p",GQtyArgs
1)] ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
args50
     pairwisePermutations :: PermutationsType
pairwisePermutations = [String] -> PermutationsType
R.bTransform2Perms ([String] -> PermutationsType)
-> (Args -> [String]) -> Args -> PermutationsType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Args -> [String]
forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getB String
"+p" (Args -> PermutationsType) -> Args -> PermutationsType
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 = String -> Args -> [String]
forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getC String
"+t" Args
txtPFs
     textProcessment0 :: String
textProcessment0
       | String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (String -> Bool) -> ([String] -> String) -> [String] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Args -> [String]
forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getB String
"+t" (Args -> [String]) -> ([String] -> Args) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Args, [String]) -> Args
forall a b. (a, b) -> a
fst ((Args, [String]) -> Args)
-> ([String] -> (Args, [String])) -> [String] -> Args
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+t",GQtyArgs
1)] ([String] -> Bool) -> [String] -> Bool
forall a b. (a -> b) -> a -> b
$ [String]
args00000 = []
       | Bool
otherwise = String
"+t" String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` ([String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Args -> [String]
forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getB String
"+t" (Args -> [String]) -> ([String] -> Args) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Args, [String]) -> Args
forall a b. (a, b) -> a
fst ((Args, [String]) -> Args)
-> ([String] -> (Args, [String])) -> [String] -> Args
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+t",GQtyArgs
1)] ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
args00000)
     textProcessment1 :: GQtyArgs
textProcessment1 = GQtyArgs -> Maybe GQtyArgs -> GQtyArgs
forall a. a -> Maybe a -> a
fromMaybe GQtyArgs
70 (String -> Maybe GQtyArgs
forall a. Read a => String -> Maybe a
readMaybe (GQtyArgs -> String -> String
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)] ([String] -> (Args, [String]))
-> ([String] -> [String]) -> [String] -> (Args, [String])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (String -> Bool) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) ([String] -> (Args, [String])) -> [String] -> (Args, [String])
forall a b. (a -> b) -> a -> b
$ [String]
args0000F
     recursiveMode :: Bool
recursiveMode = String -> Args -> Bool
forall (t :: * -> *). Foldable t => String -> t Arguments -> Bool
oneA String
"+r" Args
rcrs -- Specifies whether to use the interactive recursive mode
     (![String]
args15,![String]
args00) = GQtyArgs -> [String] -> ([String], [String])
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 <- (String -> IO String) -> [String] -> IO [String]
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 = (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (String -> Bool) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null) [String]
textProcessmentFss0
 if Coeffs2 -> Bool
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
-> 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 {- old arguments follow -} String
toFileMode1 Bool
recursiveMode Bool
interactiveP Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX (GQtyArgs -> [String] -> [String]
forall a. GQtyArgs -> [a] -> [a]
drop GQtyArgs
1 [String]
args) Bool
lstW Bool
syllables GQtyArgs
syllablesVs GQtyArgs
verbose
 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
-> 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

-- | Similar to the 'argsToSimplePrepare' function, but takes explicitly the four 'FilePath's for the files
-- respectively and the last argument the 'String' with all the other specifications. If it is not proper,
-- the functions returns an error.
argsToSimplePrepare4Files
 :: R.PermutationsType -- ^ Whether to use just one of the express permutations, or the full universal set.
 -> FilePath -- ^ With the 'GWritingSystemPRPLX' specifications only (see the gwrsysExample.txt file in the @phonetic-languages-phonetics-basics@ package as a schema);
 -> FilePath -- ^ With the 5 meaningful lines that are delimited with the \'~\' line one from another with the specifications for the possible allophones (if any), 'CharPhoneticClassification', white spaces information (two 'String's) and the 'String' of all the possible 'PLL' 'Char's;
 -> FilePath -- ^ With the 'SegmentRulesG' specifications only;
 -> FilePath -- ^ With the 'Concatenations' specifications only (see the data in the EnglishConcatenated.txt file in the @phonetic-languages-phonetics-basics@ package as a list of English equivalents of the needed 'String's). These are to be prepended to the next word.
 -> FilePath -- ^ With the 'Concatenations' specifications only (see the data in the EnglishConcatenated.txt file in the @phonetic-languages-phonetics-basics@ package as a list of English equivalents of the needed 'String's). These are to be appended to the previous word.
 -> (Double -> String -> MappingFunctionPL) -- ^ The function that is needed in the 'procRhythmicity23F' function.
 -- Specifies a way how the syllables represented in the phonetic language approach transforms into their durations and
 -- depends on two parameters. Is specific for every phonetic language and every representation, so must be provided
 -- by the user in every case. The example of the function can be found in the package @phonetic-languages-simplified-properties-array@.
 -> [MappingFunctionPL] -- ^ A list of 4 different functions that specifies the syllables durations, analogues of the
  -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most
  -- exact one and, therefore, the default one.
 -> String -- ^ A 'String' of data that are the further command line arguments for the function 'argsToSimplePrepare'.
 -> (String -> Bool) -- ^ The predicate that checks whether the given argument is not a phonetic language word in the representation.
 -> [String]
 -> String -- ^ If empty, the function is just 'generalProc2G' with the arguments starting from the first 'Bool' here.
 -> Int
 -> IO ()
argsToSimplePrepare4Files :: PermutationsType
-> String
-> String
-> String
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> String
-> (String -> Bool)
-> [String]
-> String
-> GQtyArgs
-> 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 = do
 let args000 :: [String]
args000 = GQtyArgs -> [String] -> [String]
forall a. GQtyArgs -> [a] -> [a]
drop GQtyArgs
5 ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words (String -> [String]) -> String -> [String]
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 = String -> Args -> Bool
forall (t :: * -> *). Foldable t => String -> t Arguments -> Bool
oneA String
"+r" Args
rcs -- Specifies whether to use the interactive recursive mode
 (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 Coeffs2 -> Bool
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
-> 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 {- old arguments follow -} String
toFileMode1 Bool
recursiveMode Bool
interactiveP Bool
jstL0 [String]
args0 Coeffs2
coeffs Coeffs2
coeffsWX (GQtyArgs -> [String] -> [String]
forall a. GQtyArgs -> [a] -> [a]
drop GQtyArgs
1 [String]
args) Bool
lstW Bool
syllables GQtyArgs
syllablesVs GQtyArgs
verbose
 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
-> 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

innerProcessmentSimple
  :: String -- ^ Must be a valid 'GWritingSystemPRPLX' specifications 'String' representation only (see the gwrsysExample.txt file in the @phonetic-languages-phonetics-basics@ package as a schema);
  -> String -- ^ Must be a 'String' with the 5 meaningful lines that are delimited with the \'~\' line one from another with the specifications for the possible allophones (if any), 'CharPhoneticClassification', white spaces information (two 'String's) and the 'String' of all the possible 'PLL' 'Char's;
  -> String -- ^ Must be a 'String' with the 'SegmentRulesG' specifications only;
  -> String -- ^ Must be a 'String' with the 'Concatenations' specifications only (see the data in the EnglishConcatenated.txt file in the @phonetic-languages-phonetics-basics@ package as a list of English equivalents of the needed 'String's). These are to be prepended to the next word.
  -> String -- ^ Must be a 'String' with the 'Concatenations' specifications only (see the data in the EnglishConcatenated.txt file in the @phonetic-languages-phonetics-basics@ package as a list of English equivalents of the needed 'String's). These are to be appended to the previous word.
  -> (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
'~' ([String] -> Concatenations)
-> (String -> [String]) -> String -> Concatenations
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines (String -> Concatenations) -> String -> Concatenations
forall a b. (a -> b) -> a -> b
$ String
controlConts
     wrs :: GWritingSystemPRPLX
wrs = Char -> String -> GWritingSystemPRPLX
getGWritingSystem Char
'~' String
gwrsCnts
     ks :: [FirstChars]
ks = [FirstChars] -> [FirstChars]
forall a. Ord a => [a] -> [a]
sort ([FirstChars] -> [FirstChars])
-> (Maybe [FirstChars] -> [FirstChars])
-> Maybe [FirstChars]
-> [FirstChars]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FirstChars] -> Maybe [FirstChars] -> [FirstChars]
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe [FirstChars] -> [FirstChars])
-> Maybe [FirstChars] -> [FirstChars]
forall a b. (a -> b) -> a -> b
$ (String -> Maybe [FirstChars]
forall a. Read a => String -> Maybe a
readMaybe ([String] -> String
unwords [String]
allophonesGs)::Maybe [(Char, Char)])
     arr :: CharPhoneticClassification
arr = String -> CharPhoneticClassification
forall a. Read a => String -> a
read ([String] -> String
unwords [String]
charClfs)::Array Int PRS -- The 'Array' must be previously sorted in the ascending order.
     gs :: SegmentRulesG
gs = String -> SegmentRulesG
forall a. Read a => String -> a
read String
segmentData::SegmentRulesG
     ysss :: Concatenations
ysss = Concatenations -> Concatenations
sort2Concat (Concatenations -> Concatenations)
-> (Maybe Concatenations -> Concatenations)
-> Maybe Concatenations
-> Concatenations
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Concatenations -> Maybe Concatenations -> Concatenations
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe Concatenations -> Concatenations)
-> Maybe Concatenations -> Concatenations
forall a b. (a -> b) -> a -> b
$ (String -> Maybe Concatenations
forall a. Read a => String -> Maybe a
readMaybe String
concatenationsFileP::Maybe [[String]])
     zzzsss :: Concatenations
zzzsss = Concatenations -> Concatenations
sort2Concat (Concatenations -> Concatenations)
-> (Maybe Concatenations -> Concatenations)
-> Maybe Concatenations
-> Concatenations
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Concatenations -> Maybe Concatenations -> Concatenations
forall a. a -> Maybe a -> a
fromMaybe [] (Maybe Concatenations -> Concatenations)
-> Maybe Concatenations -> Concatenations
forall a b. (a -> b) -> a -> b
$ (String -> Maybe Concatenations
forall a. Read a => String -> Maybe a
readMaybe String
concatenationsFileA::Maybe [[String]])
     js :: String
js = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String]
jss
     vs :: String
vs = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String]
vss
     ws :: String
ws = String -> String
forall a. Ord a => [a] -> [a]
sort (String -> String) -> ([String] -> String) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String) -> [String] -> String
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)

{-| @ since 0.5.0.0
The function also can process \"w\" and \"x\" lines so returns two 'Coeffs2' values.
-}
argsProcessment
 :: FilePath -- ^ With the 'GWritingSystemPRPLX' specifications only (see the gwrsysExample.txt file in the @phonetic-languages-phonetics-basics@ package as a schema);
 -> FilePath -- ^ With the 5 meaningful lines that are delimited with the \'~\' line one from another with the specifications for the possible allophones (if any), 'CharPhoneticClassification', white spaces information (two 'String's) and the 'String' of all the possible 'PLL' 'Char's;
 -> FilePath -- ^ With the 'SegmentRulesG' specifications only;
 -> FilePath -- ^ With the 'Concatenations' specifications only (see the data in the EnglishConcatenated.txt file in the @phonetic-languages-phonetics-basics@ package as a list of English equivalents of the needed 'String's). These are to be prepended to the next word.
 -> FilePath -- ^ With the 'Concatenations' specifications only (see the data in the EnglishConcatenated.txt file in the @phonetic-languages-phonetics-basics@ package as a list of English equivalents of the needed 'String's). These are to be appended to the previous word.
 -> [String] -- ^ List of other args afterwards.
 -> 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 = (Args, [String]) -> [String]
forall a b. (a, b) -> b
snd ((Args, [String]) -> [String])
-> ([String] -> (Args, [String])) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+x",GQtyArgs
1)] ([String] -> (Args, [String]))
-> ([String] -> [String]) -> [String] -> (Args, [String])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Args, [String]) -> [String]
forall a b. (a, b) -> b
snd ((Args, [String]) -> [String])
-> ([String] -> (Args, [String])) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeAsR ([String] -> [GQtyArgs] -> CLSpecifications
forall a b. [a] -> [b] -> [(a, b)]
zip [String
"+b",String
"+l",String
"+bl",String
"+i"] ([GQtyArgs] -> CLSpecifications)
-> ([GQtyArgs] -> [GQtyArgs]) -> [GQtyArgs] -> CLSpecifications
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [GQtyArgs] -> [GQtyArgs]
forall a. [a] -> [a]
cycle ([GQtyArgs] -> CLSpecifications) -> [GQtyArgs] -> CLSpecifications
forall a b. (a -> b) -> a -> b
$ [GQtyArgs
0]) ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
args00
     lstW :: Bool
lstW = (String -> Bool) -> [String] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\String
x -> String
x String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"+b" Bool -> Bool -> Bool
|| String
x String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"+bl") [String]
args00 -- If one of the command line options is \"+b\" or \"+bl\" then the last word of the line will remain the last one.
     jstL0 :: Bool
jstL0 = (String -> Bool) -> [String] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\String
x -> String
x String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"+l" Bool -> Bool -> Bool
|| String
x String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"+bl") [String]
args00 -- If one of the command line options is \"+l\" or \"+bl\" then the program outputs just lines without metrices values.
     toFileMode1 :: String
toFileMode1 = [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Args -> [String]
forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getB String
"+f" (Args -> [String]) -> ([String] -> Args) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> Args
bSpcs ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
args0  -- Prints the last resulting line of the interactive mode processment (the last selected variant) to the file and also to the stdout.
     interactiveP :: Bool
interactiveP = (String -> Bool) -> [String] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"+i") [String]
args00 Bool -> Bool -> Bool
|| Bool -> Bool
not (String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
toFileMode1) -- If one of the command line options is \"+i\", or \"+f\" then the program prints the variants and then prompts for the preferred variant. Afterwards, it prints just that variant alone.
     args01 :: [String]
args01 = (Args, [String]) -> [String]
forall a b. (a, b) -> b
snd ((Args, [String]) -> [String])
-> ([String] -> (Args, [String])) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FirstChars -> CLSpecifications -> [String] -> (Args, [String])
takeCs1R FirstChars
fstCharsMA [(String
"+a",-GQtyArgs
1)] ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
args0
     syllables :: Bool
syllables = String -> Args -> Bool
forall (t :: * -> *). Foldable t => String -> t Arguments -> Bool
oneB String
"+s" (Args -> Bool) -> ([String] -> Args) -> [String] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Args, [String]) -> Args
forall a b. (a, b) -> a
fst ((Args, [String]) -> Args)
-> ([String] -> (Args, [String])) -> [String] -> Args
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+s",GQtyArgs
1)] ([String] -> Bool) -> [String] -> Bool
forall a b. (a -> b) -> a -> b
$ [String]
args00
     syllablesVs :: GQtyArgs
syllablesVs = if Bool
syllables then GQtyArgs -> Maybe GQtyArgs -> GQtyArgs
forall a. a -> Maybe a -> a
fromMaybe GQtyArgs
1 (String -> Maybe GQtyArgs
forall a. Read a => String -> Maybe a
readMaybe ([String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Args -> [String]
forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getB String
"+s" (Args -> [String]) -> ([String] -> Args) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Args, [String]) -> Args
forall a b. (a, b) -> a
fst ((Args, [String]) -> Args)
-> ([String] -> (Args, [String])) -> [String] -> Args
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+s",GQtyArgs
1)] ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
args00)::Maybe Int) else GQtyArgs
0
     verbose :: GQtyArgs
verbose = if (String -> Args -> Bool
forall (t :: * -> *). Foldable t => String -> t Arguments -> Bool
oneB String
"+v" (Args -> Bool) -> ([String] -> Args) -> [String] -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Args, [String]) -> Args
forall a b. (a, b) -> a
fst ((Args, [String]) -> Args)
-> ([String] -> (Args, [String])) -> [String] -> Args
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+v",GQtyArgs
1)] ([String] -> Bool) -> [String] -> Bool
forall a b. (a -> b) -> a -> b
$ [String]
args00) then GQtyArgs -> Maybe GQtyArgs -> GQtyArgs
forall a. a -> Maybe a -> a
fromMaybe GQtyArgs
1 (String -> Maybe GQtyArgs
forall a. Read a => String -> Maybe a
readMaybe ([String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Args -> [String]
forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getB String
"+v" (Args -> [String]) -> ([String] -> Args) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Args, [String]) -> Args
forall a b. (a, b) -> a
fst ((Args, [String]) -> Args)
-> ([String] -> (Args, [String])) -> [String] -> Args
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+v",GQtyArgs
1)] ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
args00)::Maybe Int) else GQtyArgs
0
     args02 :: [String]
args02
         | String -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
toFileMode1 = (String -> Bool) -> [String] -> [String]
forall a. (a -> Bool) -> [a] -> [a]
filter (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
"+f") [String]
args01
         | Bool
otherwise = (Args, [String]) -> [String]
forall a b. (a, b) -> b
snd ((Args, [String]) -> [String])
-> ([String] -> (Args, [String])) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+f",GQtyArgs
1)] ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
args01
     args :: [String]
args = (Args, [String]) -> [String]
forall a b. (a, b) -> b
snd ((Args, [String]) -> [String])
-> ([String] -> (Args, [String])) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FirstChars -> CLSpecifications -> [String] -> (Args, [String])
takeCs1R FirstChars
fstCharsMA [(String
"+m",-GQtyArgs
1)] ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
args02
     coeffs :: Coeffs2
coeffs = String -> Coeffs2
readCF (String -> Coeffs2) -> ([String] -> String) -> [String] -> Coeffs2
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GQtyArgs -> [String] -> [String]
forall a. GQtyArgs -> [a] -> [a]
take GQtyArgs
1 ([String] -> Coeffs2) -> [String] -> Coeffs2
forall a b. (a -> b) -> a -> b
$ [String]
args
     coeffsWX :: Coeffs2
coeffsWX = String -> Coeffs2
readCF (String -> Coeffs2) -> ([String] -> String) -> [String] -> Coeffs2
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Args -> [String]
forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getB String
"+x" (Args -> [String]) -> ([String] -> Args) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Args, [String]) -> Args
forall a b. (a, b) -> a
fst ((Args, [String]) -> Args)
-> ([String] -> (Args, [String])) -> [String] -> Args
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR [(String
"+x",GQtyArgs
1)] ([String] -> Coeffs2) -> [String] -> Coeffs2
forall a b. (a -> b) -> a -> b
$ [String]
args00
 [String
controlConts, String
gwrsCnts, String
segmentData, String
concatenationsFileP1, String
concatenationsFileA1] <- (String -> IO String) -> [String] -> IO [String]
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]
 (String, String, String, String, String, String, Bool, Bool,
 [String], Coeffs2, Coeffs2, [String], Bool, Bool, GQtyArgs,
 GQtyArgs)
-> IO
     (String, String, String, String, String, String, Bool, Bool,
      [String], Coeffs2, Coeffs2, [String], Bool, Bool, GQtyArgs,
      GQtyArgs)
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 = [String] -> [GQtyArgs] -> CLSpecifications
forall a b. [a] -> [b] -> [(a, b)]
zip [String
"+r",String
"+b",String
"+l",String
"+bl",String
"+i"] ([GQtyArgs] -> CLSpecifications)
-> ([GQtyArgs] -> [GQtyArgs]) -> [GQtyArgs] -> CLSpecifications
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [GQtyArgs] -> [GQtyArgs]
forall a. [a] -> [a]
cycle ([GQtyArgs] -> CLSpecifications) -> [GQtyArgs] -> CLSpecifications
forall a b. (a -> b) -> a -> b
$ [GQtyArgs
0]

aSpcs :: [String] -> Args
aSpcs :: [String] -> Args
aSpcs = (Args, [String]) -> Args
forall a b. (a, b) -> a
fst ((Args, [String]) -> Args)
-> ([String] -> (Args, [String])) -> [String] -> Args
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeAsR CLSpecifications
aSpecs

cSpecs1MA :: CLSpecifications
cSpecs1MA :: CLSpecifications
cSpecs1MA = [String] -> [GQtyArgs] -> CLSpecifications
forall a b. [a] -> [b] -> [(a, b)]
zip [String
"+m",String
"+a"] ([GQtyArgs] -> CLSpecifications)
-> ([GQtyArgs] -> [GQtyArgs]) -> [GQtyArgs] -> CLSpecifications
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [GQtyArgs] -> [GQtyArgs]
forall a. [a] -> [a]
cycle ([GQtyArgs] -> CLSpecifications) -> [GQtyArgs] -> CLSpecifications
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 = [String] -> [GQtyArgs] -> CLSpecifications
forall a b. [a] -> [b] -> [(a, b)]
zip [String
"+d",String
"+f",String
"+p",String
"+s",String
"+v"] ([GQtyArgs] -> CLSpecifications)
-> ([GQtyArgs] -> [GQtyArgs]) -> [GQtyArgs] -> CLSpecifications
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [GQtyArgs] -> [GQtyArgs]
forall a. [a] -> [a]
cycle ([GQtyArgs] -> CLSpecifications) -> [GQtyArgs] -> CLSpecifications
forall a b. (a -> b) -> a -> b
$ [GQtyArgs
1]

bSpcs :: [String] -> Args
bSpcs :: [String] -> Args
bSpcs = (Args, [String]) -> Args
forall a b. (a, b) -> a
fst ((Args, [String]) -> Args)
-> ([String] -> (Args, [String])) -> [String] -> Args
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR CLSpecifications
bSpecs

specs1 :: CLSpecifications
specs1 :: CLSpecifications
specs1 = CLSpecifications
aSpecs CLSpecifications -> CLSpecifications -> CLSpecifications
forall a. Monoid a => a -> a -> a
`mappend` CLSpecifications
bSpecs CLSpecifications -> CLSpecifications -> CLSpecifications
forall a. Monoid a => a -> a -> a
`mappend` CLSpecifications
cSpecs1MA