{-# LANGUAGE DeriveDataTypeable #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Graphics.X11.Xlib.Region
-- Copyright   :  (c) Alastair Reid, 1999-2003
-- License     :  BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer  :  libraries@haskell.org
-- Stability   :  provisional
-- Portability :  portable
--
-- A collection of FFI declarations for interfacing with Xlib Regions.
--
-----------------------------------------------------------------------------

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

----------------------------------------------------------------
-- Regions
----------------------------------------------------------------

newtype Region = Region (ForeignPtr Region)
#if __GLASGOW_HASKELL__
        deriving (Region -> Region -> Bool
(Region -> Region -> Bool)
-> (Region -> Region -> Bool) -> Eq Region
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Region -> Region -> Bool
$c/= :: Region -> Region -> Bool
== :: Region -> Region -> Bool
$c== :: Region -> Region -> Bool
Eq, Eq Region
Eq Region
-> (Region -> Region -> Ordering)
-> (Region -> Region -> Bool)
-> (Region -> Region -> Bool)
-> (Region -> Region -> Bool)
-> (Region -> Region -> Bool)
-> (Region -> Region -> Region)
-> (Region -> Region -> Region)
-> Ord Region
Region -> Region -> Bool
Region -> Region -> Ordering
Region -> Region -> Region
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Region -> Region -> Region
$cmin :: Region -> Region -> Region
max :: Region -> Region -> Region
$cmax :: Region -> Region -> Region
>= :: Region -> Region -> Bool
$c>= :: Region -> Region -> Bool
> :: Region -> Region -> Bool
$c> :: Region -> Region -> Bool
<= :: Region -> Region -> Bool
$c<= :: Region -> Region -> Bool
< :: Region -> Region -> Bool
$c< :: Region -> Region -> Bool
compare :: Region -> Region -> Ordering
$ccompare :: Region -> Region -> Ordering
$cp1Ord :: Eq Region
Ord, Int -> Region -> ShowS
[Region] -> ShowS
Region -> String
(Int -> Region -> ShowS)
-> (Region -> String) -> ([Region] -> ShowS) -> Show Region
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Region] -> ShowS
$cshowList :: [Region] -> ShowS
show :: Region -> String
$cshow :: Region -> String
showsPrec :: Int -> Region -> ShowS
$cshowsPrec :: Int -> Region -> ShowS
Show, Typeable, Typeable Region
DataType
Constr
Typeable Region
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Region -> c Region)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Region)
-> (Region -> Constr)
-> (Region -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Region))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Region))
-> ((forall b. Data b => b -> b) -> Region -> Region)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Region -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Region -> r)
-> (forall u. (forall d. Data d => d -> u) -> Region -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Region -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Region -> m Region)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Region -> m Region)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Region -> m Region)
-> Data Region
Region -> DataType
Region -> Constr
(forall b. Data b => b -> b) -> Region -> Region
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Region -> c Region
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Region
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Region -> u
forall u. (forall d. Data d => d -> u) -> Region -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Region -> m Region
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Region -> m Region
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Region
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Region -> c Region
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Region)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Region)
$cRegion :: Constr
$tRegion :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Region -> m Region
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Region -> m Region
gmapMp :: (forall d. Data d => d -> m d) -> Region -> m Region
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Region -> m Region
gmapM :: (forall d. Data d => d -> m d) -> Region -> m Region
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Region -> m Region
gmapQi :: Int -> (forall d. Data d => d -> u) -> Region -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Region -> u
gmapQ :: (forall d. Data d => d -> u) -> Region -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Region -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Region -> r
gmapT :: (forall b. Data b => b -> b) -> Region -> Region
$cgmapT :: (forall b. Data b => b -> b) -> Region -> Region
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Region)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Region)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Region)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Region)
dataTypeOf :: Region -> DataType
$cdataTypeOf :: Region -> DataType
toConstr :: Region -> Constr
$ctoConstr :: Region -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Region
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Region
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Region -> c Region
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Region -> c Region
$cp1Data :: Typeable Region
Data)
#else
        deriving (Eq, Ord, Show)
#endif

withRegion :: Region -> (Ptr Region -> IO a) -> IO a
withRegion :: Region -> (Ptr Region -> IO a) -> IO a
withRegion (Region ForeignPtr Region
r) = ForeignPtr Region -> (Ptr Region -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Region
r

type RectInRegionResult = CInt

-- Return values from XRectInRegion()
rectangleOut, rectangleIn, rectanglePart :: RectInRegionResult
rectangleOut :: RectInRegionResult
rectangleOut  = RectInRegionResult
0
rectangleIn :: RectInRegionResult
rectangleIn   = RectInRegionResult
1
rectanglePart :: RectInRegionResult
rectanglePart = RectInRegionResult
2

----------------------------------------------------------------
-- Creating regions
----------------------------------------------------------------

-- regions deallocation is handled by the GC (ForeignPtr magic)
-- so we don't provide XDestroyRegion explicitly
-- no idea what the int is for
-- %fun XDestroyRegion :: Region -> IO Int
foreign import ccall unsafe "HsXlib.h &XDestroyRegion"
        xDestroyRegionPtr :: FunPtr (Ptr Region -> IO ())

makeRegion :: Ptr Region -> IO Region
makeRegion :: Ptr Region -> IO Region
makeRegion Ptr Region
rp = do
        ForeignPtr Region
r <- FinalizerPtr Region -> Ptr Region -> IO (ForeignPtr Region)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr Region
xDestroyRegionPtr Ptr Region
rp
        Region -> IO Region
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Region -> Region
Region ForeignPtr Region
r)

-- an empty region
-- (often used as "out argument" to binary operators which return regions)

-- | interface to the X11 library function @XCreateRegion()@.
createRegion :: IO Region
createRegion :: IO Region
createRegion = do
        Ptr Region
rp <- IO (Ptr Region)
xCreateRegion
        Ptr Region -> IO Region
makeRegion Ptr Region
rp
foreign import ccall unsafe "HsXlib.h XCreateRegion"
        xCreateRegion :: IO (Ptr Region)

-- | interface to the X11 library function @XPolygonRegion()@.
polygonRegion :: [Point] -> FillRule -> IO Region
polygonRegion :: [Point] -> RectInRegionResult -> IO Region
polygonRegion [Point]
points RectInRegionResult
fill_rule =
        [Point] -> (Int -> Ptr Point -> IO Region) -> IO Region
forall a b. Storable a => [a] -> (Int -> Ptr a -> IO b) -> IO b
withArrayLen [Point]
points ((Int -> Ptr Point -> IO Region) -> IO Region)
-> (Int -> Ptr Point -> IO Region) -> IO Region
forall a b. (a -> b) -> a -> b
$ \ Int
n Ptr Point
point_arr -> do
        Ptr Region
rp <- Ptr Point
-> RectInRegionResult -> RectInRegionResult -> IO (Ptr Region)
xPolygonRegion Ptr Point
point_arr (Int -> RectInRegionResult
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n) RectInRegionResult
fill_rule
        Ptr Region -> IO Region
makeRegion Ptr Region
rp
foreign import ccall unsafe "HsXlib.h XPolygonRegion"
        xPolygonRegion :: Ptr Point -> CInt -> FillRule -> IO (Ptr Region)

----------------------------------------------------------------
-- Combining Regions
--
-- The usual shoddy state of Xlib documentation fails to mention
-- what the Int is for.
--
-- All operations overwrite the region in their third argument
-- which is usually a freshly created region.
----------------------------------------------------------------

-- | interface to the X11 library function @XIntersectRegion()@.
intersectRegion     :: Region -> Region -> Region -> IO CInt
intersectRegion :: Region -> Region -> Region -> IO RectInRegionResult
intersectRegion Region
src1 Region
src2 Region
dest =
        Region
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
src1 ((Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
src1_ptr ->
        Region
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
src2 ((Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
src2_ptr ->
        Region
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
dest ((Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
dest_ptr ->
        Ptr Region -> Ptr Region -> Ptr Region -> IO RectInRegionResult
xIntersectRegion Ptr Region
src1_ptr Ptr Region
src2_ptr Ptr Region
dest_ptr
foreign import ccall unsafe
        "HsXlib.h XIntersectRegion" xIntersectRegion ::
        Ptr Region -> Ptr Region -> Ptr Region -> IO CInt

-- | interface to the X11 library function @XSubtractRegion()@.
subtractRegion     :: Region -> Region -> Region -> IO CInt
subtractRegion :: Region -> Region -> Region -> IO RectInRegionResult
subtractRegion Region
src1 Region
src2 Region
dest =
        Region
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
src1 ((Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
src1_ptr ->
        Region
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
src2 ((Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
src2_ptr ->
        Region
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
dest ((Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
dest_ptr ->
        Ptr Region -> Ptr Region -> Ptr Region -> IO RectInRegionResult
xSubtractRegion Ptr Region
src1_ptr Ptr Region
src2_ptr Ptr Region
dest_ptr
foreign import ccall unsafe
        "HsXlib.h XSubtractRegion" xSubtractRegion ::
        Ptr Region -> Ptr Region -> Ptr Region -> IO CInt

-- | interface to the X11 library function @XUnionRectWithRegion()@.
unionRectWithRegion     :: Rectangle -> Region -> Region -> IO CInt
unionRectWithRegion :: Rectangle -> Region -> Region -> IO RectInRegionResult
unionRectWithRegion Rectangle
rect Region
src Region
dest =
        Rectangle
-> (Ptr Rectangle -> IO RectInRegionResult)
-> IO RectInRegionResult
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with Rectangle
rect ((Ptr Rectangle -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Rectangle -> IO RectInRegionResult)
-> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Rectangle
rect_ptr ->
        Region
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
src ((Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
src_ptr ->
        Region
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
dest ((Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
dest_ptr ->
        Ptr Rectangle -> Ptr Region -> Ptr Region -> IO RectInRegionResult
xUnionRectWithRegion Ptr Rectangle
rect_ptr Ptr Region
src_ptr Ptr Region
dest_ptr
foreign import ccall unsafe
        "HsXlib.h XUnionRectWithRegion" xUnionRectWithRegion ::
        Ptr Rectangle -> Ptr Region -> Ptr Region -> IO CInt

-- | interface to the X11 library function @XUnionRegion()@.
unionRegion     :: Region -> Region -> Region -> IO CInt
unionRegion :: Region -> Region -> Region -> IO RectInRegionResult
unionRegion Region
src1 Region
src2 Region
dest =
        Region
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
src1 ((Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
src1_ptr ->
        Region
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
src2 ((Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
src2_ptr ->
        Region
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
dest ((Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
dest_ptr ->
        Ptr Region -> Ptr Region -> Ptr Region -> IO RectInRegionResult
xUnionRegion Ptr Region
src1_ptr Ptr Region
src2_ptr Ptr Region
dest_ptr
foreign import ccall unsafe
        "HsXlib.h XUnionRegion" xUnionRegion ::
        Ptr Region -> Ptr Region -> Ptr Region -> IO CInt

-- | interface to the X11 library function @XXorRegion()@.
xorRegion     :: Region -> Region -> Region -> IO CInt
xorRegion :: Region -> Region -> Region -> IO RectInRegionResult
xorRegion Region
src1 Region
src2 Region
dest =
        Region
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
src1 ((Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
src1_ptr ->
        Region
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
src2 ((Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
src2_ptr ->
        Region
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
dest ((Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
dest_ptr ->
        Ptr Region -> Ptr Region -> Ptr Region -> IO RectInRegionResult
xXorRegion Ptr Region
src1_ptr Ptr Region
src2_ptr Ptr Region
dest_ptr
foreign import ccall unsafe
        "HsXlib.h XXorRegion" xXorRegion ::
        Ptr Region -> Ptr Region -> Ptr Region -> IO CInt

----------------------------------------------------------------
-- Examining regions (tests, bounding boxes, etc)
----------------------------------------------------------------

-- | interface to the X11 library function @XEmptyRegion()@.
emptyRegion :: Region -> IO Bool
emptyRegion :: Region -> IO Bool
emptyRegion Region
r = Region -> (Ptr Region -> IO Bool) -> IO Bool
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
r Ptr Region -> IO Bool
xEmptyRegion
foreign import ccall unsafe "HsXlib.h XEmptyRegion"
        xEmptyRegion :: Ptr Region -> IO Bool

-- | interface to the X11 library function @XEqualRegion()@.
equalRegion :: Region -> Region -> IO Bool
equalRegion :: Region -> Region -> IO Bool
equalRegion Region
r1 Region
r2 =
        Region -> (Ptr Region -> IO Bool) -> IO Bool
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
r1 ((Ptr Region -> IO Bool) -> IO Bool)
-> (Ptr Region -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
rp1 ->
        Region -> (Ptr Region -> IO Bool) -> IO Bool
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
r2 ((Ptr Region -> IO Bool) -> IO Bool)
-> (Ptr Region -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
rp2 ->
        Ptr Region -> Ptr Region -> IO Bool
xEqualRegion Ptr Region
rp1 Ptr Region
rp2
foreign import ccall unsafe "HsXlib.h XEqualRegion"
        xEqualRegion :: Ptr Region -> Ptr Region -> IO Bool

-- | interface to the X11 library function @XPointInRegion()@.
pointInRegion :: Region -> Point -> IO Bool
pointInRegion :: Region -> Point -> IO Bool
pointInRegion Region
r (Point Position
x Position
y) =
        Region -> (Ptr Region -> IO Bool) -> IO Bool
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
r ((Ptr Region -> IO Bool) -> IO Bool)
-> (Ptr Region -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
rp ->
        Ptr Region -> Position -> Position -> IO Bool
xPointInRegion Ptr Region
rp Position
x Position
y
foreign import ccall unsafe "HsXlib.h XPointInRegion"
        xPointInRegion :: Ptr Region -> Position -> Position -> IO Bool

-- | interface to the X11 library function @XRectInRegion()@.
rectInRegion :: Region -> Rectangle -> IO RectInRegionResult
rectInRegion :: Region -> Rectangle -> IO RectInRegionResult
rectInRegion Region
r (Rectangle Position
x Position
y Dimension
w Dimension
h) =
        Region
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
r ((Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
rp ->
        Ptr Region
-> Position
-> Position
-> Dimension
-> Dimension
-> IO RectInRegionResult
xRectInRegion Ptr Region
rp Position
x Position
y Dimension
w Dimension
h
foreign import ccall unsafe "HsXlib.h XRectInRegion"
        xRectInRegion :: Ptr Region -> Position -> Position ->
                Dimension -> Dimension -> IO RectInRegionResult

-- I have no idea what the int is for

-- | interface to the X11 library function @XClipBox()@.
clipBox :: Region -> IO (Rectangle,CInt)
clipBox :: Region -> IO (Rectangle, RectInRegionResult)
clipBox Region
r =
        Region
-> (Ptr Region -> IO (Rectangle, RectInRegionResult))
-> IO (Rectangle, RectInRegionResult)
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
r ((Ptr Region -> IO (Rectangle, RectInRegionResult))
 -> IO (Rectangle, RectInRegionResult))
-> (Ptr Region -> IO (Rectangle, RectInRegionResult))
-> IO (Rectangle, RectInRegionResult)
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
rp ->
        (Ptr Rectangle -> IO (Rectangle, RectInRegionResult))
-> IO (Rectangle, RectInRegionResult)
forall a b. Storable a => (Ptr a -> IO b) -> IO b
alloca ((Ptr Rectangle -> IO (Rectangle, RectInRegionResult))
 -> IO (Rectangle, RectInRegionResult))
-> (Ptr Rectangle -> IO (Rectangle, RectInRegionResult))
-> IO (Rectangle, RectInRegionResult)
forall a b. (a -> b) -> a -> b
$ \ Ptr Rectangle
rect_ptr -> do
        RectInRegionResult
res <- Ptr Region -> Ptr Rectangle -> IO RectInRegionResult
xClipBox Ptr Region
rp Ptr Rectangle
rect_ptr
        Rectangle
rect <- Ptr Rectangle -> IO Rectangle
forall a. Storable a => Ptr a -> IO a
peek Ptr Rectangle
rect_ptr
        (Rectangle, RectInRegionResult)
-> IO (Rectangle, RectInRegionResult)
forall (m :: * -> *) a. Monad m => a -> m a
return (Rectangle
rect, RectInRegionResult
res)
foreign import ccall unsafe "HsXlib.h XClipBox"
        xClipBox :: Ptr Region -> Ptr Rectangle -> IO CInt

----------------------------------------------------------------
-- Modifying regions
-- (If you use any of these, you can't make regions look like
--  first class data structures.)
----------------------------------------------------------------

-- translate region

-- | interface to the X11 library function @XOffsetRegion()@.
offsetRegion :: Region -> Point -> IO CInt
offsetRegion :: Region -> Point -> IO RectInRegionResult
offsetRegion Region
r (Point Position
x Position
y) =
        Region
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
r ((Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
rp ->
        Ptr Region -> Position -> Position -> IO RectInRegionResult
xOffsetRegion Ptr Region
rp Position
x Position
y
foreign import ccall unsafe "HsXlib.h XOffsetRegion"
        xOffsetRegion :: Ptr Region -> Position -> Position -> IO CInt

-- increase size of region by +ve or -ve number of pixels
-- while preserving the centre of the region (ie half the pixels
-- come off the left, and half off the right)

-- | interface to the X11 library function @XShrinkRegion()@.
shrinkRegion :: Region -> Point -> IO CInt
shrinkRegion :: Region -> Point -> IO RectInRegionResult
shrinkRegion Region
r (Point Position
x Position
y) =
        Region
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
r ((Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
rp ->
        Ptr Region -> Position -> Position -> IO RectInRegionResult
xShrinkRegion Ptr Region
rp Position
x Position
y
foreign import ccall unsafe "HsXlib.h XShrinkRegion"
        xShrinkRegion :: Ptr Region -> Position -> Position -> IO CInt

----------------------------------------------------------------
-- Graphics Context
----------------------------------------------------------------

-- set clip mask of GC

-- | interface to the X11 library function @XSetRegion()@.
setRegion :: Display -> GC -> Region -> IO CInt
setRegion :: Display -> GC -> Region -> IO RectInRegionResult
setRegion Display
disp GC
gc Region
r =
        Region
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a. Region -> (Ptr Region -> IO a) -> IO a
withRegion Region
r ((Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult)
-> (Ptr Region -> IO RectInRegionResult) -> IO RectInRegionResult
forall a b. (a -> b) -> a -> b
$ \ Ptr Region
rp ->
        Display -> GC -> Ptr Region -> IO RectInRegionResult
xSetRegion Display
disp GC
gc Ptr Region
rp
foreign import ccall unsafe "HsXlib.h XSetRegion"
        xSetRegion :: Display -> GC -> Ptr Region -> IO CInt

----------------------------------------------------------------
-- End
----------------------------------------------------------------