-- | -- Module : Main -- Copyright : (c) OleksandrZhabenko 2020 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Analyzes a poetic text in Ukrainian, for every line prints statistic data and -- then for the whole poem prints the hypothesis evaluation information. module Main where import qualified Data.Vector as V import String.Languages.UniquenessPeriods.Vector import Languages.UniquenessPeriods.Vector.General.Debug import Languages.UniquenessPeriods.Vector.Properties import Melodics.Ukrainian import System.Environment import Languages.Phonetic.Ukrainian.PrepareText import Languages.UniquenessPeriods.Vector.Data import Languages.UniquenessPeriods.Vector.Auxiliary import Languages.UniquenessPeriods.Vector.StrictV import Numeric main :: IO () main = do args <- getArgs let file = concat . take 1 $ args contents <- readFile file let flines = filter (not . null . filter isUkrainian) . prepareText $ contents data3 <- mapM (\ts -> do let maxE = (\k -> if k == 0 then 1 else k) . (\rs -> if null rs then 0 else head rs) . firstFrom3 . maximumElBy 1 (V.singleton (oneProperty)) $ UL2 ([],uniquenessVariants2GN " 01-" (V.singleton (oneProperty)) (uniquenessPeriodsVector3 " 01-" . aux0 . convertToProperUkrainian) (justOneValue2Property . diverse2) $ ts) minE = (\k -> if k == 0 then 1 else k) . abs . (\rs -> if null rs then 0 else head rs) . firstFrom3 . maximumElBy 1 (V.singleton (oneProperty)) $ UL2 ([],uniquenessVariants2GN " 01-" (V.singleton (oneProperty)) (uniquenessPeriodsVector3 " 01-" . aux0 . convertToProperUkrainian) (justOneValue2Property . negate . diverse2) $ ts) data2 = (\k -> if k == 0 then 1 else k) . diverse2 . uniquenessPeriodsVector3 " 01-" . aux0 . convertToProperUkrainian $ ts let ratio = 2.0 * fromIntegral data2 / fromIntegral (minE + maxE) putStrLn $ show (minE::Int) ++ "\t" ++ show (data2::Int) ++ "\t" ++ show (maxE::Int) ++ "\t" ++ showFFloat (Just 3) (fromIntegral data2 / fromIntegral minE) "\t" ++ showFFloat (Just 3) (fromIntegral maxE / fromIntegral data2) "\t" ++ showFFloat (Just 3) ratio "\t" ++ show (length . words $ ts) return ratio) $ flines let mean1 = sum data3 / fromIntegral (length data3) putStrLn $ showFFloat (Just 3) mean1 "+-" ++ showFFloat (Just 3) (sqrt ((sum (map (**2) data3) / fromIntegral (length data3)) - mean1 ** 2)) "" isUkrainian :: Char -> Bool isUkrainian x | x == '\x0404' || (x >= '\x0406' && x <= '\x0407') || (x >= '\x0410' && x <= '\x0429') || x == '\x042C' || (x >= '\x042E' && x <= '\x0449') || x == '\x044C' || (x >= '\x044E' && x <= '\x044F') || x == '\x0454' || (x >= '\x0456' && x <= '\x0457') = True | otherwise = False