module Vector where import Graphics.UI.GLUT normalize :: Floating a => Vector3 a -> Vector3 a normalize (Vector3 x y z) = Vector3 (x/d) (y/d) (z/d) where d = sqrt (x*x+y*y+z*z) prod (Vector3 x1 y1 z1) (Vector3 x2 y2 z2) = Vector3 (y1 * z2 - z1 * y2) (z1 * x2 - x1 * z2) (x1 * y2 - y1 * x2) xmove (Vector3 x y z) incr = Vector3 (x+incr) y z ymove (Vector3 x y z) incr = Vector3 x (y+incr) z zmove (Vector3 x y z) incr = Vector3 x y (z+incr) xpart (Vector3 x _ _) = x ypart (Vector3 _ y _) = y zpart (Vector3 _ _ z) = z instance Floating a => Num (Vector3 a) where (Vector3 x1 y1 z1) + (Vector3 x2 y2 z2) = Vector3 (x1 + x2) (y1 + y2) (z1 + z2) (Vector3 x1 y1 z1) * (Vector3 x2 y2 z2) = Vector3 (y1 * z2 - z1 * y2) (z1 * x2 - x1 * z2) (x1 * y2 - y1 * x2) (Vector3 x1 y1 z1) - (Vector3 x2 y2 z2) = Vector3 (x1 - x2) (y1 - y2) (z1 - z2) negate (Vector3 x y z) = Vector3 (-x) (-y) (-z) fromInteger i = Vector3 (fromInteger i) 0 0 -- dummy definitions abs v = v signum (Vector3 0 0 0) = 0 signum _ = 1