{-# LANGUAGE BangPatterns #-} -- | Consider the following function, which, given 'i' and 'k', finds the index of -- the minimum element in the range @i..i+k-1@. -- -- @ -- rangeMin :: 'G.Vector' v a => (a -> a -> 'Ordering') -> 'Int' -> 'Int' -> v a -> 'Int' -- rangeMin cmp i k xs = i + 'G.minIndexBy' cmp ('G.slice' i k xs) -- @ -- -- This module implements functions which, given a fixed comparison function, preprocess -- an array in /O(n)/ time to support queries of this form in /O(1)/ time. -- -- Compiling this library with LLVM can significantly improve its performance. Even -- with only -fasm, however, it has been clocked within 30% of a fully optimized and unrolled -- C++ implementation. (With -fllvm -optlc-O3, it has been within 10%.) -- -- For all methods in this module, ties are broken by which element comes first in the array. module Data.RangeMin ( RangeMin, LEq, unsafeIntRangeMin, intRangeMin, unsafeVecRangeMinBy, unsafeVecRangeMin, vecRangeMinBy, vecRangeMin) where import Data.RangeMin.Common import qualified Data.RangeMin.Int.Linear as N import qualified Data.RangeMin.Int.NearLinear as NearN import qualified Data.RangeMin.Int.Linearithmic as Nlogn import qualified Data.RangeMin.Int.Quadratic as N2 import Data.RangeMin.Cartesian import qualified Data.Vector.Unboxed as UV import qualified Data.Vector as V import qualified Data.Vector.Generic as G -- | A range min function. Given an index @i@ and a length @m@, returns the -- minimum element in the range @i..i+m-1@. type RangeMin = Int -> Int -> Int internalIntRangeMin :: UV.Vector Int -> RM internalIntRangeMin !xs | n <= n2Cross = N2.rangeMin xs | n <= nlognCross = Nlogn.rangeMin xs | n <= nearNCross = NearN.rangeMin xs | otherwise = N.rangeMin xs where !n = UV.length xs -- | /O(n)/. Returns a range-min function on the vector, under the natural ordering. -- This function can be six times as fast as 'unsafeVecRangeMin'. -- -- The returned function /does not/ do bounds checks. unsafeIntRangeMin :: UV.Vector Int -> RangeMin unsafeIntRangeMin xs = runRM (internalIntRangeMin xs) {-# NOINLINE intRangeMin #-} -- | /O(n)/. Returns a range-min function on the vector, under the natural ordering. -- This function can be six times as fast as 'vecRangeMin'. -- -- The returned function /does/ do bounds checks. intRangeMin :: UV.Vector Int -> RangeMin intRangeMin !xs = let !rM = internalIntRangeMin xs in \ i m -> if i >= 0 && m >= 1 && i + m <= n then runRM rM i m else error "Error: range min query out of bounds" where !n = UV.length xs {-# SPECIALIZE unsafeVecRangeMinBy :: LEq a -> V.Vector a -> RangeMin #-} {-# SPECIALIZE unsafeVecRangeMinBy :: LEq Int -> UV.Vector Int -> RangeMin #-} -- | /O(n)/. Returns a range-min function on the vector, under the specified ordering. -- The returned function /does not/ do bounds checks. unsafeVecRangeMinBy :: G.Vector v a => LEq a -> v a -> RangeMin unsafeVecRangeMinBy (<=?) !xs = unsafeIntRangeMin (buildDepths (<=?) xs) {-# INLINE [0] unsafeVecRangeMin #-} -- | /O(n)/. Returns a range-min function on the vector, under the elements' natural ordering. -- The returned function /does not/ do bounds checks. unsafeVecRangeMin :: (G.Vector v a, Ord a) => v a -> RangeMin unsafeVecRangeMin = unsafeVecRangeMinBy (<=) {-# SPECIALIZE vecRangeMinBy :: LEq a -> V.Vector a -> RangeMin #-} -- | /O(n)/. Returns a range-min function on the vector, under the specified ordering. -- The returned function /does/ do bounds checks. vecRangeMinBy :: G.Vector v a => LEq a -> v a -> RangeMin vecRangeMinBy (<=?) !xs = intRangeMin (buildDepths (<=?) xs) {-# NOINLINE [1] vecRangeMin #-} -- | /O(n)/. Returns a range-min function on the vector, under the elements' natural ordering. -- The returned function /does/ do bounds checks. vecRangeMin :: (G.Vector v a, Ord a) => v a -> RangeMin vecRangeMin = vecRangeMinBy (<=) {-# RULES "unsafeVecRangeMin/Int" forall xs . unsafeVecRangeMin xs = unsafeIntRangeMin (G.unstream (G.stream xs)); "vecRangeMin/Int" forall xs . vecRangeMin xs = intRangeMin (G.unstream (G.stream xs)); #-}