{-# LANGUAGE ForeignFunctionInterface #-} -- Polygon.chs -- hgeometric: A geometric library with bindings to GPC. -- Polygon.chs is part of hgeometric. -- Copyright (C) 2007 Marco TĂșlio Gontijo e Silva -- Copyright (C) 2007 Rafael Cunha de Almeida -- hgeometric is free software; you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation; either version 2 of the License, or -- (at your option) any later version. -- hgeometric is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- You should have received a copy of the GNU General Public License -- along with hgeometric; if not, write to the Free Software -- Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA -- | 'Polygon' data type. module Algebra.Geometric.Polygon (Polygon (PolygonC, polygonSet)) where #include "gpc.h" import Data.Set hiding (map) import Control.Monad import Foreign import Foreign.C import Algebra.Geometric.Area import Algebra.Geometric.Contour {#context prefix = "gpc"#} -- | A 'Polygon', which support holes and disjoint areas. Each 'Bool' in the -- tuple tells if the 'Contour' is the border of a hole ('True') or of a -- 'Polygon' ('False'). newtype Polygon = PolygonC {polygonSet :: Set (Bool, Contour)} deriving Show {#pointer *vertex_list as CContour -> Contour#} instance Storable Polygon where sizeOf _ = {#sizeof polygon#} alignment _ = alignment (undefined :: Int) peek cPolygon = (PolygonC . fromList) `liftM` do numContours <- fromIntegral `liftM` {#get polygon.num_contours#} cPolygon cHoles <- {#get polygon.hole#} cPolygon holes <- peekArray numContours cHoles cContours <- {#get polygon.contour#} cPolygon contours <- peekArray numContours cContours return $ zip (map toBool holes) contours poke cPolygon (PolygonC polygon) = do {#set polygon.num_contours#} cPolygon $ fromIntegral $ size polygon cHoles <- newArray $ map fromBool holes {#set polygon.hole#} cPolygon cHoles cContours <- newArray contours {#set polygon.contour#} cPolygon cContours where (holes, contours) = unzip $ toList polygon instance Area Polygon where area (PolygonC polygon) = sum $ map signal $ toList polygon where signal (False, contour) = area contour signal (True, contour) = negate $ area contour