module Graphics.Rendering.Cairo.Matrix (
Matrix(Matrix)
, MatrixPtr
, identity
, translate
, scale
, rotate
, transformDistance
, transformPoint
, scalarMultiply
, adjoint
, invert
) where
import Foreign hiding (rotate)
import Foreign.C
data Matrix = Matrix { xx :: !Double, yx :: !Double,
xy :: !Double, yy :: !Double,
x0 :: !Double, y0 :: !Double }
deriving (Show, Eq)
type MatrixPtr = Ptr (Matrix)
instance Storable Matrix where
sizeOf _ = 48
alignment _ = alignment (undefined :: CDouble)
peek p = do
xx <- (\ptr -> do {peekByteOff ptr 0 ::IO CDouble}) p
yx <- (\ptr -> do {peekByteOff ptr 8 ::IO CDouble}) p
xy <- (\ptr -> do {peekByteOff ptr 16 ::IO CDouble}) p
yy <- (\ptr -> do {peekByteOff ptr 24 ::IO CDouble}) p
x0 <- (\ptr -> do {peekByteOff ptr 32 ::IO CDouble}) p
y0 <- (\ptr -> do {peekByteOff ptr 40 ::IO CDouble}) p
return $ Matrix (realToFrac xx) (realToFrac yx)
(realToFrac xy) (realToFrac yy)
(realToFrac x0) (realToFrac y0)
poke p (Matrix xx yx xy yy x0 y0) = do
(\ptr val -> do {pokeByteOff ptr 0 (val::CDouble)}) p (realToFrac xx)
(\ptr val -> do {pokeByteOff ptr 8 (val::CDouble)}) p (realToFrac yx)
(\ptr val -> do {pokeByteOff ptr 16 (val::CDouble)}) p (realToFrac xy)
(\ptr val -> do {pokeByteOff ptr 24 (val::CDouble)}) p (realToFrac yy)
(\ptr val -> do {pokeByteOff ptr 32 (val::CDouble)}) p (realToFrac x0)
(\ptr val -> do {pokeByteOff ptr 40 (val::CDouble)}) p (realToFrac y0)
return ()
instance Num Matrix where
(*) (Matrix xx yx xy yy x0 y0) (Matrix xx' yx' xy' yy' x0' y0') =
Matrix (xx * xx' + yx * xy')
(xx * yx' + yx * yy')
(xy * xx' + yy * xy')
(xy * yx' + yy * yy')
(x0 * xx' + y0 * xy' + x0')
(x0 * yx' + y0 * yy' + y0')
(+) = pointwise2 (+)
() = pointwise2 ()
negate = pointwise negate
abs = pointwise abs
signum = pointwise signum
fromInteger n = Matrix (fromInteger n) 0 0 (fromInteger n) 0 0
pointwise f (Matrix xx yx xy yy x0 y0) =
Matrix (f xx) (f yx) (f xy) (f yy) (f x0) (f y0)
pointwise2 f (Matrix xx yx xy yy x0 y0) (Matrix xx' yx' xy' yy' x0' y0') =
Matrix (f xx xx') (f yx yx') (f xy xy') (f yy yy') (f x0 x0') (f y0 y0')
identity :: Matrix
identity = Matrix 1 0 0 1 0 0
translate :: Double -> Double -> Matrix -> Matrix
translate tx ty m = m * (Matrix 1 0 0 1 tx ty)
scale :: Double -> Double -> Matrix -> Matrix
scale sx sy m = m * (Matrix sx 0 0 sy 0 0)
rotate :: Double -> Matrix -> Matrix
rotate r m = m * (Matrix c s (s) c 0 0)
where s = sin r
c = cos r
transformDistance :: Matrix -> (Double,Double) -> (Double,Double)
transformDistance (Matrix xx yx xy yy _ _) (dx,dy) =
newX `seq` newY `seq` (newX,newY)
where newX = xx * dx + xy * dy
newY = yx * dx + yy * dy
transformPoint :: Matrix -> (Double,Double) -> (Double,Double)
transformPoint (Matrix xx yx xy yy x0 y0) (dx,dy) =
newX `seq` newY `seq` (newX,newY)
where newX = xx * dx + xy * dy + x0
newY = yx * dx + yy * dy + y0
scalarMultiply :: Double -> Matrix -> Matrix
scalarMultiply scalar = pointwise (*scalar)
adjoint :: Matrix -> Matrix
adjoint (Matrix a b c d tx ty) =
Matrix d (b) (c) a (c*ty d*tx) (b*tx a*ty)
invert :: Matrix -> Matrix
invert m@(Matrix xx yx xy yy _ _) = scalarMultiply (recip det) $ adjoint m
where det = xx*yy yx*xy