module Graphics.PS.Pt ( Pt(Pt), polarToRectangular, ptMin, ptMax, ptXYs, origin, ptTransform ) where import Graphics.PS.Matrix -- | Point data type, component values are real. data Pt = Pt Double Double deriving (Eq, Show) instance Num Pt where negate (Pt x y) = Pt (- x) (- y) Pt x0 y0 + Pt x1 y1 = Pt (x0 + x1) (y0 + y1) Pt x0 y0 - Pt x1 y1 = Pt (x0 - x1) (y0 - y1) Pt x0 y0 * Pt x1 y1 = Pt (x0 * x1) (y0 * y1) abs (Pt x y) = Pt (abs x) (abs y) signum _ = 0 fromInteger a = let a' = fromInteger a in Pt a' a' instance Ord Pt where (Pt x0 y0) <= (Pt x1 y1) = x0 <= x1 && y0 <= y1 -- | Origin, ie. (Pt 0 0). origin :: Pt origin = Pt 0 0 ptXYs :: [Pt] -> [Double] ptXYs [] = [] ptXYs (Pt x y : ps) = x : y : ptXYs ps ptOp :: (Double -> Double -> Double) -> Pt -> Pt -> Pt ptOp op (Pt x1 y1) (Pt x2 y2) = Pt (op x1 x2) (op y1 y2) ptMin :: Pt -> Pt -> Pt ptMin = ptOp min ptMax :: Pt -> Pt -> Pt ptMax = ptOp max -- | Convert from polar to rectangular co-ordinates. polarToRectangular :: Pt -> Pt polarToRectangular (Pt r t) = Pt (r * cos t) (r * sin t) -- | Apply a transformation matrix to a point. ptTransform :: Matrix -> Pt -> Pt ptTransform (Matrix a b c d e f) (Pt x y) = let x' = x * a + y * c + e y' = x * b + y * d + f in Pt x' y' {-- pt :: (Double, Double) -> Pt pt (x,y) = Pt x y ptX :: Pt -> Double ptX (Pt x _) = x ptY :: Pt -> Double ptY (Pt _ y) = y hypot :: (Floating a) => a -> a -> a hypot x y = sqrt (x * x + y * y) distance :: Pt -> Pt -> Double distance (Pt x1 y1) (Pt x2 y2) = hypot (x2 - x1) (y2 - y1) rectangularToPolar :: Pt -> Pt rectangularToPolar (Pt x y) | (x == 0) && (y == 0) = Pt 0 t | otherwise = Pt (atan2 y x) t where t = hypot x y --}