module Data.SG.Vector.Basic where
import Control.Applicative
import Data.Foldable
import Data.Traversable
import Data.SG.Vector
newtype Pair a = Pair (a, a)
deriving (Eq, Ord, Show, Read)
newtype Triple a = Triple (a, a, a)
deriving (Eq, Ord, Show, Read)
newtype Quad a = Quad (a, a, a, a)
deriving (Eq, Ord, Show, Read)
newtype LinePair a = LinePair (Pair a, Pair a)
deriving (Eq, Ord, Show, Read)
newtype LineTriple a = LineTriple (Triple a, Triple a)
deriving (Eq, Ord, Show, Read)
instance VectorNum Pair where
fmapNum1 = fmap
fmapNum1inv = fmap
fmapNum2 = liftA2
simpleVec = pure
instance VectorNum Triple where
fmapNum1 = fmap
fmapNum1inv = fmap
fmapNum2 = liftA2
simpleVec = pure
instance VectorNum Quad where
fmapNum1 = fmap
fmapNum1inv = fmap
fmapNum2 = liftA2
simpleVec = pure
instance (Show a, Eq a, Num a) => Num (Pair a) where
(+) = fmapNum2 (+)
() = fmapNum2 ()
(*) = fmapNum2 (*)
abs = fmapNum1inv abs
signum = fmapNum1 signum
negate = fmapNum1inv negate
fromInteger = simpleVec . fromInteger
instance (Show a, Eq a, Num a) => Num (Triple a) where
(+) = fmapNum2 (+)
() = fmapNum2 ()
(*) = fmapNum2 (*)
abs = fmapNum1inv abs
signum = fmapNum1 signum
negate = fmapNum1inv negate
fromInteger = simpleVec . fromInteger
instance (Show a, Eq a, Num a) => Num (Quad a) where
(+) = fmapNum2 (+)
() = fmapNum2 ()
(*) = fmapNum2 (*)
abs = fmapNum1inv abs
signum = fmapNum1 signum
negate = fmapNum1inv negate
fromInteger = simpleVec . fromInteger
instance Applicative Pair where
pure a = Pair (a, a)
(<*>) (Pair (fa, fb)) (Pair (a, b)) = Pair (fa a, fb b)
instance Foldable Pair where
foldr f t (Pair (x, y)) = x `f` (y `f` t)
instance Traversable Pair where
traverse f (Pair (x, y)) = Pair <$> liftA2 (,) (f x) (f y)
instance Applicative Triple where
pure a = Triple (a, a, a)
(<*>) (Triple (fa, fb, fc)) (Triple (a, b, c)) = Triple (fa a, fb b, fc c)
instance Foldable Triple where
foldr f t (Triple (x, y, z)) = x `f` (y `f` (z `f` t))
instance Traversable Triple where
traverse f (Triple (x, y, z)) = Triple <$> liftA3 (,,) (f x) (f y) (f z)
instance Applicative Quad where
pure a = Quad (a, a, a, a)
(<*>) (Quad (fa, fb, fc, fd)) (Quad (a, b, c, d))
= Quad (fa a, fb b, fc c, fd d)
instance Foldable Quad where
foldr f t (Quad (x, y, z, a)) = x `f` (y `f` (z `f` (a `f` t)))
instance Traversable Quad where
traverse f (Quad (x, y, z, a)) = Quad <$> ((,,,) <$> f x <*> f y <*> f z <*> f a)
instance Functor Pair where
fmap = fmapDefault
instance Functor Triple where
fmap = fmapDefault
instance Functor Quad where
fmap = fmapDefault
instance Coord Pair where
getComponents (Pair (a, b)) = [a, b]
fromComponents (a:b:_) = Pair (a, b)
fromComponents xs = fromComponents $ xs ++ repeat 0
instance Coord2 Pair where
getX (Pair (a, _)) = a
getY (Pair (_, b)) = b
instance Coord Triple where
getComponents (Triple (a, b, c)) = [a, b, c]
fromComponents (a:b:c:_) = Triple (a, b, c)
fromComponents xs = fromComponents $ xs ++ repeat 0
instance Coord2 Triple where
getX (Triple (a, _, _)) = a
getY (Triple (_, b, _)) = b
instance Coord3 Triple where
getZ (Triple (_, _, c)) = c
instance Coord Quad where
getComponents (Quad (a, b, c, d)) = [a, b, c, d]
fromComponents (a:b:c:d:_) = Quad (a, b, c, d)
fromComponents xs = fromComponents $ xs ++ repeat 0
instance Coord2 Quad where
getX (Quad (a, _, _, _)) = a
getY (Quad (_, b, _, _)) = b
instance Coord3 Quad where
getZ (Quad (_, _, c, _)) = c