{-# LANGUAGE MultiParamTypeClasses, FlexibleContexts #-} {-# OPTIONS_GHC -Wall #-} ---------------------------------------------------------------------- -- | -- Module : Graphics.FieldTrip.Transform3 -- Copyright : (c) Conal Elliott and Andy J Gill 2008 -- License : BSD3 -- -- Maintainer : conal@conal.net, andygill@ku.edu -- Stability : experimental -- -- 3D transforms ---------------------------------------------------------------------- module Graphics.FieldTrip.Transform3 ( Transform3(..) , translate3, rotate3, scale3, uscale3 , tweakMatrix3, tweakError3 ) where import Data.Monoid import Data.VectorSpace (AdditiveGroup,negateV) import Graphics.Rendering.OpenGL import Graphics.FieldTrip.Vector3 import Graphics.FieldTrip.Render (ErrorBound) import Graphics.FieldTrip.Transform -- | 3D affine transform data Transform3 s = Identity3 | Translate3 (Vector3 s) | Rotate3 s (Vector3 s) -- ^ angle (radians) and axis | Scale3 s s s | Compose3 (Transform3 s) (Transform3 s) -- outer and inner deriving (Eq,Show) instance (Fractional s, AdditiveGroup s) => Invertible (Transform3 s) where inverse Identity3 = Identity3 inverse (Translate3 v) = Translate3 (negateV v) inverse (Rotate3 a axis) = Rotate3 (-a) axis inverse (Scale3 r s t) = Scale3 (recip r) (recip s) (recip t) inverse (Compose3 outer inner) = Compose3 (inverse inner) (inverse outer) -- | Translation (motion) in 3D translate3 :: Vector3 s -> Transform3 s translate3 = Translate3 -- | Rotation in 3D, with angle in radians. rotate3 :: s -> Vector3 s -> Transform3 s rotate3 = Rotate3 -- | Scaling in 3D scale3 :: s -> s -> s -> Transform3 s scale3 = Scale3 -- | Uniform scale in 3D. uscale3 :: s -> Transform3 s uscale3 s = scale3 s s s instance Monoid (Transform3 s) where mempty = Identity3 mappend = Compose3 -- TODO: optimize mappend -- instance Transform (Transform3 s) (Point3 s) where -- xf *% p = ... -- instance Transform (Transform3 s) (Vector3 s) where -- xf *% v = ... -- instance Transform (Transform3 s) (Normal3 s) where -- xf *% n = ... -- | Change the matrix state, according to the given transform. tweakMatrix3 :: (Floating s, MatrixComponent s) => Transform3 s -> IO () tweakMatrix3 Identity3 = return () tweakMatrix3 (Translate3 vec) = translate vec tweakMatrix3 (Rotate3 r vec ) = rotate (r * (180/pi)) vec tweakMatrix3 (Scale3 x y z ) = scale x y z tweakMatrix3 (Compose3 o i) = tweakMatrix3 o >> tweakMatrix3 i -- Error bounds. Needs to be worked through carefully. My treatment -- doesn't yet consider the effect of perspective viewing on Translate3, -- which is considerable. -- | Change the required upper error bound, to one that applies before -- transforming. Hack for now. tweakError3 :: (Real s, Fractional s) => Transform3 s -> ErrorBound -> ErrorBound tweakError3 (Scale3 x y z ) = (/ toBound (abs x `max` abs y `max` abs z)) -- guess tweakError3 (Compose3 o i) = tweakError3 o . tweakError3 i tweakError3 _ = id toBound :: (Real s, Fractional s) => s -> ErrorBound toBound = fromRational . toRational