-- | -- Module : DobutokO.Poetry -- 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 ( -- * Main functions uniq10Poetical4 , uniq10Poetical5 , uniq10PoeticalG , uniqNPoeticalG , uniqNPoeticalGN , uniqNPoeticalVGN -- * Additional functions , uniquenessVariantsGN , uniqMaxPoeticalGN -- * Generalized variants -- ** Main ones , uniqNPoetical2GN , uniqNPoetical2VGN , uniqNPoeticalUGN_ , uniqNPoeticalUGN , uniqNPoeticalUGN51_ , uniqNPoeticalUGN51 -- ** Additional functions , uniqMaxPoetical2GN -- * On one line output , uniqNPoetical2GNLine -- * With all the norms used , uniqMaxPoeticalGNL , uniqNPoeticalGNL , uniqNPoeticalVGNL , uniqMaxPoetical2GNL , uniqNPoetical2GNL , uniqNPoetical2GNLineL , uniqNPoetical2VGNL , uniqNPoeticalUGNL_ , uniqNPoeticalUGNL ) where import Data.Char (isPunctuation) import qualified Data.Vector as V import Data.List ((\\)) import MMSyn7s import DobutokO.Poetry.Norms import DobutokO.Poetry.Auxiliary import DobutokO.Poetry.UniquenessPeriodsG import DobutokO.Poetry.StrictV import DobutokO.Poetry.Basic -- | Returns the 'V.Vector' of all possible permutations of the 'String' that represent the Ukrainian text and the linked information with them for -- analysis with usage of several norms (instead of one). They constitute a 'V.Vector' of functions -- @norm :: [Int] -> Int@. So the inner vector in the each resulting 'Uniqueness' has the same length as the vector of norms. uniquenessVariantsGN :: V.Vector ([Int] -> Int) -> String -> V.Vector Uniqueness uniquenessVariantsGN vN = uniquenessVariants2GN vN (uniquenessPeriods) {-# INLINE uniquenessVariantsGN #-} -- | A variant of the 'uniqMaxPoetical2GN' with the several norms given as a 'V.Vector' of functions and an 'Int' parameter. The function evaluates -- the generated '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. uniqMaxPoeticalGN :: Int -> V.Vector ([Int] -> Int) -> String -> Uniqueness uniqMaxPoeticalGN k vN = uniqMaxPoetical2GN k vN (uniquenessPeriods) {-# INLINE uniqMaxPoeticalGN #-} -- | Variant of 'uniqMaxPoeticalGN' where all the elements in the norms 'V.Vector' are used as norms from right to left. uniqMaxPoeticalGNL :: V.Vector ([Int] -> Int) -> String -> Uniqueness uniqMaxPoeticalGNL vN = uniqMaxPoeticalGN (V.length vN) vN {-# INLINE uniqMaxPoeticalGNL #-} -- | A variant of the 'uniqNPoeticalGN' with only one norm. uniqNPoeticalG :: Int -> ([Int] -> Int) -> String -> IO () uniqNPoeticalG n g = uniqNPoeticalGN n 1 (V.singleton g) {-# INLINE uniqNPoeticalG #-} -- | A variant of the 'uniqNPoeticalG' function with the @n@ equal to 10. uniq10PoeticalG :: ([Int] -> Int) -> String -> IO () uniq10PoeticalG = uniqNPoeticalG 10 {-# INLINE uniq10PoeticalG #-} -- | A variant of 'uniq10PoeticalG' with the 'norm4' applied. The list is (according to some model, not universal, but a reasonable one in the most cases) the -- most suitable for intonation changing and, therefore, for the accompaniment of the highly changable or variative melody. uniq10Poetical4 :: String -> IO () uniq10Poetical4 = uniq10PoeticalG norm4 {-# INLINE uniq10Poetical4 #-} -- | A variant of 'uniq10PoeticalG' with the 'norm5' applied. The list is (according to some model, not universal, but a reasonable one in the most cases) the -- most suitable for rhythmic speech and two-syllabilistic-based poetry. Therefore, it can be used to create a poetic composition or to emphasize some -- thoughts. uniq10Poetical5 :: String -> IO () uniq10Poetical5 = uniq10PoeticalG norm5 {-# INLINE uniq10Poetical5 #-} -- | 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 #-} -- | A variant of the 'uniqNPoetical2GN' with the conversion (\"uniquenessPeriods\" function) function 'uniquenessPeriods'. uniqNPoeticalGN :: Int -> Int -> V.Vector ([Int] -> Int) -> String -> IO () uniqNPoeticalGN n k vN = uniqNPoetical2GN n k vN (uniquenessPeriods) {-# INLINE uniqNPoeticalGN #-} -- | Variant of 'uniqNPoeticalGN' where all the elements in the norms 'V.Vector' are used as norms from right to left. uniqNPoeticalGNL :: Int -> V.Vector ([Int] -> Int) -> String -> IO () uniqNPoeticalGNL n vN = uniqNPoetical2GNL n vN (uniquenessPeriods) {-# INLINE uniqNPoeticalGNL #-} -- | Generalized variant of the 'uniqNPoeticalVG' with usage of several norms. uniqNPoeticalVGN :: Int -> Int -> V.Vector ([Int] -> Int) -> String -> IO (V.Vector Uniqueness) uniqNPoeticalVGN n k vN = uniqNPoetical2VGN n k vN (uniquenessPeriods) {-# INLINE uniqNPoeticalVGN #-} -- | Variant of 'uniqNPoeticalVGN' where all the elements in the norms 'V.Vector' are used as norms from right to left. uniqNPoeticalVGNL :: Int -> V.Vector ([Int] -> Int) -> String -> IO (V.Vector Uniqueness) uniqNPoeticalVGNL n vN = uniqNPoetical2VGN n (V.length vN) vN (uniquenessPeriods) {-# INLINE uniqNPoeticalVGNL #-} -- | The function evaluates -- the generated '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. uniqMaxPoetical2GN :: Int -> V.Vector ([Int] -> Int) -> (String -> [Int]) -> String -> Uniqueness uniqMaxPoetical2GN k vN g xs | compare k (V.length vN) == GT = error "DobutokO.Poetry.uniqMaxPoetical2GN: undefined for that amount of norms. " | compare k 0 == GT = let vM = uniquenessVariants2GN vN g xs 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)) . uniquenessVariantsGN vN $ xs -- | Variant of 'uniqMaxPoetical2GN' where all the elements in the norms 'V.Vector' are used as norms from right to left. uniqMaxPoetical2GNL :: V.Vector ([Int] -> Int) -> (String -> [Int]) -> String -> Uniqueness uniqMaxPoetical2GNL vN = uniqMaxPoetical2GN (V.length vN) vN {-# INLINE uniqMaxPoetical2GNL #-} -- | Prints @n@ (given as the first 'Int' argument) maximum elements with respect to the several norms (their quantity is the second 'Int' argument) starting -- from the right to the left. The last norm is the first element in the 'V.Vector' of norms (@[Int] -> Int@). uniqNPoetical2GN :: Int -> Int -> V.Vector ([Int] -> Int) -> (String -> [Int]) -> String -> IO () uniqNPoetical2GN n k vN g xs | n == 0 = return () | otherwise = do let v = uniquenessVariants2GN vN g xs if compare (V.length v) n == LT then V.mapM_ (\x -> putStr ((filter (not . isPunctuation) . lastFrom3 $ x)) >> putStrLn "" ) v else (uniqInMaxPoeticalN k vN v >>= uniqNPoeticalN (n - 1) k vN) -- | Variant of 'uniqNPoetical2GN' where all the elements in the norms 'V.Vector' are used as norms from right to left. uniqNPoetical2GNL :: Int -> V.Vector ([Int] -> Int) -> (String -> [Int]) -> String -> IO () uniqNPoetical2GNL n vN = uniqNPoetical2GN n (V.length vN) vN {-# INLINE uniqNPoetical2GNL #-} -- | A variant of the 'uniqNPoetical2GN', but prints its output on the same line. uniqNPoetical2GNLine :: Int -> Int -> V.Vector ([Int] -> Int) -> (String -> [Int]) -> String -> IO () uniqNPoetical2GNLine n k vN g xs | n == 0 = putStrLn "" | otherwise = do let v = uniquenessVariants2GN vN g xs if compare (V.length v) n == LT then V.mapM_ (\x -> putStr ((filter (not . isPunctuation) . lastFrom3 $ x)) >> putStr " " ) v >> putStrLn "" else (uniqInMaxPoeticalNLine k vN v >>= uniqNPoeticalNLine (n - 1) k vN) -- | Variant of 'uniqNPoetical2GNLine' where all the elements in the norms 'V.Vector' are used as norms from right to left. uniqNPoetical2GNLineL :: Int -> V.Vector ([Int] -> Int) -> (String -> [Int]) -> String -> IO () uniqNPoetical2GNLineL n vN = uniqNPoetical2GNLine n (V.length vN) vN {-# INLINE uniqNPoetical2GNLineL #-} -- | Prints @n@ (given as the first 'Int' argument) maximum elements with respect to the several norms (their quantity is the second 'Int' 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 -- 'uniqNPoetical2GN' returns then the rest of the given 'V.Vector' 'Uniqueness' after filtering the printed elements 'String'. uniqNPoetical2VGN :: Int -> Int -> V.Vector ([Int] -> Int) -> (String -> [Int]) -> String -> IO (V.Vector Uniqueness) uniqNPoetical2VGN n k vN g xs | n == 0 = return V.empty | otherwise = do let v = uniquenessVariants2GN vN g xs if compare (V.length v) n == LT then return v else uniqNPoeticalVN n k vN v -- | Variant of 'uniqNPoetical2VGN' where all the elements in the norms 'V.Vector' are used as norms from right to left. uniqNPoetical2VGNL :: Int -> V.Vector ([Int] -> Int) -> (String -> [Int]) -> String -> IO (V.Vector Uniqueness) uniqNPoetical2VGNL n vN = uniqNPoetical2VGN n (V.length vN) vN {-# INLINE uniqNPoetical2VGNL #-} -- | Variant of the 'uniqNPoetical2GN', which uses as a function 'uniquenessPeriods2' with the first argument equal to the first 'Int' argument. uniqNPoeticalUGN_ :: Int -> Int -> Int -> V.Vector ([Int] -> Int) -> String -> IO () uniqNPoeticalUGN_ x n k vN = uniqNPoetical2GN n k vN (uniquenessPeriods2 x) {-# INLINE uniqNPoeticalUGN_ #-} -- | Variant of 'uniqNPoeticalUGN_' where all the elements in the norms 'V.Vector' are used as norms from right to left. uniqNPoeticalUGNL_ :: Int -> Int -> V.Vector ([Int] -> Int) -> String -> IO () uniqNPoeticalUGNL_ x n vN = uniqNPoetical2GNL n vN (uniquenessPeriods2 x) {-# INLINE uniqNPoeticalUGNL_ #-} -- | Variant of the 'uniqNPoetical2VGN', which uses as a function 'uniquenessPeriods2' with the first argument equal to the first 'Int' argument. uniqNPoeticalUGN :: Int -> Int -> Int -> V.Vector ([Int] -> Int) -> String -> IO (V.Vector Uniqueness) uniqNPoeticalUGN x n k vN = uniqNPoetical2VGN n k vN (uniquenessPeriods2 x) {-# INLINE uniqNPoeticalUGN #-} -- | Variant of 'uniqNPoeticalUGN' where all the elements in the norms 'V.Vector' are used as norms from right to left. uniqNPoeticalUGNL :: Int -> Int -> V.Vector ([Int] -> Int) -> String -> IO (V.Vector Uniqueness) uniqNPoeticalUGNL x n vN = uniqNPoetical2VGN n (V.length vN) vN (uniquenessPeriods2 x) {-# INLINE uniqNPoeticalUGNL #-} -- | Variant of the 'uniqNPoeticalUGN_', which uses as a single norm 'norm51'. uniqNPoeticalUGN51_ :: Int -> Int -> String -> IO () uniqNPoeticalUGN51_ x n = uniqNPoeticalUGN_ x n 1 (V.singleton norm51) {-# INLINE uniqNPoeticalUGN51_ #-} -- | Variant of the 'uniqNPoeticalUGN', which uses as a single norm 'norm51'. uniqNPoeticalUGN51 :: Int -> Int -> String -> IO (V.Vector Uniqueness) uniqNPoeticalUGN51 x n = uniqNPoeticalUGN x n 1 (V.singleton norm51) {-# INLINE uniqNPoeticalUGN51 #-}