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

{-| @ 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 -> ([[[PRS]]] -> [[Double]]))-- ^ 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@.
 -> [([[[PRS]]] -> [[Double]])] -- ^ A list of 4 different functions that specifies the syllables durations, analogues of the
  -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most
  -- exact one and, therefore, the default one.
 -> Concatenations -- ^ Data used to concatenate 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] -- ^ 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 -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Concatenations
-> String
-> String
-> String
-> Coeffs2
-> [String]
-> [String]
-> Int
-> String
-> IO ()
generalProcessment PermutationsType
pairwisePermutations (Int
gr1,Int
gr2) GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs Double -> String -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
rs Concatenations
ysss String
xs String
js String
vs Coeffs2
coeffs [String]
numericArgs [String]
choices Int
numberI String
file = do
  String
contents <- String -> IO String
readFile String
file
  let !permsV :: Array Int [Array Int Int]
permsV
        | PermutationsType
pairwisePermutations PermutationsType -> PermutationsType -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> PermutationsType
R.P Int
2 = Int -> Array Int [Array Int Int]
genPairwisePermutationsArrLN Int
10
        | PermutationsType
pairwisePermutations PermutationsType -> PermutationsType -> Bool
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 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 = Int
-> Concatenations
-> String
-> String
-> String
-> Int
-> String
-> [String]
fLinesN (if PermutationsType
pairwisePermutations PermutationsType -> PermutationsType -> Bool
forall a. Eq a => a -> a -> Bool
/= Int -> PermutationsType
R.P Int
0 then Int
10 else Int
7) Concatenations
ysss String
xs String
js String
vs Int
0 String
contents
        | Bool
otherwise = Int -> Int -> Concatenations -> String -> String -> [String]
prepareGrowTextMN Int
gr1 Int
gr2 Concatenations
ysss String
xs (String -> [String]) -> (String -> String) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
unlines ([String] -> String) -> (String -> [String]) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int
-> Concatenations
-> String
-> String
-> String
-> Int
-> String
-> [String]
fLinesN (if PermutationsType
pairwisePermutations PermutationsType -> PermutationsType -> Bool
forall a. Eq a => a -> a -> Bool
/= Int -> PermutationsType
R.P Int
0 then Int
10 else Int
7) Concatenations
ysss String
xs String
js String
vs Int
0 (String -> [String]) -> String -> [String]
forall a b. (a -> b) -> a -> b
$ String
contents
      !lasts :: [String]
lasts = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\String
ts -> if [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null ([String] -> Bool) -> (String -> [String]) -> String -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words (String -> Bool) -> String -> Bool
forall a b. (a -> b) -> a -> b
$ String
ts then [] else [String] -> String
forall a. [a] -> a
last ([String] -> String) -> (String -> [String]) -> String -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
words (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
ts) [String]
flines
  if Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
numberI Int
2 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
LT then
    (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\String
choice -> String -> [String] -> IO ()
toFileStr (String
choice String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"." String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
file String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".new.txt") (GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Coeffs2
-> 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 -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
rs Coeffs2
coeffs Array Int [Array Int Int]
permsV String
choice [] ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
flines)) [String]
choices
  else do
    let !intervalNmbrs :: [Int]
intervalNmbrs = (\[Int]
vs -> if [Int] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Int]
vs then [Int
numberI] else [Int] -> [Int]
forall a. Eq a => [a] -> [a]
nub [Int]
vs) ([Int] -> [Int]) -> ([String] -> [Int]) -> [String] -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [Int]
forall a. Ord a => [a] -> [a]
sort ([Int] -> [Int]) -> ([String] -> [Int]) -> [String] -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Bool) -> [Int] -> [Int]
forall a. (a -> Bool) -> [a] -> [a]
filter (Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
numberI) ([Int] -> [Int]) -> ([String] -> [Int]) -> [String] -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
           (String -> Int) -> [String] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (\String
t -> Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
numberI (String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
t::Maybe Int)) ([String] -> [Int]) -> ([String] -> [String]) -> [String] -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop Int
2 ([String] -> [Int]) -> [String] -> [Int]
forall a b. (a -> b) -> a -> b
$ [String]
numericArgs
        !us :: [String]
us = String -> [String]
words (String -> [String])
-> ([String] -> String) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
1 ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
flines
        !l2 :: Int
l2 = (Int -> Int -> Int
forall a. Num a => a -> a -> a
subtract Int
3) (Int -> Int) -> ([String] -> Int) -> [String] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([String] -> Int) -> [String] -> Int
forall a b. (a -> b) -> a -> b
$ [String]
us
    if Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
l2 Int
0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
/= Ordering
LT then do
      let !perms2 :: [Array Int Int]
perms2 = Array Int [Array Int Int] -> Int -> [Array Int Int]
forall i e. Array i e -> Int -> e
unsafeAt Array Int [Array Int Int]
permsV (Int -> [Array Int Int]) -> Int -> [Array Int Int]
forall a b. (a -> b) -> a -> b
$ Int
l2
          minMaxTuples :: [(Double, Double)]
minMaxTuples = let !frep20Zip :: [(String, FuncRep2 String Double Double)]
frep20Zip = [String]
-> [FuncRep2 String Double Double]
-> [(String, FuncRep2 String Double Double)]
forall a b. [a] -> [b] -> [(a, b)]
zip [String]
choices ([FuncRep2 String Double Double]
 -> [(String, FuncRep2 String Double Double)])
-> ([String] -> [FuncRep2 String Double Double])
-> [String]
-> [(String, FuncRep2 String Double Double)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> FuncRep2 String Double Double)
-> [String] -> [FuncRep2 String Double Double]
forall a b. (a -> b) -> [a] -> [b]
map (GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> Double)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double Double
forall c.
Ord c =>
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> c)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double c
chooseMax GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> Double
forall a. a -> a
id Double -> String -> [[[PRS]]] -> [[Double]]
h Coeffs2
coeffs [[[[PRS]]] -> [[Double]]]
rs) ([String] -> [(String, FuncRep2 String Double Double)])
-> [String] -> [(String, FuncRep2 String Double Double)]
forall a b. (a -> b) -> a -> b
$ [String]
choices in
            ((String, FuncRep2 String Double Double) -> (Double, Double))
-> [(String, FuncRep2 String Double Double)] -> [(Double, Double)]
forall a b. (a -> b) -> [a] -> [b]
map (\(String
choice,FuncRep2 String Double Double
frep20) -> [Double] -> (Double, Double)
forall a (t :: * -> *).
(Ord a, InsertLeft t a, Monoid (t a)) =>
t a -> (a, a)
minMax11C ([Double] -> (Double, Double))
-> ([String] -> [Double]) -> [String] -> (Double, Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Double) -> [String] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map (FuncRep2 String Double Double -> String -> Double
forall (t :: * -> *) a b c. FuncRep2 (t a) b c -> t a -> b
toPropertiesF' FuncRep2 String Double Double
frep20) ([String] -> [Double])
-> ([String] -> [String]) -> [String] -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                    String
-> String
-> Char
-> (String -> String)
-> ([String] -> [String])
-> (String -> String)
-> [Array Int Int]
-> [String]
-> [String]
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 [] ([String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
1 ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
lasts) Char
' ' String -> String
forall a. a -> a
id [String] -> [String]
forall a. a -> a
id String -> String
forall a. a -> a
id [Array Int Int]
perms2 ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [String]
forall a. [a] -> [a]
init ([String] -> (Double, Double)) -> [String] -> (Double, Double)
forall a b. (a -> b) -> a -> b
$ [String]
us) [(String, FuncRep2 String Double Double)]
frep20Zip
      ((String, (Double, Double)) -> IO ())
-> [(String, (Double, Double))] -> IO ()
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 String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"." String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
file String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".new.txt") (GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Coeffs2
-> 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 -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
rs Coeffs2
coeffs Array Int [Array Int Int]
permsV String
choice [] Int
numberI [Int]
intervalNmbrs Double
minE Double
maxE ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
flines)) ([(String, (Double, Double))] -> IO ())
-> ([(Double, Double)] -> [(String, (Double, Double))])
-> [(Double, Double)]
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
          [String] -> [(Double, Double)] -> [(String, (Double, Double))]
forall a b. [a] -> [b] -> [(a, b)]
zip [String]
choices ([(Double, Double)] -> IO ()) -> [(Double, Double)] -> IO ()
forall a b. (a -> b) -> a -> b
$ [(Double, Double)]
minMaxTuples
    else (String -> IO ()) -> [String] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\String
choice -> String -> [String] -> IO ()
toFileStr (String
choice String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"." String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
file String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
".new.txt") (([String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
1 ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
flines)String -> [String] -> [String]
forall a. a -> [a] -> [a]
:
       (GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Coeffs2
-> 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 -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
rs Coeffs2
coeffs Array Int [Array Int Int]
permsV String
choice [] Int
numberI [Int]
intervalNmbrs Double
0.0 Double
0.0 ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop Int
1 ([String] -> [String]) -> [String] -> [String]
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 <- ((Int, String) -> IO (Int, [(Int, String)]))
-> [(Int, String)] -> IO [(Int, [(Int, String)])]
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 IO String
-> (String -> IO (Int, [(Int, String)]))
-> IO (Int, [(Int, String)])
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \String
fs -> (Int, [(Int, String)]) -> IO (Int, [(Int, String)])
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
j, [Int] -> [String] -> [(Int, String)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..] ([String] -> [(Int, String)])
-> (String -> [String]) -> String -> [(Int, String)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines (String -> [(Int, String)]) -> String -> [(Int, String)]
forall a b. (a -> b) -> a -> b
$ String
fs)})) ([(Int, String)] -> IO [(Int, [(Int, String)])])
-> ([String] -> [(Int, String)])
-> [String]
-> IO [(Int, [(Int, String)])]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [String] -> [(Int, String)]
forall a b. [a] -> [b] -> [(a, b)]
zip [Int
1..Int
7] ([String] -> [(Int, String)])
-> ([String] -> [String]) -> [String] -> [(Int, String)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
7 ([String] -> IO [(Int, [(Int, String)])])
-> [String] -> IO [(Int, [(Int, String)])]
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 = (Int -> IO ()) -> [Int] -> IO ()
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 = ((Int, [(Int, String)]) -> (Int, String))
-> [(Int, [(Int, String)])] -> [(Int, String)]
forall a b. (a -> b) -> [a] -> [b]
map (\(Int
j,[(Int, String)]
ks) -> (\[(Int, String)]
ts -> if [(Int, String)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Int, String)]
ts then (Int
j,String
"")
                      else let (Int
k,String
rs) = [(Int, String)] -> (Int, String)
forall a. [a] -> a
head [(Int, String)]
ts in  (Int
j,String
rs)) ([(Int, String)] -> (Int, String))
-> ([(Int, String)] -> [(Int, String)])
-> [(Int, String)]
-> (Int, String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                       ((Int, String) -> Bool) -> [(Int, String)] -> [(Int, String)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
i) (Int -> Bool) -> ((Int, String) -> Int) -> (Int, String) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, String) -> Int
forall a b. (a, b) -> a
fst) ([(Int, String)] -> (Int, String))
-> [(Int, String)] -> (Int, String)
forall a b. (a -> b) -> a -> b
$ [(Int, String)]
ks) [(Int, [(Int, String)])]
ysss
          ((Int, String) -> IO ()) -> [(Int, String)] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\(Int
i,String
xs) -> String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ Int -> String
forall a. Show a => a -> String
show Int
i String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
":\t" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
xs) [(Int, String)]
strs
          String
ch <- IO String
getLine
          let choice2 :: Int
choice2 = Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
0 (String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
ch::Maybe Int)
          String -> [String] -> IO ()
toFileStr String
file3 ((\[(Int, String)]
us -> if [(Int, String)] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [(Int, String)]
us then [String
""] else [(Int, String) -> String
forall a b. (a, b) -> b
snd ((Int, String) -> String)
-> ([(Int, String)] -> (Int, String)) -> [(Int, String)] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Int, String)] -> (Int, String)
forall a. [a] -> a
head ([(Int, String)] -> String) -> [(Int, String)] -> String
forall a b. (a -> b) -> a -> b
$ [(Int, String)]
us]) ([(Int, String)] -> [String])
-> ([(Int, String)] -> [(Int, String)])
-> [(Int, String)]
-> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, String) -> Bool) -> [(Int, String)] -> [(Int, String)]
forall a. (a -> Bool) -> [a] -> [a]
filter ((Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
choice2) (Int -> Bool) -> ((Int, String) -> Int) -> (Int, String) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, String) -> Int
forall a b. (a, b) -> a
fst) ([(Int, String)] -> [String]) -> [(Int, String)] -> [String]
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 -> ([[[PRS]]] -> [[Double]]))-- ^ 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@.
 -> [([[[PRS]]] -> [[Double]])] -- ^ A list of 4 different functions that specifies the syllables durations, analogues of the
  -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most
  -- exact one and, therefore, the default one.
 -> Coeffs2
 -> 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 (that is the default 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 -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Coeffs2
-> 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 -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Coeffs2
coeffs Array Int [Array Int Int]
permsG1 String
choice [String]
yss [String]
xss
 | [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
xss = [String]
yss
 | Bool
otherwise = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Coeffs2
-> 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 -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Coeffs2
coeffs Array Int [Array Int Int]
permsG1 String
choice ([String]
yss [String] -> [String] -> [String]
forall a. Monoid a => a -> a -> a
`mappend` [String
ws]) [String]
tss
      where (![String]
zss,![String]
tss) = Int -> [String] -> ([String], [String])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
1 [String]
xss
            !rs :: [String]
rs = String -> [String]
words (String -> [String])
-> ([String] -> String) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
zss
            !l :: Int
l = [String] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
rs
            !frep2 :: FuncRep2 String Double Double
frep2 = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> Double)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double Double
forall c.
Ord c =>
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> c)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double c
chooseMax GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> Double
forall a. a -> a
id Double -> String -> [[[PRS]]] -> [[Double]]
h Coeffs2
coeffs [[[[PRS]]] -> [[Double]]]
qs String
choice
            !ws :: String
ws = if Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
l Int
3 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
LT then [String] -> String
unwords [String]
rs else Result [] Char Double Double -> String
forall (t :: * -> *) a b c. Result t a b c -> t a
line (Result [] Char Double Double -> String)
-> ([String] -> Result [] Char Double Double) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Result [] Char Double Double] -> Result [] Char Double Double
forall (t2 :: * -> *) c (t :: * -> *) a b.
(Foldable t2, Ord c) =>
t2 (Result t a b c) -> Result t a b c
maximumElR ([Result [] Char Double Double] -> Result [] Char Double Double)
-> ([String] -> [Result [] Char Double Double])
-> [String]
-> Result [] Char Double Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Result [] Char Double Double)
-> [String] -> [Result [] Char Double Double]
forall a b. (a -> b) -> [a] -> [b]
map (FuncRep2 String Double Double
-> String -> Result [] Char Double Double
forall (t :: * -> *) a b c.
FuncRep2 (t a) b c -> t a -> Result t a b c
toResultR FuncRep2 String Double Double
frep2) ([String] -> [Result [] Char Double Double])
-> ([String] -> [String])
-> [String]
-> [Result [] Char Double Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
               String
-> String
-> Char
-> (String -> String)
-> ([String] -> [String])
-> (String -> String)
-> [Array Int Int]
-> [String]
-> [String]
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 [] ([String] -> String
forall a. [a] -> a
last [String]
rs) Char
' ' String -> String
forall a. a -> a
id [String] -> [String]
forall a. a -> a
id String -> String
forall a. a -> a
id (Array Int [Array Int Int] -> Int -> [Array Int Int]
forall i e. Array i e -> Int -> e
unsafeAt Array Int [Array Int Int]
permsG1 (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
3)) ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [String]
forall a. [a] -> [a]
init ([String] -> String) -> [String] -> String
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 -> ([[[PRS]]] -> [[Double]])) -- ^ 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@.
  -> [([[[PRS]]] -> [[Double]])]-- ^ A list of 4 different functions that specifies the syllables durations, analogues of the
  -- syllableDurationsD functions from the @ukrainian-phonetics-basics-array@ package. The last one must be probably the most
  -- exact one and, therefore, the default one.
  -> Coeffs2
  -> 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 (that is the default 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 -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Coeffs2
-> 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 -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Coeffs2
coeffs Array Int [Array Int Int]
permsG1 String
choice [String]
yss Int
numberI [Int]
intervNbrs Double
minE Double
maxE [String]
xss
 | [String] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
xss = [String]
yss
 | Bool
otherwise = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> [[[[PRS]]] -> [[Double]]]
-> Coeffs2
-> 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 -> [[[PRS]]] -> [[Double]]
h [[[[PRS]]] -> [[Double]]]
qs Coeffs2
coeffs Array Int [Array Int Int]
permsG1 String
choice ([String]
yss [String] -> [String] -> [String]
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) = Int -> [String] -> ([String], [String])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
1 [String]
xss
            !w2s :: [String]
w2s = String -> [String]
words (String -> [String])
-> ([String] -> String) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
1 ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
tss
            !l3 :: Int
l3 = (Int -> Int -> Int
forall a. Num a => a -> a -> a
subtract Int
3) (Int -> Int) -> ([String] -> Int) -> [String] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length ([String] -> Int) -> [String] -> Int
forall a b. (a -> b) -> a -> b
$ [String]
w2s
            !rs :: [String]
rs = String -> [String]
words (String -> [String])
-> ([String] -> String) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ [String]
zss
            !l :: Int
l = [String] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
rs
            !frep2 :: FuncRep2 String Double Double
frep2 = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> Double)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double Double
forall c.
Ord c =>
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> c)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double c
chooseMax GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs (Double -> Double -> Int -> [Int] -> Double -> Double
forall b c.
(RealFrac b, Integral c) =>
b -> b -> c -> [c] -> b -> b
unsafeSwapVecIWithMaxI Double
minE Double
maxE Int
numberI [Int]
intervNbrs) Double -> String -> [[[PRS]]] -> [[Double]]
h Coeffs2
coeffs [[[[PRS]]] -> [[Double]]]
qs String
choice
            !ws :: String
ws = if Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare ([String] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
rs) Int
3 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Ordering
LT then [String] -> String
unwords [String]
rs else Result [] Char Double Double -> String
forall (t :: * -> *) a b c. Result t a b c -> t a
line (Result [] Char Double Double -> String)
-> ([String] -> Result [] Char Double Double) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Result [] Char Double Double] -> Result [] Char Double Double
forall (t2 :: * -> *) c (t :: * -> *) a b.
(Foldable t2, Ord c) =>
t2 (Result t a b c) -> Result t a b c
maximumElR ([Result [] Char Double Double] -> Result [] Char Double Double)
-> ([String] -> [Result [] Char Double Double])
-> [String]
-> Result [] Char Double Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Result [] Char Double Double)
-> [String] -> [Result [] Char Double Double]
forall a b. (a -> b) -> [a] -> [b]
map (FuncRep2 String Double Double
-> String -> Result [] Char Double Double
forall (t :: * -> *) a b c.
FuncRep2 (t a) b c -> t a -> Result t a b c
toResultR FuncRep2 String Double Double
frep2) ([String] -> [Result [] Char Double Double])
-> ([String] -> [String])
-> [String]
-> [Result [] Char Double Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
               String
-> String
-> Char
-> (String -> String)
-> ([String] -> [String])
-> (String -> String)
-> [Array Int Int]
-> [String]
-> [String]
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 [] ([String] -> String
forall a. [a] -> a
last [String]
rs) Char
' ' String -> String
forall a. a -> a
id [String] -> [String]
forall a. a -> a
id String -> String
forall a. a -> a
id (Array Int [Array Int Int] -> Int -> [Array Int Int]
forall i e. Array i e -> Int -> e
unsafeAt Array Int [Array Int Int]
permsG1 (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
3)) ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [String]
forall a. [a] -> [a]
init ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
rs
            (!Double
minE1,!Double
maxE1)
             | Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
l3 Int
0 Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
/= Ordering
LT =
               let !perms3 :: [Array Int Int]
perms3 = Array Int [Array Int Int] -> Int -> [Array Int Int]
forall i e. Array i e -> Int -> e
unsafeAt Array Int [Array Int Int]
permsG1 Int
l3
                   !v4 :: [String]
v4 = [String] -> [String]
forall a. [a] -> [a]
init [String]
w2s
                   !frep20 :: FuncRep2 String Double Double
frep20 = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> Double)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double Double
forall c.
Ord c =>
GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> c)
-> (Double -> String -> [[[PRS]]] -> [[Double]])
-> Coeffs2
-> [[[[PRS]]] -> [[Double]]]
-> String
-> FuncRep2 String Double c
chooseMax GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> Double
forall a. a -> a
id Double -> String -> [[[PRS]]] -> [[Double]]
h Coeffs2
coeffs [[[[PRS]]] -> [[Double]]]
qs String
choice in [Double] -> (Double, Double)
forall a (t :: * -> *).
(Ord a, InsertLeft t a, Monoid (t a)) =>
t a -> (a, a)
minMax11C ([Double] -> (Double, Double))
-> ([String] -> [Double]) -> [String] -> (Double, Double)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> Double) -> [String] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map (FuncRep2 String Double Double -> String -> Double
forall (t :: * -> *) a b c. FuncRep2 (t a) b c -> t a -> b
toPropertiesF' FuncRep2 String Double Double
frep20) ([String] -> [Double])
-> ([String] -> [String]) -> [String] -> [Double]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                      String
-> String
-> Char
-> (String -> String)
-> ([String] -> [String])
-> (String -> String)
-> [Array Int Int]
-> [String]
-> [String]
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 [] ([String] -> String
forall a. [a] -> a
last [String]
w2s) Char
' ' String -> String
forall a. a -> a
id [String] -> [String]
forall a. a -> a
id String -> String
forall a. a -> a
id [Array Int Int]
perms3 ([String] -> (Double, Double)) -> [String] -> (Double, Double)
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 = (String -> IO ()) -> [String] -> IO ()
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 String -> String -> String
forall a. Monoid a => a -> a -> a
`mappend` String
newLineEnding)) [String]
xss