{-# LANGUAGE ForeignFunctionInterface #-} -- | FFI module for defining and using rectangles module GEGL.FFI.Rectangle ( GeglRectangle(..) , c_gegl_rectangle_intersect -- , c_gegl_rectangle_infinite_plane ) where import Foreign import Foreign.Ptr import Foreign.C.Types #include -- | A standard GEGL rectangle data GeglRectangle = GeglRectangle { rectangleX :: Int -- ^ X coordinate of upper left corner , rectangleY :: Int -- ^ Y coordinate of upper left corner , rectangleWidth :: Int -- ^ Width in pixels , rectangleHeight :: Int -- ^ Height in picels } deriving (Show) instance Storable GeglRectangle where sizeOf _ = (#size GeglRectangle) alignment _ = alignment (undefined :: CDouble) peek ptr = do x <- (#peek GeglRectangle, x) ptr :: IO CInt y <- (#peek GeglRectangle, y) ptr :: IO CInt width <- (#peek GeglRectangle, width) ptr :: IO CInt height <- (#peek GeglRectangle, height) ptr :: IO CInt return GeglRectangle { rectangleX = fromIntegral x , rectangleY = fromIntegral y , rectangleWidth = fromIntegral width , rectangleHeight = fromIntegral height } poke ptr (GeglRectangle x y w h) = do (#poke GeglRectangle, x) ptr (CInt $ fromIntegral x) (#poke GeglRectangle, y) ptr (CInt $ fromIntegral y) (#poke GeglRectangle, width) ptr (CInt $ fromIntegral w) (#poke GeglRectangle, height) ptr (CInt $ fromIntegral h) -- | Interface to @gegl_rectangle_intersect@ function in C. foreign import ccall unsafe "gegl.h gegl_rectangle_intersect" c_gegl_rectangle_intersect :: Ptr GeglRectangle -- ^ destination rectangle -> Ptr GeglRectangle -- ^ A Rectangle -> Ptr GeglRectangle -- ^ A rectangle -> IO Bool -- ^ Returns @True@ if rectangles intersect -- -- | Interface to the @gegl_rectangle_infinite_plane@ function in C. -- foreign import ccall unsafe "gegl.h gegl_rectangle_infinite_plane" -- c_gegl_rectangle_infinite_plane -- :: GeglRectangle