{-# OPTIONS -fno-warn-missing-methods #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Graphics.Gloss.Data.Vector
( Vector
, magV
, argV
, dotV
, detV
, mulSV
, rotateV
, angleVV
, normalizeV
, unitVectorAtAngle )
where
import Graphics.Gloss.Data.Picture
import Graphics.Gloss.Geometry.Angle
magV :: Vector -> Float
magV (x, y)
= sqrt (x * x + y * y)
{-# INLINE magV #-}
argV :: Vector -> Float
argV (x, y)
= normalizeAngle $ atan2 y x
{-# INLINE argV #-}
dotV :: Vector -> Vector -> Float
dotV (x1, x2) (y1, y2)
= x1 * y1 + x2 * y2
{-# INLINE dotV #-}
detV :: Vector -> Vector -> Float
detV (x1, y1) (x2, y2)
= x1 * y2 - y1 * x2
{-# INLINE detV #-}
mulSV :: Float -> Vector -> Vector
mulSV s (x, y)
= (s * x, s * y)
{-# INLINE mulSV #-}
rotateV :: Float -> Vector -> Vector
rotateV r (x, y)
= ( x * cos r - y * sin r
, x * sin r + y * cos r)
{-# INLINE rotateV #-}
angleVV :: Vector -> Vector -> Float
angleVV p1 p2
= let m1 = magV p1
m2 = magV p2
d = p1 `dotV` p2
aDiff = acos $ d / (m1 * m2)
in aDiff
{-# INLINE angleVV #-}
normalizeV :: Vector -> Vector
normalizeV v = mulSV (1 / magV v) v
{-# INLINE normalizeV #-}
unitVectorAtAngle :: Float -> Vector
unitVectorAtAngle r
= (cos r, sin r)
{-# INLINE unitVectorAtAngle #-}