{-# LANGUAGE BangPatterns #-} module Data.RangeMin.Int.Linear (rangeMin) where import Data.RangeMin.Int.Catalan import Data.RangeMin.Common import qualified Data.RangeMin.Int.NearLinear as NearN import qualified Data.RangeMin.Int.Linearithmic as Nlogn rangeMin :: PVector Value -> RM rangeMin !xs = let !multiBlockRM0 | not forceNLogN && vlength blockMinVals <= nearNCross = NearN.rangeMin blockMinVals | otherwise = Nlogn.rangeMin blockMinVals multiBlockRM !bI !bJ = blockMins ! runRM multiBlockRM0 bI (bJ - bI) in toRM $ \ i d -> let j = i + d (bI, xI) = i `divMod'` bS (bJ, xJ) = j `divMod'` bS in case (xI, xJ) of (0, 0) -> multiBlockRM bI bJ (0, _) | d < bS -- from a block start to some fraction of the same block -> blockMin bI 0 d | otherwise -- from a block start to some other point -> multiBlockRM bI bJ `mix` blockMin bJ 0 xJ (_, 0) | d < bS -- from mid-block to the end of the same block -> blockMin bI xI bS | otherwise -- from mid-block to the end of another block -> blockMin bI xI bS `mix` multiBlockRM (bI + 1) bJ _ -> case bJ - bI of 0 -> blockMin bI xI xJ -- in the same block 1 -> blockMin bI xI bS `mix` blockMin bJ 0 xJ -- in adjacent blocks _ -> blockMin bI xI bS `mix` blockMin bJ 0 xJ `mix` multiBlockRM (bI + 1) bJ -- in separated blocks where !n = vlength xs !bS = ceilLog n `div'` 4 + 1 !(!blockTypes, !typeRMs, !blockMins, !blockMinVals) = catalanIndexer xs bS blockMin !b !i !j = runRM (typeRMs ! (blockTypes ! b)) i (j - i) + bS * b mix = minIndex xs