module Graphics.X11.Xlib.Region(
Region,
RectInRegionResult,
rectangleOut,
rectangleIn,
rectanglePart,
createRegion,
polygonRegion,
intersectRegion,
subtractRegion,
unionRectWithRegion,
unionRegion,
xorRegion,
emptyRegion,
equalRegion,
pointInRegion,
rectInRegion,
clipBox,
offsetRegion,
shrinkRegion,
setRegion,
) where
import Graphics.X11.Types
import Graphics.X11.Xlib.Types
import Foreign.ForeignPtr
import Foreign.Ptr
import Foreign.C.Types
import Foreign.Storable
import Foreign.Marshal.Alloc
import Foreign.Marshal.Array
import Foreign.Marshal.Utils
#if __GLASGOW_HASKELL__
import Data.Data
#endif
newtype Region = Region (ForeignPtr Region)
#if __GLASGOW_HASKELL__
deriving (Eq, Ord, Show, Typeable, Data)
#else
deriving (Eq, Ord, Show)
#endif
withRegion :: Region -> (Ptr Region -> IO a) -> IO a
withRegion (Region r) = withForeignPtr r
type RectInRegionResult = CInt
rectangleOut, rectangleIn, rectanglePart :: RectInRegionResult
rectangleOut = 0
rectangleIn = 1
rectanglePart = 2
foreign import ccall unsafe "HsXlib.h &XDestroyRegion"
xDestroyRegionPtr :: FunPtr (Ptr Region -> IO ())
makeRegion :: Ptr Region -> IO Region
makeRegion rp = do
r <- newForeignPtr xDestroyRegionPtr rp
return (Region r)
createRegion :: IO Region
createRegion = do
rp <- xCreateRegion
makeRegion rp
foreign import ccall unsafe "HsXlib.h XCreateRegion"
xCreateRegion :: IO (Ptr Region)
polygonRegion :: [Point] -> FillRule -> IO Region
polygonRegion points fill_rule =
withArrayLen points $ \ n point_arr -> do
rp <- xPolygonRegion point_arr (fromIntegral n) fill_rule
makeRegion rp
foreign import ccall unsafe "HsXlib.h XPolygonRegion"
xPolygonRegion :: Ptr Point -> CInt -> FillRule -> IO (Ptr Region)
intersectRegion :: Region -> Region -> Region -> IO CInt
intersectRegion src1 src2 dest =
withRegion src1 $ \ src1_ptr ->
withRegion src2 $ \ src2_ptr ->
withRegion dest $ \ dest_ptr ->
xIntersectRegion src1_ptr src2_ptr dest_ptr
foreign import ccall unsafe
"HsXlib.h XIntersectRegion" xIntersectRegion ::
Ptr Region -> Ptr Region -> Ptr Region -> IO CInt
subtractRegion :: Region -> Region -> Region -> IO CInt
subtractRegion src1 src2 dest =
withRegion src1 $ \ src1_ptr ->
withRegion src2 $ \ src2_ptr ->
withRegion dest $ \ dest_ptr ->
xSubtractRegion src1_ptr src2_ptr dest_ptr
foreign import ccall unsafe
"HsXlib.h XSubtractRegion" xSubtractRegion ::
Ptr Region -> Ptr Region -> Ptr Region -> IO CInt
unionRectWithRegion :: Rectangle -> Region -> Region -> IO CInt
unionRectWithRegion rect src dest =
with rect $ \ rect_ptr ->
withRegion src $ \ src_ptr ->
withRegion dest $ \ dest_ptr ->
xUnionRectWithRegion rect_ptr src_ptr dest_ptr
foreign import ccall unsafe
"HsXlib.h XUnionRectWithRegion" xUnionRectWithRegion ::
Ptr Rectangle -> Ptr Region -> Ptr Region -> IO CInt
unionRegion :: Region -> Region -> Region -> IO CInt
unionRegion src1 src2 dest =
withRegion src1 $ \ src1_ptr ->
withRegion src2 $ \ src2_ptr ->
withRegion dest $ \ dest_ptr ->
xUnionRegion src1_ptr src2_ptr dest_ptr
foreign import ccall unsafe
"HsXlib.h XUnionRegion" xUnionRegion ::
Ptr Region -> Ptr Region -> Ptr Region -> IO CInt
xorRegion :: Region -> Region -> Region -> IO CInt
xorRegion src1 src2 dest =
withRegion src1 $ \ src1_ptr ->
withRegion src2 $ \ src2_ptr ->
withRegion dest $ \ dest_ptr ->
xXorRegion src1_ptr src2_ptr dest_ptr
foreign import ccall unsafe
"HsXlib.h XXorRegion" xXorRegion ::
Ptr Region -> Ptr Region -> Ptr Region -> IO CInt
emptyRegion :: Region -> IO Bool
emptyRegion r = withRegion r xEmptyRegion
foreign import ccall unsafe "HsXlib.h XEmptyRegion"
xEmptyRegion :: Ptr Region -> IO Bool
equalRegion :: Region -> Region -> IO Bool
equalRegion r1 r2 =
withRegion r1 $ \ rp1 ->
withRegion r2 $ \ rp2 ->
xEqualRegion rp1 rp2
foreign import ccall unsafe "HsXlib.h XEqualRegion"
xEqualRegion :: Ptr Region -> Ptr Region -> IO Bool
pointInRegion :: Region -> Point -> IO Bool
pointInRegion r (Point x y) =
withRegion r $ \ rp ->
xPointInRegion rp x y
foreign import ccall unsafe "HsXlib.h XPointInRegion"
xPointInRegion :: Ptr Region -> Position -> Position -> IO Bool
rectInRegion :: Region -> Rectangle -> IO RectInRegionResult
rectInRegion r (Rectangle x y w h) =
withRegion r $ \ rp ->
xRectInRegion rp x y w h
foreign import ccall unsafe "HsXlib.h XRectInRegion"
xRectInRegion :: Ptr Region -> Position -> Position ->
Dimension -> Dimension -> IO RectInRegionResult
clipBox :: Region -> IO (Rectangle,CInt)
clipBox r =
withRegion r $ \ rp ->
alloca $ \ rect_ptr -> do
res <- xClipBox rp rect_ptr
rect <- peek rect_ptr
return (rect, res)
foreign import ccall unsafe "HsXlib.h XClipBox"
xClipBox :: Ptr Region -> Ptr Rectangle -> IO CInt
offsetRegion :: Region -> Point -> IO CInt
offsetRegion r (Point x y) =
withRegion r $ \ rp ->
xOffsetRegion rp x y
foreign import ccall unsafe "HsXlib.h XOffsetRegion"
xOffsetRegion :: Ptr Region -> Position -> Position -> IO CInt
shrinkRegion :: Region -> Point -> IO CInt
shrinkRegion r (Point x y) =
withRegion r $ \ rp ->
xShrinkRegion rp x y
foreign import ccall unsafe "HsXlib.h XShrinkRegion"
xShrinkRegion :: Ptr Region -> Position -> Position -> IO CInt
setRegion :: Display -> GC -> Region -> IO CInt
setRegion disp gc r =
withRegion r $ \ rp ->
xSetRegion disp gc rp
foreign import ccall unsafe "HsXlib.h XSetRegion"
xSetRegion :: Display -> GC -> Ptr Region -> IO CInt