{-# OPTIONS_GHC -threaded -rtsopts #-}
{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE BangPatterns #-}

-- |
-- Module      :  Phonetic.Languages.General.Lines
-- Copyright   :  (c) OleksandrZhabenko 2020-2022
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  olexandr543@yahoo.com
--
-- Library module that contains functions earlier used by the rewritePoemG3
-- executable for the Ukrainian language (see: https://hackage.haskell.org/package/phonetic-languages-simplified-examples-array).
-- Inspired by: https://functional-art.org/2020/papers/Poetry-OleksandrZhabenko.pdf from the https://functional-art.org/2020/performances ;
-- Allows to rewrite the given text (usually a poetical one).
-- Is rewritten from the Phonetic.Languages.Lines module from the
-- @phonetic-languages-simplified-examples-array@ package.

module Phonetic.Languages.General.Lines where

import Phonetic.Languages.General.DeEnCoding (newLineEnding)
import System.IO
import Data.SubG
import Data.MinMax.Preconditions
import GHC.Arr
import Data.List (sort,nub)
import Phonetic.Languages.Array.General.PropertiesSyllablesG2
import Phonetic.Languages.Simplified.StrictVG.Base
import Phonetic.Languages.Permutations.Arr
import Phonetic.Languages.Permutations.ArrMini
import Phonetic.Languages.Permutations.ArrMini1
import Phonetic.Languages.Filters (unsafeSwapVecIWithMaxI)
import Text.Read (readMaybe)
import Data.Maybe (fromMaybe)
import Data.Phonetic.Languages.PrepareText
import Data.Phonetic.Languages.Base
import Data.Phonetic.Languages.Syllables
import Phonetic.Languages.Simplified.DataG.Base
import Phonetic.Languages.Basis
import Phonetic.Languages.Simplified.DataG.Partir
import Data.Char (isDigit)
import Phonetic.Languages.Simplified.Array.General.FuncRep2RelatedG2
import Data.Monoid (mappend)
import Phonetic.Languages.General.Common
import Interpreter.StringConversion
import qualified Phonetic.Languages.Permutations.Represent as R
import Phonetic.Languages.EmphasisG
import Phonetic.Languages.Coeffs

{-| @ since 0.12.0.0 -- Changed the arguments. Now it can run multiple rewritings for the one given data file
on the given list of choices for the properties given as the second ['String'] argument. Every new file is being
saved with the choice prefix.
-}
generalProcessment
 :: R.PermutationsType -- ^ Whether to use just one of the express permutations, or the full universal set.
 -> (Int,Int) -- ^ Argument to specify possible 'line growing'.
 -> 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 -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly.
 -> SegmentRulesG
 -> (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.
 -> Concatenations -- ^ Data used to concatenate (prepend) the basic grammar preserving words and word sequences to the next word to
 -- leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to.
 -> Concatenations -- ^ Data used to concatenate (append) the basic grammar preserving words and word sequences to the next word to
 -- leave the most of the meaning (semantics) of the text available to easy understanding while reading and listening to.
 -> String
 -> String
 -> String
 -> Coeffs2
 -> (String -> String) -- ^ A function that specifies what 'Char's in the list the first argument makes to be the function sensitive to. Analogue of the @g@ function in the definition: https://hackage.haskell.org/package/phonetic-languages-simplified-examples-array-0.21.0.0/docs/src/Phonetic.Languages.Simplified.Array.Ukrainian.FuncRep2RelatedG2.html#parsey0Choice. Use just small 'Char' if they are letters, do not use \'.\' and spaces.
 -> [String]
 -> [String] -- ^ List of properties encoded which are used to rewrite the text.
 -> Int
 -> FilePath
 -> IO ()
generalProcessment :: PermutationsType
-> (Int, Int)
-> GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Concatenations
-> Concatenations
-> String
-> String
-> String
-> Coeffs2
-> (String -> String)
-> [String]
-> [String]
-> Int
-> String
-> IO ()
generalProcessment PermutationsType
pairwisePermutations (Int
gr1,Int
gr2) GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
rs Concatenations
ysss Concatenations
zzzsss String
xs String
js String
vs Coeffs2
coeffs String -> String
g1 [String]
numericArgs [String]
choices0 Int
numberI String
file = do
  String
contents <- String -> IO String
readFile String
file
  let !choices :: [String]
choices = forall a b. (a -> b) -> [a] -> [b]
map (forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
/=Char
'a')) [String]
choices0
      !permsV :: Array Int [Array Int Int]
permsV
        | PermutationsType
pairwisePermutations forall a. Eq a => a -> a -> Bool
== Int -> PermutationsType
R.P Int
2 = Int -> Array Int [Array Int Int]
genPairwisePermutationsArrLN Int
10
        | PermutationsType
pairwisePermutations forall a. Eq a => a -> a -> Bool
== Int -> PermutationsType
R.P Int
1 = Int -> Array Int [Array Int Int]
genElementaryPermutationsArrLN1 Int
10
        | Bool
otherwise = Array Int [Array Int Int]
genPermutationsArrL
      !flines :: [String]
flines
        | Int
gr1 forall a. Eq a => a -> a -> Bool
== Int
0 = Int
-> Concatenations
-> Concatenations
-> String
-> String
-> String
-> Int
-> String
-> [String]
fLinesN (if PermutationsType
pairwisePermutations forall a. Eq a => a -> a -> Bool
/= Int -> PermutationsType
R.P Int
0 then Int
10 else Int
7) Concatenations
ysss Concatenations
zzzsss String
xs String
js String
vs Int
0 String
contents
        | Bool
otherwise = Int
-> Int
-> Concatenations
-> Concatenations
-> String
-> String
-> [String]
prepareGrowTextMN Int
gr1 Int
gr2 Concatenations
ysss Concatenations
zzzsss String
xs forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
unlines forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int
-> Concatenations
-> Concatenations
-> String
-> String
-> String
-> Int
-> String
-> [String]
fLinesN (if PermutationsType
pairwisePermutations forall a. Eq a => a -> a -> Bool
/= Int -> PermutationsType
R.P Int
0 then Int
10 else Int
7) Concatenations
ysss Concatenations
zzzsss String
xs String
js String
vs Int
0 forall a b. (a -> b) -> a -> b
$ String
contents
      !lasts :: [String]
lasts = forall a b. (a -> b) -> [a] -> [b]
map (\String
ts -> if forall (t :: * -> *) a. Foldable t => t a -> Bool
null forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words forall a b. (a -> b) -> a -> b
$ String
ts then [] else forall a. [a] -> a
last forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words forall a b. (a -> b) -> a -> b
$ String
ts) [String]
flines
  if forall a. Ord a => a -> a -> Ordering
compare Int
numberI Int
2 forall a. Eq a => a -> a -> Bool
== Ordering
LT then
    forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\String
choice -> String -> [String] -> IO ()
toFileStr (String
choice forall a. [a] -> [a] -> [a]
++ String
"." forall a. [a] -> [a] -> [a]
++ String
file forall a. [a] -> [a] -> [a]
++ String
".new.txt") (GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Coeffs2
-> (String -> String)
-> Array Int [Array Int Int]
-> String
-> [String]
-> [String]
-> [String]
circle2 GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
rs Coeffs2
coeffs String -> String
g1 Array Int [Array Int Int]
permsV String
choice [] forall a b. (a -> b) -> a -> b
$ [String]
flines)) [String]
choices
  else do
    let !intervalNmbrs :: [Int]
intervalNmbrs = (\[Int]
vs -> if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Int]
vs then [Int
numberI] else forall a. Eq a => [a] -> [a]
nub [Int]
vs) 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. Ord a => a -> a -> Bool
<= Int
numberI) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
           forall a b. (a -> b) -> [a] -> [b]
map (\String
t -> forall a. a -> Maybe a -> a
fromMaybe Int
numberI (forall a. Read a => String -> Maybe a
readMaybe String
t::Maybe Int)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
drop Int
2 forall a b. (a -> b) -> a -> b
$ [String]
numericArgs
        !us :: [String]
us = String -> [String]
words 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. Int -> [a] -> [a]
take Int
1 forall a b. (a -> b) -> a -> b
$ [String]
flines
        !l2 :: Int
l2 = (forall a. Num a => a -> a -> a
subtract Int
3) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Int
length forall a b. (a -> b) -> a -> b
$ [String]
us
    if forall a. Ord a => a -> a -> Ordering
compare Int
l2 Int
0 forall a. Eq a => a -> a -> Bool
/= Ordering
LT then do
      let !perms2 :: [Array Int Int]
perms2 = forall i e. Array i e -> Int -> e
unsafeAt Array Int [Array Int Int]
permsV forall a b. (a -> b) -> a -> b
$ Int
l2
          minMaxTuples :: [(Double, Double)]
minMaxTuples = let !frep20Zip :: [(String, FuncRep2 ReadyForConstructionPL Double Double)]
frep20Zip = forall a b. [a] -> [b] -> [(a, b)]
zip [String]
choices forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (\String
choice -> forall c.
Ord c =>
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> c)
-> (Double -> String -> MappingFunctionPL)
-> Coeffs2
-> String
-> [MappingFunctionPL]
-> String
-> String
-> FuncRep2 ReadyForConstructionPL Double c
chooseMax GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs forall a. a -> a
id Double -> String -> MappingFunctionPL
h Coeffs2
coeffs ((String -> String) -> String -> String
parsey0Choice String -> String
g1 String
choice) [MappingFunctionPL]
rs String
choice String
"") forall a b. (a -> b) -> a -> b
$ [String]
choices in
            forall a b. (a -> b) -> [a] -> [b]
map (\(String
choice,FuncRep2 ReadyForConstructionPL Double Double
frep20) -> forall a (t :: * -> *).
(Ord a, InsertLeft t a, Monoid (t a)) =>
t a -> (a, a)
minMax11C forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (forall a b c. FuncRep2 a b c -> a -> b
toPropertiesF'2 FuncRep2 ReadyForConstructionPL Double Double
frep20 forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ReadyForConstructionPL
StrG) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                    forall a (t :: * -> *).
(Eq a, Foldable t, InsertLeft t a, Monoid (t a),
 Monoid (t (t a))) =>
t a
-> t a
-> a
-> (t a -> [a])
-> (t (t a) -> [[a]])
-> ([a] -> t a)
-> [Array Int Int]
-> t (t a)
-> [t a]
uniquenessVariants2GNPBL [] (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
take Int
1 forall a b. (a -> b) -> a -> b
$ [String]
lasts) Char
' ' forall a. a -> a
id forall a. a -> a
id forall a. a -> a
id [Array Int Int]
perms2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
init forall a b. (a -> b) -> a -> b
$ [String]
us) [(String, FuncRep2 ReadyForConstructionPL Double Double)]
frep20Zip
      forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(String
choice, (Double
minE,Double
maxE)) ->
        String -> [String] -> IO ()
toFileStr (String
choice forall a. [a] -> [a] -> [a]
++ String
"." forall a. [a] -> [a] -> [a]
++ String
file forall a. [a] -> [a] -> [a]
++ String
".new.txt") (GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Coeffs2
-> (String -> String)
-> Array Int [Array Int Int]
-> String
-> [String]
-> Int
-> [Int]
-> Double
-> Double
-> [String]
-> [String]
circle2I GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
rs Coeffs2
coeffs String -> String
g1 Array Int [Array Int Int]
permsV String
choice [] Int
numberI [Int]
intervalNmbrs Double
minE Double
maxE forall a b. (a -> b) -> a -> b
$ [String]
flines)) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
          forall a b. [a] -> [b] -> [(a, b)]
zip [String]
choices forall a b. (a -> b) -> a -> b
$ [(Double, Double)]
minMaxTuples
    else forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\String
choice -> String -> [String] -> IO ()
toFileStr (String
choice forall a. [a] -> [a] -> [a]
++ String
"." forall a. [a] -> [a] -> [a]
++ String
file forall a. [a] -> [a] -> [a]
++ String
".new.txt") ((forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
take Int
1 forall a b. (a -> b) -> a -> b
$ [String]
flines)forall a. a -> [a] -> [a]
:
       (GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Coeffs2
-> (String -> String)
-> Array Int [Array Int Int]
-> String
-> [String]
-> Int
-> [Int]
-> Double
-> Double
-> [String]
-> [String]
circle2I GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
rs Coeffs2
coeffs String -> String
g1 Array Int [Array Int Int]
permsV String
choice [] Int
numberI [Int]
intervalNmbrs Double
0.0 Double
0.0 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
drop Int
1 forall a b. (a -> b) -> a -> b
$ [String]
flines))) [String]
choices

compareFilesToOneCommon :: [FilePath] -> FilePath -> IO ()
compareFilesToOneCommon :: [String] -> String -> IO ()
compareFilesToOneCommon [String]
files String
file3 = do
 [(Int, [(Int, String)])]
contentss <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((\(Int
j,String
ks) -> do {String -> IO String
readFileIfAny String
ks forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \String
fs -> forall (m :: * -> *) a. Monad m => a -> m a
return (Int
j, forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..] forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines forall a b. (a -> b) -> a -> b
$ String
fs)})) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..Int
7] forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
take Int
14 forall a b. (a -> b) -> a -> b
$ [String]
files
 [(Int, [(Int, String)])] -> String -> IO ()
compareF [(Int, [(Int, String)])]
contentss String
file3
   where compareF :: [(Int,[(Int,String)])] -> FilePath -> IO ()
         compareF :: [(Int, [(Int, String)])] -> String -> IO ()
compareF [(Int, [(Int, String)])]
ysss String
file3 = forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\Int
i -> do
          String -> IO ()
putStr String
"Please, specify which variant to use as the result, "
          String -> IO ()
putStrLn String
"maximum number is the quantity of the files from which the data is read: "
          let strs :: [(Int, String)]
strs = forall a b. (a -> b) -> [a] -> [b]
map (\(Int
j,[(Int, String)]
ks) -> (\[(Int, String)]
ts -> if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Int, String)]
ts then (Int
j,String
"")
                      else let (Int
k,String
rs) = forall a. [a] -> a
head [(Int, String)]
ts in  (Int
j,String
rs)) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                       forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Eq a => a -> a -> Bool
== Int
i) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) forall a b. (a -> b) -> a -> b
$ [(Int, String)]
ks) [(Int, [(Int, String)])]
ysss
          forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Int
i,String
xs) -> String -> IO ()
putStrLn forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> String
show Int
i forall a. [a] -> [a] -> [a]
++ String
":\t" forall a. [a] -> [a] -> [a]
++ String
xs) [(Int, String)]
strs
          String
ch <- IO String
getLine
          let choice2 :: Int
choice2 = forall a. a -> Maybe a -> a
fromMaybe Int
0 (forall a. Read a => String -> Maybe a
readMaybe String
ch::Maybe Int)
          String -> [String] -> IO ()
toFileStr String
file3 ((\[(Int, String)]
us -> if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Int, String)]
us then [String
""] else [forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> a
head forall a b. (a -> b) -> a -> b
$ [(Int, String)]
us]) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
filter ((forall a. Eq a => a -> a -> Bool
== Int
choice2) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) forall a b. (a -> b) -> a -> b
$ [(Int, String)]
strs)) [Int
1..]

-- | Processment without rearrangements.
circle2
 :: 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 -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly.
 -> SegmentRulesG
 -> String
 -> String
 -> (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.
 -> Coeffs2
 -> (String -> String) -- ^ A function that specifies what 'Char's in the list the first argument makes to be the function sensitive to. Analogue of the @g@ function in the definition: https://hackage.haskell.org/package/phonetic-languages-simplified-examples-array-0.21.0.0/docs/src/Phonetic.Languages.Simplified.Array.Ukrainian.FuncRep2RelatedG2.html#parsey0Choice. Use just small 'Char' if they are letters, do not use \'.\' and spaces.
 -> Array Int [Array Int Int] -- ^ A permutations array of indices.
 -> String -- ^ Is intended to be one of the following strings: \"02y\", \"02z\", \"03y\", \"03z\", \"04y\", \"04z\",
 -- \"0y\", \"0z\", \"y\", \"y0\", \"y2\", \"y3\", \"y4\", \"yy\", \"yy2\", \"yy3\", \"z\", \"z2\", \"z3\", \"z4\",
 -- \"zz\", \"zz2\", \"zz3\", \"zz4\" or some other one. Specifies the applied properties
 -- to get the result. The \"z\"-line uses \'F\' functions.
 -> [String]
 -> [String]
 -> [String]
circle2 :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Coeffs2
-> (String -> String)
-> Array Int [Array Int Int]
-> String
-> [String]
-> [String]
-> [String]
circle2 GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
qs Coeffs2
coeffs String -> String
g1 Array Int [Array Int Int]
permsG1 String
choice [String]
yss [String]
xss
 | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
xss = [String]
yss
 | Bool
otherwise = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Coeffs2
-> (String -> String)
-> Array Int [Array Int Int]
-> String
-> [String]
-> [String]
-> [String]
circle2 GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
qs Coeffs2
coeffs String -> String
g1 Array Int [Array Int Int]
permsG1 String
choice ([String]
yss forall a. Monoid a => a -> a -> a
`mappend` [String
ws]) [String]
tss
      where (![String]
zss,![String]
tss) = forall a. Int -> [a] -> ([a], [a])
splitAt Int
1 [String]
xss
            !rs :: [String]
rs = String -> [String]
words forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ [String]
zss
            !l :: Int
l = forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
rs
            !sels :: String
sels = (String -> String) -> String -> String
parsey0Choice String -> String
g1 String
choice
            !frep2 :: FuncRep2 ReadyForConstructionPL Double Double
frep2 = forall c.
Ord c =>
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> c)
-> (Double -> String -> MappingFunctionPL)
-> Coeffs2
-> String
-> [MappingFunctionPL]
-> String
-> String
-> FuncRep2 ReadyForConstructionPL Double c
chooseMax GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs forall a. a -> a
id Double -> String -> MappingFunctionPL
h Coeffs2
coeffs String
sels [MappingFunctionPL]
qs String
choice String
""
            !ws :: String
ws = if forall a. Ord a => a -> a -> Ordering
compare Int
l Int
3 forall a. Eq a => a -> a -> Bool
== Ordering
LT then [String] -> String
unwords [String]
rs else (\ReadyForConstructionPL
rrrr -> forall a. a -> Maybe a -> a
fromMaybe String
"" forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadyForConstructionPL -> Maybe String
fromReadyFCPLS forall a b. (a -> b) -> a -> b
$ ReadyForConstructionPL
rrrr) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. Result2 a b c -> a
line2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t2 :: * -> *) c a b.
(Foldable t2, Ord c) =>
t2 (Result2 a b c) -> Result2 a b c
maximumElR2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (forall a b c. FuncRep2 a b c -> a -> Result2 a b c
toResultR2 FuncRep2 ReadyForConstructionPL Double Double
frep2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ReadyForConstructionPL
StrG) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
               forall a (t :: * -> *).
(Eq a, Foldable t, InsertLeft t a, Monoid (t a),
 Monoid (t (t a))) =>
t a
-> t a
-> a
-> (t a -> [a])
-> (t (t a) -> [[a]])
-> ([a] -> t a)
-> [Array Int Int]
-> t (t a)
-> [t a]
uniquenessVariants2GNPBL [] (forall a. [a] -> a
last [String]
rs) Char
' ' forall a. a -> a
id forall a. a -> a
id forall a. a -> a
id (forall i e. Array i e -> Int -> e
unsafeAt Array Int [Array Int Int]
permsG1 (Int
l forall a. Num a => a -> a -> a
- Int
3)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
init forall a b. (a -> b) -> a -> b
$ [String]
rs

-- | Processment with rearrangements.
circle2I
  :: 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 -- ^ The 'Array' 'Int' 'PRS' must be sorted in the ascending order to be used in the module correctly.
  -> SegmentRulesG
  -> String
  -> String
  -> (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.
  -> Coeffs2
  -> (String -> String) -- ^ A function that specifies what 'Char's in the list the first argument makes to be the function sensitive to. Analogue of the @g@ function in the definition: https://hackage.haskell.org/package/phonetic-languages-simplified-examples-array-0.21.0.0/docs/src/Phonetic.Languages.Simplified.Array.Ukrainian.FuncRep2RelatedG2.html#parsey0Choice. Use just small 'Char' if they are letters, do not use \'.\' and spaces.
  -> Array Int [Array Int Int] -- ^ A permutations array of indices.
  -> String -- ^ Is intended to be one of the following strings: \"02y\", \"02z\", \"03y\", \"03z\", \"04y\", \"04z\",
 -- \"0y\", \"0z\", \"y\", \"y0\", \"y2\", \"y3\", \"y4\", \"yy\", \"yy2\", \"yy3\", \"z\", \"z2\", \"z3\", \"z4\",
 -- \"zz\", \"zz2\", \"zz3\", \"zz4\" or some other one. Specifies the applied properties
 -- to get the result. The \"z\"-line uses \'F\' functions.
  -> [String]
  -> Int
  -> [Int]
  -> Double
  -> Double
  -> [String]
  -> [String]
circle2I :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Coeffs2
-> (String -> String)
-> Array Int [Array Int Int]
-> String
-> [String]
-> Int
-> [Int]
-> Double
-> Double
-> [String]
-> [String]
circle2I GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
qs Coeffs2
coeffs String -> String
g1 Array Int [Array Int Int]
permsG1 String
choice [String]
yss Int
numberI [Int]
intervNbrs Double
minE Double
maxE [String]
xss
 | forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
xss = [String]
yss
 | Bool
otherwise = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Coeffs2
-> (String -> String)
-> Array Int [Array Int Int]
-> String
-> [String]
-> Int
-> [Int]
-> Double
-> Double
-> [String]
-> [String]
circle2I GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
qs Coeffs2
coeffs String -> String
g1 Array Int [Array Int Int]
permsG1 String
choice ([String]
yss forall a. Monoid a => a -> a -> a
`mappend` [String
ws]) Int
numberI [Int]
intervNbrs Double
minE1 Double
maxE1 [String]
tss
      where (![String]
zss,![String]
tss) = forall a. Int -> [a] -> ([a], [a])
splitAt Int
1 [String]
xss
            !w2s :: [String]
w2s = String -> [String]
words 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. Int -> [a] -> [a]
take Int
1 forall a b. (a -> b) -> a -> b
$ [String]
tss
            !l3 :: Int
l3 = (forall a. Num a => a -> a -> a
subtract Int
3) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Int
length forall a b. (a -> b) -> a -> b
$ [String]
w2s
            !rs :: [String]
rs = String -> [String]
words forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ [String]
zss
            !l :: Int
l = forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
rs
            !sels :: String
sels = (String -> String) -> String -> String
parsey0Choice String -> String
g1 String
choice
            !frep2 :: FuncRep2 ReadyForConstructionPL Double Double
frep2 = forall c.
Ord c =>
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> c)
-> (Double -> String -> MappingFunctionPL)
-> Coeffs2
-> String
-> [MappingFunctionPL]
-> String
-> String
-> FuncRep2 ReadyForConstructionPL Double c
chooseMax GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs (forall b c.
(RealFrac b, Integral c, Ord c) =>
b -> b -> c -> [c] -> b -> b
unsafeSwapVecIWithMaxI Double
minE Double
maxE Int
numberI [Int]
intervNbrs) Double -> String -> MappingFunctionPL
h Coeffs2
coeffs String
sels [MappingFunctionPL]
qs String
choice String
""
            !ws :: String
ws = if forall a. Ord a => a -> a -> Ordering
compare (forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
rs) Int
3 forall a. Eq a => a -> a -> Bool
== Ordering
LT then [String] -> String
unwords [String]
rs else (\ReadyForConstructionPL
rrrr -> forall a. a -> Maybe a -> a
fromMaybe String
"" forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReadyForConstructionPL -> Maybe String
fromReadyFCPLS forall a b. (a -> b) -> a -> b
$ ReadyForConstructionPL
rrrr) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b c. Result2 a b c -> a
line2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t2 :: * -> *) c a b.
(Foldable t2, Ord c) =>
t2 (Result2 a b c) -> Result2 a b c
maximumElR2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (forall a b c. FuncRep2 a b c -> a -> Result2 a b c
toResultR2 FuncRep2 ReadyForConstructionPL Double Double
frep2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ReadyForConstructionPL
StrG) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
               forall a (t :: * -> *).
(Eq a, Foldable t, InsertLeft t a, Monoid (t a),
 Monoid (t (t a))) =>
t a
-> t a
-> a
-> (t a -> [a])
-> (t (t a) -> [[a]])
-> ([a] -> t a)
-> [Array Int Int]
-> t (t a)
-> [t a]
uniquenessVariants2GNPBL [] (forall a. [a] -> a
last [String]
rs) Char
' ' forall a. a -> a
id forall a. a -> a
id forall a. a -> a
id (forall i e. Array i e -> Int -> e
unsafeAt Array Int [Array Int Int]
permsG1 (Int
l forall a. Num a => a -> a -> a
- Int
3)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
init forall a b. (a -> b) -> a -> b
$ [String]
rs
            (!Double
minE1,!Double
maxE1)
             | forall a. Ord a => a -> a -> Ordering
compare Int
l3 Int
0 forall a. Eq a => a -> a -> Bool
/= Ordering
LT =
               let !perms3 :: [Array Int Int]
perms3 = forall i e. Array i e -> Int -> e
unsafeAt Array Int [Array Int Int]
permsG1 Int
l3
                   !v4 :: [String]
v4 = forall a. [a] -> [a]
init [String]
w2s
                   !frep20 :: FuncRep2 ReadyForConstructionPL Double Double
frep20 = forall c.
Ord c =>
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> c)
-> (Double -> String -> MappingFunctionPL)
-> Coeffs2
-> String
-> [MappingFunctionPL]
-> String
-> String
-> FuncRep2 ReadyForConstructionPL Double c
chooseMax GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs forall a. a -> a
id Double -> String -> MappingFunctionPL
h Coeffs2
coeffs String
sels [MappingFunctionPL]
qs String
choice String
"" in forall a (t :: * -> *).
(Ord a, InsertLeft t a, Monoid (t a)) =>
t a -> (a, a)
minMax11C forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (forall a b c. FuncRep2 a b c -> a -> b
toPropertiesF'2 FuncRep2 ReadyForConstructionPL Double Double
frep20 forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ReadyForConstructionPL
StrG) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                      forall a (t :: * -> *).
(Eq a, Foldable t, InsertLeft t a, Monoid (t a),
 Monoid (t (t a))) =>
t a
-> t a
-> a
-> (t a -> [a])
-> (t (t a) -> [[a]])
-> ([a] -> t a)
-> [Array Int Int]
-> t (t a)
-> [t a]
uniquenessVariants2GNPBL [] (forall a. [a] -> a
last [String]
w2s) Char
' ' forall a. a -> a
id forall a. a -> a
id forall a. a -> a
id [Array Int Int]
perms3 forall a b. (a -> b) -> a -> b
$ [String]
v4
             | Bool
otherwise = (Double
0.0,Double
0.0)

-- | Prints every element from the structure on the new line to the file. Uses 'appendFile' function inside. Is taken from
-- the Languages.UniquenessPeriods.Vector.General.DebugG module from the @phonetic-languages-general@ package.
toFileStr ::
  FilePath -- ^ The 'FilePath' to the file to be written in the 'AppendMode' (actually appended with) the information output.
  -> [String] -- ^ Each element is appended on the new line to the file.
  -> IO ()
toFileStr :: String -> [String] -> IO ()
toFileStr String
file [String]
xss = forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\String
xs -> String -> String -> IO ()
appendFile String
file (String
xs forall a. Monoid a => a -> a -> a
`mappend` String
newLineEnding)) [String]
xss