{-# LANGUAGE BangPatterns #-} module Data.RangeMin.Int.Quadratic (rangeMin) where import qualified Data.Vector.Primitive as UV (Vector, length) -- import Data.RangeMin.Common.Unf import qualified Data.RangeMin.Fusion as F import Data.RangeMin.Common.Types (RM, toRM) import Data.RangeMin.Common.Vector.Utils ((!)) import Data.RangeMin.Common.Math (div') rangeMin :: UV.Vector Int -> RM rangeMin !xs = let !table = quadTable xs !m = 2 * n + 1 encode !i !d = (i * (m - i)) `div'` 2 + d - 1 in toRM $ \ i j -> table ! encode i j where !n = UV.length xs data Q = Q {-# UNPACK #-} !Int {-# UNPACK #-} !Int {-# UNPACK #-} !Int {-# UNPACK #-} !Int {-# INLINE quadTable #-} quadTable :: UV.Vector Int -> UV.Vector Int quadTable !xs = F.unfoldN ((n * (n + 1)) `div'` 2) suc (Q 0 0 0 (xs ! 0)) where !n = UV.length xs suc (Q i j x vx) | j == n = let i' = i + 1 in if i' == n then Nothing else Just (i', Q i' (i' + 1) i' (xs ! i')) | otherwise = let vj = xs ! j in if vx <= vj then Just (x, Q i (j+1) x vx) else Just (j, Q i (j+1) j vj) -- Q i j x vx has the following interpretation: -- we are about to compute the minimum element in [i..j] -- the minimum index in [i..j-1] is x, and the value at x is vx