{-# LANGUAGE TemplateHaskell #-} import Geom2d.Intersect import Geom2d.Point import Geom2d.Line import Test.QuickCheck.All import Test.QuickCheck import Test.Utils import Data.AEq prop_intersect_point_point :: Point' Float -> Point' Float -> Bool prop_intersect_point_point a b = (a == b) == (a `intersect` b) prop_intersect_infline_infline_xaxis :: Float -> Float -> Bool prop_intersect_infline_infline_xaxis a b = maybe True id $ do l <- mkInfLine (fromCoords a 0) (fromCoords a b) :: Maybe (InfLine Point' Float) xAxis <- mkInfLine (fromCoords 0 0) (fromCoords 1 0) :: Maybe (InfLine Point' Float) return (l `intersect` xAxis) prop_intersect_infline_infline_yaxis :: Float -> Float -> Bool prop_intersect_infline_infline_yaxis a b = maybe True id $ do l <- mkInfLine (fromCoords 0 a) (fromCoords b a) :: Maybe (InfLine Point' Float) yAxis <- mkInfLine (fromCoords 0 0) (fromCoords 0 1) :: Maybe (InfLine Point' Float) return (l `intersect` yAxis) prop_intersect_infline_point :: InfLine Point' Float -> Point' Float -> Bool prop_intersect_infline_point line p = (line `intersect` p) `implies` ( maybe True id $ do f <- lineF line return (y p ~== f (x p))) where True `implies` False = False _ `implies` _ = True return [] runTests = $quickCheckAll main = do putStrLn "Test Intersect.hs" runTests >>= doExit