{-# LANGUAGE NoImplicitPrelude, BangPatterns #-}

module Phladiprelio.General.Simple where

import GHC.Base
import GHC.Enum (fromEnum)
import GHC.Real (fromIntegral,(/))
import Text.Show (show)
import Phladiprelio.General.PrepareText 
import Phladiprelio.General.Syllables 
import Phladiprelio.General.Base
import System.Environment (getArgs)
import GHC.Num ((+),(-),(*))
import Text.Read (readMaybe)
import System.IO (putStrLn, FilePath,stdout,universalNewlineMode,hSetNewlineMode)
import Rhythmicity.MarkerSeqs hiding (id) 
import Rhythmicity.BasicF 
import Data.List hiding (foldr)
import Data.Maybe (fromMaybe, mapMaybe, catMaybes) 
import Data.Tuple (fst,snd)
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

generalF 
 :: 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 
 -> [String] 
 -> IO [()] 
generalF :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> ([[[PRS]]] -> [[Double]])
-> GQtyArgs
-> HashCorrections
-> (Int8, [Int8])
-> Bool
-> GQtyArgs
-> Bool
-> [String]
-> IO [()]
generalF 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 [String]
universalSet 
 | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
universalSet = forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM String -> IO ()
putStrLn [String
"You have specified the data and constraints on it that lead to no further possible options.", String
"Please, specify another data and constraints."]
 | Bool
otherwise = do
   let syllN :: GQtyArgs
syllN = GWritingSystemPRPLX
-> CharPhoneticClassification
-> String
-> String
-> String
-> GQtyArgs
countSyll GWritingSystemPRPLX
wrs CharPhoneticClassification
arr String
us String
vs 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]
universalSet
--       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. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[[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
   if GQtyArgs
numTest forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` GQtyArgs
0forall a. a -> [a] -> [a]
:[GQtyArgs
2..GQtyArgs
9] then do
      Handle -> NewlineMode -> IO ()
hSetNewlineMode Handle
stdout NewlineMode
universalNewlineMode
      String -> IO ()
putStrLn String
"Feet   Val  Stat   Proxim" 
      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) in let max1 :: String
max1 = forall (t :: * -> *) a.
Foldable t =>
(a -> a -> Ordering) -> t a -> a
maximumBy (forall a b. Ord a => (b -> a) -> b -> b -> Ordering
comparing (Int8 -> [Int8] -> String -> Integer
f Int8
q [Int8]
qs)) [String]
universalSet in let mx :: Integer
mx = Int8 -> [Int8] -> String -> Integer
f Int8
q [Int8]
qs String
max1 in String -> IO ()
putStrLn (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. Show a => a -> String
show (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) forall a. Monoid a => a -> a -> a
`mappend` String
"%" forall a. Monoid a => a -> a -> a
`mappend` (if GQtyArgs
numTest 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
""))) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. [a] -> [b] -> [(a, b)]
zip [Int8
2..Int8
7] forall a b. (a -> b) -> a -> b
$ (forall {a} {a}. (Eq a, Num a, Num a) => a -> [[a]]
sel GQtyArgs
numTest)
   else (if Bool
emptyline 
             then forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (\[(Integer, String)]
tss -> forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (\(Integer
x, String
y) -> String -> IO ()
putStrLn (forall a. Show a => a -> String
show Integer
x forall a. Monoid a => a -> a -> a
`mappend` (Char
' 'forall a. a -> [a] -> [a]
:String
y))) [(Integer, String)]
tss forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> String -> IO ()
putStrLn String
"") forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy (\(Integer
x1,String
_) (Integer
x2,String
_) -> Integer
x1 forall a. Eq a => a -> a -> Bool
== Integer
x2)
             else forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (\(Integer
x,String
y) -> String -> IO ()
putStrLn (forall a. Show a => a -> String
show Integer
x forall a. Monoid a => a -> a -> a
`mappend` (Char
' 'forall a. a -> [a] -> [a]
:String
y))))  
                 forall b c a. (b -> c) -> (a -> b) -> a -> c
. (let h1 :: (a, b) -> (a, b)
h1 (a
u,b
w) = if Bool
descending then ((-a
1)forall a. Num a => a -> a -> a
*a
u,b
w) else (a
u,b
w) in forall b a. Ord b => (a -> b) -> [a] -> [a]
sortOn forall {a} {b}. Num a => (a, b) -> (a, 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
      where sel :: a -> [[a]]
sel a
x 
              | a
x forall a. Eq a => a -> a -> Bool
== a
0 Bool -> Bool -> Bool
|| a
x forall a. Eq a => a -> a -> Bool
== a
4 = [[a
1],[a
2,a
1],[a
3,a
2],[a
4,a
3,a
2],[a
5,a
4,a
3],[a
6,a
5,a
4,a
3,a
2]]
              | a
x forall a. Eq a => a -> a -> Bool
== a
2 Bool -> Bool -> Bool
|| a
x forall a. Eq a => a -> a -> Bool
== a
5 = [[a
1],[a
2],[a
3],[a
4,a
3],[a
5,a
4],[a
6,a
5,a
4]]
              | a
x forall a. Eq a => a -> a -> Bool
== a
7 = [[a
0],[a
1,a
0],[a
1,a
0],[a
1,a
0],[a
1,a
0],[a
1,a
0]]
              | a
x forall a. Eq a => a -> a -> Bool
== a
8 = [[a
0],[a
1,a
0],[a
1,a
0],[a
2,a
1,a
0],[a
2,a
1,a
0],[a
2,a
1,a
0]]
              | a
x forall a. Eq a => a -> a -> Bool
== a
9 = [[a
0],[a
1,a
0],[a
1,a
0],[a
2,a
1,a
0],[a
3,a
2,a
1,a
0],[a
3,a
2,a
1,a
0]]
              | Bool
otherwise = [[a
1],[a
2,a
1],[a
3,a
2,a
1],[a
3,a
2],[a
4,a
3,a
2]]

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

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 = do
  [String]
args0 <- IO [String]
getArgs
  let (Args
argsC, [String]
args) = (Char, Char) -> CLSpecifications -> [String] -> (Args, [String])
takeCs1R (Char
'+',Char
'-') CLSpecifications
cSpecs [String]
args0
      prepare :: Bool
prepare = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall a. Eq a => a -> a -> Bool
== String
"-p") [String]
args
      emptyline :: Bool
emptyline = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (forall a. Eq a => a -> a -> Bool
== String
"+l") [String]
args 
      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) -- . (showB l lstW2:)
                                                    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)
      ll :: [String]
ll = forall a. GQtyArgs -> [a] -> [a]
take GQtyArgs
7 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
. [[String]] -> [[String]] -> String -> String -> [String]
prepareText [[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]
args
      l :: GQtyArgs
l = forall (t :: * -> *) a. Foldable t => t a -> GQtyArgs
length [String]
ll
      argCBs :: String
argCBs = 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]
getC String
"+b" forall a b. (a -> b) -> a -> b
$ Args
argsC 
      !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 
      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
  GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> ([[[PRS]]] -> [[Double]])
-> GQtyArgs
-> HashCorrections
-> (Int8, [Int8])
-> Bool
-> GQtyArgs
-> Bool
-> [String]
-> IO [()]
generalF 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 [String]
variants1 forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- | 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]