module IntQC where import Test.QuickCheck import Data.RangeMin import Data.RangeMin.Common hiding (Vector, minIndex) import Data.Vector.Primitive (Vector, fromListN, minIndex, fromList) main = quickCheckWith stdArgs{maxSize = 10000} testAll testRM :: [Int] -> RangeMin testRM = intRangeMin . fromList correctAlgo :: (Vector Int -> RM) -> [Int] -> Property correctAlgo _ [] = property True correctAlgo algo xs = do i0 <- choose (0, n-1) j0 <- choose (0, n-1) let i = min i0 j0 let m = max i0 j0 + 1 - i property (rM i m == i + minIndex (slice i m ys)) where ys :: Vector Int !ys = fromList xs !n = Prelude.length xs !rM = runRM (algo ys) testAll :: [Int] -> Property testAll xs = goodMin xs .&. goodIntMin xs goodIntMin :: [Int] -> Property goodIntMin [] = property True goodIntMin xs = do i0 <- choose (0, n-1) j0 <- choose (0, n-1) let i = min i0 j0 let m = max i0 j0 + 1 - i property (rM i m == i + minIndex (slice i m ys)) where ys :: Vector Int !ys = fromListN n xs !n = Prelude.length xs !rM = intRangeMin ys goodMin :: [Int] -> Property goodMin [] = property True goodMin xs = do i0 <- choose (0, n-1) j0 <- choose (0, n-1) let i = min i0 j0 let m = max i0 j0 + 1 - i property (rM i m == i + minIndex (slice i m ys)) where ys :: Vector Int !ys = fromListN n xs !n = Prelude.length xs !rM = vecRangeMinBy (<=) ys