module Graphics.PDF.Coordinates
( module Data.Complex
, Angle(..)
, Point
, Matrix(..)
, toRadian
, dot, scalePt
, project, projectX, projectY
, pointMatrix
, transform
, identity, rotate, translate, scale, spiral
)
where
import Data.Complex
import Graphics.PDF.LowLevel.Types(PDFFloat)
data Angle = Degree !PDFFloat
| Radian !PDFFloat
toRadian :: Angle -> PDFFloat
toRadian (Degree x) = (pi / 180) * x
toRadian (Radian x) = x
type Point = Complex PDFFloat
dot :: (RealFloat t) => Complex t -> Complex t -> t
dot (x0 :+ y0) (x1 :+ y1) = x0 * x1 + y0 * y1
scalePt :: (RealFloat t) => t -> Complex t -> Complex t
scalePt a (x :+ y) = a*x :+ a*y
project :: (RealFloat t) => Complex t -> Complex t -> Complex t
project z w = scalePt (dot z w / dot w w) w
projectX :: (RealFloat t) => Complex t -> Complex t
projectX (x :+ _) = (x :+ 0)
projectY :: (RealFloat t) => Complex t -> Complex t
projectY (_ :+ y) = (0 :+ y)
data Matrix = Matrix !PDFFloat !PDFFloat !PDFFloat !PDFFloat !PDFFloat !PDFFloat deriving (Eq, Show)
instance Num Matrix where
(+) (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
identity :: Matrix
identity = Matrix 1 0 0 1 0 0
pointMatrix :: Point
-> Point
-> Point
-> Matrix
pointMatrix (x0 :+ y0) (x1 :+ y1) (x2 :+ y2) = Matrix x0 y0 x1 y1 x2 y2
transform :: Matrix -> Point -> Point
transform (Matrix x0 y0 x1 y1 x2 y2) (x :+ y) = (x*x0 + y*x1 + x2) :+ (x*y0 + y*y1 + y2)
rotate :: Angle
-> Matrix
rotate r = spiral (cis (toRadian r))
translate :: Point
-> Matrix
translate (tx :+ ty) = Matrix 1 0 0 1 tx ty
spiral :: Point
-> Matrix
spiral (x :+ y) = Matrix x y (-y) x 0 0
scale :: PDFFloat
-> PDFFloat
-> Matrix
scale sx sy = Matrix sx 0 0 sy 0 0