module Data.Geo.Jord.Vector3d
( Vector3d(..)
, IsVector3d(..)
, vadd
, vsub
, vdot
, vnorm
, vcross
, vrotate
, vscale
, vunit
, vzero
, transpose
, mdot
) where
data Vector3d = Vector3d
{ vx :: Double
, vy :: Double
, vz :: Double
} deriving (Eq, Show)
class IsVector3d a where
vec :: a -> Vector3d
vadd :: Vector3d -> Vector3d -> Vector3d
vadd v1 v2 = Vector3d x y z
where
x = vx v1 + vx v2
y = vy v1 + vy v2
z = vz v1 + vz v2
vsub :: Vector3d -> Vector3d -> Vector3d
vsub v1 v2 = Vector3d x y z
where
x = vx v1 - vx v2
y = vy v1 - vy v2
z = vz v1 - vz v2
vcross :: Vector3d -> Vector3d -> Vector3d
vcross v1 v2 = Vector3d x y z
where
x = vy v1 * vz v2 - vz v1 * vy v2
y = vz v1 * vx v2 - vx v1 * vz v2
z = vx v1 * vy v2 - vy v1 * vx v2
vdot :: Vector3d -> Vector3d -> Double
vdot v1 v2 = vx v1 * vx v2 + vy v1 * vy v2 + vz v1 * vz v2
vnorm :: Vector3d -> Double
vnorm v = sqrt (x * x + y * y + z * z)
where
x = vx v
y = vy v
z = vz v
vrotate :: Vector3d -> [Vector3d] -> Vector3d
vrotate v rm
| length rm /= 3 = error ("Invalid rotation matrix" ++ show rm)
| otherwise = Vector3d x y z
where
[x, y, z] = map (vdot v) rm
vscale :: Vector3d -> Double -> Vector3d
vscale v s = Vector3d x y z
where
x = vx v * s
y = vy v * s
z = vz v * s
vunit :: Vector3d -> Vector3d
vunit v
| s == 1.0 = v
| otherwise = vscale v s
where
s = 1.0 / vnorm v
vzero :: Vector3d
vzero = Vector3d 0 0 0
transpose :: [Vector3d] -> [Vector3d]
transpose m = fmap ds2v (transpose' xs)
where
xs = fmap v2ds m
transpose' :: [[Double]] -> [[Double]]
transpose' ([]:_) = []
transpose' x = map head x : transpose' (map tail x)
mdot :: [Vector3d] -> [Vector3d] -> [Vector3d]
mdot a b = fmap ds2v [[vdot ar bc | bc <- transpose b] | ar <- a]
v2ds :: Vector3d -> [Double]
v2ds (Vector3d x' y' z') = [x', y', z']
ds2v :: [Double] -> Vector3d
ds2v [x', y', z'] = Vector3d x' y' z'
ds2v xs = error ("Invalid list: " ++ show xs)