{-# LANGUAGE FlexibleInstances #-} module Point ( Point(..), dot, scale ) where import Test.Tasty.QuickCheck ( Arbitrary(..) ) -- | Represents a point in three dimensions. We use a custom type (as -- opposed to a 3-tuple) so that we can make the coordinates strict. -- data Point = Point !Double !Double !Double deriving (Eq, Show) instance Arbitrary Point where arbitrary = do (x,y,z) <- arbitrary return $ Point x y z instance Num Point where (Point x1 y1 z1) + (Point x2 y2 z2) = Point (x1+x2) (y1+y2) (z1+z2) (Point x1 y1 z1) - (Point x2 y2 z2) = Point (x1-x2) (y1-y2) (z1-z2) (Point x1 y1 z1) * (Point x2 y2 z2) = Point (x1*x2) (y1*y2) (z1*z2) abs (Point x y z) = Point (abs x) (abs y) (abs z) signum (Point x y z) = Point (signum x) (signum y) (signum z) fromInteger n = Point coord coord coord where coord = fromInteger n -- | Scale a point by a constant. scale :: Point -> Double -> Point scale (Point x y z) d = Point (x*d) (y*d) (z*d) -- | Returns the dot product of two points (taken as three-vectors). {-# INLINE dot #-} dot :: Point -> Point -> Double dot (Point x1 y1 z1) (Point x2 y2 z2) = (x2 - x1)^(2::Int) + (y2 - y1)^(2::Int) + (z2 - z1)^(2::Int)