-- | -- Module : DobutokO.Poetry.PrependAppend -- 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. -- In contrast to the the same named functions from the 'DobutokO.Poetry' module each its function uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. {-# LANGUAGE BangPatterns #-} module DobutokO.Poetry.PrependAppend ( -- * Main functions uniq10Poetical4 , uniq10Poetical5 , uniq10PoeticalG , uniqNPoeticalG , uniqNPoeticalGN , uniqNPoeticalN , uniqNPoeticalVN , uniqNPoeticalVGN -- * Additional functions , uniquenessVariantsGN , uniqMaxPoeticalGN , uniqMaxPoeticalGNV , uniqInMaxPoeticalN -- * Generalized variants -- ** Main ones , uniqNPoetical2GN , uniqNPoetical2VGN , uniqNPoeticalUGN_ , uniqNPoeticalUGN , uniqNPoeticalUGN51_ , uniqNPoeticalUGN51 -- ** Additional functions , uniqMaxPoetical2GN -- * On one line output , uniqInMaxPoeticalNLine , uniqNPoeticalNLine , uniqNPoetical2GNLine -- * With all the norms used , uniqMaxPoeticalGNL , uniqInMaxPoeticalNL , uniqInMaxPoeticalNLineL , uniqNPoeticalNL , uniqNPoeticalNLineL , uniqNPoeticalVNL , uniqNPoeticalGNL , uniqNPoeticalVGNL , uniqMaxPoetical2GNL , uniqMaxPoeticalGNVL , 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 -- | Generalization of the 'uniquenessVariantsG' 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. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniquenessVariantsGN :: String -> String -> V.Vector ([Int] -> Int) -> String -> V.Vector Uniqueness uniquenessVariantsGN !ts !us vN = uniquenessVariants2GNP ts us vN (uniquenessPeriods) {-# INLINE uniquenessVariantsGN #-} -- | Generalized variant of the 'uniqMaxPoeticalG' 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. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqMaxPoeticalGN :: String -> String -> Int -> V.Vector ([Int] -> Int) -> String -> Uniqueness uniqMaxPoeticalGN !ts !us k vN = uniqMaxPoetical2GN ts us 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. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqMaxPoeticalGNL :: String -> String -> V.Vector ([Int] -> Int) -> String -> Uniqueness uniqMaxPoeticalGNL !ts !us vN = uniqMaxPoeticalGN ts us (V.length vN) vN {-# INLINE uniqMaxPoeticalGNL #-} -- | A variant of the 'uniqNPoeticalGN' with only one norm. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqNPoeticalG :: String -> String -> Int -> ([Int] -> Int) -> String -> IO () uniqNPoeticalG !ts !us n g = uniqNPoeticalGN ts us n 1 (V.singleton g) {-# INLINE uniqNPoeticalG #-} -- | A variant of the 'uniqNPoeticalG' function with the @n@ equal to 10. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniq10PoeticalG :: String -> String -> ([Int] -> Int) -> String -> IO () uniq10PoeticalG !ts !us = uniqNPoeticalG ts us 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. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniq10Poetical4 :: String -> String -> String -> IO () uniq10Poetical4 !ts !us = uniq10PoeticalG ts us 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. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniq10Poetical5 :: String -> String -> String -> IO () uniq10Poetical5 !ts !us = uniq10PoeticalG ts us norm5 {-# INLINE uniq10Poetical5 #-} -- | A variant of the 'uniqNPoetical2GN' with the conversion (\"uniquenessPeriods\" function) function 'uniquenessPeriods'. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqNPoeticalGN :: String -> String -> Int -> Int -> V.Vector ([Int] -> Int) -> String -> IO () uniqNPoeticalGN !ts !us n k vN = uniqNPoetical2GN ts us 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. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqNPoeticalGNL :: String -> String -> Int -> V.Vector ([Int] -> Int) -> String -> IO () uniqNPoeticalGNL !ts !us n vN = uniqNPoetical2GNL ts us n vN (uniquenessPeriods) {-# INLINE uniqNPoeticalGNL #-} -- | Generalized variant of the 'uniqNPoeticalVG' with usage of several norms. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqNPoeticalVGN :: String -> String -> Int -> Int -> V.Vector ([Int] -> Int) -> String -> IO (V.Vector Uniqueness) uniqNPoeticalVGN !ts !us n k vN = uniqNPoetical2VGN ts us 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. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqNPoeticalVGNL :: String -> String -> Int -> V.Vector ([Int] -> Int) -> String -> IO (V.Vector Uniqueness) uniqNPoeticalVGNL !ts !us n vN = uniqNPoetical2VGN ts us 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. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqMaxPoetical2GN :: String -> String -> Int -> V.Vector ([Int] -> Int) -> (String -> [Int]) -> String -> Uniqueness uniqMaxPoetical2GN !ts !us k vN g !xs | compare k (V.length vN) == GT = error "DobutokO.Poetry.PrependAppend.uniqMaxPoetical2GN: undefined for that amount of norms. " | compare k 0 == GT = let vM = uniquenessVariants2GNP ts us 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 ts us vN $ xs -- | Variant of 'uniqMaxPoetical2GN' where all the elements in the norms 'V.Vector' are used as norms from right to left. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqMaxPoetical2GNL :: String -> String -> V.Vector ([Int] -> Int) -> (String -> [Int]) -> String -> Uniqueness uniqMaxPoetical2GNL !ts !us vN = uniqMaxPoetical2GN ts us (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@). -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqNPoetical2GN :: String -> String -> Int -> Int -> V.Vector ([Int] -> Int) -> (String -> [Int]) -> String -> IO () uniqNPoetical2GN !ts !us n k vN g !xs | n == 0 = return () | otherwise = do let v = uniquenessVariants2GNP ts us vN g xs if compare (V.length v) n == LT then V.mapM_ (\x -> putStrLn ((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. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqNPoetical2GNL :: String -> String -> Int -> V.Vector ([Int] -> Int) -> (String -> [Int]) -> String -> IO () uniqNPoetical2GNL !ts !us n vN = uniqNPoetical2GN ts us n (V.length vN) vN {-# INLINE uniqNPoetical2GNL #-} -- | Generalized variant of the 'uniqNPoeticalG' with usage of the several norms, but prints its output on the same line. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqNPoetical2GNLine :: String -> String -> Int -> Int -> V.Vector ([Int] -> Int) -> (String -> [Int]) -> String -> IO () uniqNPoetical2GNLine !ts !us n k vN g !xs | n == 0 = putStrLn "" | otherwise = do let v = uniquenessVariants2GNP ts us 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. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqNPoetical2GNLineL :: String -> String -> Int -> V.Vector ([Int] -> Int) -> (String -> [Int]) -> String -> IO () uniqNPoetical2GNLineL !ts !us n vN = uniqNPoetical2GNLine ts us 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'. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqNPoetical2VGN :: String -> String -> Int -> Int -> V.Vector ([Int] -> Int) -> (String -> [Int]) -> String -> IO (V.Vector Uniqueness) uniqNPoetical2VGN !ts !us n k vN g !xs | n == 0 = return V.empty | otherwise = do let v = uniquenessVariants2GNP ts us 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. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqNPoetical2VGNL :: String -> String -> Int -> V.Vector ([Int] -> Int) -> (String -> [Int]) -> String -> IO (V.Vector Uniqueness) uniqNPoetical2VGNL !ts !us n vN = uniqNPoetical2VGN ts us 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. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqNPoeticalUGN_ :: String -> String -> Int -> Int -> Int -> V.Vector ([Int] -> Int) -> String -> IO () uniqNPoeticalUGN_ !ts !us x n k vN = uniqNPoetical2GN ts us 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. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqNPoeticalUGNL_ :: String -> String -> Int -> Int -> V.Vector ([Int] -> Int) -> String -> IO () uniqNPoeticalUGNL_ !ts !us x n vN = uniqNPoetical2GNL ts us 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. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqNPoeticalUGN :: String -> String -> Int -> Int -> Int -> V.Vector ([Int] -> Int) -> String -> IO (V.Vector Uniqueness) uniqNPoeticalUGN !ts !us x n k vN = uniqNPoetical2VGN ts us 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. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqNPoeticalUGNL :: String -> String -> Int -> Int -> V.Vector ([Int] -> Int) -> String -> IO (V.Vector Uniqueness) uniqNPoeticalUGNL !ts !us x n vN = uniqNPoetical2VGN ts us n (V.length vN) vN (uniquenessPeriods2 x) {-# INLINE uniqNPoeticalUGNL #-} -- | Variant of the 'uniqNPoeticalUGN_', which uses as a single norm 'norm51'. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqNPoeticalUGN51_ :: String -> String -> Int -> Int -> String -> IO () uniqNPoeticalUGN51_ !ts !us x n = uniqNPoeticalUGN_ ts us x n 1 (V.singleton norm51) {-# INLINE uniqNPoeticalUGN51_ #-} -- | Variant of the 'uniqNPoeticalUGN', which uses as a single norm 'norm51'. -- In contrast to the the same named function from the 'DobutokO.Poetry' module uses in the processment prepending and appending 'String' given -- as the first two arguments. The first one is prepended and the second one is appended to the processed 'String' to be processed with it. -- This allows to create more connection with the previous and postpending text. uniqNPoeticalUGN51 :: String -> String -> Int -> Int -> String -> IO (V.Vector Uniqueness) uniqNPoeticalUGN51 !ts !us x n = uniqNPoeticalUGN ts us x n 1 (V.singleton norm51) {-# INLINE uniqNPoeticalUGN51 #-}