module Graphics.SceneGraph.Vector where
import Graphics.Rendering.OpenGL
import Numeric.LinearAlgebra (Vector,fromList)
import Foreign.Storable
type VectorD = Vector GLdouble
betweenV3 :: (Storable a,Num a) => Vertex3 a -> Vertex3 a -> Vector a
betweenV3 (Vertex3 x y z) (Vertex3 x' y' z') = vector3 (x'x) (y'y) (z'z)
lengthV3 :: Floating a => Vector3 a -> a
lengthV3 (Vector3 x y z) = sqrt (x*x + y*y + z*z)
vector3X (Vector3 x _ _) = x
vector3Y (Vector3 _ y _) = y
vector3Z (Vector3 _ _ z) = z
vector3 :: (Storable a,Num a) => a -> a -> a -> Vector a
vector3 x y z = fromList [x,y,z]
vx,vy :: (Storable a,Num a) => a -> Vector a
vx x = vector3 x 0 0
vy y = vector3 0 y 0
vxy,vxz :: (Storable a,Num a) => a -> a -> Vector a
vxy x y = vector3 x y 0
vxz x z = vector3 x 0 z
vz,v1z,v1y,v1x :: (Storable a,Num a) => a -> Vector a
vz = vector3 0 0
v1z = vector3 1 1
v1y y = vector3 1 y 1
v1x x = vector3 x 1 1
v0,v1 :: VectorD
v0 = vector3 0 0 0
v1 = vector3 1 1 1
vyz :: (Storable a,Num a) => a -> a -> Vector a
vyz = vector3 0