#define Flt Double
#define VECT_Double
module Data.Vect.Flt.Util.Dim2 where
import Data.Vect.Flt.Base
structVec2 :: [Flt] -> [Vec2]
structVec2 [] = []
structVec2 (x:y:ls) = (Vec2 x y):(structVec2 ls)
structVec2 _ = error "structVec2"
destructVec2 :: [Vec2] -> [Flt]
destructVec2 [] = []
destructVec2 ((Vec2 x y):ls) = x:y:(destructVec2 ls)
det2 :: Vec2 -> Vec2 -> Flt
det2 u v = det (u,v)
vec2X :: Vec2
vec2Y :: Vec2
vec2X = Vec2 1 0
vec2Y = Vec2 0 1
translate2X :: Flt -> Vec2 -> Vec2
translate2Y :: Flt -> Vec2 -> Vec2
translate2X t (Vec2 x y) = Vec2 (x+t) y
translate2Y t (Vec2 x y) = Vec2 x (y+t)
sinCos :: Flt -> Vec2
sinCos a = Vec2 (cos a) (sin a)
sinCos' :: Flt -> Normal2
sinCos' = toNormalUnsafe . sinCos
sinCosRadius :: Flt
-> Flt
-> Vec2
sinCosRadius a r = Vec2 (r * cos a) (r * sin a)
angle2 :: Vec2 -> Flt
angle2 (Vec2 x y) = atan2 y x
angle2' :: Normal2 -> Flt
angle2' = angle2 . fromNormal
rotMatrix2 :: Flt -> Mat2
rotMatrix2 a = Mat2 (Vec2 c s) (Vec2 (s) c) where c = cos a; s = sin a
rotMatrixOrtho2 :: Flt -> Ortho2
rotMatrixOrtho2 = toOrthoUnsafe . rotMatrix2
rotate2 :: Flt -> Vec2 -> Vec2
rotate2 a v = v .* (rotMatrix2 a)
rotateCCW :: Vec2 -> Vec2
rotateCCW (Vec2 x y) = Vec2 (y) x
rotateCW :: Vec2 -> Vec2
rotateCW (Vec2 x y) = Vec2 y (x)