-- | -- Module : DobutokO.Poetry.Basic -- Copyright : (c) OleksandrZhabenko 2020 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Helps to order the 7 or less Ukrainian words (or their concatenations) -- to obtain (to some extent) suitable for poetry or music text. module DobutokO.Poetry.Basic ( Uniqueness -- * Main functions , uniqNPoeticalN , uniqNPoeticalVN -- * Additional functions , uniqMaxPoeticalGNV , uniqInMaxPoeticalN -- * On one line output , uniqInMaxPoeticalNLine , uniqNPoeticalNLine -- * With all the norms used , uniqInMaxPoeticalNL , uniqInMaxPoeticalNLineL , uniqNPoeticalNL , uniqNPoeticalNLineL , uniqNPoeticalVNL , uniqMaxPoeticalGNVL ) where import Data.Char (isPunctuation) import qualified Data.Vector as V import DobutokO.Poetry.Auxiliary type Uniqueness = ([Int],V.Vector Int,String) -- | Prints the maximum element with respect of the @k@ norms (the most significant of which is the rightest one, then to the left less significant etc.), -- which is given as the first argument. The last norm is the first element in the 'V.Vector' of norms (@[Int] -> Int@). uniqInMaxPoeticalN :: Int -> V.Vector ([Int] -> Int) -> V.Vector Uniqueness -> IO (V.Vector Uniqueness) uniqInMaxPoeticalN k vN v = do let uniq = uniqMaxPoeticalGNV k vN v let fsT = (\(ys,_,_) -> ys) uniq putStr (filter (not . isPunctuation) . lastFrom3 $ uniq) >> putStrLn "" return . V.filter (\(xs,_,_) -> xs /= fsT) $ v -- | Variant of 'uniqInMaxPoticalN' where all the elements in the norms 'V.Vector' are used as norms from right to left. uniqInMaxPoeticalNL :: V.Vector ([Int] -> Int) -> V.Vector Uniqueness -> IO (V.Vector Uniqueness) uniqInMaxPoeticalNL vN = uniqInMaxPoeticalN (V.length vN) vN {-# INLINE uniqInMaxPoeticalNL #-} -- | Generalized variant of the 'uniqInMaxPoeticalN' with usage of the several norms and all the information is printed on the same line. uniqInMaxPoeticalNLine :: Int -> V.Vector ([Int] -> Int) -> V.Vector Uniqueness -> IO (V.Vector Uniqueness) uniqInMaxPoeticalNLine k vN v = do let uniq = uniqMaxPoeticalGNV k vN v let fsT = (\(ys,_,_) -> ys) uniq putStr (filter (not . isPunctuation) . lastFrom3 $ uniq) >> putStr " " return . V.filter (\(xs,_,_) -> xs /= fsT) $ v -- | Variant of 'uniqInMaxPoticalNLine' where all the elements in the norms 'V.Vector' are used as norms from right to left. uniqInMaxPoeticalNLineL :: V.Vector ([Int] -> Int) -> V.Vector Uniqueness -> IO (V.Vector Uniqueness) uniqInMaxPoeticalNLineL vN = uniqInMaxPoeticalNLine (V.length vN) vN {-# INLINE uniqInMaxPoeticalNLineL #-} -- | Prints @n@ (given as the first argument) maximum elements with respect to the several norms (their quantity is the second argument) starting -- from the right to the left. The last norm is the first element in the 'V.Vector' of norms (@[Int] -> Int@). uniqNPoeticalN :: Int -> Int -> V.Vector ([Int] -> Int) -> V.Vector Uniqueness -> IO () uniqNPoeticalN n k vN v | n == 0 = return () | compare (V.length v) n == LT = V.mapM_ (\x -> putStr (filter (not . isPunctuation) . lastFrom3 $ x) >> putStrLn "" ) v | otherwise = (uniqInMaxPoeticalN k vN v >>= uniqNPoeticalN (n - 1) k vN) -- | Variant of 'uniqNPoeticalN' where all the elements in the norms 'V.Vector' are used as norms from right to left. uniqNPoeticalNL :: Int -> V.Vector ([Int] -> Int) -> V.Vector Uniqueness -> IO () uniqNPoeticalNL n vN = uniqNPoeticalN n (V.length vN) vN {-# INLINE uniqNPoeticalNL #-} -- | Variant of the 'uniqNPoeticalN' with its output being printed on the same line. uniqNPoeticalNLine :: Int -> Int -> V.Vector ([Int] -> Int) -> V.Vector Uniqueness -> IO () uniqNPoeticalNLine n k vN v | n == 0 = putStrLn "" | compare (V.length v) n == LT = V.mapM_ (\x -> putStr (filter (not . isPunctuation) . lastFrom3 $ x) >> putStr " " ) v >> putStrLn "" | otherwise = (uniqInMaxPoeticalNLine k vN v >>= uniqNPoeticalNLine (n - 1) k vN) -- | Variant of 'uniqNPoeticalNLine' where all the elements in the norms 'V.Vector' are used as norms from right to left. uniqNPoeticalNLineL :: Int -> V.Vector ([Int] -> Int) -> V.Vector Uniqueness -> IO () uniqNPoeticalNLineL n vN = uniqNPoeticalNLine n (V.length vN) vN {-# INLINE uniqNPoeticalNLineL #-} -- | Prints @n@ (given as the first argument) maximum elements with respect to the several norms (their quantity is the second argument) starting -- from the right to the left. The last norm is the first element in the 'V.Vector' of norms (@[Int] -> Int@). Contrary to its pair function -- 'uniqNPoeticalN' returns then the rest of the given 'V.Vector' 'Uniqueness' after filtering the printed elements 'String'. uniqNPoeticalVN :: Int -> Int -> V.Vector ([Int] -> Int) -> V.Vector Uniqueness -> IO (V.Vector Uniqueness) uniqNPoeticalVN n k vN v | n == 0 || compare (V.length v) n == LT = return v | otherwise = (uniqInMaxPoeticalN k vN v >>= uniqNPoeticalVN (n - 1) k vN) -- | Variant of 'uniqNPoeticalVN' where all the elements in the norms 'V.Vector' are used as norms from right to left. uniqNPoeticalVNL :: Int -> V.Vector ([Int] -> Int) -> V.Vector Uniqueness -> IO (V.Vector Uniqueness) uniqNPoeticalVNL n vN = uniqNPoeticalVN n (V.length vN) vN {-# INLINE uniqNPoeticalVNL #-} -- | The function evaluates the 'V.Vector' of 'Uniqueness' elements to retrieve the possibly maximum element in it with respect to the order -- and significance (principality) of the norms being evaluated. The most significant and principal is the norm, which index in the 'V.Vector' of them is -- the 'Int' argument of the function minus 1, then less significant is the next to the left norm and so on. Is similar to 'DobutokO.Poetry.uniqMaxPoeticalGN' -- function. uniqMaxPoeticalGNV :: Int -> V.Vector ([Int] -> Int) -> V.Vector Uniqueness -> Uniqueness uniqMaxPoeticalGNV k vN vM | compare k (V.length vN) == GT = error "DobutokO.Poetry.Basic.uniqMaxPoeticalGNV: undefined for that amount of norms. " | compare k 0 == GT = let maxK = V.maximumBy (\(_,vN0,_) (_,vN1,_) -> compare (V.unsafeIndex vN0 (k - 1)) (V.unsafeIndex vN1 (k - 1))) vM vK = V.filter (\(_,vN2,_) -> V.unsafeIndex vN2 (k - 1) == ((\(_,vNk,_) -> V.unsafeIndex vNk (k - 1)) maxK)) vM in uniqMaxPoeticalGNV (k - 1) (V.unsafeSlice 0 (V.length vN - 1) vN) vK | otherwise = V.maximumBy (\(_,vN0,_) (_,vN1,_) -> compare (V.unsafeIndex vN0 0) (V.unsafeIndex vN1 0)) vM -- | Variant of 'uniqMaxPoeticalGNV' where all the elements in the norms 'V.Vector' are used as norms from right to left. uniqMaxPoeticalGNVL :: V.Vector ([Int] -> Int) -> V.Vector Uniqueness -> Uniqueness uniqMaxPoeticalGNVL vN = uniqMaxPoeticalGNV (V.length vN) vN {-# INLINE uniqMaxPoeticalGNVL #-}