{-# LANGUAGE BangPatterns #-} module Data.RangeMin.Int.Quadratic (rangeMin) where import qualified Data.RangeMin.Fusion as F import Data.RangeMin.Common -- | This implements the brute-force, /O(n^2)/ DP algorithm that precomputes the answer to -- /every/ range-min query explicitly. rangeMin :: PVector Value -> 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 = vlength xs data Q = Q {-# UNPACK #-} !Int {-# UNPACK #-} !Int {-# UNPACK #-} !Int {-# UNPACK #-} !Value quadTable :: PVector Value -> PVector Index quadTable !xs = F.convert $ F.unfoldN ((n * (n + 1)) `div'` 2) suc (Q 0 0 0 (xs ! 0)) where !n = vlength xs {-# INLINE [1] suc #-} suc (Q i j x vx) | j < n = 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) | otherwise = let i' = i + 1 in if i' < n then Just (i', Q i' (i' + 1) i' (xs ! i')) else Nothing -- 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