-- | Classic 4x4 projective matrices. Our convention is that they are intended for multiplication on -- the /right/, that is, they are of the form -- -- > _____ -- > [ | | 0 ] -- > [ | 3x3 | 0 ] -- > [ |_____| 0 ] -- > [ p q r 1 ] -- -- Please note that by default, OpenGL stores the matrices (in memory) by columns, while we -- store them by rows; but OpenGL also use the opposite convention (so the OpenGL projective matrices -- are intended for multiplication on the /left/). So in effect, they are the same when stored in the memory, -- say with @poke :: Ptr Mat4 -> Mat4 -> IO ()@. module Data.Vect.Flt.Util.Projective where import Data.Vect.Flt.Base import Data.Vect.Flt.Util.Dim3 import qualified Data.Vect.Flt.Util.Dim4 as Dim4 class ExtendProjective v e | v->e where extendProj :: v -> e extendProjWith :: Flt -> v -> e extendProj = extendProjWith 1 instance ExtendProjective Vec2 Vec4 where extendProj (Vec2 x y) = Vec4 x y 0 1 extendProjWith w (Vec2 x y) = Vec4 x y 0 w instance ExtendProjective Vec3 Vec4 where extendProj (Vec3 x y z) = Vec4 x y z 1 extendProjWith w (Vec3 x y z) = Vec4 x y z w instance ExtendProjective Vec4 Vec4 where extendProj = id extendProjWith w (Vec4 x y z w') = let s = w/w' in Vec4 (s*x) (s*y) (s*z) w instance ExtendProjective Mat2 Mat4 where extendProj (Mat2 r1 r2) = Mat4 (extendZero r1) (extendZero r2) (Dim4.vec4Z) (Vec4 0 0 0 1) extendProjWith w (Mat2 r1 r2) = Mat4 (extendZero r1) (extendZero r2) (Dim4.vec4Z) (Vec4 0 0 0 w) instance ExtendProjective Mat3 Mat4 where extendProj (Mat3 r1 r2 r3) = Mat4 (extendZero r1) (extendZero r2) (extendZero r3) (Vec4 0 0 0 1) extendProjWith w (Mat3 r1 r2 r3) = Mat4 (extendZero r1) (extendZero r2) (extendZero r3) (Vec4 0 0 0 w) rotMatrixProj :: Flt -> Normal3 -> Mat4 rotMatrixProj angle axis = extendProj $ rotMatrix3' axis angle rotMatrixProj' :: {- ' CPP is sensitive to primes -} Flt -> Vec3 -> Mat4 rotMatrixProj' angle axis = extendProj $ rotMatrix3 axis angle translMatrixProj :: Vec3 -> Mat4 translMatrixProj v = Mat4 Dim4.vec4X Dim4.vec4Y Dim4.vec4Z (extendProj v) -- | we assume that the bottom-right corner is 1. translWithProj :: Vec3 -> Mat4 -> Mat4 translWithProj v mat@(Mat4 r1 r2 r3 r4) = Mat4 r1 r2 r3 (extendProjWith 0 v &+ r4) scaleMatrixProj :: Vec3 -> Mat4 scaleMatrixProj v = diag $ extendProj v scaleMatrixUniformProj :: Flt -> Mat4 scaleMatrixUniformProj s = diag (Vec4 s s s 1) class ProjectiveAction v where actProj :: v -> Mat4 -> v instance ProjectiveAction Vec3 where actProj v m = trim $ (extendProj v) .* m instance ProjectiveAction Vec4 where actProj v m = v .* m -- | When acting on unit vectors, we ignore the translation part. instance ProjectiveAction Normal3 where actProj (Normal3 v) m = Normal3 (v .* (trim m :: Mat3)) -- | Inverts a projective 4x4 matrix, assuming that the top-left 3x3 part is /orthogonal/, -- and the bottom-right corner is 1. invertProj :: Mat4 -> Mat4 invertProj mat@(Mat4 u v w t) = translWithProj t' $ extendProj $ transpose $ (trim mat :: Mat3) where t' = Vec3 (- u &. t) (- v &. t) (- w &. t)