-- | -- Module : Languages.UniquenessPeriods.Vector.General.Debug -- Copyright : (c) OleksandrZhabenko 2020 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Generalization of the functionality of the DobutokO.Poetry.General.Debug -- module from the @dobutokO-poetry-general-languages@ package. module Languages.UniquenessPeriods.Vector.General.Debug where import Data.Maybe (fromJust) import Data.Print.Info import System.IO import qualified Data.Vector as V import Languages.UniquenessPeriods.Vector.Auxiliary import Languages.UniquenessPeriods.Vector.StrictV import Languages.UniquenessPeriods.Vector.Data -- | The function evaluates the 'V.Vector' of 'UniquenessG1' @a@ @b@ elements (related with the third argument) to retrieve the possibly maximum element -- in it with respect to the order and significance (principality) of the \"properties\" (represented as the functions @f :: [b] -> b@) being evaluated. -- The most significant and principal is the \"property\", which index in the 'V.Vector' of them is the 'Int' argument (so it is the first one) of the -- function minus 1, then less significant is the next to the left \"property\" and so on. -- The predefined library \"properties\" or related to them functions can be found in the package @uniqueness-periods-vector-properties@. uniqMaxPoeticalGNV :: (Eq a, Ord b) => Int -- ^ The quantity of the represented as functions \"properties\" to be applied from the second argument. The order is from the right to the left. -> V.Vector ([b] -> b) -- ^ 'V.Vector' of the represented as functions \"properties\" to be applied consequently. -> UniqG a b -- ^ The data to be analyzed. -> UniquenessG1 a b -- ^ The maximum element in respect with the given parameters. uniqMaxPoeticalGNV k vN y | compare k (V.length vN) == GT = error "Languages.UniquenessPeriods.Vector.General.Debug.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))) . snd . get2 $ y vK = V.filter (\(_,vN2,_) -> V.unsafeIndex vN2 (k - 1) == ((\(_,vNk,_) -> V.unsafeIndex vNk (k - 1)) maxK)) . snd . get2 $ y in if isU y then uniqMaxPoeticalGNV (k - 1) (V.unsafeSlice 0 (V.length vN - 1) vN) (U vK) else uniqMaxPoeticalGNV (k - 1) (V.unsafeSlice 0 (V.length vN - 1) vN) (UL (fromJust . fst . get2 $ y,vK)) | otherwise = V.maximumBy (\(_,vN0,_) (_,vN1,_) -> compare (V.unsafeIndex vN0 0) (V.unsafeIndex vN1 0)) . snd . get2 $ y {-# INLINE uniqMaxPoeticalGNV #-} -- | Inspired by appendS16LEFile function from Melodics.Ukrainian module from @mmsyn6ukr@ package. toFile :: FilePath -- ^ The 'FilePath' to the file to be written in the 'AppendMode' (actually appended with) the information output. -> [String] -- ^ Each 'String' is appended on the new line to the file. -> IO () toFile file xss = withFile file AppendMode (\hdl -> do hClose hdl closedHdl <- hIsClosed hdl if closedHdl then openFile file AppendMode >>= \hdl -> mapM_ (hPutStrLn hdl) xss else error "The handle is not closed!" hClose hdl) -- | Is used to print output specified to the 'stdout' or to the 'FilePath' specified as the inner argument in the 'Info2' parameter. printHelp :: (Show a, Show b) => Info2 -- ^ A parameter to control the predefined behaviour of the printing. The 'I1' branch prints to the 'stdout' and the 'I2' - to the file. -> UniquenessG1 a b -- ^ The element, for which the information is printed. -> IO () printHelp info uni | isI1 info = case (\(I1 x) -> x) info of A -> putStr "" -- nothing is printed B -> mapM_ putStrLn [show . lastFrom3 $ uni] C -> mapM_ putStrLn [show . firstFrom3 $ uni] D -> mapM_ putStrLn [show . secondFrom3 $ uni] E -> mapM_ putStrLn [show . lastFrom3 $ uni, show . firstFrom3 $ uni] F -> mapM_ putStrLn [show . lastFrom3 $ uni, show . secondFrom3 $ uni] G -> mapM_ putStrLn [show . firstFrom3 $ uni, show . secondFrom3 $ uni] _ -> mapM_ putStrLn [show . lastFrom3 $ uni, show . firstFrom3 $ uni, show. secondFrom3 $ uni] -- the most verbose output | otherwise = case (\(I2 x) -> x) info of Af xs -> putStr "" -- nothing is printed Bf xs -> toFile xs [show . lastFrom3 $ uni] Cf xs -> toFile xs [show . firstFrom3 $ uni] Df xs -> toFile xs [show . secondFrom3 $ uni] Ef xs -> toFile xs [show . lastFrom3 $ uni, show . firstFrom3 $ uni] Ff xs -> toFile xs [show . lastFrom3 $ uni, show . secondFrom3 $ uni] Gf xs -> toFile xs [show . firstFrom3 $ uni, show . secondFrom3 $ uni] ~(Hf xs) -> toFile xs [show . lastFrom3 $ uni, show . firstFrom3 $ uni, show. secondFrom3 $ uni] -- the most verbose output -- | Auxiliary function that is used inside the 'uniqInMaxPoeticalN'. Finds the maximum element, prints needed information and returns the result. inner1 :: (Eq a, Ord b, Show a, Show b) => Int -- ^ The quantity of the represented as functions \"properties\" to be applied from the second argument. The order is from the right to the left. -> Info2 -- ^ A parameter to control the predefined behaviour of the printing. The 'I1' branch prints to the 'stdout' and the 'I2' - to the file. -> V.Vector ([b] -> b) -- ^ 'V.Vector' of the represented as functions \"properties\" to be applied consequently. -> UniqG a b -- ^ The data to be analyzed. -> IO ([b],UniqG a b) inner1 k info vN x = do let uniq = uniqMaxPoeticalGNV k vN x let fsT = (\(ys,_,_) -> ys) uniq printHelp info uniq return (fsT,x) {-# INLINE inner1 #-} -- | Variant of the 'uniqMaxPoeticalGNV' function where all the given \"properties\" are used. -- The predefined library \"properties\" or related to them functions can be found in the package @uniqueness-periods-vector-properties@. uniqMaxPoeticalGNVL :: (Eq a, Ord b, Show a, Show b) => V.Vector ([b] -> b) -- ^ 'V.Vector' of the represented as functions \"properties\" to be applied consequently. -> UniqG a b -- ^ The data to be analyzed. -> UniquenessG1 a b -- ^ The maximum element according to the given \"properties\". uniqMaxPoeticalGNVL vN = uniqMaxPoeticalGNV (V.length vN) vN {-# INLINE uniqMaxPoeticalGNVL #-} -- | The function evaluates -- the generated 'V.Vector' of 'UniquenessG1' @a@ @b@ elements to retrieve the possibly maximum element in it with respect to the order and significance (principality) -- of the \"properties\" being evaluated. The most significant and principal is the \"property\", 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 \"property\" and so on. uniqMaxPoetical2GN :: (Eq a, Ord b, Show a, Show b) => [a] -- ^ A list of \"whitespace symbols\" that delimits the sublists in the list to be processed. -> Preapp a -- ^ A parameter to specify the lists to be prepended and postpended to the given data to be processed before actual processment. -> Int -- ^ The quantity of the represented as functions \"properties\" to be applied from the second argument. The order is from the right to the left. -> V.Vector ([b] -> b) -- ^ 'V.Vector' of the represented as functions \"properties\" to be applied consequently. -> ([a] -> V.Vector c) -- ^ The first function that transforms the processed list into the form suitable for analyzing by the functions in the module. -> (V.Vector c -> [b]) -- ^ The second function that transforms the suitable form data representation obtained by the previous argument application into the data that can be evaluated to get the result. -> [a] -- ^ The data to be processed. Often it can be a 'String' of the text. -> UniquenessG1 a b uniqMaxPoetical2GN whspss rr k vN g1 g2 xs | compare k (V.length vN) == GT = error "Languages.UniquenessPeriods.Vector.General.Debug.uniqMaxPoetical2GN: undefined for that amount of norms. " | compare k 0 == GT = let vM = uniquenessVariants2GNP (get1m rr) (get2m rr) whspss vN g1 g2 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) (U vK) | otherwise = V.maximumBy (\(_,vN0,_) (_,vN1,_) -> compare (V.unsafeIndex vN0 0) (V.unsafeIndex vN1 0)) . uniquenessVariantsGN whspss rr vN g1 g2 $ xs -- | A variant for 'uniquenessVariants2GN' and 'uniquenessVariants2GNP' with the second argument defining, which one is used. uniquenessVariantsGN :: (Eq a, Ord b, Show a, Show b) => [a] -- ^ A list of \"whitespace symbols\" that delimits the sublists in the list to be processed. -> Preapp a -- ^ A parameter to specify the lists to be prepended and postpended to the given data to be processed before actual processment. -> V.Vector ([b] -> b) -- ^ 'V.Vector' of the represented as functions \"properties\" to be applied consequently. -> ([a] -> V.Vector c) -- ^ The first function that transforms the processed list into the form suitable for analyzing by the functions in the module. Usually it is one of the functions 'uniquenessPeriodsVector1', 'uniquenessPeriodsVector2', or 'uniquenessPeriodsVector2' from the @uniqueness-periods-vector@ package. Usually it is one of the functions 'uniquenessPeriodsVector1', 'uniquenessPeriodsVector2', or 'uniquenessPeriodsVector3' from the @uniqueness-periods-vector@ package. -> (V.Vector c -> [b]) -- ^ The second function that transforms the suitable form data representation obtained by the previous argument application into the data that can be evaluated to get the result. The predefined functions can be found in the package @uniqueness-periods-vector-properties@. -> [a] -- ^ The data to be processed. Often it can be a 'String' of the text. -> V.Vector (UniquenessG1 a b) uniquenessVariantsGN whspss (PA ts us) vN g1 g2 = uniquenessVariants2GNP ts us whspss vN g1 g2 uniquenessVariantsGN whspss K vN g1 g2 = uniquenessVariants2GN whspss vN g1 g2 {-# INLINE uniquenessVariantsGN #-} -- | Prints the maximum element with respect of the @k@ \"properties\" (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 \"property\" is the first element in the 'V.Vector' of \"properties\" (@[b] -> b@). uniqInMaxPoeticalN :: (Eq a, Ord b, Show a, Show b) => Int -- ^ The quantity of the represented as functions \"properties\" to be applied from the second argument. The order is from the right to the left. -> Info2 -- ^ A parameter to control the predefined behaviour of the printing. The 'I1' branch prints to the 'stdout' and the 'I2' - to the file. -> V.Vector ([b] -> b) -- ^ 'V.Vector' of the represented as functions \"properties\" to be applied consequently. -> UniqG a b -- ^ The data to be analyzed. -> IO (UniqG a b) uniqInMaxPoeticalN k info vN x = do inner1 k info vN x >>= \(fsT,x) -> if isU x then return (U (V.filter (\(xs,_,_) -> xs /= fsT) . snd . get2 $ x)) else return (UL ((\(v1,v2) -> ((V.toList . V.map lastFrom3 $ v1) ++ (fromJust . fst . get2 $ x),v2)) . V.unstablePartition (\(xs,_,_) -> xs == fsT) . snd . get2 $ x)) {-# INLINE uniqInMaxPoeticalN #-} -- | A variant of the 'uniqInMaxPoeticalN' where all the given \"properties\" are used. uniqInMaxPoeticalNL :: (Eq a, Ord b, Show a, Show b) => Info2 -- ^ A parameter to control the predefined behaviour of the printing. The 'I1' branch prints to the 'stdout' and the 'I2' - to the file. -> V.Vector ([b] -> b) -- ^ 'V.Vector' of the represented as functions \"properties\" to be applied consequently. -> UniqG a b -- ^ The data to be analyzed. -> IO (UniqG a b) uniqInMaxPoeticalNL info vN = uniqInMaxPoeticalN (V.length vN) info vN {-# INLINE uniqInMaxPoeticalNL #-} -- | Is a pair function for monadic recursive calls with 'uniqInMaxPoeticalN'. Prints the @n@ (the first 'Int' argument) consequential maximum elements. uniqNPoeticalN :: (Eq a, Ord b, Show a, Show b) => Int -- ^ A quantity of the recursive calls that returns each one a new result from the rest of the data processed. -> Int -- ^ The quantity of the represented as functions \"properties\" to be applied from the second argument. The order is from the right to the left. -> Info2 -- ^ A parameter to control the predefined behaviour of the printing. The 'I1' branch prints to the 'stdout' and the 'I2' - to the file. -> V.Vector ([b] -> b) -- ^ 'V.Vector' of the represented as functions \"properties\" to be applied consequently. -> UniqG a b -- ^ The data to be analyzed. -> IO () uniqNPoeticalN n k info vN y | n <= 0 = return () | compare (V.length . snd . get2 $ y) n == LT = V.mapM_ (printHelp info) . snd . get2 $ y | otherwise = (uniqInMaxPoeticalN k info vN y >>= uniqNPoeticalN (n - 1) k info vN) {-# INLINE uniqNPoeticalN #-} -- | A variant of the 'uniqNPoeticalN' where all the given \"properties\" are used. uniqNPoeticalNL :: (Eq a, Ord b, Show a, Show b) => Int -- ^ A quantity of the recursive calls that returns each one a new result from the rest of the data processed. -> Info2 -- ^ A parameter to control the predefined behaviour of the printing. The 'I1' branch prints to the 'stdout' and the 'I2' - to the file. -> V.Vector ([b] -> b) -- ^ 'V.Vector' of the represented as functions \"properties\" to be applied consequently. -> UniqG a b -- ^ The data to be analyzed. -> IO () uniqNPoeticalNL n info vN = uniqNPoeticalN n (V.length vN) info vN {-# INLINE uniqNPoeticalNL #-} -- | Is a pair function for monadic recursive calls with 'uniqInMaxPoeticalN'. Prints the @n@ (the first 'Int' argument) consequential maximum elements. -- Is similar to 'uniqNPoeticalN' in actions but has another return data type. uniqNPoeticalVN :: (Eq a, Ord b, Show a, Show b) => Int -- ^ A quantity of the recursive calls that returns each one a new result from the rest of the data processed. -> Int -- ^ The quantity of the represented as functions \"properties\" to be applied from the second argument. The order is from the right to the left. -> Info2 -- ^ A parameter to control the predefined behaviour of the printing. The 'I1' branch prints to the 'stdout' and the 'I2' - to the file. -> V.Vector ([b] -> b) -- ^ 'V.Vector' of the represented as functions \"properties\" to be applied consequently. -> UniqG a b -- ^ The data to be analyzed. -> IO (UniqG a b) uniqNPoeticalVN n k info vN y | n <= 0 || compare (V.length . snd . get2 $ y) n == LT = return y | otherwise = (uniqInMaxPoeticalN k info vN y >>= uniqNPoeticalVN (n - 1) k info vN) {-# INLINE uniqNPoeticalVN #-} -- | A variant of the 'uniqNPoeticalVN' where all the given \"properties\" are used. uniqNPoeticalVNL :: (Eq a, Ord b, Show a, Show b) => Int -- ^ A quantity of the recursive calls that returns each one a new result from the rest of the data processed. -> Info2 -- ^ A parameter to control the predefined behaviour of the printing. The 'I1' branch prints to the 'stdout' and the 'I2' - to the file. -> V.Vector ([b] -> b) -- ^ 'V.Vector' of the represented as functions \"properties\" to be applied consequently. -> UniqG a b -- ^ The data to be analyzed. -> IO (UniqG a b) uniqNPoeticalVNL n info vN = uniqNPoeticalVN n (V.length vN) info vN {-# INLINE uniqNPoeticalVNL #-} -------------------------------------------------------------------------------------------- -- | The full analyzing and processment function. A pair with 'uniqNPoetical2VGN', returns another data type as its result. uniqNPoetical2GN :: (Eq a, Ord b, Show a, Show b) => [a] -- ^ A list of \"whitespace symbols\" that delimits the sublists in the list to be processed. -> Preapp a -- ^ A parameter to specify the lists to be prepended and postpended to the given data to be processed before actual processment. -> Int -- ^ A quantity of the recursive calls that returns each one a new result from the rest of the data processed. -> Int -- ^ The quantity of the represented as functions \"properties\" to be applied from the second argument. The order is from the right to the left. -> Info2 -- ^ A parameter to control the predefined behaviour of the printing. The 'I1' branch prints to the 'stdout' and the 'I2' - to the file. -> V.Vector ([b] -> b) -- ^ 'V.Vector' of the represented as functions \"properties\" to be applied consequently. -> ([a] -> V.Vector c) -- ^ The first function that transforms the processed list into the form suitable for analyzing by the functions in the module. Usually it is one of the functions 'uniquenessPeriodsVector1', 'uniquenessPeriodsVector2', or 'uniquenessPeriodsVector3' from the @uniqueness-periods-vector@ package. -> (V.Vector c -> [b]) -- ^ The second function that transforms the suitable form data representation obtained by the previous argument application into the data that can be evaluated to get the result. The predefined functions can be found in the package @uniqueness-periods-vector-properties@. -> [a] -- ^ The data to be processed. Often it can be a 'String' of the text. -> IO () uniqNPoetical2GN whspss rr n k info vN g1 g2 xs | n <= 0 = return () | otherwise = do let v = uniquenessVariants2GNP (get1m rr) (get2m rr) whspss vN g1 g2 xs if compare (V.length v) n == LT then V.mapM_ (printHelp info) v else (uniqInMaxPoeticalN k info vN (U v) >>= uniqNPoeticalN (n - 1) k info vN) -- | The full analyzing and processment function. A pair with 'uniqNPoetical2GN', returns another data type as its result. uniqNPoetical2VGN :: (Eq a, Ord b, Show a, Show b) => [a] -- ^ A list of \"whitespace symbols\" that delimits the sublists in the list to be processed. -> Preapp a -- ^ A parameter to specify the lists to be prepended and postpended to the given data to be processed before actual processment. -> Int -- ^ A quantity of the recursive calls that returns each one a new result from the rest of the data processed. -> Int -- ^ The quantity of the represented as functions \"properties\" to be applied from the second argument. The order is from the right to the left. -> Info2 -- ^ A parameter to control the predefined behaviour of the printing. The 'I1' branch prints to the 'stdout' and the 'I2' - to the file. -> V.Vector ([b] -> b) -- ^ 'V.Vector' of the represented as functions \"properties\" to be applied consequently. -> ([a] -> V.Vector c) -- ^ The first function that transforms the processed list into the form suitable for analyzing by the functions in the module. Usually it is one of the functions 'uniquenessPeriodsVector1', 'uniquenessPeriodsVector2', or 'uniquenessPeriodsVector3' from the @uniqueness-periods-vector@ package. -> (V.Vector c -> [b]) -- ^ The second function that transforms the suitable form data representation obtained by the previous argument application into the data that can be evaluated to get the result. The predefined functions can be found in the package @uniqueness-periods-vector-properties@. -> UniqG a b -- ^ A parameter to control the behaviour of the function. The data constructor (either 'U' or 'UL') is preserved. -> [a] -- ^ The data to be processed. Often it can be a 'String' of the text. -> IO (UniqG a b) uniqNPoetical2VGN whspss rr n k info vN g1 g2 y xs | n <= 0 = if isU y then return (U V.empty) else return (UL ([],V.empty)) | otherwise = do let v = uniquenessVariants2GNP (get1m rr) (get2m rr) whspss vN g1 g2 xs if compare (V.length v) n == LT then if isU y then return (U v) else return (UL ([],v)) else if isU y then uniqNPoeticalVN n k info vN (U v) else uniqNPoeticalVN n k info vN (UL ([],v))