{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, TypeSynonymInstances #-} module Graphics.SceneGraph.Matrix where -- Warning: Because this matrix is going to get passed directly to GL we convert to GL space -- here. import Graphics.Rendering.OpenGL hiding (Matrix) import Graphics.SceneGraph.Vector import Data.List import Numeric.LinearAlgebra -- (inv, (><),toLists,Matrix,Vector,mul,fromLists,toList,fromList ) type MatrixD = Matrix GLdouble identityMatrix :: MatrixD identityMatrix = fromLists [ [1,0,0,0], [0,1,0,0], [0,0,1,0],[0,0,0,1]] asMatrix :: VectorD -> MatrixD asMatrix vec = let v = toList vec in fromLists [ [1, 0, 0, v!!0],[ 0, 1, 0, v!!2],[ 0, 0, 1 , (-(v!!1))],[ 0, 0, 0, 1] ] translateM :: VectorD -> MatrixD -> MatrixD translateM v m = (asMatrix v) `multiply` m translatePostM :: VectorD -> MatrixD -> MatrixD translatePostM v m = m `multiply` (asMatrix v) scaleM :: VectorD -> MatrixD -> MatrixD scaleM vec m = let v = toList vec in m `multiply` (fromLists [ [ v!!0,0,0,0],[ 0, v!!2,0,0],[ 0, 0, (-(v!!1)),0],[ 0, 0, 0, 1] ]) -- | Build rotational transform matrix for rotate of ''theta'' around a vector. rotateM' :: ((Element a)) => a -> Vector a -> Matrix a rotateM' theta v = fromLists [ [ t*x*x + c, t*x*y-s*z, t*x*z + s*y, 0], [ t*x*y+s*z, t*y*y + c, t*y*z - s*x , 0], [ t*x*z-s*y, t*y*z + s*x, t*z*z+c, 0], [0,0,0,1]] where t = 1 - cos theta c = cos theta s = sin theta [x',y',z'] = toList v [x,y,z] = [x',z',(-y')] rotateM theta v m = (rotateM' theta v) `multiply` m rotatePostM theta v m = m `multiply` (rotateM' theta v) mulV :: MatrixD -> VectorD -> VectorD mulV m v = head $ toColumns $ m `multiply` (asColumn v)