module Graphics.UI.Gtk.Gdk.Region (
makeNewRegion,
Region(Region),
regionNew,
FillRule(..),
regionPolygon,
regionCopy,
regionRectangle,
regionGetClipbox,
regionGetRectangles,
regionEmpty,
regionEqual,
regionPointIn,
OverlapType(..),
regionRectIn,
regionOffset,
regionShrink,
regionUnionWithRect,
regionIntersect,
regionUnion,
regionSubtract,
regionXor) where
import Control.Monad (liftM)
import System.Glib.FFI
import Graphics.UI.Gtk.General.Structs (Point, Rectangle(..))
newtype Region = Region (ForeignPtr (Region))
instance Show Region where
show r = show (unsafePerformIO (regionGetRectangles r))
makeNewRegion :: Ptr Region -> IO Region
makeNewRegion rPtr = do
region <- newForeignPtr rPtr region_destroy
return (Region region)
foreign import ccall unsafe "&gdk_region_destroy"
region_destroy :: FinalizerPtr Region
data FillRule = EvenOddRule
| WindingRule
deriving (Enum)
data OverlapType = OverlapRectangleIn
| OverlapRectangleOut
| OverlapRectanglePart
deriving (Enum)
regionNew :: IO Region
regionNew = do
rPtr <- gdk_region_new
makeNewRegion rPtr
regionPolygon :: [Point] -> FillRule -> IO Region
regionPolygon points rule =
withArray (concatMap (\(x,y) -> [fromIntegral x, fromIntegral y]) points) $
\(aPtr :: Ptr (CInt)) -> do
rPtr <- gdk_region_polygon (castPtr aPtr)
(fromIntegral (length points)) ((fromIntegral.fromEnum) rule)
makeNewRegion rPtr
regionCopy :: Region -> IO Region
regionCopy r = do
rPtr <- (\(Region arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_region_copy argPtr1) r
makeNewRegion rPtr
regionRectangle :: Rectangle -> IO Region
regionRectangle rect = with rect $ \rectPtr -> do
regPtr <- gdk_region_rectangle (castPtr rectPtr)
makeNewRegion regPtr
regionGetClipbox :: Region -> IO Rectangle
regionGetClipbox r = alloca $ \rPtr -> do
(\(Region arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_region_get_clipbox argPtr1 arg2) r (castPtr rPtr)
peek rPtr
regionGetRectangles :: Region -> IO [Rectangle]
regionGetRectangles region =
alloca $ \(rectPtrPtr :: Ptr (Ptr Rectangle)) ->
alloca $ \(iPtr :: Ptr (CInt)) -> do
(\(Region arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gdk_region_get_rectangles argPtr1 arg2 arg3) region (castPtr rectPtrPtr) iPtr
size <- peek iPtr
rectPtr <- peek rectPtrPtr
rects <- peekArray (fromIntegral size) rectPtr
g_free (castPtr rectPtr)
return rects
regionEmpty :: Region -> IO Bool
regionEmpty r = liftM toBool $ (\(Region arg1) -> withForeignPtr arg1 $ \argPtr1 ->gdk_region_empty argPtr1) r
regionEqual :: Region -> Region -> IO Bool
regionEqual r1 r2 = liftM toBool $ (\(Region arg1) (Region arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gdk_region_equal argPtr1 argPtr2) r1 r2
regionPointIn :: Region -> Point -> IO Bool
regionPointIn r (x,y) = liftM toBool $
(\(Region arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gdk_region_point_in argPtr1 arg2 arg3) r (fromIntegral x) (fromIntegral y)
regionRectIn :: Region -> Rectangle -> IO OverlapType
regionRectIn reg rect = liftM (toEnum.fromIntegral) $ with rect $
\rPtr -> (\(Region arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_region_rect_in argPtr1 arg2) reg (castPtr rPtr)
regionOffset :: Region -> Int -> Int -> IO ()
regionOffset r dx dy =
(\(Region arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gdk_region_offset argPtr1 arg2 arg3) r (fromIntegral dx) (fromIntegral dy)
regionShrink :: Region -> Int -> Int -> IO ()
regionShrink r dx dy =
(\(Region arg1) arg2 arg3 -> withForeignPtr arg1 $ \argPtr1 ->gdk_region_shrink argPtr1 arg2 arg3) r (fromIntegral dx) (fromIntegral dy)
regionUnionWithRect :: Region -> Rectangle -> IO ()
regionUnionWithRect reg rect = with rect $ \rPtr ->
(\(Region arg1) arg2 -> withForeignPtr arg1 $ \argPtr1 ->gdk_region_union_with_rect argPtr1 arg2) reg (castPtr rPtr)
regionIntersect :: Region -> Region -> IO ()
regionIntersect reg1 reg2 = (\(Region arg1) (Region arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gdk_region_intersect argPtr1 argPtr2) reg1 reg2
regionUnion :: Region -> Region -> IO ()
regionUnion reg1 reg2 = (\(Region arg1) (Region arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gdk_region_union argPtr1 argPtr2) reg1 reg2
regionSubtract :: Region -> Region -> IO ()
regionSubtract reg1 reg2 = (\(Region arg1) (Region arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gdk_region_subtract argPtr1 argPtr2) reg1 reg2
regionXor :: Region -> Region -> IO ()
regionXor reg1 reg2 = (\(Region arg1) (Region arg2) -> withForeignPtr arg1 $ \argPtr1 ->withForeignPtr arg2 $ \argPtr2 ->gdk_region_xor argPtr1 argPtr2) reg1 reg2
foreign import ccall unsafe "gdk_region_new"
gdk_region_new :: (IO (Ptr Region))
foreign import ccall unsafe "gdk_region_polygon"
gdk_region_polygon :: ((Ptr ()) -> (CInt -> (CInt -> (IO (Ptr Region)))))
foreign import ccall unsafe "gdk_region_copy"
gdk_region_copy :: ((Ptr Region) -> (IO (Ptr Region)))
foreign import ccall unsafe "gdk_region_rectangle"
gdk_region_rectangle :: ((Ptr ()) -> (IO (Ptr Region)))
foreign import ccall unsafe "gdk_region_get_clipbox"
gdk_region_get_clipbox :: ((Ptr Region) -> ((Ptr ()) -> (IO ())))
foreign import ccall unsafe "gdk_region_get_rectangles"
gdk_region_get_rectangles :: ((Ptr Region) -> ((Ptr (Ptr ())) -> ((Ptr CInt) -> (IO ()))))
foreign import ccall unsafe "g_free"
g_free :: ((Ptr ()) -> (IO ()))
foreign import ccall unsafe "gdk_region_empty"
gdk_region_empty :: ((Ptr Region) -> (IO CInt))
foreign import ccall unsafe "gdk_region_equal"
gdk_region_equal :: ((Ptr Region) -> ((Ptr Region) -> (IO CInt)))
foreign import ccall unsafe "gdk_region_point_in"
gdk_region_point_in :: ((Ptr Region) -> (CInt -> (CInt -> (IO CInt))))
foreign import ccall unsafe "gdk_region_rect_in"
gdk_region_rect_in :: ((Ptr Region) -> ((Ptr ()) -> (IO CInt)))
foreign import ccall unsafe "gdk_region_offset"
gdk_region_offset :: ((Ptr Region) -> (CInt -> (CInt -> (IO ()))))
foreign import ccall unsafe "gdk_region_shrink"
gdk_region_shrink :: ((Ptr Region) -> (CInt -> (CInt -> (IO ()))))
foreign import ccall unsafe "gdk_region_union_with_rect"
gdk_region_union_with_rect :: ((Ptr Region) -> ((Ptr ()) -> (IO ())))
foreign import ccall unsafe "gdk_region_intersect"
gdk_region_intersect :: ((Ptr Region) -> ((Ptr Region) -> (IO ())))
foreign import ccall unsafe "gdk_region_union"
gdk_region_union :: ((Ptr Region) -> ((Ptr Region) -> (IO ())))
foreign import ccall unsafe "gdk_region_subtract"
gdk_region_subtract :: ((Ptr Region) -> ((Ptr Region) -> (IO ())))
foreign import ccall unsafe "gdk_region_xor"
gdk_region_xor :: ((Ptr Region) -> ((Ptr Region) -> (IO ())))