Skip to content

Commit

Permalink
Add another test. Qualify KdTree import.
Browse files Browse the repository at this point in the history
  • Loading branch information
ijt committed Jun 26, 2011
1 parent 2bd5601 commit b1fbf4b
Showing 1 changed file with 16 additions and 10 deletions.
26 changes: 16 additions & 10 deletions KdTreeTest.hs
Expand Up @@ -2,28 +2,34 @@

module Main where

import Data.Maybe
import qualified Data.List as L

import Test.QuickCheck
import Test.QuickCheck.All

import Data.Trees.KdTree
import qualified Data.Trees.KdTree as Kd

prop_invariant :: [Point3d] -> Bool
prop_invariant points = invariant' . fromList $ points
prop_invariant :: [Kd.Point3d] -> Bool
prop_invariant points = Kd.invariant' . Kd.fromList $ points

prop_samePoints :: [Point3d] -> Bool
prop_samePoints points = L.sort points == (L.sort . toList . fromList $ points)
prop_samePoints :: [Kd.Point3d] -> Bool
prop_samePoints points = L.sort points == (L.sort . Kd.toList . Kd.fromList $ points)

prop_nearestNeighbor :: [Point3d] -> Point3d -> Bool
prop_nearestNeighbor :: [Kd.Point3d] -> Kd.Point3d -> Bool
prop_nearestNeighbor points probe =
nearestNeighbor tree probe == bruteNearestNeighbor points probe
where tree = fromList points
Kd.nearestNeighbor tree probe == bruteNearestNeighbor points probe
where tree = Kd.fromList points

bruteNearestNeighbor :: [Point3d] -> Point3d -> Maybe Point3d
prop_pointsAreClosestToThemselves :: [Kd.Point3d] -> Bool
prop_pointsAreClosestToThemselves points =
map Just points == map (Kd.nearestNeighbor tree) points
where tree = Kd.fromList points

bruteNearestNeighbor :: [Kd.Point3d] -> Kd.Point3d -> Maybe Kd.Point3d
bruteNearestNeighbor [] _ = Nothing
bruteNearestNeighbor points probe =
Just . head . L.sortBy (compareDistance probe) $ points
Just . head . L.sortBy (Kd.compareDistance probe) $ points

main = $quickCheckAll

0 comments on commit b1fbf4b

Please sign in to comment.