{-# LANGUAGE NoImplicitPrelude, BangPatterns #-}

module Phladiprelio.General.Simple where

import GHC.Base
import GHC.Enum (fromEnum,toEnum)
import GHC.Real (fromIntegral,(/),quot,rem,quotRem)
import Text.Show (Show(..))
import Phladiprelio.General.PrepareText 
import Phladiprelio.General.Syllables 
import Phladiprelio.General.Base
import System.Environment (getArgs)
import GHC.Num ((+),(-),(*),Integer)
import Text.Read (readMaybe)
import System.IO (putStrLn, FilePath,stdout,universalNewlineMode,hSetNewlineMode,getLine,appendFile,readFile)
import Rhythmicity.MarkerSeqs hiding (id) 
import Rhythmicity.BasicF 
import Data.List hiding (foldr)
import Data.Maybe (fromMaybe, mapMaybe, catMaybes,isNothing,fromJust) 
import Data.Tuple (fst,snd)
import Data.Char (isDigit,isAlpha)
import CLI.Arguments
import CLI.Arguments.Get
import CLI.Arguments.Parsing
import GHC.Int (Int8)
import Data.Ord (comparing)
import Phladiprelio.PermutationsRepresent
import Phladiprelio.ConstraintsEncoded
import Phladiprelio.PermutationsArr
import Phladiprelio.StrictVG
import Numeric (showFFloat)
import Phladiprelio.Halfsplit
import System.Directory (doesFileExist,readable,writable,getPermissions,Permissions(..))
import Data.ReversedScientific
import Control.Concurrent.Async (mapConcurrently)
import Phladiprelio.Tests
import Phladiprelio.General.Datatype (readBasic3, readBasic4, readBasic1G)

generalF 
 :: (String, String)  -- ^ If the next element is not equal to -1, then the prepending and appending lines to be displayed. Used basically for working with the multiline textual input data.
 -> Int -- ^ The number of the line in the file to be read the lines from. If equal to -1 then neither reading from the file is done nor the first argument influences the processment results.
 -> GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text.
 -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon (e. g. allophones). Must be sorted in the ascending order to be used correctly. 
 -> CharPhoneticClassification
 -> SegmentRulesG
 -> String -- ^ Corresponds to the 100 delimiter in the @ukrainian-phonetics-basic-array@ package.
 -> String -- ^ Corresponds to the 101 delimiter in the @ukrainian-phonetics-basic-array@ package.
 -> ([[[PRS]]] -> [[Double]])
 -> Int
 -> HashCorrections 
 -> (Int8,[Int8])
 -> Bool
 -> Int -- ^ The hashing function step. The default value is 20. Is expected to be greater than 2, and better greater than 12. 
 -> Bool 
 -> Int8
 -> (FilePath, Int)
 -> Bool -- ^ In the testing mode, whether to execute computations in concurrent mode (for speed up) or in single thread. If specified needs the executable to be compiled with -rtsopts and -threaded options and run with the command line +RTS -N -RTS options.
 -> String -- ^ An initial string to be analyzed.
 -> [String] 
 -> IO [String] 
generalF :: (String, String)
-> GQtyArgs
-> GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> ([[[PRS]]] -> [[Double]])
-> GQtyArgs
-> HashCorrections
-> (Int8, [Int8])
-> Bool
-> GQtyArgs
-> Bool
-> Int8
-> (String, GQtyArgs)
-> Bool
-> String
-> [String]
-> IO [String]
generalF (String
prestr,String
poststr) GQtyArgs
lineNmb GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
us String
vs [[[PRS]]] -> [[Double]]
h GQtyArgs
numTest HashCorrections
hc (Int8
grps,[Int8]
mxms) Bool
descending GQtyArgs
hashStep Bool
emptyline Int8
splitting (String
fs, GQtyArgs
code) Bool
concurrently String
initstr [String]
universalSet 
 | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
universalSet = let strOutput :: [String]
strOutput = [String
"You have specified the data and constraints on it that lead to no further possible options.", String
"Please, specify another data and constraints."] in forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM String -> IO ()
putStrLn [String]
strOutput forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return [String]
strOutput
 | forall (t :: * -> *) a. Foldable t => t a -> GQtyArgs
length [String]
universalSet forall a. Eq a => a -> a -> Bool
== GQtyArgs
1 = forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM String -> IO ()
putStrLn [String]
universalSet forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return [String]
universalSet
 | Bool
otherwise = do
   let syllN :: GQtyArgs
syllN = GWritingSystemPRPLX
-> CharPhoneticClassification
-> String
-> String
-> String
-> GQtyArgs
countSyll GWritingSystemPRPLX
wrs CharPhoneticClassification
arr String
us String
vs String
initstr
--       universalSet = map unwords . permutations $ rss
       f :: Int8 -> [Int8] -> String -> Integer
f Int8
grps [Int8]
mxms = forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Ord a =>
GQtyArgs -> HashCorrections -> Int8 -> [Int8] -> [a] -> [Integer]
countHashes2G GQtyArgs
hashStep HashCorrections
hc Int8
grps [Int8]
mxms forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}.
(String -> [a]) -> ([a] -> [Double]) -> String -> [Double]
readBasic3 ([[[PRS]]] -> [[Double]]
h forall b c a. (b -> c) -> (a -> b) -> a -> c
.  GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [[[PRS]]]
createSyllablesPL GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
us String
vs) (forall a. Monoid a => [a] -> a
mconcat)
   Handle -> NewlineMode -> IO ()
hSetNewlineMode Handle
stdout NewlineMode
universalNewlineMode
   if GQtyArgs
numTest forall a. Ord a => a -> a -> Bool
>= GQtyArgs
0 Bool -> Bool -> Bool
&& GQtyArgs
numTest forall a. Ord a => a -> a -> Bool
<= GQtyArgs
179 Bool -> Bool -> Bool
&& GQtyArgs
numTest forall a. Eq a => a -> a -> Bool
/= GQtyArgs
1 then do
      String -> IO ()
putStrLn String
"Feet   Val  Stat   Proxim" 
      (if Bool
concurrently then forall (t :: * -> *) a b.
Traversable t =>
(a -> IO b) -> t a -> IO (t b)
mapConcurrently else forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM) 
           (\(Int8
q,[Int8]
qs) -> let m :: GQtyArgs
m = GQtyArgs -> (Int8, [Int8]) -> GQtyArgs
stat1 GQtyArgs
syllN (Int8
q,[Int8]
qs)
                           (String
min1,String
max1) = forall a. Ord a => (a -> a -> Ordering) -> [a] -> (a, a)
minMax11ByCList (forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (Int8 -> [Int8] -> String -> Integer
f Int8
q [Int8]
qs)) [String]
universalSet 
                           mx :: Integer
mx = Int8 -> [Int8] -> String -> Integer
f Int8
q [Int8]
qs String
max1
                           strTest :: String
strTest = (forall a. Show a => a -> String
show (forall a. Enum a => a -> GQtyArgs
fromEnum Int8
q) forall a. Monoid a => a -> a -> a
`mappend` String
"   |   " forall a. Monoid a => a -> a -> a
`mappend`  forall a. Show a => a -> String
show Integer
mx forall a. Monoid a => a -> a -> a
`mappend` String
"     " forall a. Monoid a => a -> a -> a
`mappend` forall a. Show a => a -> String
show GQtyArgs
m forall a. Monoid a => a -> a -> a
`mappend` String
"  -> " forall a. Monoid a => a -> a -> a
`mappend` forall a. RealFloat a => Maybe GQtyArgs -> a -> ShowS
showFFloat (forall a. a -> Maybe a
Just GQtyArgs
3) (Double
100 forall a. Num a => a -> a -> a
* forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
mx forall a. Fractional a => a -> a -> a
/ forall a b. (Integral a, Num b) => a -> b
fromIntegral GQtyArgs
m) String
"%" forall a. Monoid a => a -> a -> a
`mappend` (if forall a. Integral a => a -> a -> a
rem GQtyArgs
numTest GQtyArgs
10 forall a. Ord a => a -> a -> Bool
>= GQtyArgs
4 
                                                               then let min1 :: String
min1 = forall (t :: * -> *) a.
Foldable t =>
(a -> a -> Ordering) -> t a -> a
minimumBy (forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (Int8 -> [Int8] -> String -> Integer
f Int8
q [Int8]
qs)) [String]
universalSet in (String
"\n" forall a. Monoid a => a -> a -> a
`mappend` String
min1 forall a. Monoid a => a -> a -> a
`mappend` String
"\n" forall a. Monoid a => a -> a -> a
`mappend` String
max1 forall a. Monoid a => a -> a -> a
`mappend` String
"\n")  
                                                               else String
"")) in String -> IO ()
putStrLn String
strTest forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return String
strTest) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. [a] -> [b] -> [(a, b)]
zip (GQtyArgs -> [Int8]
sel2 GQtyArgs
numTest) forall a b. (a -> b) -> a -> b
$ (GQtyArgs -> [[Int8]]
sel GQtyArgs
numTest)
   else let sRepresent :: [PhladiprelioGen]
sRepresent = forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\GQtyArgs
k (Integer
x, String
ys) -> GQtyArgs -> Integer -> String -> PhladiprelioGen
S GQtyArgs
k Integer
x String
ys) [GQtyArgs
1..] forall b c a. (b -> c) -> (a -> b) -> a -> c
. 
             (let h1 :: (Integer, b) -> (Integer, b)
h1 = if Bool
descending then (\(Integer
u,b
w) -> ((-Integer
1)forall a. Num a => a -> a -> a
*Integer
u,b
w)) else forall a. a -> a
id in forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn forall {b}. (Integer, b) -> (Integer, b)
h1) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (\String
xss -> (Int8 -> [Int8] -> String -> Integer
f Int8
grps [Int8]
mxms String
xss, String
xss)) forall a b. (a -> b) -> a -> b
$ [String]
universalSet
            strOutput :: [String]
strOutput = (forall a. a -> [a] -> [a]
:[]) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Show a, Eq b) => (a -> b) -> Int8 -> [a] -> String
halfsplit (\(S GQtyArgs
_ Integer
y String
_) -> Integer
y) (forall {a}. Integral a => a -> a
jjj Int8
splitting) forall a b. (a -> b) -> a -> b
$ [PhladiprelioGen]
sRepresent
                          in do
                             [()]
_ <- forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM String -> IO ()
putStrLn [String]
strOutput
                             let l1 :: GQtyArgs
l1 = forall (t :: * -> *) a. Foldable t => t a -> GQtyArgs
length [PhladiprelioGen]
sRepresent
                             if GQtyArgs
code forall a. Eq a => a -> a -> Bool
== -GQtyArgs
1 
                                 then if GQtyArgs
lineNmb forall a. Eq a => a -> a -> Bool
== -GQtyArgs
1 then forall (m :: * -> *) a. Monad m => a -> m a
return [String]
strOutput
                                      else do 
                                          String -> String -> GQtyArgs -> [String] -> IO ()
print23 String
prestr String
poststr GQtyArgs
1 [String
initstr]
                                          forall (m :: * -> *) a. Monad m => a -> m a
return [String]
strOutput
                                 else do 
                                       String -> String -> GQtyArgs -> [String] -> IO ()
print23 String
prestr String
poststr GQtyArgs
1 [String
initstr]
                                       GQtyArgs -> IO GQtyArgs
parseLineNumber GQtyArgs
l1 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \GQtyArgs
num -> do
                                         Permissions
permiss <- String -> IO Permissions
getPermissions String
fs
                                         let writ :: Bool
writ = Permissions -> Bool
writable Permissions
permiss
                                             readab :: Bool
readab = Permissions -> Bool
readable Permissions
permiss
                                         if Bool
writ Bool -> Bool -> Bool
&& Bool
readab then do
                                             let lineOption :: PhladiprelioGen
lineOption = forall a. [a] -> a
head forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (\(S GQtyArgs
k Integer
_ String
ts) -> GQtyArgs
k forall a. Eq a => a -> a -> Bool
== GQtyArgs
num) forall a b. (a -> b) -> a -> b
$ [PhladiprelioGen]
sRepresent
                                                 textP :: String
textP = (\(S GQtyArgs
_ Integer
_ String
ts) -> String
ts) PhladiprelioGen
lineOption
                                                 sylls :: [[[PRS]]]
sylls = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [[[PRS]]]
createSyllablesPL GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
us String
vs String
textP
                                             if GQtyArgs
code forall a. Ord a => a -> a -> Bool
>= GQtyArgs
10 Bool -> Bool -> Bool
&& GQtyArgs
code forall a. Ord a => a -> a -> Bool
<= GQtyArgs
19 Bool -> Bool -> Bool
&& Int8
grps forall a. Eq a => a -> a -> Bool
== Int8
2
                                                 then do
                                                     let qqs :: [(String, Double)]
qqs = forall {a} {b}.
(String -> [a])
-> ([a] -> [Double])
-> (String -> [b])
-> ([b] -> [String])
-> [Read2]
-> [(String, Double)]
readBasic4 ([[[PRS]]] -> [[Double]]
h forall b c a. (b -> c) -> (a -> b) -> a -> c
. GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [[[PRS]]]
createSyllablesPL GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
us String
vs) (forall a. Monoid a => [a] -> a
mconcat) (forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [[[PRS]]]
createSyllablesPL GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
us String
vs) (forall a b. (a -> b) -> [a] -> [b]
map (forall a b. (a -> b) -> [a] -> [b]
map PRS -> Char
charS)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [Read2]
readBasic1G forall a b. (a -> b) -> a -> b
$ String
textP
                                                         (String
breaks,[Integer]
rs) = [(String, Double)] -> (String, [Integer])
showZerosFor2PeriodMusic [(String, Double)]
qqs
                                                     String -> IO ()
putStrLn String
textP
                                                     String -> IO ()
putStrLn String
breaks
                                                     String -> IO ()
putStrLn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall a b. (a -> b) -> a -> b
$ [Integer]
rs
                                                     String -> String -> IO ()
appendFile String
fs ((if GQtyArgs
code forall a. Ord a => a -> a -> Bool
>= GQtyArgs
15 then (forall a. Show a => a -> String
show [Integer]
rs forall a. Monoid a => a -> a -> a
`mappend` String
"\n" forall a. Monoid a => a -> a -> a
`mappend` String
breaks forall a. Monoid a => a -> a -> a
`mappend` String
"\n") else String
"") forall a. Monoid a => a -> a -> a
`mappend` PhladiprelioGen -> GQtyArgs -> String
outputSel PhladiprelioGen
lineOption GQtyArgs
code)
                                                 else String -> String -> IO ()
appendFile String
fs (PhladiprelioGen -> GQtyArgs -> String
outputSel PhladiprelioGen
lineOption GQtyArgs
code)
                                         else forall a. HasCallStack => String -> a
error String
"The specified file cannot be used for appending the text! Please, specify another file!"
                                         forall (m :: * -> *) a. Monad m => a -> m a
return []
     where jjj :: a -> a
jjj a
kk = let (a
q1,a
r1) = forall a. Integral a => a -> a -> (a, a)
quotRem a
kk (if a
kk forall a. Ord a => a -> a -> Bool
< a
0 then -a
10 else a
10) in forall {a}. (Num a, Ord a) => a -> a -> Bool -> a
jjj' a
q1 a
r1 Bool
emptyline
           jjj' :: a -> a -> Bool -> a
jjj' a
q1 a
r1 Bool
emptyline
             | a
r1 forall a. Eq a => a -> a -> Bool
== (-a
1) Bool -> Bool -> Bool
|| a
r1 forall a. Eq a => a -> a -> Bool
== (-a
3) = -a
10forall a. Num a => a -> a -> a
*a
q1 forall a. Num a => a -> a -> a
+ (if Bool
emptyline then -a
5 else a
r1)
             | a
r1 forall a. Eq a => a -> a -> Bool
== a
1 Bool -> Bool -> Bool
|| a
r1 forall a. Eq a => a -> a -> Bool
== a
3 = a
10forall a. Num a => a -> a -> a
*a
q1 forall a. Num a => a -> a -> a
+ (if Bool
emptyline then a
5 else a
r1)
             | a
r1 forall a. Ord a => a -> a -> Bool
< a
0 = -a
10forall a. Num a => a -> a -> a
*a
q1 forall a. Num a => a -> a -> a
+ (if Bool
emptyline then -a
4 else a
r1)
             | Bool
otherwise = a
10forall a. Num a => a -> a -> a
*a
q1 forall a. Num a => a -> a -> a
+ (if Bool
emptyline then a
4 else a
r1)

data PhladiprelioGen = S Int Integer String deriving PhladiprelioGen -> PhladiprelioGen -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhladiprelioGen -> PhladiprelioGen -> Bool
$c/= :: PhladiprelioGen -> PhladiprelioGen -> Bool
== :: PhladiprelioGen -> PhladiprelioGen -> Bool
$c== :: PhladiprelioGen -> PhladiprelioGen -> Bool
Eq

instance Show PhladiprelioGen where
  show :: PhladiprelioGen -> String
show (S GQtyArgs
i Integer
j String
xs) = GQtyArgs -> Integer -> String
showBignum GQtyArgs
7 Integer
j forall a. Monoid a => a -> a -> a
`mappend` String
" " forall a. Monoid a => a -> a -> a
`mappend` String
xs forall a. Monoid a => a -> a -> a
`mappend` String
"  " forall a. Monoid a => a -> a -> a
`mappend` forall a. Show a => GQtyArgs -> a -> String
showWithSpaces GQtyArgs
4 GQtyArgs
i

countSyll 
  :: GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text.
  -> CharPhoneticClassification 
  ->  String -- ^ Corresponds to the 100 delimiter in the @ukrainian-phonetics-basic-array@ package.
  -> String -- ^ Corresponds to the 101 delimiter in the @ukrainian-phonetics-basic-array@ package.
  -> String 
  -> Int
countSyll :: GWritingSystemPRPLX
-> CharPhoneticClassification
-> String
-> String
-> String
-> GQtyArgs
countSyll GWritingSystemPRPLX
wrs CharPhoneticClassification
arr String
us String
vs String
xs = forall a. Enum a => a -> GQtyArgs
fromEnum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b -> b) -> b -> [a] -> b
foldr (\PRS
x Integer
y -> if PRS -> Bool
createsSyllable PRS
x then Integer
y forall a. Num a => a -> a -> a
+ Integer
1 else Integer
y) Integer
0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (CharPhoneticClassification -> String -> [PRS]
str2PRSs CharPhoneticClassification
arr) forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Char -> Maybe Char
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap PhoneticsRepresentationPLX -> String
string1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. GWritingSystemPRPLX -> String -> [PhoneticsRepresentationPLX]
stringToXG GWritingSystemPRPLX
wrs forall a b. (a -> b) -> a -> b
$ String
xs
   where g :: Char -> Maybe Char
         g :: Char -> Maybe Char
g Char
x
          | Char
x forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
us = forall a. Maybe a
Nothing
          | Char
x forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` String
vs = forall a. a -> Maybe a
Just Char
x
          | Bool
otherwise = forall a. a -> Maybe a
Just Char
' '
         words1 :: String -> [String]
words1 String
xs = if forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
ts then [] else String
w forall a. a -> [a] -> [a]
: String -> [String]
words1 String
s'' -- Practically this is an optimized version for this case 'words' function from Prelude.
           where ts :: String
ts = forall a. (a -> Bool) -> [a] -> [a]
dropWhile (forall a. Eq a => a -> a -> Bool
== Char
' ') String
xs
                 (String
w, String
s'') = forall a. (a -> Bool) -> [a] -> ([a], [a])
break (forall a. Eq a => a -> a -> Bool
== Char
' ') String
ts
         {-# NOINLINE words1 #-}

stat1 :: Int -> (Int8,[Int8]) -> Int
stat1 :: GQtyArgs -> (Int8, [Int8]) -> GQtyArgs
stat1 GQtyArgs
n (Int8
k, [Int8]
ks) = forall a b. (a, b) -> a
fst (GQtyArgs
n GQtyArgs -> GQtyArgs -> (GQtyArgs, GQtyArgs)
`quotRemInt` forall a. Enum a => a -> GQtyArgs
fromEnum Int8
k) forall a. Num a => a -> a -> a
* forall (t :: * -> *) a. Foldable t => t a -> GQtyArgs
length [Int8]
ks

outputSel :: PhladiprelioGen -> Int -> String
outputSel :: PhladiprelioGen -> GQtyArgs -> String
outputSel (S GQtyArgs
x1 Integer
y1 String
ts) GQtyArgs
code
  | GQtyArgs
code forall a. Ord a => a -> a -> Bool
< GQtyArgs
0 = []
  | GQtyArgs
code forall a. Eq a => a -> a -> Bool
== GQtyArgs
1 Bool -> Bool -> Bool
|| GQtyArgs
code forall a. Eq a => a -> a -> Bool
== GQtyArgs
11 Bool -> Bool -> Bool
|| GQtyArgs
code forall a. Eq a => a -> a -> Bool
== GQtyArgs
16 = forall a. [a] -> [[a]] -> [a]
intercalate String
" " [forall a. Show a => a -> String
show GQtyArgs
x1, String
ts] forall a. Monoid a => a -> a -> a
`mappend` String
"\n"
  | GQtyArgs
code forall a. Eq a => a -> a -> Bool
== GQtyArgs
2 Bool -> Bool -> Bool
|| GQtyArgs
code forall a. Eq a => a -> a -> Bool
== GQtyArgs
12 Bool -> Bool -> Bool
|| GQtyArgs
code forall a. Eq a => a -> a -> Bool
== GQtyArgs
17 = forall a. [a] -> [[a]] -> [a]
intercalate String
" " [forall a. Show a => a -> String
show Integer
y1, String
ts] forall a. Monoid a => a -> a -> a
`mappend` String
"\n"
  | GQtyArgs
code forall a. Eq a => a -> a -> Bool
== GQtyArgs
3 Bool -> Bool -> Bool
|| GQtyArgs
code forall a. Eq a => a -> a -> Bool
== GQtyArgs
13 Bool -> Bool -> Bool
|| GQtyArgs
code forall a. Eq a => a -> a -> Bool
== GQtyArgs
18 = forall a. [a] -> [[a]] -> [a]
intercalate String
" " [forall a. Show a => a -> String
show GQtyArgs
x1, String
ts, forall a. Show a => a -> String
show Integer
y1] forall a. Monoid a => a -> a -> a
`mappend` String
"\n"
  | GQtyArgs
code forall a. Eq a => a -> a -> Bool
== GQtyArgs
4 Bool -> Bool -> Bool
|| GQtyArgs
code forall a. Eq a => a -> a -> Bool
== GQtyArgs
14 Bool -> Bool -> Bool
|| GQtyArgs
code forall a. Eq a => a -> a -> Bool
== GQtyArgs
19 = forall a. [a] -> [[a]] -> [a]
intercalate String
" " [forall a. Show a => a -> String
show GQtyArgs
x1, forall a. Show a => a -> String
show Integer
y1] forall a. Monoid a => a -> a -> a
`mappend` String
"\n"
  | Bool
otherwise = String
ts forall a. Monoid a => a -> a -> a
`mappend` String
"\n"

parseLineNumber :: Int -> IO Int
parseLineNumber :: GQtyArgs -> IO GQtyArgs
parseLineNumber GQtyArgs
l1 = do 
  String -> IO ()
putStrLn String
"Please, specify the number of the option to be written to the file specified: "
  String
number <- IO String
getLine
  let num :: Maybe GQtyArgs
num = forall a. Read a => String -> Maybe a
readMaybe (forall a. (a -> Bool) -> [a] -> [a]
filter Char -> Bool
isDigit String
number)::Maybe Int
  if forall a. Maybe a -> Bool
isNothing Maybe GQtyArgs
num Bool -> Bool -> Bool
|| Maybe GQtyArgs
num forall a. Ord a => a -> a -> Bool
> forall a. a -> Maybe a
Just GQtyArgs
l1 Bool -> Bool -> Bool
|| Maybe GQtyArgs
num forall a. Eq a => a -> a -> Bool
== forall a. a -> Maybe a
Just GQtyArgs
0 
      then GQtyArgs -> IO GQtyArgs
parseLineNumber GQtyArgs
l1 
      else forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HasCallStack => Maybe a -> a
fromJust forall a b. (a -> b) -> a -> b
$ Maybe GQtyArgs
num

{-| Uses 'getArgs' inside to get the needed data from the command line arguments. Use with this in
 mind. 
-}
argsProcessing
 :: [[String]]
 -> [[String]]
 -> String 
 -> IO (String, String, Int, Bool, Int8, FilePath, Int, Bool, String, [String]) -- ^ These ones are intended to be used inside 'generalF'.
argsProcessing :: [[String]]
-> [[String]]
-> String
-> IO
     (String, String, GQtyArgs, Bool, Int8, String, GQtyArgs, Bool,
      String, [String])
argsProcessing [[String]]
ysss [[String]]
zsss String
xs = do
  [String]
args0 <- IO [String]
getArgs
  let (Args
argsC, [String]
args) = (Char, Char) -> CLSpecifications -> [String] -> (Args, [String])
takeCs1R (Char
'+',Char
'-') CLSpecifications
cSpecs [String]
args0
      (Args
argsB, [String]
args11) = CLSpecifications -> [String] -> (Args, [String])
takeBsR CLSpecifications
bSpecs [String]
args
      prepare :: Bool
prepare = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall a. Eq a => a -> a -> Bool
== String
"-p") [String]
args11
      emptyline :: Bool
emptyline = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall a. Eq a => a -> a -> Bool
== String
"+l") [String]
args11 
      splitting :: Int8
splitting = forall a. a -> Maybe a -> a
fromMaybe Int8
50 (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
"+w" forall a b. (a -> b) -> a -> b
$ Args
argsB)::Maybe Int8) 
      concurrently :: Bool
concurrently = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall a. Eq a => a -> a -> Bool
== String
"-C") [String]
args11
      filedata :: [String]
filedata = forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getB String
"+f" Args
argsB
      multiline2 :: [String]
multiline2 = forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getB String
"+m" Args
argsB
      (String
fileread,GQtyArgs
lineNmb)
        | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
multiline2 = (String
"",-GQtyArgs
1)
        | forall (t :: * -> *) a. Foldable t => t a -> GQtyArgs
length [String]
multiline2 forall a. Eq a => a -> a -> Bool
== GQtyArgs
2 = (forall a. [a] -> a
head [String]
multiline2, forall a. a -> Maybe a -> a
fromMaybe GQtyArgs
1 (forall a. Read a => String -> Maybe a
readMaybe (forall a. [a] -> a
last [String]
multiline2)::Maybe Int))
        | Bool
otherwise = (forall a. [a] -> a
head [String]
multiline2, GQtyArgs
1)
  ([String]
arg3s,String
prestr,String
poststr) <- do 
       if GQtyArgs
lineNmb forall a. Eq a => a -> a -> Bool
/= -GQtyArgs
1 then do
           String
txtFromFile <- String -> IO String
readFile String
fileread
           let lns :: [String]
lns = String -> [String]
lines String
txtFromFile
               ln0 :: GQtyArgs
ln0 = forall a. Ord a => a -> a -> a
max GQtyArgs
1 (forall a. Ord a => a -> a -> a
min GQtyArgs
lineNmb (forall (t :: * -> *) a. Foldable t => t a -> GQtyArgs
length [String]
lns))
               ln_1 :: GQtyArgs
ln_1 
                  | GQtyArgs
ln0 forall a. Eq a => a -> a -> Bool
== GQtyArgs
1 = GQtyArgs
0
                  | Bool
otherwise = GQtyArgs
ln0 forall a. Num a => a -> a -> a
- GQtyArgs
1
               ln1 :: GQtyArgs
ln1
                  | GQtyArgs
ln0 forall a. Eq a => a -> a -> Bool
== forall (t :: * -> *) a. Foldable t => t a -> GQtyArgs
length [String]
lns = GQtyArgs
0
                  | Bool
otherwise = GQtyArgs
ln0 forall a. Num a => a -> a -> a
+ GQtyArgs
1
               lineF :: String
lineF = [String]
lns forall a. [a] -> GQtyArgs -> a
!! (GQtyArgs
ln0 forall a. Num a => a -> a -> a
- GQtyArgs
1)
               line_1F :: String
line_1F 
                  | GQtyArgs
ln_1 forall a. Eq a => a -> a -> Bool
== GQtyArgs
0 = []
                  | Bool
otherwise = [String]
lns forall a. [a] -> GQtyArgs -> a
!! (GQtyArgs
ln_1 forall a. Num a => a -> a -> a
- GQtyArgs
1)
               line1F :: String
line1F
                  | GQtyArgs
ln1 forall a. Eq a => a -> a -> Bool
== GQtyArgs
0 = []
                  | Bool
otherwise = [String]
lns forall a. [a] -> GQtyArgs -> a
!! (GQtyArgs
ln1 forall a. Num a => a -> a -> a
- GQtyArgs
1)
           forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ (String -> [String]
words String
lineF, String
line_1F,String
line1F)
       else forall (m :: * -> *) a. Monad m => a -> m a
return ([String]
args11, [], [])
  let (String
filesave,GQtyArgs
codesave)  
        | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
filedata = (String
"",-GQtyArgs
1)
        | forall (t :: * -> *) a. Foldable t => t a -> GQtyArgs
length [String]
filedata forall a. Eq a => a -> a -> Bool
== GQtyArgs
2 = (forall a. [a] -> a
head [String]
filedata, forall a. a -> Maybe a -> a
fromMaybe GQtyArgs
0 (forall a. Read a => String -> Maybe a
readMaybe (forall a. [a] -> a
last [String]
filedata)::Maybe Int))
        | Bool
otherwise = (forall a. [a] -> a
head [String]
filedata,GQtyArgs
0)
      ll :: [String]
ll = let maxWordsNum :: GQtyArgs
maxWordsNum = (if forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall a. Eq a => a -> a -> Bool
== String
"+x") [String]
arg3s then GQtyArgs
9 else GQtyArgs
7) in forall a. GQtyArgs -> [a] -> [a]
take GQtyArgs
maxWordsNum forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if Bool
prepare then forall a. a -> a
id else String -> [String]
words forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. GQtyArgs
-> [[String]] -> [[String]] -> String -> String -> [String]
prepareTextN GQtyArgs
maxWordsNum [[String]]
ysss [[String]]
zsss String
xs forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
unwords) forall a b. (a -> b) -> a -> b
$ [String]
arg3s
      l :: GQtyArgs
l = forall (t :: * -> *) a. Foldable t => t a -> GQtyArgs
length [String]
ll
      argCs :: [EncodedCnstrs]
argCs = forall a. [Maybe a] -> [a]
catMaybes (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (GQtyArgs -> String -> Maybe EncodedCnstrs
readMaybeECG GQtyArgs
l) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getC String
"+a" forall a b. (a -> b) -> a -> b
$ Args
argsC)
      argCBs :: String
argCBs = [String] -> String
unwords forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *).
Foldable t =>
String -> t Arguments -> [String]
getC String
"+b" forall a b. (a -> b) -> a -> b
$ Args
argsC -- If you use the parenthese with +b ... -b then consider also using the quotation marks for the whole algebraic constraint. At the moment though it is still not working properly for parentheses functionality. The issue should be fixed in the further releases.
      !perms :: [Array GQtyArgs GQtyArgs]
perms 
        | Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
argCBs) = GQtyArgs
-> String -> [Array GQtyArgs GQtyArgs] -> [Array GQtyArgs GQtyArgs]
filterGeneralConv GQtyArgs
l String
argCBs forall b c a. (b -> c) -> (a -> b) -> a -> c
. GQtyArgs -> [Array GQtyArgs GQtyArgs]
genPermutationsL forall a b. (a -> b) -> a -> b
$ GQtyArgs
l
        | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [EncodedCnstrs]
argCs = GQtyArgs -> [Array GQtyArgs GQtyArgs]
genPermutationsL GQtyArgs
l
        | Bool
otherwise = forall (t :: * -> *).
(InsertLeft t (Array GQtyArgs GQtyArgs),
 Monoid (t (Array GQtyArgs GQtyArgs))) =>
[EncodedCnstrs]
-> t (Array GQtyArgs GQtyArgs) -> t (Array GQtyArgs GQtyArgs)
decodeLConstraints [EncodedCnstrs]
argCs forall b c a. (b -> c) -> (a -> b) -> a -> c
. GQtyArgs -> [Array GQtyArgs GQtyArgs]
genPermutationsL forall a b. (a -> b) -> a -> b
$ GQtyArgs
l 
      basiclineoption :: String
basiclineoption = [String] -> String
unwords [String]
arg3s
      variants1 :: [String]
variants1 = forall a (t :: * -> *).
(Eq a, Foldable t, InsertLeft t a, Monoid (t a),
 Monoid (t (t a))) =>
a
-> (t a -> [a])
-> (t (t a) -> [[a]])
-> ([a] -> t a)
-> [Array GQtyArgs GQtyArgs]
-> t (t a)
-> [t a]
uniquenessVariants2GNBL Char
' ' forall a. a -> a
id forall a. a -> a
id forall a. a -> a
id [Array GQtyArgs GQtyArgs]
perms [String]
ll
  forall (m :: * -> *) a. Monad m => a -> m a
return (String
prestr, String
poststr, GQtyArgs
lineNmb, Bool
emptyline, Int8
splitting, String
filesave, GQtyArgs
codesave, Bool
concurrently, String
basiclineoption, [String]
variants1)

processingF
 :: GWritingSystemPRPLX -- ^ Data used to obtain the phonetic language representation of the text.
 -> [(Char,Char)] -- ^ The pairs of the 'Char' that corresponds to the similar phonetic languages consonant phenomenon (e. g. allophones). Must be sorted in the ascending order to be used correctly. 
 -> CharPhoneticClassification
 -> SegmentRulesG
 -> String -- ^ Corresponds to the 100 delimiter in the @ukrainian-phonetics-basic-array@ package.
 -> String -- ^ Corresponds to the 101 delimiter in the @ukrainian-phonetics-basic-array@ package.
 -> ([[[PRS]]] -> [[Double]])
 -> Int
 -> HashCorrections 
 -> (Int8,[Int8]) 
 -> [[String]] 
 -> [[String]] 
 -> Bool
 -> Int -- ^ The hashing function step. The default value is 20. Is expected to be greater than 2, and better greater than 12. 
 -> String 
 -> IO ()
processingF :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> ([[[PRS]]] -> [[Double]])
-> GQtyArgs
-> HashCorrections
-> (Int8, [Int8])
-> [[String]]
-> [[String]]
-> Bool
-> GQtyArgs
-> String
-> IO ()
processingF GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
us String
vs [[[PRS]]] -> [[Double]]
h GQtyArgs
numTest HashCorrections
hc (Int8
grps,[Int8]
mxms) [[String]]
ysss [[String]]
zsss Bool
descending GQtyArgs
hashStep String
xs = [[String]]
-> [[String]]
-> String
-> IO
     (String, String, GQtyArgs, Bool, Int8, String, GQtyArgs, Bool,
      String, [String])
argsProcessing [[String]]
ysss [[String]]
zsss String
xs forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \(String
prestr, String
poststr, GQtyArgs
lineNmb, Bool
emptyline, Int8
splitting, String
filesave, GQtyArgs
codesave, Bool
concurrently, String
basiclineoption, [String]
variants1) -> (String, String)
-> GQtyArgs
-> GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> ([[[PRS]]] -> [[Double]])
-> GQtyArgs
-> HashCorrections
-> (Int8, [Int8])
-> Bool
-> GQtyArgs
-> Bool
-> Int8
-> (String, GQtyArgs)
-> Bool
-> String
-> [String]
-> IO [String]
generalF (String
prestr,String
poststr) GQtyArgs
lineNmb GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
us String
vs [[[PRS]]] -> [[Double]]
h GQtyArgs
numTest HashCorrections
hc (Int8
grps,[Int8]
mxms) Bool
descending GQtyArgs
hashStep Bool
emptyline Int8
splitting (String
filesave, GQtyArgs
codesave) Bool
concurrently String
basiclineoption [String]
variants1 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()
{-# INLINE processingF #-}

-- | Specifies the group of the command line arguments for 'processingF', which specifies the
-- PhLADiPreLiO constraints. For more information, see:
-- https://oleksandr-zhabenko.github.io/uk/rhythmicity/PhLADiPreLiO.Eng.21.html#constraints 
cSpecs :: CLSpecifications
cSpecs :: CLSpecifications
cSpecs = forall a b. [a] -> [b] -> [(a, b)]
zip [String
"+a",String
"+b"] forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
cycle forall a b. (a -> b) -> a -> b
$ [-GQtyArgs
1]

bSpecs :: CLSpecifications
bSpecs :: CLSpecifications
bSpecs = [(String
"+f",GQtyArgs
2), (String
"+w",GQtyArgs
1), (String
"+m",GQtyArgs
2)]