{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A @GdkRectangle@ data type for representing rectangles.
-- 
-- @GdkRectangle@ is identical to @cairo_rectangle_t@. Together with Cairo’s
-- @cairo_region_t@ data type, these are the central types for representing
-- sets of pixels.
-- 
-- The intersection of two rectangles can be computed with
-- 'GI.Gdk.Structs.Rectangle.rectangleIntersect'; to find the union of two rectangles use
-- 'GI.Gdk.Structs.Rectangle.rectangleUnion'.
-- 
-- The @cairo_region_t@ type provided by Cairo is usually used for managing
-- non-rectangular clipping of graphical operations.
-- 
-- The Graphene library has a number of other data types for regions and
-- volumes in 2D and 3D.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Gdk.Structs.Rectangle
    ( 

-- * Exported types
    Rectangle(..)                           ,
    newZeroRectangle                        ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [containsPoint]("GI.Gdk.Structs.Rectangle#g:method:containsPoint"), [equal]("GI.Gdk.Structs.Rectangle#g:method:equal"), [intersect]("GI.Gdk.Structs.Rectangle#g:method:intersect"), [union]("GI.Gdk.Structs.Rectangle#g:method:union").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveRectangleMethod                  ,
#endif

-- ** containsPoint #method:containsPoint#

#if defined(ENABLE_OVERLOADING)
    RectangleContainsPointMethodInfo        ,
#endif
    rectangleContainsPoint                  ,


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    RectangleEqualMethodInfo                ,
#endif
    rectangleEqual                          ,


-- ** intersect #method:intersect#

#if defined(ENABLE_OVERLOADING)
    RectangleIntersectMethodInfo            ,
#endif
    rectangleIntersect                      ,


-- ** union #method:union#

#if defined(ENABLE_OVERLOADING)
    RectangleUnionMethodInfo                ,
#endif
    rectangleUnion                          ,




 -- * Properties


-- ** height #attr:height#
-- | the height of the rectangle

    getRectangleHeight                      ,
#if defined(ENABLE_OVERLOADING)
    rectangle_height                        ,
#endif
    setRectangleHeight                      ,


-- ** width #attr:width#
-- | the width of the rectangle

    getRectangleWidth                       ,
#if defined(ENABLE_OVERLOADING)
    rectangle_width                         ,
#endif
    setRectangleWidth                       ,


-- ** x #attr:x#
-- | the x coordinate of the top left corner

    getRectangleX                           ,
#if defined(ENABLE_OVERLOADING)
    rectangle_x                             ,
#endif
    setRectangleX                           ,


-- ** y #attr:y#
-- | the y coordinate of the top left corner

    getRectangleY                           ,
#if defined(ENABLE_OVERLOADING)
    rectangle_y                             ,
#endif
    setRectangleY                           ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R


-- | Memory-managed wrapper type.
newtype Rectangle = Rectangle (SP.ManagedPtr Rectangle)
    deriving (Rectangle -> Rectangle -> Bool
(Rectangle -> Rectangle -> Bool)
-> (Rectangle -> Rectangle -> Bool) -> Eq Rectangle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Rectangle -> Rectangle -> Bool
== :: Rectangle -> Rectangle -> Bool
$c/= :: Rectangle -> Rectangle -> Bool
/= :: Rectangle -> Rectangle -> Bool
Eq)

instance SP.ManagedPtrNewtype Rectangle where
    toManagedPtr :: Rectangle -> ManagedPtr Rectangle
toManagedPtr (Rectangle ManagedPtr Rectangle
p) = ManagedPtr Rectangle
p

foreign import ccall "gdk_rectangle_get_type" c_gdk_rectangle_get_type :: 
    IO GType

type instance O.ParentTypes Rectangle = '[]
instance O.HasParentTypes Rectangle

instance B.Types.TypedObject Rectangle where
    glibType :: IO GType
glibType = IO GType
c_gdk_rectangle_get_type

instance B.Types.GBoxed Rectangle

-- | Convert 'Rectangle' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe Rectangle) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_rectangle_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Rectangle -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Rectangle
P.Nothing = Ptr GValue -> Ptr Rectangle -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr Rectangle
forall a. Ptr a
FP.nullPtr :: FP.Ptr Rectangle)
    gvalueSet_ Ptr GValue
gv (P.Just Rectangle
obj) = Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Rectangle
obj (Ptr GValue -> Ptr Rectangle -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Rectangle)
gvalueGet_ Ptr GValue
gv = do
        Ptr Rectangle
ptr <- Ptr GValue -> IO (Ptr Rectangle)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr Rectangle)
        if Ptr Rectangle
ptr Ptr Rectangle -> Ptr Rectangle -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Rectangle
forall a. Ptr a
FP.nullPtr
        then Rectangle -> Maybe Rectangle
forall a. a -> Maybe a
P.Just (Rectangle -> Maybe Rectangle)
-> IO Rectangle -> IO (Maybe Rectangle)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Rectangle -> Rectangle
Rectangle Ptr Rectangle
ptr
        else Maybe Rectangle -> IO (Maybe Rectangle)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Rectangle
forall a. Maybe a
P.Nothing
        
    

-- | Construct a `Rectangle` struct initialized to zero.
newZeroRectangle :: MonadIO m => m Rectangle
newZeroRectangle :: forall (m :: * -> *). MonadIO m => m Rectangle
newZeroRectangle = IO Rectangle -> m Rectangle
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rectangle -> m Rectangle) -> IO Rectangle -> m Rectangle
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr Rectangle)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
16 IO (Ptr Rectangle)
-> (Ptr Rectangle -> IO Rectangle) -> IO Rectangle
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rectangle -> Rectangle
Rectangle

instance tag ~ 'AttrSet => Constructible Rectangle tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr Rectangle -> Rectangle)
-> [AttrOp Rectangle tag] -> m Rectangle
new ManagedPtr Rectangle -> Rectangle
_ [AttrOp Rectangle tag]
attrs = do
        Rectangle
o <- m Rectangle
forall (m :: * -> *). MonadIO m => m Rectangle
newZeroRectangle
        Rectangle -> [AttrOp Rectangle 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set Rectangle
o [AttrOp Rectangle tag]
[AttrOp Rectangle 'AttrSet]
attrs
        Rectangle -> m Rectangle
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Rectangle
o


-- | Get the value of the “@x@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' rectangle #x
-- @
getRectangleX :: MonadIO m => Rectangle -> m Int32
getRectangleX :: forall (m :: * -> *). MonadIO m => Rectangle -> m Int32
getRectangleX Rectangle
s = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO Int32) -> IO Int32)
-> (Ptr Rectangle -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@x@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' rectangle [ #x 'Data.GI.Base.Attributes.:=' value ]
-- @
setRectangleX :: MonadIO m => Rectangle -> Int32 -> m ()
setRectangleX :: forall (m :: * -> *). MonadIO m => Rectangle -> Int32 -> m ()
setRectangleX Rectangle
s Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO ()) -> IO ())
-> (Ptr Rectangle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data RectangleXFieldInfo
instance AttrInfo RectangleXFieldInfo where
    type AttrBaseTypeConstraint RectangleXFieldInfo = (~) Rectangle
    type AttrAllowedOps RectangleXFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint RectangleXFieldInfo = (~) Int32
    type AttrTransferTypeConstraint RectangleXFieldInfo = (~)Int32
    type AttrTransferType RectangleXFieldInfo = Int32
    type AttrGetType RectangleXFieldInfo = Int32
    type AttrLabel RectangleXFieldInfo = "x"
    type AttrOrigin RectangleXFieldInfo = Rectangle
    attrGet = getRectangleX
    attrSet = setRectangleX
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.Rectangle.x"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Structs-Rectangle.html#g:attr:x"
        })

rectangle_x :: AttrLabelProxy "x"
rectangle_x = AttrLabelProxy

#endif


-- | Get the value of the “@y@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' rectangle #y
-- @
getRectangleY :: MonadIO m => Rectangle -> m Int32
getRectangleY :: forall (m :: * -> *). MonadIO m => Rectangle -> m Int32
getRectangleY Rectangle
s = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO Int32) -> IO Int32)
-> (Ptr Rectangle -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@y@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' rectangle [ #y 'Data.GI.Base.Attributes.:=' value ]
-- @
setRectangleY :: MonadIO m => Rectangle -> Int32 -> m ()
setRectangleY :: forall (m :: * -> *). MonadIO m => Rectangle -> Int32 -> m ()
setRectangleY Rectangle
s Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO ()) -> IO ())
-> (Ptr Rectangle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data RectangleYFieldInfo
instance AttrInfo RectangleYFieldInfo where
    type AttrBaseTypeConstraint RectangleYFieldInfo = (~) Rectangle
    type AttrAllowedOps RectangleYFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint RectangleYFieldInfo = (~) Int32
    type AttrTransferTypeConstraint RectangleYFieldInfo = (~)Int32
    type AttrTransferType RectangleYFieldInfo = Int32
    type AttrGetType RectangleYFieldInfo = Int32
    type AttrLabel RectangleYFieldInfo = "y"
    type AttrOrigin RectangleYFieldInfo = Rectangle
    attrGet = getRectangleY
    attrSet = setRectangleY
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.Rectangle.y"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Structs-Rectangle.html#g:attr:y"
        })

rectangle_y :: AttrLabelProxy "y"
rectangle_y = AttrLabelProxy

#endif


-- | Get the value of the “@width@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' rectangle #width
-- @
getRectangleWidth :: MonadIO m => Rectangle -> m Int32
getRectangleWidth :: forall (m :: * -> *). MonadIO m => Rectangle -> m Int32
getRectangleWidth Rectangle
s = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO Int32) -> IO Int32)
-> (Ptr Rectangle -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@width@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' rectangle [ #width 'Data.GI.Base.Attributes.:=' value ]
-- @
setRectangleWidth :: MonadIO m => Rectangle -> Int32 -> m ()
setRectangleWidth :: forall (m :: * -> *). MonadIO m => Rectangle -> Int32 -> m ()
setRectangleWidth Rectangle
s Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO ()) -> IO ())
-> (Ptr Rectangle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data RectangleWidthFieldInfo
instance AttrInfo RectangleWidthFieldInfo where
    type AttrBaseTypeConstraint RectangleWidthFieldInfo = (~) Rectangle
    type AttrAllowedOps RectangleWidthFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint RectangleWidthFieldInfo = (~) Int32
    type AttrTransferTypeConstraint RectangleWidthFieldInfo = (~)Int32
    type AttrTransferType RectangleWidthFieldInfo = Int32
    type AttrGetType RectangleWidthFieldInfo = Int32
    type AttrLabel RectangleWidthFieldInfo = "width"
    type AttrOrigin RectangleWidthFieldInfo = Rectangle
    attrGet = getRectangleWidth
    attrSet = setRectangleWidth
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.Rectangle.width"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Structs-Rectangle.html#g:attr:width"
        })

rectangle_width :: AttrLabelProxy "width"
rectangle_width = AttrLabelProxy

#endif


-- | Get the value of the “@height@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' rectangle #height
-- @
getRectangleHeight :: MonadIO m => Rectangle -> m Int32
getRectangleHeight :: forall (m :: * -> *). MonadIO m => Rectangle -> m Int32
getRectangleHeight Rectangle
s = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO Int32) -> IO Int32)
-> (Ptr Rectangle -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) :: IO Int32
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@height@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' rectangle [ #height 'Data.GI.Base.Attributes.:=' value ]
-- @
setRectangleHeight :: MonadIO m => Rectangle -> Int32 -> m ()
setRectangleHeight :: forall (m :: * -> *). MonadIO m => Rectangle -> Int32 -> m ()
setRectangleHeight Rectangle
s Int32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rectangle
s ((Ptr Rectangle -> IO ()) -> IO ())
-> (Ptr Rectangle -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Rectangle
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Rectangle
ptr Ptr Rectangle -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data RectangleHeightFieldInfo
instance AttrInfo RectangleHeightFieldInfo where
    type AttrBaseTypeConstraint RectangleHeightFieldInfo = (~) Rectangle
    type AttrAllowedOps RectangleHeightFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint RectangleHeightFieldInfo = (~) Int32
    type AttrTransferTypeConstraint RectangleHeightFieldInfo = (~)Int32
    type AttrTransferType RectangleHeightFieldInfo = Int32
    type AttrGetType RectangleHeightFieldInfo = Int32
    type AttrLabel RectangleHeightFieldInfo = "height"
    type AttrOrigin RectangleHeightFieldInfo = Rectangle
    attrGet = getRectangleHeight
    attrSet = setRectangleHeight
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.Rectangle.height"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Structs-Rectangle.html#g:attr:height"
        })

rectangle_height :: AttrLabelProxy "height"
rectangle_height = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Rectangle
type instance O.AttributeList Rectangle = RectangleAttributeList
type RectangleAttributeList = ('[ '("x", RectangleXFieldInfo), '("y", RectangleYFieldInfo), '("width", RectangleWidthFieldInfo), '("height", RectangleHeightFieldInfo)] :: [(Symbol, *)])
#endif

-- method Rectangle::contains_point
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rect"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Rectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkRectangle`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "X coordinate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Y coordinate" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_rectangle_contains_point" gdk_rectangle_contains_point :: 
    Ptr Rectangle ->                        -- rect : TInterface (Name {namespace = "Gdk", name = "Rectangle"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    IO CInt

-- | Returns 'P.True' if /@rect@/ contains the point described by /@x@/ and /@y@/.
rectangleContainsPoint ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rectangle
    -- ^ /@rect@/: a @GdkRectangle@
    -> Int32
    -- ^ /@x@/: X coordinate
    -> Int32
    -- ^ /@y@/: Y coordinate
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@rect@/ contains the point
rectangleContainsPoint :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Rectangle -> Int32 -> Int32 -> m Bool
rectangleContainsPoint Rectangle
rect Int32
x Int32
y = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rectangle
rect' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
rect
    CInt
result <- Ptr Rectangle -> Int32 -> Int32 -> IO CInt
gdk_rectangle_contains_point Ptr Rectangle
rect' Int32
x Int32
y
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
rect
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data RectangleContainsPointMethodInfo
instance (signature ~ (Int32 -> Int32 -> m Bool), MonadIO m) => O.OverloadedMethod RectangleContainsPointMethodInfo Rectangle signature where
    overloadedMethod = rectangleContainsPoint

instance O.OverloadedMethodInfo RectangleContainsPointMethodInfo Rectangle where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.Rectangle.rectangleContainsPoint",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Structs-Rectangle.html#v:rectangleContainsPoint"
        })


#endif

-- method Rectangle::equal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "rect1"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Rectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkRectangle`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "rect2"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Rectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkRectangle`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_rectangle_equal" gdk_rectangle_equal :: 
    Ptr Rectangle ->                        -- rect1 : TInterface (Name {namespace = "Gdk", name = "Rectangle"})
    Ptr Rectangle ->                        -- rect2 : TInterface (Name {namespace = "Gdk", name = "Rectangle"})
    IO CInt

-- | Checks if the two given rectangles are equal.
rectangleEqual ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rectangle
    -- ^ /@rect1@/: a @GdkRectangle@
    -> Rectangle
    -- ^ /@rect2@/: a @GdkRectangle@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the rectangles are equal.
rectangleEqual :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Rectangle -> Rectangle -> m Bool
rectangleEqual Rectangle
rect1 Rectangle
rect2 = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rectangle
rect1' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
rect1
    Ptr Rectangle
rect2' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
rect2
    CInt
result <- Ptr Rectangle -> Ptr Rectangle -> IO CInt
gdk_rectangle_equal Ptr Rectangle
rect1' Ptr Rectangle
rect2'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
rect1
    Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
rect2
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data RectangleEqualMethodInfo
instance (signature ~ (Rectangle -> m Bool), MonadIO m) => O.OverloadedMethod RectangleEqualMethodInfo Rectangle signature where
    overloadedMethod = rectangleEqual

instance O.OverloadedMethodInfo RectangleEqualMethodInfo Rectangle where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.Rectangle.rectangleEqual",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Structs-Rectangle.html#v:rectangleEqual"
        })


#endif

-- method Rectangle::intersect
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "src1"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Rectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkRectangle`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "src2"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Rectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkRectangle`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Rectangle" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the\n  intersection of @src1 and @src2"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_rectangle_intersect" gdk_rectangle_intersect :: 
    Ptr Rectangle ->                        -- src1 : TInterface (Name {namespace = "Gdk", name = "Rectangle"})
    Ptr Rectangle ->                        -- src2 : TInterface (Name {namespace = "Gdk", name = "Rectangle"})
    Ptr Rectangle ->                        -- dest : TInterface (Name {namespace = "Gdk", name = "Rectangle"})
    IO CInt

-- | Calculates the intersection of two rectangles.
-- 
-- It is allowed for /@dest@/ to be the same as either /@src1@/ or /@src2@/.
-- If the rectangles do not intersect, /@dest@/’s width and height is set
-- to 0 and its x and y values are undefined. If you are only interested
-- in whether the rectangles intersect, but not in the intersecting area
-- itself, pass 'P.Nothing' for /@dest@/.
rectangleIntersect ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rectangle
    -- ^ /@src1@/: a @GdkRectangle@
    -> Rectangle
    -- ^ /@src2@/: a @GdkRectangle@
    -> m ((Bool, Rectangle))
    -- ^ __Returns:__ 'P.True' if the rectangles intersect.
rectangleIntersect :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Rectangle -> Rectangle -> m (Bool, Rectangle)
rectangleIntersect Rectangle
src1 Rectangle
src2 = IO (Bool, Rectangle) -> m (Bool, Rectangle)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Rectangle) -> m (Bool, Rectangle))
-> IO (Bool, Rectangle) -> m (Bool, Rectangle)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rectangle
src1' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
src1
    Ptr Rectangle
src2' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
src2
    Ptr Rectangle
dest <- Int -> IO (Ptr Rectangle)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Rectangle)
    CInt
result <- Ptr Rectangle -> Ptr Rectangle -> Ptr Rectangle -> IO CInt
gdk_rectangle_intersect Ptr Rectangle
src1' Ptr Rectangle
src2' Ptr Rectangle
dest
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Rectangle
dest' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rectangle -> Rectangle
Rectangle) Ptr Rectangle
dest
    Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
src1
    Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
src2
    (Bool, Rectangle) -> IO (Bool, Rectangle)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Rectangle
dest')

#if defined(ENABLE_OVERLOADING)
data RectangleIntersectMethodInfo
instance (signature ~ (Rectangle -> m ((Bool, Rectangle))), MonadIO m) => O.OverloadedMethod RectangleIntersectMethodInfo Rectangle signature where
    overloadedMethod = rectangleIntersect

instance O.OverloadedMethodInfo RectangleIntersectMethodInfo Rectangle where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.Rectangle.rectangleIntersect",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Structs-Rectangle.html#v:rectangleIntersect"
        })


#endif

-- method Rectangle::union
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "src1"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Rectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkRectangle`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "src2"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Rectangle" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkRectangle`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dest"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Rectangle" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the union of @src1 and @src2"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_rectangle_union" gdk_rectangle_union :: 
    Ptr Rectangle ->                        -- src1 : TInterface (Name {namespace = "Gdk", name = "Rectangle"})
    Ptr Rectangle ->                        -- src2 : TInterface (Name {namespace = "Gdk", name = "Rectangle"})
    Ptr Rectangle ->                        -- dest : TInterface (Name {namespace = "Gdk", name = "Rectangle"})
    IO ()

-- | Calculates the union of two rectangles.
-- 
-- The union of rectangles /@src1@/ and /@src2@/ is the smallest rectangle which
-- includes both /@src1@/ and /@src2@/ within it. It is allowed for /@dest@/ to be
-- the same as either /@src1@/ or /@src2@/.
-- 
-- Note that this function does not ignore \'empty\' rectangles (ie. with
-- zero width or height).
rectangleUnion ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rectangle
    -- ^ /@src1@/: a @GdkRectangle@
    -> Rectangle
    -- ^ /@src2@/: a @GdkRectangle@
    -> m (Rectangle)
rectangleUnion :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Rectangle -> Rectangle -> m Rectangle
rectangleUnion Rectangle
src1 Rectangle
src2 = IO Rectangle -> m Rectangle
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rectangle -> m Rectangle) -> IO Rectangle -> m Rectangle
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rectangle
src1' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
src1
    Ptr Rectangle
src2' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
src2
    Ptr Rectangle
dest <- Int -> IO (Ptr Rectangle)
forall a. GBoxed a => Int -> IO (Ptr a)
SP.callocBoxedBytes Int
16 :: IO (Ptr Rectangle)
    Ptr Rectangle -> Ptr Rectangle -> Ptr Rectangle -> IO ()
gdk_rectangle_union Ptr Rectangle
src1' Ptr Rectangle
src2' Ptr Rectangle
dest
    Rectangle
dest' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rectangle -> Rectangle
Rectangle) Ptr Rectangle
dest
    Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
src1
    Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rectangle
src2
    Rectangle -> IO Rectangle
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Rectangle
dest'

#if defined(ENABLE_OVERLOADING)
data RectangleUnionMethodInfo
instance (signature ~ (Rectangle -> m (Rectangle)), MonadIO m) => O.OverloadedMethod RectangleUnionMethodInfo Rectangle signature where
    overloadedMethod = rectangleUnion

instance O.OverloadedMethodInfo RectangleUnionMethodInfo Rectangle where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.Rectangle.rectangleUnion",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.5/docs/GI-Gdk-Structs-Rectangle.html#v:rectangleUnion"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveRectangleMethod (t :: Symbol) (o :: *) :: * where
    ResolveRectangleMethod "containsPoint" o = RectangleContainsPointMethodInfo
    ResolveRectangleMethod "equal" o = RectangleEqualMethodInfo
    ResolveRectangleMethod "intersect" o = RectangleIntersectMethodInfo
    ResolveRectangleMethod "union" o = RectangleUnionMethodInfo
    ResolveRectangleMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveRectangleMethod t Rectangle, O.OverloadedMethod info Rectangle p) => OL.IsLabel t (Rectangle -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveRectangleMethod t Rectangle, O.OverloadedMethod info Rectangle p, R.HasField t Rectangle p) => R.HasField t Rectangle p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveRectangleMethod t Rectangle, O.OverloadedMethodInfo info Rectangle) => OL.IsLabel t (O.MethodProxy info Rectangle) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif