{-# OPTIONS_GHC -threaded -rtsopts #-}
{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE BangPatterns, FlexibleContexts #-}
module Phonetic.Languages.General.GetTextualInfo (
generalProc
, linesFromArgs1
, linesFromArgsG
, getData3
, process1Line
) where
import Phonetic.Languages.General.Parsing
import Data.SubG hiding (takeWhile,dropWhile)
import System.IO
import Control.Concurrent
import Control.Exception
import Control.Parallel.Strategies
import Data.Maybe (fromMaybe)
import Data.List (sort)
import Text.Read (readMaybe)
import GHC.Arr
import Data.Phonetic.Languages.Base
import Data.Phonetic.Languages.PrepareText
import Numeric (showFFloat)
import Phonetic.Languages.Filters
import Data.Char (isAlpha)
import Data.Statistics.RulesIntervalsPlus
import Data.MinMax.Preconditions
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.Simplified.DataG.Base
import Phonetic.Languages.Basis
import Phonetic.Languages.Simplified.DataG.Partir
import Phonetic.Languages.Simplified.Array.General.FuncRep2RelatedG2
import Languages.UniquenessPeriods.Array.Constraints.Encoded
import Phonetic.Languages.General.SimpleConstraints
import Phonetic.Languages.General.Common
import Data.Phonetic.Languages.Base
import Data.Phonetic.Languages.Syllables
import qualified Phonetic.Languages.Permutations.Represent as R
import Phonetic.Languages.EmphasisG
import Phonetic.Languages.Coeffs
generalProc
:: R.PermutationsType
-> (Int,Int)
-> GWritingSystemPRPLX
-> [(Char,Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Concatenations
-> Concatenations
-> String
-> String
-> String
-> Bool
-> [String]
-> [String]
-> Coeffs2
-> Coeffs2
-> FilePath
-> String
-> Int
-> Int
-> (String -> String)
-> Bool
-> String
-> IO ()
generalProc :: PermutationsType
-> (Int, Int)
-> GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Concatenations
-> Concatenations
-> String
-> String
-> String
-> Bool
-> [String]
-> [String]
-> Coeffs2
-> Coeffs2
-> String
-> String
-> Int
-> Int
-> (String -> String)
-> Bool
-> String
-> IO ()
generalProc 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 Bool
lstW [String]
multiples2 [String]
lInes Coeffs2
coeffs Coeffs2
coeffsWX String
file String
gzS Int
printLine Int
toOneLine String -> String
g1 Bool
syllableStats String
choice
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
lInes = do
String
contents0 <- do (if String
file forall a. Eq a => a -> a -> Bool
== String
"+i" then IO String
getContents else String -> IO String
readFile String
file)
let !contsWss :: Concatenations
contsWss = forall a b. (a -> b) -> [a] -> [b]
map String -> [String]
words forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines forall a b. (a -> b) -> a -> b
$ String
contents0
!newconts :: String
newconts = [String] -> String
unlines forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (\[String]
lineswrdss -> if [String] -> Bool
variations [String]
lineswrdss then [String] -> String
unlines forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map [String] -> String
unwords forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> Concatenations
transformToVariations forall a b. (a -> b) -> a -> b
$ [String]
lineswrdss else [String] -> String
unwords [String]
lineswrdss) forall a b. (a -> b) -> a -> b
$ Concatenations
contsWss
!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
toOneLine String
newconts
| 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
toOneLine forall a b. (a -> b) -> a -> b
$ String
newconts
PermutationsType
-> GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Bool
-> Coeffs2
-> Coeffs2
-> Int
-> Int
-> (String -> String)
-> String
-> [String]
-> Bool
-> [String]
-> IO ()
getData3 PermutationsType
pairwisePermutations GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
rs Bool
lstW Coeffs2
coeffs Coeffs2
coeffsWX (Bool -> String -> [String] -> Int
getIntervalsNS Bool
lstW String
gzS [String]
flines) Int
printLine String -> String
g1 String
choice [String]
multiples2 Bool
syllableStats [String]
flines
| Bool
otherwise = do
String
contents0 <- do (if String
file forall a. Eq a => a -> a -> Bool
== String
"+i" then IO String
getContents else String -> IO String
readFile String
file)
let !contsWss :: Concatenations
contsWss = forall a b. (a -> b) -> [a] -> [b]
map String -> [String]
words forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
lines forall a b. (a -> b) -> a -> b
$ String
contents0
!newconts :: String
newconts = [String] -> String
unlines forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (\[String]
lineswrdss -> if [String] -> Bool
variations [String]
lineswrdss then [String] -> String
unlines forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map [String] -> String
unwords forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> Concatenations
transformToVariations forall a b. (a -> b) -> a -> b
$ [String]
lineswrdss else [String] -> String
unwords [String]
lineswrdss) forall a b. (a -> b) -> a -> b
$ Concatenations
contsWss
!flines :: [String]
flines = (if Int
gr1 forall a. Eq a => a -> a -> Bool
== Int
0 then forall a. a -> a
id else 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
toOneLine forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
unlines forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [String] -> [String]
linesFromArgsG [String]
lInes 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
newconts
PermutationsType
-> GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Bool
-> Coeffs2
-> Coeffs2
-> Int
-> Int
-> (String -> String)
-> String
-> [String]
-> Bool
-> [String]
-> IO ()
getData3 PermutationsType
pairwisePermutations GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
rs Bool
lstW Coeffs2
coeffs Coeffs2
coeffsWX (Bool -> String -> [String] -> Int
getIntervalsNS Bool
lstW String
gzS [String]
flines) Int
printLine String -> String
g1 String
choice [String]
multiples2 Bool
syllableStats [String]
flines
linesFromArgs1
:: Int
-> String
-> [String]
-> [String]
linesFromArgs1 :: Int -> String -> [String] -> [String]
linesFromArgs1 Int
n String
xs [String]
yss =
let (!String
ys,!String
zs) = (\(String
x,String
z) -> (String
x, forall a. Int -> [a] -> [a]
drop Int
1 String
z)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> ([a], [a])
break (forall a. Eq a => a -> a -> Bool
== Char
':') forall a b. (a -> b) -> a -> b
$ String
xs
!ts :: [Int]
ts = forall a. Ord a => [a] -> [a]
sort forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map (forall a. Ord a => a -> a -> a
min Int
n forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => a -> a
abs) forall a b. (a -> b) -> a -> b
$ [forall a. a -> Maybe a -> a
fromMaybe Int
1 (forall a. Read a => String -> Maybe a
readMaybe String
ys::Maybe Int), forall a. a -> Maybe a -> a
fromMaybe Int
n (forall a. Read a => String -> Maybe a
readMaybe String
zs::Maybe Int)] in
forall a. Int -> [a] -> [a]
drop (forall a. [a] -> a
head [Int]
ts forall a. Num a => a -> a -> a
- Int
1) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Int -> [a] -> [a]
take (forall a. [a] -> a
last [Int]
ts) forall a b. (a -> b) -> a -> b
$ [String]
yss
linesFromArgsG :: [String] -> [String] -> [String]
linesFromArgsG :: [String] -> [String] -> [String]
linesFromArgsG [String]
xss [String]
yss = let n :: Int
n = forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
yss in forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\String
ts -> Int -> String -> [String] -> [String]
linesFromArgs1 Int
n String
ts [String]
yss) [String]
xss
getData3
:: R.PermutationsType
-> GWritingSystemPRPLX
-> [(Char,Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Bool
-> Coeffs2
-> Coeffs2
-> Int
-> Int
-> (String -> String)
-> String
-> [String]
-> Bool
-> [String]
-> IO ()
getData3 :: PermutationsType
-> GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Bool
-> Coeffs2
-> Coeffs2
-> Int
-> Int
-> (String -> String)
-> String
-> [String]
-> Bool
-> [String]
-> IO ()
getData3 PermutationsType
pairwisePermutations GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
rs Bool
lstW Coeffs2
coeffs Coeffs2
coeffsWX Int
gz Int
printLine String -> String
g1 String
choice0 [String]
multiples3 Bool
syllableStats [String]
zss = do
let choice :: String
choice = forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
/= Char
'a') String
choice0
!permsV4 :: Array Int [Array Int Int]
permsV4
| 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
String -> IO ()
putStrLn (forall a. Int -> a -> [a]
replicate (forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
multiples3 forall a. Num a => a -> a -> a
+ Int
1) Char
'\t' forall a. Monoid a => a -> a -> a
`mappend` forall a. Show a => a -> String
show Int
gz)
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\String
qs -> case Bool
syllableStats of
Bool
True -> let tsss :: [[[PRS]]]
tsss = GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> String
-> [[[PRS]]]
createSyllablesPL GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs String
qs in String -> IO ()
putStrLn ((forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a. Foldable t => t a -> Int
length 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
$ [[[PRS]]]
tsss) forall a. Monoid a => a -> a -> a
`mappend` String
"\t" forall a. Monoid a => a -> a -> a
`mappend` (forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall (t :: * -> *) a. Foldable t => t a -> Int
length forall a b. (a -> b) -> a -> b
$ [[[PRS]]]
tsss) forall a. Monoid a => a -> a -> a
`mappend` (if Int
printLine forall a. Eq a => a -> a -> Bool
== Int
1 then Char
'\t'forall a. a -> [a] -> [a]
:String
qs else String
""))
Bool
_ -> GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Bool
-> Coeffs2
-> Coeffs2
-> Int
-> Int
-> (String -> String)
-> String
-> [String]
-> Array Int [Array Int Int]
-> String
-> IO ()
process1Line GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
rs Bool
lstW Coeffs2
coeffs Coeffs2
coeffsWX Int
gz Int
printLine String -> String
g1 String
choice [String]
multiples3 Array Int [Array Int Int]
permsV4 String
qs) [String]
zss
process1Line
:: GWritingSystemPRPLX
-> [(Char,Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Bool
-> Coeffs2
-> Coeffs2
-> Int
-> Int
-> (String -> String)
-> String
-> [String]
-> Array Int [Array Int Int]
-> String
-> IO ()
process1Line :: GWritingSystemPRPLX
-> [(Char, Char)]
-> CharPhoneticClassification
-> SegmentRulesG
-> String
-> String
-> (Double -> String -> MappingFunctionPL)
-> [MappingFunctionPL]
-> Bool
-> Coeffs2
-> Coeffs2
-> Int
-> Int
-> (String -> String)
-> String
-> [String]
-> Array Int [Array Int Int]
-> String
-> IO ()
process1Line GWritingSystemPRPLX
wrs [(Char, Char)]
ks CharPhoneticClassification
arr SegmentRulesG
gs String
js String
vs Double -> String -> MappingFunctionPL
h [MappingFunctionPL]
qs Bool
lstW Coeffs2
coeffs Coeffs2
coeffsWX Int
gz Int
printLine String -> String
g1 String
choice [String]
multiples4 !Array Int [Array Int Int]
permsV50 String
v
| forall (t :: * -> *) a. Foldable t => t a -> Bool
null [String]
multiples4 = forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (do {
ThreadId
myThread <- IO () -> IO ThreadId
forkIO (do
let !v2 :: [String]
v2 = String -> [String]
words String
v
!l2 :: Int
l2 = forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
v2 forall a. Num a => a -> a -> a
- Int
2
!sels :: String
sels = (String -> String) -> String -> String
parsey0Choice String -> String
g1 String
choice
if Int
l2 forall a. Ord a => a -> a -> Bool
>= (if Bool
lstW then Int
1 else Int
0) then do
let !permsV5 :: [Array Int Int]
permsV5 = forall (t :: * -> *).
(InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) =>
EncodedCnstrs -> t (Array Int Int) -> t (Array Int Int)
decodeConstraint1 (forall a. a -> Maybe a -> a
fromMaybe (forall a b. a -> EncodedContraints a b
E Int
1) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> Maybe EncodedCnstrs
readMaybeECG (Int
l2 forall a. Num a => a -> a -> a
+ Int
1) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Bool -> String
showB (Int
l2 forall a. Num a => a -> a -> a
+ Int
2) forall a b. (a -> b) -> a -> b
$ Bool
lstW) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall i e. Array i e -> Int -> e
unsafeAt Array Int [Array Int Int]
permsV50 forall a b. (a -> b) -> a -> b
$ Int
l2
((!Double
minE,!Double
maxE),!Double
data2) = forall a. Eval a -> a
runEval (forall a b. Strategy a -> Strategy b -> Strategy (a, b)
parTuple2 forall a. Strategy a
rpar forall a. Strategy a
rpar (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 -> c
toTransPropertiesF'2 (if forall a. Int -> [a] -> [a]
take Int
1 String
choice forall a. Eq a => a -> a -> Bool
== String
"w" Bool -> Bool -> Bool
|| forall a. Int -> [a] -> [a]
take Int
1 String
choice forall a. Eq a => a -> a -> Bool
== String
"x" then 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
coeffsWX String
sels [MappingFunctionPL]
qs String
choice String
"" else 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
"")) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall a b. (a -> b) -> [a] -> [b]
map 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))) =>
a
-> (t a -> [a])
-> (t (t a) -> [[a]])
-> ([a] -> t a)
-> [Array Int Int]
-> t (t a)
-> [t a]
uniquenessVariants2GNBL Char
' ' forall a. a -> a
id forall a. a -> a
id forall a. a -> a
id [Array Int Int]
permsV5 forall a b. (a -> b) -> a -> b
$ [String]
v2, forall a b c. FuncRep2 a b c -> a -> c
toTransPropertiesF'2 (if forall a. Int -> [a] -> [a]
take Int
1 String
choice forall a. Eq a => a -> a -> Bool
== String
"w" Bool -> Bool -> Bool
|| forall a. Int -> [a] -> [a]
take Int
1 String
choice forall a. Eq a => a -> a -> Bool
== String
"x" then 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
coeffsWX String
sels [MappingFunctionPL]
qs String
choice String
"" else 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
"") forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> ReadyForConstructionPL
StrG forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
unwords forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a), Monoid (t (t a))) =>
t a -> t a -> t (t a)
subG (Char
' 'forall a. a -> [a] -> [a]
:String
js forall a. Monoid a => a -> a -> a
`mappend` String
vs) forall a b. (a -> b) -> a -> b
$ String
v))
(!Int
wordsN,!Int
intervalN) = (Int
l2 forall a. Num a => a -> a -> a
+ Int
2, forall b c. (RealFrac b, Integral c) => b -> b -> c -> b -> c
intervalNRealFrac Double
minE Double
maxE Int
gz Double
data2)
!ratio :: Double
ratio = if Double
maxE forall a. Eq a => a -> a -> Bool
== Double
0.0 then Double
0.0 else Double
2.0 forall a. Num a => a -> a -> a
* Double
data2 forall a. Fractional a => a -> a -> a
/ (Double
minE forall a. Num a => a -> a -> a
+ Double
maxE)
Handle -> String -> IO ()
hPutStr Handle
stdout forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (String -> Maybe Int
precChoice String
choice) Double
minE forall a b. (a -> b) -> a -> b
$ String
"\t"
Handle -> String -> IO ()
hPutStr Handle
stdout forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (String -> Maybe Int
precChoice String
choice) Double
data2 forall a b. (a -> b) -> a -> b
$ String
"\t"
Handle -> String -> IO ()
hPutStr Handle
stdout forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (String -> Maybe Int
precChoice String
choice) Double
maxE forall a b. (a -> b) -> a -> b
$ String
"\t"
Handle -> String -> IO ()
hPutStr Handle
stdout forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (forall a. a -> Maybe a
Just Int
4) (Double
data2 forall a. Fractional a => a -> a -> a
/ Double
minE) forall a b. (a -> b) -> a -> b
$ String
"\t"
Handle -> String -> IO ()
hPutStr Handle
stdout forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (forall a. a -> Maybe a
Just Int
4) (Double
maxE forall a. Fractional a => a -> a -> a
/ Double
minE) forall a b. (a -> b) -> a -> b
$ String
"\t"
Handle -> String -> IO ()
hPutStr Handle
stdout forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (forall a. a -> Maybe a
Just Int
4) (Double
maxE forall a. Fractional a => a -> a -> a
/ Double
data2) forall a b. (a -> b) -> a -> b
$ String
"\t"
Handle -> String -> IO ()
hPutStr Handle
stdout forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. RealFloat a => Maybe Int -> a -> String -> String
showFFloat (forall a. a -> Maybe a
Just Int
8) Double
ratio forall a b. (a -> b) -> a -> b
$ String
"\t"
Handle -> String -> IO ()
hPutStr Handle
stdout (Char
'\t'forall a. a -> [a] -> [a]
:forall a. Show a => a -> String
show (Int
wordsN::Int))
Handle -> String -> IO ()
hPutStr Handle
stdout (Char
'\t'forall a. a -> [a] -> [a]
:forall a. Show a => a -> String
show (Int
intervalN::Int))
Handle -> String -> IO ()
hPutStrLn Handle
stdout (if Int
printLine forall a. Eq a => a -> a -> Bool
== Int
1 then Char
'\t'forall a. a -> [a] -> [a]
:String
v else String
"")
else String -> IO ()
putStrLn (forall a. Int -> a -> [a]
replicate (forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
multiples4) Char
'\t' forall a. [a] -> [a] -> [a]
++ if Int
printLine forall a. Eq a => a -> a -> Bool
== Int
1 then Char
'\t'forall a. a -> [a] -> [a]
:String
v else String
""))
; forall (m :: * -> *) a. Monad m => a -> m a
return ThreadId
myThread }) (ThreadId -> IO ()
killThread) (\ThreadId
_ -> String -> IO ()
putStr String
"")
| Bool
otherwise = forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (do {
ThreadId
myThread <- IO () -> IO ThreadId
forkIO (do
let !v2 :: [String]
v2 = String -> [String]
words String
v
!l2 :: Int
l2 = forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
v2 forall a. Num a => a -> a -> a
- Int
2
if Int
l2 forall a. Ord a => a -> a -> Bool
>= (if Bool
lstW then Int
1 else Int
0) then do
let !permsV5 :: [Array Int Int]
permsV5 = forall (t :: * -> *).
(InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) =>
EncodedCnstrs -> t (Array Int Int) -> t (Array Int Int)
decodeConstraint1 (forall a. a -> Maybe a -> a
fromMaybe (forall a b. a -> EncodedContraints a b
E Int
1) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String -> Maybe EncodedCnstrs
readMaybeECG (Int
l2 forall a. Num a => a -> a -> a
+ Int
1) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Bool -> String
showB (Int
l2 forall a. Num a => a -> a -> a
+ Int
2) forall a b. (a -> b) -> a -> b
$ Bool
lstW) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall i e. Array i e -> Int -> e
unsafeAt Array Int [Array Int Int]
permsV50 forall a b. (a -> b) -> a -> b
$ Int
l2
rs :: [((Double, Double), Double, Int)]
rs = forall b a. Strategy b -> (a -> b) -> [a] -> [b]
parMap forall a. Strategy a
rpar (\String
choiceMMs -> let sels :: String
sels = (String -> String) -> String -> String
parsey0Choice String -> String
g1 String
choiceMMs 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 -> c
toTransPropertiesF'2 (if forall a. Int -> [a] -> [a]
take Int
1 String
choiceMMs forall a. Eq a => a -> a -> Bool
== String
"w" Bool -> Bool -> Bool
|| forall a. Int -> [a] -> [a]
take Int
1 String
choiceMMs forall a. Eq a => a -> a -> Bool
== String
"x" then 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
coeffsWX String
sels [MappingFunctionPL]
qs String
choiceMMs String
"" else 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
choiceMMs String
"")) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall a b. (a -> b) -> [a] -> [b]
map 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))) =>
a
-> (t a -> [a])
-> (t (t a) -> [[a]])
-> ([a] -> t a)
-> [Array Int Int]
-> t (t a)
-> [t a]
uniquenessVariants2GNBL Char
' ' forall a. a -> a
id forall a. a -> a
id forall a. a -> a
id [Array Int Int]
permsV5 forall a b. (a -> b) -> a -> b
$ [String]
v2,
forall a b c. FuncRep2 a b c -> a -> c
toTransPropertiesF'2 (if forall a. Int -> [a] -> [a]
take Int
1 String
choiceMMs forall a. Eq a => a -> a -> Bool
== String
"w" Bool -> Bool -> Bool
|| forall a. Int -> [a] -> [a]
take Int
1 String
choiceMMs forall a. Eq a => a -> a -> Bool
== String
"x" then 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
coeffsWX String
sels [MappingFunctionPL]
qs String
choiceMMs String
"" else 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
choiceMMs String
"") forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> ReadyForConstructionPL
StrG forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
unwords forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a), Monoid (t (t a))) =>
t a -> t a -> t (t a)
subG (Char
' 'forall a. a -> [a] -> [a]
:String
js forall a. Monoid a => a -> a -> a
`mappend` String
vs) forall a b. (a -> b) -> a -> b
$ String
v,Int
gz)) [String]
multiples4
(!Int
wordsN,![Int]
intervalNs) = (Int
l2 forall a. Num a => a -> a -> a
+ Int
2, forall a b. (a -> b) -> [a] -> [b]
map (\((!Double
x,!Double
y),!Double
z,!Int
t) -> forall b c. (RealFrac b, Integral c) => b -> b -> c -> b -> c
intervalNRealFrac Double
x Double
y Int
t Double
z) [((Double, Double), Double, Int)]
rs)
in do
Handle -> String -> IO ()
hPutStr Handle
stdout (forall a. Show a => a -> String
show (Int
wordsN::Int))
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (\Int
i -> Handle -> String -> IO ()
hPutStr Handle
stdout (Char
'\t'forall a. a -> [a] -> [a]
:forall a. Show a => a -> String
show (Int
i::Int))) [Int]
intervalNs
Handle -> String -> IO ()
hPutStrLn Handle
stdout (if Int
printLine forall a. Eq a => a -> a -> Bool
== Int
1 then Char
'\t'forall a. a -> [a] -> [a]
:String
v else String
"")
else String -> IO ()
putStrLn (forall a. Int -> a -> [a]
replicate (forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
multiples4) Char
'\t' forall a. [a] -> [a] -> [a]
++ if Int
printLine forall a. Eq a => a -> a -> Bool
== Int
1 then Char
'\t'forall a. a -> [a] -> [a]
:String
v else String
""))
; forall (m :: * -> *) a. Monad m => a -> m a
return ThreadId
myThread }) (ThreadId -> IO ()
killThread) (\ThreadId
_ -> String -> IO ()
putStr String
"")