-- GENERATED by C->Haskell Compiler, version 0.16.0 Crystal Seed, 24 Jan 2009 (Haskell) -- Edit the ORIGNAL .chs file instead! {-# LINE 1 "./Algebra/Geometric/Strip.chs" #-}{-# LANGUAGE ForeignFunctionInterface #-} -- Strip.chs -- hgeometric: A geometric library with bindings to GPC. -- Strip.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 -- | 'Strip' data type and convertions. module Algebra.Geometric.Strip ( -- * Data Type Strip (StripC, stripSet), -- * Convertion safePolygonToStrip, polygonToStrip) where import Data.Set hiding (map) import Control.Monad import Foreign import Foreign.C import Algebra.Geometric.Contour import Algebra.Geometric.Polygon {-# LINE 43 "./Algebra/Geometric/Strip.chs" #-} type CContour = Ptr (Contour) {-# LINE 45 "./Algebra/Geometric/Strip.chs" #-} type CPolygon = Ptr (Polygon) {-# LINE 46 "./Algebra/Geometric/Strip.chs" #-} type CStrip = Ptr (Strip) {-# LINE 47 "./Algebra/Geometric/Strip.chs" #-} -- | A 'Strip' is an alternative form of representing a 'Polygon' composed -- by 'Contour's that are not holes. It's a good idea to use it to draw filled -- figures, and to use 'Polygon' to draw the 'Contour's. newtype Strip = StripC {stripSet :: Set Contour} deriving Show instance Storable Strip where sizeOf _ = 8 {-# LINE 55 "./Algebra/Geometric/Strip.chs" #-} alignment _ = alignment (undefined :: Int) peek cStrip = (StripC . fromList) `liftM` do numStrips <- fromIntegral `liftM` (\ptr -> do {peekByteOff ptr 0 ::IO CInt}) cStrip (\ptr -> do {peekByteOff ptr 4 ::IO (CContour)}) cStrip >>= peekArray numStrips poke cStrip (StripC strip) = (\ptr val -> do {pokeByteOff ptr 0 (val::CInt)}) cStrip (fromIntegral $ size strip) >> newArray (toList strip) >>= (\ptr val -> do {pokeByteOff ptr 4 (val::(CContour))}) cStrip -- | An 'IO' version of 'polygonToStrip', which does not use 'unsafePerformIO'. safePolygonToStrip :: Polygon -> IO Strip safePolygonToStrip polygon = alloca $ \cStrip -> alloca $ \cPolygon -> do poke cPolygon polygon gpc_polygon_to_tristrip cPolygon cStrip result <- peek cStrip gpc_free_polygon cPolygon gpc_free_tristrip cStrip return result -- | Converts a 'Polygon' to a 'Strip'. polygonToStrip :: Polygon -> Strip polygonToStrip = unsafePerformIO . safePolygonToStrip foreign import ccall unsafe "Algebra/Geometric/Strip.chs.h gpc_polygon_to_tristrip" gpc_polygon_to_tristrip :: ((CPolygon) -> ((CStrip) -> (IO ()))) foreign import ccall unsafe "Algebra/Geometric/Strip.chs.h gpc_free_polygon" gpc_free_polygon :: ((CPolygon) -> (IO ())) foreign import ccall unsafe "Algebra/Geometric/Strip.chs.h gpc_free_tristrip" gpc_free_tristrip :: ((CStrip) -> (IO ()))