-- | -- Module : Languages.UniquenessPeriods.Vector.Filters -- Copyright : (c) OleksandrZhabenko 2020 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- A module allows to change the structure of the function output for the functions of -- elements from 'RealFrac' class. At the moment only the equal intervals are supported. module Languages.UniquenessPeriods.Vector.Filters ( -- * One interval used intervalNRealFrac , unsafeTransfer1I5 , transfer1IEq3 -- * Several intervals , unsafeRearrangeIG , unsafeRearrangeIGV ) where import CaseBi import qualified Data.Vector as V -- | Given the minimum and maximum elements, a quantity of equal intervals, and an element in between the first two arguments (or equal to one of them), finds out the -- index of the interval, to which the element belongs (starting from 1). The minimum element belongs to the interval with the index 1. intervalNRealFrac :: RealFrac b => b -> b -> Int -> b -> Int intervalNRealFrac minE maxE n x = zero2One . ceiling $ fromIntegral n * (x - minE) / (maxE - minE) {-# INLINE intervalNRealFrac #-} zero2One :: Int -> Int zero2One x = if x == 0 then 1 else x {-# INLINE zero2One #-} -- | Moves (if needed) the given value so that its result divides the new [min..max] interval in the same proportion as the starting one. Is intended to be used -- for the arguments satisfying some additional constraints, but they are not checked (hence, its name prefix \"unsafe\"). For example, the second argument must be -- greater than the first one, the fourth -- than the third one, and the fifth must be located in between the first two. Then the result is also located in between -- the third and fourth arguments similarly. unsafeTransfer1I5 :: RealFrac b => b -> b -> b -> b -> b -> b unsafeTransfer1I5 minE0 maxE0 minE1 maxE1 x = minE1 + (x - minE0) * (maxE1 - minE1) / (maxE0 - minE0) {-# INLINE unsafeTransfer1I5 #-} -- | A variant of the 'unsafeTransfer1I5' where the lengths of the both intervals (the old and the new ones) are equal. transfer1IEq3 :: RealFrac b => b -> b -> b -> b transfer1IEq3 minE0 minE1 = (+ (minE1 - minE0)) {-# INLINE transfer1IEq3 #-} -- | Makes a complex interval-based transformation moving the value from its own interval to the corresponding by the 'V.Vector' of tuples second element of the -- respective pair with the first element being the starting number of the interval (numeration of them begins at 1). The 'V.Vector' argument must be sorted -- by the first argument in the ascending order. Usually, its first elements in the tuples are from the range @[1..n]@. Number of the intervals are given as -- the third argument and for many cases should not be greater than 10. There do exist several semantical constraints for the possible accurate arguments, -- but they are not checked. For example, the first argument must be less than the second one; the fifth argument must be located between the first two ones; -- the 'Int' argument must be greater than zero. unsafeRearrangeIG :: RealFrac b => b -> b -> Int -> V.Vector (Int,Int) -> b -> b unsafeRearrangeIG minE maxE n v x = x + fromIntegral (getBFst' (n0, v) n0 - n0) * (maxE - minE) / fromIntegral n where n0 = intervalNRealFrac minE maxE n x -- | An unzipped variant of the 'unsafeRearrangeIG' function where the 'V.Vector' argument is internally 'V.zip'ped as the second argument with the 'V.Vector' @[1..n]@. -- This allows to shorten the time of the arguments writing given only the resulting backpermutted indexes in the 'V.Vector'. unsafeRearrangeIGV :: RealFrac b => b -> b -> Int -> V.Vector Int -> b -> b unsafeRearrangeIGV minE maxE n v = unsafeRearrangeIG minE maxE n . V.zip (V.enumFromN 1 n) . V.filter (\y -> compare y 0 /= LT && compare y n == LT) $ v {-# INLINE unsafeRearrangeIGV #-}