{-# LANGUAGE NoImplicitPrelude #-} module Main where import GHC.Base import GHC.Num ((-)) import Text.Show (show) import Text.Read (readMaybe) import System.IO (putStrLn, FilePath) import Rhythmicity.MarkerSeqs hiding (id) import Rhythmicity.BasicF import Data.List import Data.Maybe (fromMaybe) import Data.Tuple (fst,snd) import Phladiprelio.Ukrainian.PrepareText import Phladiprelio.Ukrainian.Syllable import Phladiprelio.Ukrainian.SyllableDouble import System.Environment (getArgs) import GHC.Int (Int8) import CLI.Arguments import CLI.Arguments.Get import CLI.Arguments.Parsing import Phladiprelio.Ukrainian.ReadDurations generalF :: FilePath -> HashCorrections -> (Int8,[Int8]) -> Int -> String -> IO [()] generalF file hc (grps,mxms) k rs = do syllableDurationsDs <- readSyllableDurations file mapM (\(x,y) -> putStrLn (show x `mappend` (' ':y))) . sortOn id . map ((\xss -> (f syllableDurationsDs xss, xss)) . unwords) . permutations . words $ rs where f syllableDurationsDs = sum . countHashesG 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 main :: IO () main = do args <- getArgs let (argsB, arg2s) = takeBsR bSpecs args (argsA, _) = takeAsR aSpecs 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 helpMessage = oneA "-h" argsA str1 = unwords . take 7 . words . mconcat . prepareText . unwords $ arg2s if helpMessage then do putStrLn "Synopsis:" putStrLn "phladiprelioUkr [+c ] [+d ] [+r ] [+s ] " putStrLn "" putStrLn "+s — 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 — 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 — 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 — see explanation at the link: https://hackage.haskell.org/package/rhythmic-sequences-0.2.3.1/docs/src/Rhythmicity.MarkerSeqs.html#HashCorrections" else generalF fileDu hc grpp sylD str1 >> return () bSpecs :: CLSpecifications bSpecs = zip ["+c","+d","+r","+s"] . cycle $ [1] aSpecs :: CLSpecifications aSpecs = [("-h",0)] cSpecs :: CLSpecifications cSpecs = []