{-# LANGUAGE BangPatterns #-} module Data.RangeMin.Int.Linearithmic (rangeMin) where import Data.RangeMin.Common import Data.RangeMin.Int.Linearithmic.Combinators import qualified Data.RangeMin.Fusion as F import Prelude hiding (drop) -- | This implements the /O(n log n)/ range-min algorithm, which explicitly -- precomputes the answer to every range-min query with size a power of 2. rangeMin :: PVector Value -> RM rangeMin !xs = toRM $ \ i d -> case d of 1 -> i 2 -> table ! i _ -> let !k = intLog d row = getRow nn table (k-1) in minIndex xs (row i) (row (i + d - bit' k)) where !n = vlength xs !m = intLog n !nn = n - 1 !table = buildTable m nn xs buildTable :: Length -> Length -> PVector Value -> PVector Index buildTable !m !nn !xs = buildRowsUnf m nn Nothing row0 sucRow where row0 = F.convert $ F.iunfoldN nn (\ i xi -> let i' = i + 1 xi' = xs ! i' in if i < nn then Just (if xi <= xi' then i else i', xi') else Nothing) (xs ! 0) sucRow !k !prev = let !prev' = drop (bit' k) prev in F.convert $ F.imap (\ i -> minIndex xs (prev ! i)) prev'