module Data.Geometry.Ipe.IpeGeometryTypes where import Data.Geometry.Point import Data.Geometry.Line import Data.Geometry.Polygon import Data.Geometry.Geometry import Data.Geometry.Ipe.InternalTypes(HasAttributes(..),AMap) import qualified Data.Map as M -------------------------------------------------------------------------------------- -- | An ipe point. data IpePoint' a = IpePoint (Point2' a) AMap deriving (Eq, Ord, Read, Show) instance IsPoint2Functor IpePoint' where p2fmap f (IpePoint p a) = IpePoint (f p) a instance HasPoints IpePoint' where points (IpePoint p _) = [p] instance HasAttributes (IpePoint' a) where attrs (IpePoint _ a) = a updateWith f (IpePoint p a) = IpePoint p (f a) -- | create a default ipe point from a given point fromPoint :: Point2' a -> IpePoint' a fromPoint = flip IpePoint $ M.fromList [("name","mark/disk(sx)")] -------------------------------------------------------------------------------------- -- | A polyline data IpePolyline' a = IpePolyline [LineSegment2' a] AMap deriving (Show, Eq) instance IsPoint2Functor IpePolyline' where p2fmap f (IpePolyline lines a) = IpePolyline (map (p2fmap f) lines) a instance HasPoints IpePolyline' where points = points . toPolyLine instance HasAttributes (IpePolyline' a) where attrs (IpePolyline _ a) = a updateWith f (IpePolyline p a) = IpePolyline p (f a) toPolyLine :: IpePolyline' a -> Polyline2' a toPolyLine (IpePolyline ls _) = Polyline2 ls fromPolyline :: Polyline2' a -> IpePolyline' a fromPolyline (Polyline2 ls) = IpePolyline ls M.empty -------------------------------------------------------------------------------------- -- | Polygons data IpeSimplePolygon' a = IpeSimplePolygon [Point2' a] AMap deriving (Show, Eq) instance IsPoint2Functor IpeSimplePolygon' where p2fmap f (IpeSimplePolygon pts a) = IpeSimplePolygon (map f pts) a instance HasPoints IpeSimplePolygon' where points (IpeSimplePolygon pts _) = pts instance HasAttributes (IpeSimplePolygon' a) where attrs (IpeSimplePolygon _ a) = a updateWith f (IpeSimplePolygon p a) = IpeSimplePolygon p (f a) instance IsPolygon IpeSimplePolygon' where isSimple = const True containsHoles = const False -- note a ipeMultiPolygon consists of ``SimplePolygon''s, not ``IpeSimplePolygon''s data IpeMultiPolygon' a = IpeMultiPolygon [SimplePolygon' a] AMap deriving (Show, Eq) instance IsPoint2Functor IpeMultiPolygon' where p2fmap f (IpeMultiPolygon polys a) = IpeMultiPolygon (map (p2fmap f) polys) a instance HasPoints IpeMultiPolygon' where points (IpeMultiPolygon polys _) = concatMap points polys instance HasAttributes (IpeMultiPolygon' a) where attrs (IpeMultiPolygon _ a) = a updateWith f (IpeMultiPolygon p a) = IpeMultiPolygon p (f a) -- TODO whether or not there are holes or the thing is simple actually depends -- on the thing, so we need code here rather than a simple const False instance IsPolygon IpeMultiPolygon' where isSimple = const False containsHoles = const False