Copyright | (c) Alastair Reid 1999-2003 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell98 |
A collection of FFI declarations for interfacing with Xlib Regions.
Synopsis
- data Region
- type RectInRegionResult = CInt
- rectangleOut :: RectInRegionResult
- rectangleIn :: RectInRegionResult
- rectanglePart :: RectInRegionResult
- createRegion :: IO Region
- polygonRegion :: [Point] -> FillRule -> IO Region
- intersectRegion :: Region -> Region -> Region -> IO CInt
- subtractRegion :: Region -> Region -> Region -> IO CInt
- unionRectWithRegion :: Rectangle -> Region -> Region -> IO CInt
- unionRegion :: Region -> Region -> Region -> IO CInt
- xorRegion :: Region -> Region -> Region -> IO CInt
- emptyRegion :: Region -> IO Bool
- equalRegion :: Region -> Region -> IO Bool
- pointInRegion :: Region -> Point -> IO Bool
- rectInRegion :: Region -> Rectangle -> IO RectInRegionResult
- clipBox :: Region -> IO (Rectangle, CInt)
- offsetRegion :: Region -> Point -> IO CInt
- shrinkRegion :: Region -> Point -> IO CInt
- setRegion :: Display -> GC -> Region -> IO CInt
Documentation
Instances
Data Region Source # | |
Defined in Graphics.X11.Xlib.Region gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Region -> c Region # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Region # toConstr :: Region -> Constr # dataTypeOf :: Region -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Region) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Region) # gmapT :: (forall b. Data b => b -> b) -> Region -> Region # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r # gmapQ :: (forall d. Data d => d -> u) -> Region -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Region -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Region -> m Region # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Region -> m Region # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Region -> m Region # | |
Show Region Source # | |
Eq Region Source # | |
Ord Region Source # | |
type RectInRegionResult = CInt Source #
createRegion :: IO Region Source #
interface to the X11 library function XCreateRegion()
.
polygonRegion :: [Point] -> FillRule -> IO Region Source #
interface to the X11 library function XPolygonRegion()
.
intersectRegion :: Region -> Region -> Region -> IO CInt Source #
interface to the X11 library function XIntersectRegion()
.
subtractRegion :: Region -> Region -> Region -> IO CInt Source #
interface to the X11 library function XSubtractRegion()
.
unionRectWithRegion :: Rectangle -> Region -> Region -> IO CInt Source #
interface to the X11 library function XUnionRectWithRegion()
.
unionRegion :: Region -> Region -> Region -> IO CInt Source #
interface to the X11 library function XUnionRegion()
.
xorRegion :: Region -> Region -> Region -> IO CInt Source #
interface to the X11 library function XXorRegion()
.
equalRegion :: Region -> Region -> IO Bool Source #
interface to the X11 library function XEqualRegion()
.
pointInRegion :: Region -> Point -> IO Bool Source #
interface to the X11 library function XPointInRegion()
.
rectInRegion :: Region -> Rectangle -> IO RectInRegionResult Source #
interface to the X11 library function XRectInRegion()
.
offsetRegion :: Region -> Point -> IO CInt Source #
interface to the X11 library function XOffsetRegion()
.