--------------------------------------------------------- -- | -- Copyright : (c) alpha 2007 -- License : BSD-style -- -- Maintainer : misc@NOSPAMalpheccar.org -- Stability : experimental -- Portability : portable -- -- Coordinates for a PDF document --------------------------------------------------------- module Graphics.PDF.Coordinates( -- * Geometry -- ** Types Angle(..) , Matrix(..) -- ** Transformations , rotate, translate, scale, identity -- ** Frame of reference operators , applyMatrix ) where import Graphics.PDF.LowLevel.Types import Graphics.PDF.Draw import Control.Monad.Writer import Graphics.PDF.LowLevel.Serializer import Data.Monoid -- | Angle data Angle = Degree PDFFloat -- ^ Angle in degrees | Radian PDFFloat -- ^ Angle in radians -- | A transformation matrix. An affine transformation a b c d e f -- -- @ -- a b e -- c d f -- 0 0 1 -- @ data Matrix = Matrix !PDFFloat !PDFFloat !PDFFloat !PDFFloat !PDFFloat !PDFFloat deriving (Eq) -- | Identity matrix identity :: Matrix identity = Matrix 1.0 0 0 1.0 0 0 instance Show Matrix where show (Matrix ma mb mc md me mf) = "Matrix " ++ (unwords [(show ma),(show mb),(show mc),(show md),(show me),(show mf)]) instance Num Matrix where -- Matrix addition (+) (Matrix ma mb mc md me mf ) (Matrix na nb nc nd ne nf) = Matrix (ma+na) (mb+nb) (mc+nc) (md+nd) (me+ne) (mf+nf) (*) (Matrix ma mb mc md me mf) (Matrix na nb nc nd ne nf) = Matrix (ma*na+mb*nc) (ma*nb + mb*nd ) (mc*na+md*nc) (mc*nb +md*nd) (me*na+mf*nc+ne) (me*nb+mf*nd+nf) negate (Matrix ma mb mc md me mf ) = Matrix (-ma) (-mb) (-mc) (-md) (-me) (-mf) abs m = m signum _ = identity fromInteger i = Matrix r 0 0 r 0 0 where r = fromInteger i -- | Apply a transformation matrix to the current coordinate frame applyMatrix :: Matrix -> Draw () applyMatrix (Matrix a b c d e f) = tell . mconcat $[ serialize '\n' , toPDF a , serialize ' ' , toPDF b , serialize ' ' , toPDF c , serialize ' ' , toPDF d , serialize ' ' , toPDF e , serialize ' ' , toPDF f , serialize " cm" ] -- | Rotation matrix rotate :: Angle -- ^ Rotation angle -> Matrix rotate r = Matrix ( (cos radian)) ( (sin radian)) (- ( (sin radian))) ( (cos radian)) 0 0 where radian = case r of Degree angle -> angle / 180 * pi Radian angle -> angle -- | Translation matrix translate :: PDFFloat -- ^ Horizontal translation -> PDFFloat -- ^ Vertical translation -> Matrix translate tx ty = Matrix 1 0 0 1 tx ty -- | Scaling matrix scale :: PDFFloat -- ^ Horizontal scaling -> PDFFloat -- ^ Horizontal scaling -> Matrix scale sx sy = Matrix sx 0 0 sy 0 0