{-# LANGUAGE NoImplicitPrelude #-} module Main where import GHC.Base import GHC.Num ((+),(-),(*)) import GHC.Real (fromIntegral,(/)) import GHC.Enum (fromEnum) import Text.Show (show) import Text.Read (readMaybe) import System.IO (putStrLn, FilePath,stdout,hSetNewlineMode,universalNewlineMode) import Rhythmicity.MarkerSeqs hiding (id) import Rhythmicity.BasicF import Data.List hiding (foldr) import Data.Maybe (fromMaybe) import Data.Tuple (fst,snd) import Phladiprelio.Ukrainian.PrepareText import Phladiprelio.Ukrainian.Syllable import Phladiprelio.Ukrainian.SyllableDouble import Phladiprelio.Ukrainian.Melodics import System.Environment (getArgs) import GHC.Int (Int8) import CLI.Arguments import CLI.Arguments.Get import CLI.Arguments.Parsing import Phladiprelio.Ukrainian.ReadDurations import Data.Ord (comparing) generalF :: FilePath -> Int -> HashCorrections -> (Int8,[Int8]) -> Int -> Bool -> Int -> String -> IO [()] generalF file numTest hc (grps,mxms) k descending hashStep rs = do syllableDurationsDs <- readSyllableDurations file let syllN = countSyll rs universalSet = map unwords . permutations . words $ rs f syllableDurationsDs grps mxms = sum . countHashes2G hashStep hc grps mxms . mconcat . (if null file then case k of { 1 -> syllableDurationsD; 2 -> syllableDurationsD2; 3 -> syllableDurationsD3; 4 -> syllableDurationsD4} else if length syllableDurationsDs >= k then syllableDurationsDs !! (k - 1) else syllableDurationsD2) . createSyllablesUkrS if numTest `elem` (0:[2..6]) then do hSetNewlineMode stdout universalNewlineMode putStrLn "Feet Val Stat Proxim" mapM (\(q,qs) -> let m = stat1 syllN (q,qs) in let max1 = maximumBy (comparing (f syllableDurationsDs q qs)) universalSet in let mx = f syllableDurationsDs q qs max1 in putStrLn (show (fromEnum q) `mappend` " | " `mappend` show mx `mappend` " " `mappend` show m `mappend` " -> " `mappend` show (100 * fromIntegral mx / fromIntegral m) `mappend` "%" `mappend` (if numTest >= 4 then let min1 = minimumBy (comparing (f syllableDurationsDs q qs)) universalSet in ("\n" `mappend` min1 `mappend` "\n" `mappend` max1 `mappend` "\n") else ""))) . zip [2..7] $ ([1]:sel numTest) else mapM (\(x,y) -> putStrLn (show x `mappend` (' ':y))) . (let h1 = if descending then (\(u,w) -> ((-1) * u, w)) else id in sortOn h1) . map (\xss -> (f syllableDurationsDs grps mxms xss, xss)) $ universalSet where sel x | x == 0 || x == 4 = [[2,1],[3,2],[4,3,2],[5,4,3],[6,5,4,3,2]] | x == 2 || x == 5 = [[2],[3],[4,3],[5,4],[6,5,4]] | otherwise = [[1],[2,1],[3,2,1],[3,2],[4,3,2]] countSyll :: String -> Int countSyll xs = fromEnum . foldr (\x y -> if isVowel1 x then y + 1 else y) 0 . convertToProperUkrainianI8 $ xs stat1 :: Int -> (Int8,[Int8]) -> Int stat1 n (k, ks) = fst (n `quotRemInt` fromEnum k) * length ks main :: IO () main = do args <- getArgs let (argsA, argsB, _, arg2s) = args2Args3R (aSpecs `mappend` bSpecs) args fileDu = concat . getB "+d" $ argsB sylD = let k = snd (fromMaybe 2 (readMaybe (concat . getB "+s" $ argsB)::Maybe Int) `quotRemInt` 4) in if k == 0 then 4 else k hc = readHashCorrections . concat . getB "+c" $ argsB grpp = grouppingR . concat . getB "+r" $ argsB numTest = fromMaybe 1 (readMaybe (concat . getB "-t" $ argsB)::Maybe Int) hashStep = fromMaybe 20 (readMaybe (concat . getB "+k" $ argsB)::Maybe Int) helpMessage = oneA "-h" argsA descending = oneA "+n" argsA str1 = unwords . take 7 . words . mconcat . prepareText . unwords $ arg2s if helpMessage then do putStrLn "SYNOPSIS:" putStrLn "" putStrLn "phladiprelioUkr [+c ] [+n] [+d ] [+k ] [+r ] [-t ] [+s ] " putStrLn "" putStrLn "+n \t— if specified then the order of sorting and printing is descending (the reverse one to the default otherwise). " putStrLn "+s \t— the next is the digit from 1 to 4 included. The default one is 2. Influences the result in the case of +d parameter is not given. " putStrLn "+d \t— see: https://web.archive.org/web/20220610171812/https://raw.githubusercontent.com/OleksandrZhabenko/phonetic-languages-data/main/0.20.0.0/56.csv as a format for the file." putStrLn "+r \t— afterwards are several unique digits not greater than 8 in the descending order — the first one is the length of the group of syllables to be considered as a period, the rest — positions of the maximums and minimums. Example: \"543\" means that the line is splitted into groups of 5 syllables starting from the beginning, then the positions of the most maximum (4 = 5 - 1) and the next (smaller) maximum (3 = 4 - 1). If there are no duplicated values then the lowest possible value here is 0, that corresponds to the lowest minimum. If there are duplicates then the lowest value here is the number of the groups of duplicates, e. g. in the sequence 1,6,3,3,4,4,5 that is one group there are two groups of duplicates — with 3 and 4 — and, therefore, the corresponding data after +r should be 7...2. The values less than the lowest minimum are neglected." putStrLn "+c \t— see explanation at the link: https://hackage.haskell.org/package/rhythmic-sequences-0.2.3.1/docs/src/Rhythmicity.MarkerSeqs.html#HashCorrections" putStrLn "-t \t— and afterwards the digit showing the test for \'smoothness\' (to be more accurate - absense or presense of some irregularities that influences the prosody) to be run - if 0 - more extended and strict, if 2 - less strict, more permissive, if 3 - the test for some values expected to be not the maximum nor the minimum ones in the line with no repetitions (the most common case), this option for its greatest values tends to give either more \'irregular\' lines (more jumping-like or wavy combinations) than other ones or more \'regular\' ones - it depends on the distribution of not included into account maximums and minimums; the lines with the minimum values here can be of different kinds but they are not \'stable\'; if 4 - similar to 0, but additionally there are printed two options for every part of test - one that corresponds to minimum value and one that corresponds the maximum value; if 5 - similar to 2, but additionally there are printed two options for every part of test - one that corresponds to minimum value and one that corresponds the maximum value; if 6 - similar to 3, but additionally there are printed two options for every part of test - one that corresponds to minimum value and one that corresponds the maximum value; otherwise - no tests at all (if no digit is here then it is likely that the first word can be used instead and it will be removed from the input)." putStrLn "+k \t— and then the number greater than 2 (better, greater than 12, the default value if not specified is 20). The greater value leads to greater numbers. The number less than some infimum here leads to wiping of some information from the result and, therefore, probably is not the desired behaviour. For most cases the default value is just enough sensible, but you can give it a try for other values." else generalF fileDu numTest hc grpp sylD descending hashStep str1 >> return () bSpecs :: CLSpecifications bSpecs = zip ["+c","+d","+k","+r","+s","-t"] . cycle $ [1] aSpecs :: CLSpecifications aSpecs = [("-h",0),("+n",0)] cSpecs :: CLSpecifications cSpecs = []