{-# LANGUAGE NoImplicitPrelude #-}

module Phladiprelio.Ukrainian.IO where

import GHC.Arr
import GHC.Base
import GHC.Num (Integer,(+),(-),(*))
import GHC.Real (fromIntegral,(/),quot,rem,quotRem,round,(^))
import GHC.Enum (fromEnum,toEnum)
import Text.Show (Show(..))
import Text.Read (readMaybe)
import Data.Char (isDigit, isAlpha,toLower,isSpace)
import System.IO (putStrLn, FilePath,stdout,hSetNewlineMode,universalNewlineMode,getLine,appendFile,print,writeFile)
import Rhythmicity.MarkerSeqs hiding (id) 
import Data.List hiding (foldr)
import Data.Maybe (isNothing,fromJust) 
import Data.Tuple (fst,snd)
import Phladiprelio.Ukrainian.Syllable 
import Phladiprelio.Ukrainian.SyllableDouble
import Phladiprelio.Ukrainian.Melodics 
import GHC.Int (Int8)
import CaseBi.Arr (getBFst')
import Phladiprelio.Ukrainian.ReadDurations
import Data.Ord (comparing)
import Numeric (showFFloat)
import Phladiprelio.Halfsplit
import System.Directory (readable,writable,getPermissions,Permissions(..),doesFileExist,getCurrentDirectory)
import Data.ReversedScientific
import Control.Concurrent.Async (mapConcurrently)
import Phladiprelio.Tests
import Phladiprelio.General.Datatype3 -- (readBasic3, readBasic4, readBasic1G)
import Phladiprelio.General.Distance
import Phladiprelio.UniquenessPeriodsG

generalF
 :: Int -- ^ A power of 10. 10 in this power is then multiplied the value of distance if the next ['Double'] argument is not empty. The default one is 4. The right values are in the range [2..6].
 -> Int -- ^ A 'length' of the next argument here.
 -> [Double] -- ^ A list of non-negative values normed by 1.0 (the greatest of which is 1.0) that the line options are compared with. If null, then the program works as for version 0.12.1.0 without this newly-introduced argument since the version 0.13.0.0. The length of it must be a least common multiplier of the (number of syllables plus number of \'_digits\' groups) to work correctly. Is not used when the next 'FilePath' and 'String' arguments are not null.
 -> Bool -- ^ If 'True' then adds \"<br>\" to line endings for double column output
 -> FilePath -- ^ A path to the file to save double columns output to. If empty then just prints to 'stdout'.
 -> String -- ^ If not null than instead of rhythmicity evaluation using hashes and and feets, there is computed a diversity property for the specified 'String' here using the 'selectSounds' function. For more information, see: 'https://oleksandr-zhabenko.github.io/uk/rhythmicity/PhLADiPreLiO.Eng.21.html#types'
 -> (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.
 -> FilePath -- ^ The file to read the sound representation durations from.
 -> Int 
 -> HashCorrections 
 -> (Int8,[Int8]) 
 -> Int 
 -> Bool 
 -> Int 
 -> Bool 
 -> Int8 
 -> (FilePath, Int) 
 -> Bool  -- ^ Whether to run tests concurrently or not. 'True' corresponds to concurrent execution that can speed up the getting results but use more resources.
 -> String -- ^ An initial string to be analysed.
 -> [String] 
 -> IO [String]
generalF :: Int
-> Int
-> [Double]
-> Bool
-> String
-> String
-> (String, String)
-> Int
-> String
-> Int
-> HashCorrections
-> (Sound8, [Sound8])
-> Int
-> Bool
-> Int
-> Bool
-> Sound8
-> (String, Int)
-> Bool
-> String
-> [String]
-> IO [String]
generalF Int
power10 Int
ldc [Double]
compards Bool
html String
dcfile String
selStr (String
prestr, String
poststr) Int
lineNmb String
file Int
numTest HashCorrections
hc (Sound8
grps,[Sound8]
mxms) Int
k Bool
descending Int
hashStep Bool
emptyline Sound8
splitting (String
fs,Int
code) Bool
concurrently String
initstr universalSet :: [String]
universalSet@(String
u1:String
u2:[String]
us) = do
   [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs <- String -> IO [[[[Sound8]]] -> [[Double]]]
readSyllableDurations String
file
   let syllN :: Int
syllN = String -> Int
countSyll String
initstr
--       universalSet = map unwords . permutations . words $ rs
       f :: Int
-> [Double]
-> [[[[Sound8]]] -> [[Double]]]
-> Sound8
-> [Sound8]
-> String
-> Integer
f Int
ldc [Double]
compards [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs Sound8
grps [Sound8]
mxms -- Since the version 0.12.0.0, has a possibility to evaluate diversity property.
            | forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
selStr = (if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Double]
compards then (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 =>
Int -> HashCorrections -> Sound8 -> [Sound8] -> [a] -> [Integer]
countHashes2G Int
hashStep HashCorrections
hc Sound8
grps [Sound8]
mxms) else (forall a b. (RealFrac a, Integral b) => a -> b
round forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Num a => a -> a -> a
*Double
10forall a b. (Num a, Integral b) => a -> b -> a
^Int
power10) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
(Real a, Floating a, Fractional a) =>
Int -> [a] -> [a] -> a
distanceSqrG2 Int
ldc [Double]
compards)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Bool)
-> Double -> (String -> [Double]) -> String -> [Double]
read3 (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isSpace)) Double
1.0 (forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
file then case Int
k of { Int
1 -> [[[Sound8]]] -> [[Double]]
syllableDurationsD; Int
2 -> [[[Sound8]]] -> [[Double]]
syllableDurationsD2; Int
3 -> [[[Sound8]]] -> [[Double]]
syllableDurationsD3; Int
4 -> [[[Sound8]]] -> [[Double]]
syllableDurationsD4} 
                         else  if forall (t :: * -> *) a. Foldable t => t a -> Int
length [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs forall a. Ord a => a -> a -> Bool
>= Int
k then [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs forall a. [a] -> Int -> a
!! (Int
k forall a. Num a => a -> a -> a
- Int
1) else [[[Sound8]]] -> [[Double]]
syllableDurationsD2) forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [[[Sound8]]]
createSyllablesUkrS) 
            | Bool
otherwise = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t1 :: * -> *) (t2 :: * -> *) (t3 :: * -> *) a.
(Foldable t1, Foldable t2, Foldable t3, Ord a) =>
t3 a -> t1 a -> t2 a -> Int16
diverse2GGL (String -> [Sound8]
selectSounds String
selStr) [Sound8
100,Sound8
101] forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [Sound8]
convertToProperUkrainianI8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (\Char
c -> Bool -> Bool
not (Char -> Bool
isDigit Char
c) Bool -> Bool -> Bool
&& Char
c forall a. Eq a => a -> a -> Bool
/= Char
'_' Bool -> Bool -> Bool
&& Char
cforall a. Eq a => a -> a -> Bool
/= Char
'=')
   Handle -> NewlineMode -> IO ()
hSetNewlineMode Handle
stdout NewlineMode
universalNewlineMode
   if Int
numTest forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
numTest forall a. Ord a => a -> a -> Bool
<= Int
179 Bool -> Bool -> Bool
&& Int
numTest forall a. Eq a => a -> a -> Bool
/= Int
1 Bool -> Bool -> Bool
&& forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Double]
compards 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) (\(Sound8
q,[Sound8]
qs) -> 
                          let m :: Int
m = Int -> (Sound8, [Sound8]) -> Int
stat1 Int
syllN (Sound8
q,[Sound8]
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 (Int
-> [Double]
-> [[[[Sound8]]] -> [[Double]]]
-> Sound8
-> [Sound8]
-> String
-> Integer
f Int
ldc [] [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs Sound8
q [Sound8]
qs)) [String]
universalSet 
                              mx :: Integer
mx = Int
-> [Double]
-> [[[[Sound8]]] -> [[Double]]]
-> Sound8
-> [Sound8]
-> String
-> Integer
f Int
ldc [] [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs Sound8
q [Sound8]
qs String
max1 
                              strTest :: String
strTest = (forall a. Show a => a -> String
show (forall a. Enum a => a -> Int
fromEnum Sound8
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 Int
m forall a. Monoid a => a -> a -> a
`mappend` String
"  -> " forall a. Monoid a => a -> a -> a
`mappend` 
                                  forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (forall a. a -> Maybe a
Just Int
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 Int
m) String
"%" forall a. Monoid a => a -> a -> a
`mappend` (if forall a. Integral a => a -> a -> a
rem Int
numTest Int
10 forall a. Ord a => a -> a -> Bool
>= Int
4 
                                                                                                                          then (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 (Int -> [Sound8]
sel2 Int
numTest) forall a b. (a -> b) -> a -> b
$ (Int -> [[Sound8]]
sel Int
numTest)
   else let sRepresent :: [PhladiprelioUkr]
sRepresent = forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\Int
k (Integer
x, String
ys) -> Int -> Integer -> String -> PhladiprelioUkr
S Int
k Integer
x String
ys) [Int
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 -> (Int
-> [Double]
-> [[[[Sound8]]] -> [[Double]]]
-> Sound8
-> [Sound8]
-> String
-> Integer
f Int
ldc [Double]
compards [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs Sound8
grps [Sound8]
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) -> String -> Sound8 -> [a] -> String
halfsplit1G (\(S Int
_ Integer
y String
_) -> Integer
y) (if Bool
html then String
"<br>" else String
"") (forall {a}. Integral a => a -> a
jjj Sound8
splitting) forall a b. (a -> b) -> a -> b
$ [PhladiprelioUkr]
sRepresent
                        in do
                             [()]
_ <- (if forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
dcfile then forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM String -> IO ()
putStrLn [String]
strOutput else do {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
>> String -> IO Bool
doesFileExist String
dcfile forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Bool
exist -> if Bool
exist then do {String -> IO Permissions
getPermissions String
dcfile forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Permissions
perms -> if Permissions -> Bool
writable Permissions
perms then forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (String -> String -> IO ()
writeFile String
dcfile) [String]
strOutput else forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Phladiprelio.Ukrainian.IO.generalF: File " forall a. Monoid a => a -> a -> a
`mappend` String
dcfile forall a. Monoid a => a -> a -> a
`mappend` String
" is not writable!"} else do {IO String
getCurrentDirectory forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \String
currdir -> do {String -> IO Permissions
getPermissions String
currdir forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Permissions
perms -> if Permissions -> Bool
writable Permissions
perms then forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM (String -> String -> IO ()
writeFile String
dcfile) [String]
strOutput else forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Phladiprelio.Ukrainian.IO.generalF: Directory of the file " forall a. Monoid a => a -> a -> a
`mappend` String
dcfile forall a. Monoid a => a -> a -> a
`mappend` String
" is not writable!"}}})
                             let l1 :: Int
l1 = forall (t :: * -> *) a. Foldable t => t a -> Int
length [PhladiprelioUkr]
sRepresent
                             if Int
code forall a. Eq a => a -> a -> Bool
== -Int
1 
                                 then if Int
lineNmb forall a. Eq a => a -> a -> Bool
== -Int
1 then forall (m :: * -> *) a. Monad m => a -> m a
return [String]
strOutput
                                      else do 
                                          String -> String -> Int -> [String] -> IO ()
print23 String
prestr String
poststr Int
1 [String
initstr]
                                          forall (m :: * -> *) a. Monad m => a -> m a
return [String]
strOutput
                                 else do 
                                       String -> String -> Int -> [String] -> IO ()
print23 String
prestr String
poststr Int
1 [String
initstr]
                                       Int -> IO Int
parseLineNumber Int
l1 forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Int
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
                                             if forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
selStr Bool -> Bool -> Bool
&& forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Double]
compards then do
                                                let lineOption :: PhladiprelioUkr
lineOption = forall a. [a] -> a
head forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (\(S Int
k Integer
_ String
ts) -> Int
k forall a. Eq a => a -> a -> Bool
== Int
num) forall a b. (a -> b) -> a -> b
$ [PhladiprelioUkr]
sRepresent
                                                    textP :: String
textP = (\(S Int
_ Integer
_ String
ts) -> String
ts) PhladiprelioUkr
lineOption
                                                    sylls :: [[[Sound8]]]
sylls = String -> [[[Sound8]]]
createSyllablesUkrS String
textP
                                                if Int
code forall a. Ord a => a -> a -> Bool
>= Int
10 Bool -> Bool -> Bool
&& Int
code forall a. Ord a => a -> a -> Bool
<= Int
19 Bool -> Bool -> Bool
&& Sound8
grps forall a. Eq a => a -> a -> Bool
== Sound8
2
                                                    then do
                                                        let qqs :: [(String, Double)]
qqs = (String -> [Double])
-> (String -> [String]) -> [Read0] -> [(String, Double)]
readEq4 (forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if forall (t :: * -> *) a. Foldable t => t a -> Bool
null String
file then case Int
k of { Int
1 -> [[[Sound8]]] -> [[Double]]
syllableDurationsD; Int
2 -> [[[Sound8]]] -> [[Double]]
syllableDurationsD2; Int
3 ->
       [[[Sound8]]] -> [[Double]]
syllableDurationsD3; Int
4 -> [[[Sound8]]] -> [[Double]]
syllableDurationsD4} else if forall (t :: * -> *) a. Foldable t => t a -> Int
length [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs forall a. Ord a => a -> a -> Bool
>= Int
k then [[[[Sound8]]] -> [[Double]]]
syllableDurationsDs forall a. [a] -> Int -> a
!! (Int
k forall a. Num a => a -> a -> a
- Int
1) else [[[Sound8]]] -> [[Double]]
syllableDurationsD2) forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [[[Sound8]]]
createSyllablesUkrS) (forall a b. (a -> b) -> [a] -> [b]
map [Sound8] -> String
showFS 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 -> [[[Sound8]]]
createSyllablesUkrS) forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [Read0]
basicSplit 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 Int
code forall a. Ord a => a -> a -> Bool
>= Int
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` PhladiprelioUkr -> Int -> String
outputSel PhladiprelioUkr
lineOption Int
code)
                                                    else String -> String -> IO ()
appendFile String
fs (PhladiprelioUkr -> Int -> String
outputSel PhladiprelioUkr
lineOption Int
code)
                                             else do 
                                                let lineOption :: PhladiprelioUkr
lineOption = forall a. [a] -> a
head forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (\(S Int
k Integer
_ String
ts) -> Int
k forall a. Eq a => a -> a -> Bool
== Int
num) forall a b. (a -> b) -> a -> b
$ [PhladiprelioUkr]
sRepresent
                                                String -> String -> IO ()
appendFile String
fs (PhladiprelioUkr -> Int -> String
outputSel PhladiprelioUkr
lineOption Int
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)
generalF Int
_ Int
_ [Double]
_ Bool
_ String
_ String
_ (String, String)
_ Int
_ String
_ Int
_ HashCorrections
_ (Sound8, [Sound8])
_ Int
_ Bool
_ Int
_ Bool
_ Sound8
_ (String, Int)
_ Bool
_ String
_ [String
u1] = forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM String -> IO ()
putStrLn [String
u1] forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (m :: * -> *) a. Monad m => a -> m a
return [String
u1]
generalF Int
_ Int
_ [Double]
_ Bool
_ String
_ String
_ (String, String)
_ Int
_ String
_ Int
_ HashCorrections
_ (Sound8, [Sound8])
_ Int
_ Bool
_ Int
_ Bool
_ Sound8
_ (String, Int)
_ Bool
_ String
_ [String]
_ = 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

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

instance Show PhladiprelioUkr where
  show :: PhladiprelioUkr -> String
show (S Int
i Integer
j String
xs) = Int -> Integer -> String
showBignum Int
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 => Int -> a -> String
showWithSpaces Int
4 Int
i

countSyll :: String -> Int
countSyll :: String -> Int
countSyll String
xs = forall a. Enum a => a -> Int
fromEnum forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b -> b) -> b -> [a] -> b
foldr (\Sound8
x Integer
y -> if Sound8 -> Bool
isVowel1 Sound8
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
. String -> [Sound8]
convertToProperUkrainianI8 forall a b. (a -> b) -> a -> b
$ String
xs

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

parseHelp :: [String] -> (String,[String])
parseHelp :: [String] -> (String, [String])
parseHelp [String]
xss 
  | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
xss = ([],[])
  | Bool
otherwise = ([String] -> String
unwords [String]
rss, [String]
uss forall a. Monoid a => a -> a -> a
`mappend` [String]
qss)
       where ([String]
yss,[String]
tss) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break (forall a. Eq a => a -> a -> Bool
== String
"-b") [String]
xss
             ([String]
uss,[String]
wss) = forall a. (a -> Bool) -> [a] -> ([a], [a])
break (forall a. Eq a => a -> a -> Bool
== String
"+b") [String]
yss
             [[String]
qss,[String]
rss] = forall a b. (a -> b) -> [a] -> [b]
map (forall a. Int -> [a] -> [a]
drop Int
1) [[String]
tss, [String]
wss]
             
outputSel :: PhladiprelioUkr -> Int -> String
outputSel :: PhladiprelioUkr -> Int -> String
outputSel (S Int
x1 Integer
y1 String
ts) Int
code
  | Int
code forall a. Ord a => a -> a -> Bool
< Int
0 = []
  | Int
code forall a. Eq a => a -> a -> Bool
== Int
1 Bool -> Bool -> Bool
|| Int
code forall a. Eq a => a -> a -> Bool
== Int
11 Bool -> Bool -> Bool
|| Int
code forall a. Eq a => a -> a -> Bool
== Int
16 = forall a. [a] -> [[a]] -> [a]
intercalate String
" " [forall a. Show a => a -> String
show Int
x1, String
ts] forall a. Monoid a => a -> a -> a
`mappend` String
"\n"
  | Int
code forall a. Eq a => a -> a -> Bool
== Int
2 Bool -> Bool -> Bool
|| Int
code forall a. Eq a => a -> a -> Bool
== Int
12 Bool -> Bool -> Bool
|| Int
code forall a. Eq a => a -> a -> Bool
== Int
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"
  | Int
code forall a. Eq a => a -> a -> Bool
== Int
3 Bool -> Bool -> Bool
|| Int
code forall a. Eq a => a -> a -> Bool
== Int
13 Bool -> Bool -> Bool
|| Int
code forall a. Eq a => a -> a -> Bool
== Int
18 = forall a. [a] -> [[a]] -> [a]
intercalate String
" " [forall a. Show a => a -> String
show Int
x1, String
ts, forall a. Show a => a -> String
show Integer
y1] forall a. Monoid a => a -> a -> a
`mappend` String
"\n"
  | Int
code forall a. Eq a => a -> a -> Bool
== Int
4 Bool -> Bool -> Bool
|| Int
code forall a. Eq a => a -> a -> Bool
== Int
14 Bool -> Bool -> Bool
|| Int
code forall a. Eq a => a -> a -> Bool
== Int
19 = forall a. [a] -> [[a]] -> [a]
intercalate String
" " [forall a. Show a => a -> String
show Int
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 :: Int -> IO Int
parseLineNumber Int
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 Int
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 Int
num Bool -> Bool -> Bool
|| Maybe Int
num forall a. Ord a => a -> a -> Bool
> forall a. a -> Maybe a
Just Int
l1 Bool -> Bool -> Bool
|| Maybe Int
num forall a. Eq a => a -> a -> Bool
== forall a. a -> Maybe a
Just Int
0 
      then Int -> IO Int
parseLineNumber Int
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 Int
num

{-| 'selectSounds' converts the argument after \"+ul\" command line argument into a list of  Ukrainian sound representations that is used for evaluation of \'uniqueness periods\' properties of the line. Is a modified Phonetic.Languages.Simplified.Array.Ukrainian.FuncRep2RelatedG2.parsey0Choice from the @phonetic-languages-simplified-examples-array-0.21.0.0@ package. 
-}
selectSounds :: String -> FlowSound
selectSounds :: String -> [Sound8]
selectSounds = forall {a}. Eq a => [a] -> [a]
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [a] -> [a]
sort forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
/= Sound8
101) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap String -> [Sound8]
g forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (\Char
c -> if Char
c  forall a. Eq a => a -> a -> Bool
== Char
'.' then Char
' ' else Char -> Char
toLower Char
c)
    where g :: String -> [Sound8]
g = forall a b. Ord a => (b, Array Int (a, b)) -> a -> b
getBFst' ([Sound8
101::Sound8], forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,Int
41) ((String
"1",[Sound8
1,Sound8
2,Sound8
3,Sound8
4,Sound8
5,Sound8
6,Sound8
7,Sound8
8,Sound8
10,Sound8
15,Sound8
17,Sound8
19,Sound8
21,Sound8
23,Sound8
25,Sound8
27,Sound8
28,Sound8
30,Sound8
32,Sound8
34,Sound8
36,Sound8
38,Sound8
39,Sound8
41,Sound8
43,Sound8
45,Sound8
47,Sound8
49,Sound8
50,Sound8
52,Sound8
54,Sound8
66])forall a. a -> [a] -> [a]
:(String
"sr",[Sound8
27,Sound8
28,Sound8
30,Sound8
32,Sound8
34,Sound8
36])forall a. a -> [a] -> [a]
:(String
"vd",[Sound8
8,Sound8
10,Sound8
15,Sound8
17,Sound8
19,Sound8
21,Sound8
23,Sound8
25]) forall a. a -> [a] -> [a]
:(String
"vs",[Sound8
45,Sound8
47,Sound8
49,Sound8
50,Sound8
43,Sound8
52,Sound8
38,Sound8
66,Sound8
54,Sound8
39,Sound8
41]) forall a. a -> [a] -> [a]
:(String
"vw",[Sound8
1..Sound8
6]) forall a. a -> [a] -> [a]
:forall a b. (a -> b) -> [a] -> [b]
map (\(String
k,Sound8
t) -> (String
k,[Sound8
t])) [(String
"\1072",Sound8
1),(String
"\1073",Sound8
15),(String
"\1074",Sound8
36),(String
"\1075",Sound8
21),(String
"\1076",Sound8
17),(String
"\1076\1078",Sound8
23),(String
"\1076\1079",Sound8
8),(String
"\1077",Sound8
2),(String
"\1078",Sound8
10),(String
"\1079",Sound8
25),(String
"\1080",Sound8
5),(String
"\1081",Sound8
27),(String
"\1082",Sound8
45),(String
"\1083",Sound8
28),(String
"\1084",Sound8
30),(String
"\1085",Sound8
32),(String
"\1086",Sound8
3),(String
"\1087",Sound8
47),(String
"\1088",Sound8
34),(String
"\1089",Sound8
49),(String
"\1089\1100",Sound8
54),(String
"\1090",Sound8
50),(String
"\1091",Sound8
4),(String
"\1092",Sound8
43),(String
"\1093",Sound8
52),(String
"\1094",Sound8
38),(String
"\1094\1100",Sound8
66),(String
"\1095",Sound8
39),(String
"\1096",Sound8
41),(String
"\1097",Sound8
55),(String
"\1100",Sound8
7),(String
"\1102",Sound8
56),(String
"\1103",Sound8
57),(String
"\1108",Sound8
58),(String
"\1110",Sound8
6),(String
"\1111",Sound8
59),(String
"\1169",Sound8
19),(String
"\8217",Sound8
61)]))
          f :: [a] -> [a]
f (a
x:ts :: [a]
ts@(a
y:[a]
xs)) 
            | a
x forall a. Eq a => a -> a -> Bool
== a
y = [a] -> [a]
f [a]
ts
            | Bool
otherwise = a
xforall a. a -> [a] -> [a]
:[a] -> [a]
f [a]
ts
          f [a]
xs = [a]
xs