{-# LANGUAGE LambdaCase #-} {-# LANGUAGE ScopedTypeVariables #-} module Main where import Control.Monad import qualified Data.Find.Interpolation as Interpolation import qualified Data.Find.Linear as Linear import Data.Functor.Identity import Data.List import Data.Word import qualified Data.Vector as V import Test.Tasty import qualified Test.Tasty.QuickCheck as QC main :: IO () main = defaultMain tests tests :: TestTree tests = testGroup "Find" [ linearTests , interpolationTests ] linearTests :: TestTree linearTests = testGroup "linear" [ QC.testProperty "search" $ \(valList::[Word64]) -> let v = V.fromList $ sort valList p = (`map` valList) $ \t -> (Linear.search ((v V.!) . fromIntegral) (0, toInteger $ V.length v-1) t, t) in all (\case (Nothing, _) -> False (Just tl, t) -> (v V.! (fromIntegral tl)) == t) p , QC.testProperty "searchM" $ \(valList::[Word64]) -> runIdentity $ do let v = V.fromList $ sort valList p <- forM valList $ \t -> do mtl <- Linear.searchM (pure . (v V.!) . fromIntegral) (0, toInteger $ V.length v-1) t pure (mtl, t) pure $ all (\case (Nothing, _) -> False (Just tl, t) -> (v V.! (fromIntegral tl)) == t) p ] interpolationTests :: TestTree interpolationTests = testGroup "interpolation" [ QC.testProperty "search" $ \(valList::[Word64]) -> let v = V.fromList $ sort valList p = (`map` valList) $ \t -> (Interpolation.search ((v V.!) . fromIntegral) fromIntegral (0, toInteger $ V.length v-1) t, t) in all (\case (Nothing, _) -> False (Just tl, t) -> (v V.! (fromIntegral tl)) == t) p , QC.testProperty "searchM" $ \(valList::[Word64]) -> runIdentity $ do let v = V.fromList $ sort valList p <- forM valList $ \t -> do mtl <- Interpolation.searchM (pure . (v V.!) . fromIntegral) fromIntegral (0, toInteger $ V.length v-1) t pure (mtl, t) pure $ all (\case (Nothing, _) -> False (Just tl, t) -> (v V.! (fromIntegral tl)) == t) p ]