module Data.SG.Geometry.ThreeDim where
import Control.Applicative
import Data.Foldable (Foldable(foldr))
import Data.Traversable (Traversable(traverse))
import Data.SG.Geometry
import Data.SG.Vector
import Data.SG.Vector.Basic
newtype Point3' a = Point3 (a, a, a)
deriving (Eq, Ord, Show, Read)
data Rel3' a = Rel3 (a, a, a) a
deriving (Eq, Ord, Show, Read)
makeRel3 :: Num a => (a, a, a) -> Rel3' a
makeRel3 (x, y, z) = Rel3 (x, y, z) (x * x + y * y + z * z)
instance IsomorphicVectors Rel3' Point3' where
iso (Rel3 p _) = Point3 p
instance IsomorphicVectors Point3' Rel3' where
iso (Point3 p) = makeRel3 p
instance IsomorphicVectors Rel3' Triple where
iso (Rel3 p _) = Triple p
instance IsomorphicVectors Triple Rel3' where
iso (Triple p) = makeRel3 p
instance IsomorphicVectors Point3' Triple where
iso (Point3 p) = Triple p
instance IsomorphicVectors Triple Point3' where
iso (Triple p) = Point3 p
instance VectorNum Rel3' where
fmapNum1 f (Rel3 (x, y, z) _) = makeRel3 (f x, f y, f z)
fmapNum2 f (Rel3 (x, y, z) _) (Rel3 (x', y', z') _) = makeRel3 (f x x', f y y', f z z')
fmapNum1inv f (Rel3 (x, y, z) m) = Rel3 (f x, f y, f z) m
simpleVec a = Rel3 (a, a, a) (3*a*a)
instance VectorNum Point3' where
fmapNum1 = fmap
fmapNum1inv = fmap
fmapNum2 = liftA2
simpleVec = pure
instance (Show a, Eq a, Num a) => Num (Rel3' a) where
(+) = fmapNum2 (+)
() = fmapNum2 ()
(*) = fmapNum2 (*)
abs = fmapNum1inv abs
signum = fmapNum1 signum
negate = fmapNum1inv negate
fromInteger = simpleVec . fromInteger
instance Functor Point3' where
fmap f (Point3 (x, y, z)) = Point3 (f x, f y, f z)
instance Applicative Point3' where
pure a = Point3 (a, a, a)
(<*>) (Point3 (fa, fb, fc)) (Point3 (a, b, c)) = Point3 (fa a, fb b, fc c)
instance Foldable Point3' where
foldr f t (Point3 (x, y, z)) = x `f` (y `f` (z `f` t))
instance Foldable Rel3' where
foldr f t (Rel3 (x, y, z) _) = x `f` (y `f` (z `f` t))
instance Traversable Point3' where
traverse f (Point3 (x, y, z)) = liftA3 (curry3 Point3) (f x) (f y) (f z)
where
curry3 g a b c = g (a, b, c)
instance Coord2 Point3' where
getX (Point3 (a,_,_)) = a
getY (Point3 (_,b,_)) = b
instance Coord3 Point3' where
getZ (Point3 (_,_,c)) = c
instance Coord2 Rel3' where
getX (Rel3 (a, _, _) _) = a
getY (Rel3 (_, b, _) _) = b
instance Coord3 Rel3' where
getZ (Rel3 (_, _, c) _) = c
instance Coord Point3' where
getComponents (Point3 (a, b, c)) = [a, b, c]
fromComponents (a:b:c:_) = Point3 (a, b, c)
fromComponents xs = fromComponents $ xs ++ repeat 0
instance Coord Rel3' where
getComponents (Rel3 (a, b, c) _) = [a, b, c]
fromComponents (a:b:c:_) = makeRel3 (a, b, c)
fromComponents xs = fromComponents $ xs ++ repeat 0
magSq (Rel3 _ msq) = msq
dotProduct (Rel3 (a, b, c) _) (Rel3 (a', b', c') _)
= a * a' + b * b' + c * c'
instance Geometry Rel3' Point3' Line3' where
scaleRel a (Rel3 (x, y, z) m) = Rel3 (a*x, a*y, a*z) (a*a*m)
plusDir (Point3 (x, y, z)) (Rel3 (x', y', z') _)
= Point3 (x + x', y + y', z + z')
fromPt (Point3 (x, y, z)) (Point3 (x', y', z'))
= makeRel3 (x x', y y', z z')
getLineVecs (Line3 pt dir) = (pt, dir)
makeLine = Line3
data Line3' a = Line3 {getLineStart3 :: (Point3' a) , getLineDir3 :: (Rel3' a)}
deriving (Eq, Show, Read)