module QC where import Test.QuickCheck import Data.RangeMin import Data.Vector.Unboxed import Prelude hiding (minimum, length) testAll :: Property testAll = forAllShrink arbitrary (const []) $ \ xs -> goodMin xs .&. goodSMin xs .&. goodVecMin xs .&. goodSVecMin xs goodMin :: [Int] -> Gen Prop 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 whenFail (putStrLn (show (i, m, n, rM i m, ys ! rM i m, minimum (slice i m ys)))) (ys ! (rM i m) == minimum (slice i m ys)) where ys :: Vector Int !ys = fromList xs !n = length ys !rM = rangeMin n (ys !) goodSMin :: [Int] -> Gen Prop goodSMin [] = property True goodSMin xs = do i0 <- choose (0, n-1) j0 <- choose (0, n-1) let i = min i0 j0 let m = max i0 j0 + 1 - i whenFail (putStrLn (show (i, m, n))) (rM i m == i + minIndex (slice i m ys)) where ys :: Vector Int !ys = fromList xs !n = length ys !rM = stableRangeMin n (ys !) goodVecMin :: [Int] -> Gen Prop goodVecMin [] = property True goodVecMin xs = do i0 <- choose (0, n-1) j0 <- choose (0, n-1) let i = min i0 j0 let m = max i0 j0 + 1 - i whenFail (putStrLn (show (i, m, n))) (ys ! (rM i m) == minimum (slice i m ys)) where ys :: Vector Int !ys = fromList xs !n = length ys !rM = vecRangeMin ys goodSVecMin :: [Int] -> Gen Prop goodSVecMin [] = property True goodSVecMin xs = do i0 <- choose (0, n-1) j0 <- choose (0, n-1) let i = min i0 j0 let m = max i0 j0 + 1 - i whenFail (putStrLn (show (i, m, n))) (rM i m == i + minIndex (slice i m ys)) where ys :: Vector Int !ys = fromList xs !n = length ys !rM = stableVecRangeMin ys