{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The location and size of a rectangle region.
-- 
-- The width and height of a t'GI.Graphene.Structs.Rect.Rect' can be negative; for instance,
-- a t'GI.Graphene.Structs.Rect.Rect' with an origin of [ 0, 0 ] and a size of [ 10, 10 ] is
-- equivalent to a t'GI.Graphene.Structs.Rect.Rect' with an origin of [ 10, 10 ] and a size
-- of [ -10, -10 ].
-- 
-- Application code can normalize rectangles using 'GI.Graphene.Structs.Rect.rectNormalize';
-- this function will ensure that the width and height of a rectangle are
-- positive values. All functions taking a t'GI.Graphene.Structs.Rect.Rect' as an argument
-- will internally operate on a normalized copy; all functions returning a
-- t'GI.Graphene.Structs.Rect.Rect' will always return a normalized rectangle.
-- 
-- /Since: 1.0/

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

module GI.Graphene.Structs.Rect
    ( 

-- * Exported types
    Rect(..)                                ,
    newZeroRect                             ,
    noRect                                  ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveRectMethod                       ,
#endif


-- ** alloc #method:alloc#

    rectAlloc                               ,


-- ** containsPoint #method:containsPoint#

#if defined(ENABLE_OVERLOADING)
    RectContainsPointMethodInfo             ,
#endif
    rectContainsPoint                       ,


-- ** containsRect #method:containsRect#

#if defined(ENABLE_OVERLOADING)
    RectContainsRectMethodInfo              ,
#endif
    rectContainsRect                        ,


-- ** equal #method:equal#

#if defined(ENABLE_OVERLOADING)
    RectEqualMethodInfo                     ,
#endif
    rectEqual                               ,


-- ** expand #method:expand#

#if defined(ENABLE_OVERLOADING)
    RectExpandMethodInfo                    ,
#endif
    rectExpand                              ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    RectFreeMethodInfo                      ,
#endif
    rectFree                                ,


-- ** getArea #method:getArea#

#if defined(ENABLE_OVERLOADING)
    RectGetAreaMethodInfo                   ,
#endif
    rectGetArea                             ,


-- ** getBottomLeft #method:getBottomLeft#

#if defined(ENABLE_OVERLOADING)
    RectGetBottomLeftMethodInfo             ,
#endif
    rectGetBottomLeft                       ,


-- ** getBottomRight #method:getBottomRight#

#if defined(ENABLE_OVERLOADING)
    RectGetBottomRightMethodInfo            ,
#endif
    rectGetBottomRight                      ,


-- ** getCenter #method:getCenter#

#if defined(ENABLE_OVERLOADING)
    RectGetCenterMethodInfo                 ,
#endif
    rectGetCenter                           ,


-- ** getHeight #method:getHeight#

#if defined(ENABLE_OVERLOADING)
    RectGetHeightMethodInfo                 ,
#endif
    rectGetHeight                           ,


-- ** getTopLeft #method:getTopLeft#

#if defined(ENABLE_OVERLOADING)
    RectGetTopLeftMethodInfo                ,
#endif
    rectGetTopLeft                          ,


-- ** getTopRight #method:getTopRight#

#if defined(ENABLE_OVERLOADING)
    RectGetTopRightMethodInfo               ,
#endif
    rectGetTopRight                         ,


-- ** getWidth #method:getWidth#

#if defined(ENABLE_OVERLOADING)
    RectGetWidthMethodInfo                  ,
#endif
    rectGetWidth                            ,


-- ** getX #method:getX#

#if defined(ENABLE_OVERLOADING)
    RectGetXMethodInfo                      ,
#endif
    rectGetX                                ,


-- ** getY #method:getY#

#if defined(ENABLE_OVERLOADING)
    RectGetYMethodInfo                      ,
#endif
    rectGetY                                ,


-- ** init #method:init#

#if defined(ENABLE_OVERLOADING)
    RectInitMethodInfo                      ,
#endif
    rectInit                                ,


-- ** initFromRect #method:initFromRect#

#if defined(ENABLE_OVERLOADING)
    RectInitFromRectMethodInfo              ,
#endif
    rectInitFromRect                        ,


-- ** inset #method:inset#

#if defined(ENABLE_OVERLOADING)
    RectInsetMethodInfo                     ,
#endif
    rectInset                               ,


-- ** insetR #method:insetR#

#if defined(ENABLE_OVERLOADING)
    RectInsetRMethodInfo                    ,
#endif
    rectInsetR                              ,


-- ** interpolate #method:interpolate#

#if defined(ENABLE_OVERLOADING)
    RectInterpolateMethodInfo               ,
#endif
    rectInterpolate                         ,


-- ** intersection #method:intersection#

#if defined(ENABLE_OVERLOADING)
    RectIntersectionMethodInfo              ,
#endif
    rectIntersection                        ,


-- ** normalize #method:normalize#

#if defined(ENABLE_OVERLOADING)
    RectNormalizeMethodInfo                 ,
#endif
    rectNormalize                           ,


-- ** normalizeR #method:normalizeR#

#if defined(ENABLE_OVERLOADING)
    RectNormalizeRMethodInfo                ,
#endif
    rectNormalizeR                          ,


-- ** offset #method:offset#

#if defined(ENABLE_OVERLOADING)
    RectOffsetMethodInfo                    ,
#endif
    rectOffset                              ,


-- ** offsetR #method:offsetR#

#if defined(ENABLE_OVERLOADING)
    RectOffsetRMethodInfo                   ,
#endif
    rectOffsetR                             ,


-- ** round #method:round#

#if defined(ENABLE_OVERLOADING)
    RectRoundMethodInfo                     ,
#endif
    rectRound                               ,


-- ** roundExtents #method:roundExtents#

#if defined(ENABLE_OVERLOADING)
    RectRoundExtentsMethodInfo              ,
#endif
    rectRoundExtents                        ,


-- ** roundToPixel #method:roundToPixel#

#if defined(ENABLE_OVERLOADING)
    RectRoundToPixelMethodInfo              ,
#endif
    rectRoundToPixel                        ,


-- ** scale #method:scale#

#if defined(ENABLE_OVERLOADING)
    RectScaleMethodInfo                     ,
#endif
    rectScale                               ,


-- ** union #method:union#

#if defined(ENABLE_OVERLOADING)
    RectUnionMethodInfo                     ,
#endif
    rectUnion                               ,


-- ** zero #method:zero#

    rectZero                                ,




 -- * Properties
-- ** origin #attr:origin#
-- | the coordinates of the origin of the rectangle

    getRectOrigin                           ,
#if defined(ENABLE_OVERLOADING)
    rect_origin                             ,
#endif


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

    getRectSize                             ,
#if defined(ENABLE_OVERLOADING)
    rect_size                               ,
#endif




    ) 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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
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 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 {-# SOURCE #-} qualified GI.Graphene.Structs.Point as Graphene.Point
import {-# SOURCE #-} qualified GI.Graphene.Structs.Size as Graphene.Size

-- | Memory-managed wrapper type.
newtype Rect = Rect (ManagedPtr Rect)
    deriving (Rect -> Rect -> Bool
(Rect -> Rect -> Bool) -> (Rect -> Rect -> Bool) -> Eq Rect
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Rect -> Rect -> Bool
$c/= :: Rect -> Rect -> Bool
== :: Rect -> Rect -> Bool
$c== :: Rect -> Rect -> Bool
Eq)
foreign import ccall "graphene_rect_get_type" c_graphene_rect_get_type :: 
    IO GType

instance BoxedObject Rect where
    boxedType :: Rect -> IO GType
boxedType _ = IO GType
c_graphene_rect_get_type

-- | Convert 'Rect' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue Rect where
    toGValue :: Rect -> IO GValue
toGValue o :: Rect
o = do
        GType
gtype <- IO GType
c_graphene_rect_get_type
        Rect -> (Ptr Rect -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Rect
o (GType -> (GValue -> Ptr Rect -> IO ()) -> Ptr Rect -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Rect -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO Rect
fromGValue gv :: GValue
gv = do
        Ptr Rect
ptr <- GValue -> IO (Ptr Rect)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr Rect)
        (ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Rect -> Rect
Rect Ptr Rect
ptr
        
    

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `Rect`.
noRect :: Maybe Rect
noRect :: Maybe Rect
noRect = Maybe Rect
forall a. Maybe a
Nothing

-- | Get the value of the “@origin@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' rect #origin
-- @
getRectOrigin :: MonadIO m => Rect -> m Graphene.Point.Point
getRectOrigin :: Rect -> m Point
getRectOrigin s :: Rect
s = IO Point -> m Point
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point -> m Point) -> IO Point -> m Point
forall a b. (a -> b) -> a -> b
$ Rect -> (Ptr Rect -> IO Point) -> IO Point
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rect
s ((Ptr Rect -> IO Point) -> IO Point)
-> (Ptr Rect -> IO Point) -> IO Point
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Rect
ptr -> do
    let val :: Ptr Point
val = Ptr Rect
ptr Ptr Rect -> Int -> Ptr Point
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: (Ptr Graphene.Point.Point)
    Point
val' <- ((ManagedPtr Point -> Point) -> Ptr Point -> IO Point
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Point -> Point
Graphene.Point.Point) Ptr Point
val
    Point -> IO Point
forall (m :: * -> *) a. Monad m => a -> m a
return Point
val'

#if defined(ENABLE_OVERLOADING)
data RectOriginFieldInfo
instance AttrInfo RectOriginFieldInfo where
    type AttrBaseTypeConstraint RectOriginFieldInfo = (~) Rect
    type AttrAllowedOps RectOriginFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint RectOriginFieldInfo = (~) (Ptr Graphene.Point.Point)
    type AttrTransferTypeConstraint RectOriginFieldInfo = (~)(Ptr Graphene.Point.Point)
    type AttrTransferType RectOriginFieldInfo = (Ptr Graphene.Point.Point)
    type AttrGetType RectOriginFieldInfo = Graphene.Point.Point
    type AttrLabel RectOriginFieldInfo = "origin"
    type AttrOrigin RectOriginFieldInfo = Rect
    attrGet = getRectOrigin
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined

rect_origin :: AttrLabelProxy "origin"
rect_origin = AttrLabelProxy

#endif


-- | Get the value of the “@size@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' rect #size
-- @
getRectSize :: MonadIO m => Rect -> m Graphene.Size.Size
getRectSize :: Rect -> m Size
getRectSize s :: Rect
s = IO Size -> m Size
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Size -> m Size) -> IO Size -> m Size
forall a b. (a -> b) -> a -> b
$ Rect -> (Ptr Rect -> IO Size) -> IO Size
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Rect
s ((Ptr Rect -> IO Size) -> IO Size)
-> (Ptr Rect -> IO Size) -> IO Size
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Rect
ptr -> do
    let val :: Ptr Size
val = Ptr Rect
ptr Ptr Rect -> Int -> Ptr Size
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: (Ptr Graphene.Size.Size)
    Size
val' <- ((ManagedPtr Size -> Size) -> Ptr Size -> IO Size
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Size -> Size
Graphene.Size.Size) Ptr Size
val
    Size -> IO Size
forall (m :: * -> *) a. Monad m => a -> m a
return Size
val'

#if defined(ENABLE_OVERLOADING)
data RectSizeFieldInfo
instance AttrInfo RectSizeFieldInfo where
    type AttrBaseTypeConstraint RectSizeFieldInfo = (~) Rect
    type AttrAllowedOps RectSizeFieldInfo = '[ 'AttrGet]
    type AttrSetTypeConstraint RectSizeFieldInfo = (~) (Ptr Graphene.Size.Size)
    type AttrTransferTypeConstraint RectSizeFieldInfo = (~)(Ptr Graphene.Size.Size)
    type AttrTransferType RectSizeFieldInfo = (Ptr Graphene.Size.Size)
    type AttrGetType RectSizeFieldInfo = Graphene.Size.Size
    type AttrLabel RectSizeFieldInfo = "size"
    type AttrOrigin RectSizeFieldInfo = Rect
    attrGet = getRectSize
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined

rect_size :: AttrLabelProxy "size"
rect_size = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Rect
type instance O.AttributeList Rect = RectAttributeList
type RectAttributeList = ('[ '("origin", RectOriginFieldInfo), '("size", RectSizeFieldInfo)] :: [(Symbol, *)])
#endif

-- method Rect::contains_point
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "p"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_point_t"
--                 , 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 "graphene_rect_contains_point" graphene_rect_contains_point :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Graphene.Point.Point ->             -- p : TInterface (Name {namespace = "Graphene", name = "Point"})
    IO CInt

-- | Checks whether a t'GI.Graphene.Structs.Rect.Rect' contains the given coordinates.
-- 
-- /Since: 1.0/
rectContainsPoint ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> Graphene.Point.Point
    -- ^ /@p@/: a t'GI.Graphene.Structs.Point.Point'
    -> m Bool
    -- ^ __Returns:__ @true@ if the rectangle contains the point
rectContainsPoint :: Rect -> Point -> m Bool
rectContainsPoint r :: Rect
r p :: Point
p = IO Bool -> m Bool
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 Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Point
p' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
p
    CInt
result <- Ptr Rect -> Ptr Point -> IO CInt
graphene_rect_contains_point Ptr Rect
r' Ptr Point
p'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
p
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data RectContainsPointMethodInfo
instance (signature ~ (Graphene.Point.Point -> m Bool), MonadIO m) => O.MethodInfo RectContainsPointMethodInfo Rect signature where
    overloadedMethod = rectContainsPoint

#endif

-- method Rect::contains_rect
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , 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 "graphene_rect_contains_rect" graphene_rect_contains_rect :: 
    Ptr Rect ->                             -- a : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Rect ->                             -- b : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO CInt

-- | Checks whether a t'GI.Graphene.Structs.Rect.Rect' fully contains the given
-- rectangle.
-- 
-- /Since: 1.0/
rectContainsRect ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@a@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> Rect
    -- ^ /@b@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m Bool
    -- ^ __Returns:__ @true@ if the rectangle /@a@/ fully contains /@b@/
rectContainsRect :: Rect -> Rect -> m Bool
rectContainsRect a :: Rect
a b :: Rect
b = IO Bool -> m Bool
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 Rect
a' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
a
    Ptr Rect
b' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
b
    CInt
result <- Ptr Rect -> Ptr Rect -> IO CInt
graphene_rect_contains_rect Ptr Rect
a' Ptr Rect
b'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
a
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
b
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data RectContainsRectMethodInfo
instance (signature ~ (Rect -> m Bool), MonadIO m) => O.MethodInfo RectContainsRectMethodInfo Rect signature where
    overloadedMethod = rectContainsRect

#endif

-- method Rect::equal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , 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 "graphene_rect_equal" graphene_rect_equal :: 
    Ptr Rect ->                             -- a : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Rect ->                             -- b : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO CInt

-- | Checks whether the two given rectangle are equal.
-- 
-- /Since: 1.0/
rectEqual ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@a@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> Rect
    -- ^ /@b@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m Bool
    -- ^ __Returns:__ @true@ if the rectangles are equal
rectEqual :: Rect -> Rect -> m Bool
rectEqual a :: Rect
a b :: Rect
b = IO Bool -> m Bool
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 Rect
a' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
a
    Ptr Rect
b' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
b
    CInt
result <- Ptr Rect -> Ptr Rect -> IO CInt
graphene_rect_equal Ptr Rect
a' Ptr Rect
b'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
a
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
b
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data RectEqualMethodInfo
instance (signature ~ (Rect -> m Bool), MonadIO m) => O.MethodInfo RectEqualMethodInfo Rect signature where
    overloadedMethod = rectEqual

#endif

-- method Rect::expand
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "p"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the expanded rectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_expand" graphene_rect_expand :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Graphene.Point.Point ->             -- p : TInterface (Name {namespace = "Graphene", name = "Point"})
    Ptr Rect ->                             -- res : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO ()

-- | Expands a t'GI.Graphene.Structs.Rect.Rect' to contain the given t'GI.Graphene.Structs.Point.Point'.
-- 
-- /Since: 1.4/
rectExpand ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> Graphene.Point.Point
    -- ^ /@p@/: a t'GI.Graphene.Structs.Point.Point'
    -> m (Rect)
rectExpand :: Rect -> Point -> m Rect
rectExpand r :: Rect
r p :: Point
p = IO Rect -> m Rect
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rect -> m Rect) -> IO Rect -> m Rect
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Point
p' <- Point -> IO (Ptr Point)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Point
p
    Ptr Rect
res <- Int -> IO (Ptr Rect)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 16 :: IO (Ptr Rect)
    Ptr Rect -> Ptr Point -> Ptr Rect -> IO ()
graphene_rect_expand Ptr Rect
r' Ptr Point
p' Ptr Rect
res
    Rect
res' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rect -> Rect
Rect) Ptr Rect
res
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Point -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Point
p
    Rect -> IO Rect
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
res'

#if defined(ENABLE_OVERLOADING)
data RectExpandMethodInfo
instance (signature ~ (Graphene.Point.Point -> m (Rect)), MonadIO m) => O.MethodInfo RectExpandMethodInfo Rect signature where
    overloadedMethod = rectExpand

#endif

-- method Rect::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_free" graphene_rect_free :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO ()

-- | Frees the resources allocated by 'GI.Graphene.Functions.rectAlloc'.
-- 
-- /Since: 1.0/
rectFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m ()
rectFree :: Rect -> m ()
rectFree r :: Rect
r = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Rect -> IO ()
graphene_rect_free Ptr Rect
r'
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RectFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo RectFreeMethodInfo Rect signature where
    overloadedMethod = rectFree

#endif

-- method Rect::get_area
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TFloat)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_get_area" graphene_rect_get_area :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO CFloat

-- | Compute the area of given normalized rectangle.
-- 
-- /Since: 1.10/
rectGetArea ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m Float
    -- ^ __Returns:__ the area of the normalized rectangle
rectGetArea :: Rect -> m Float
rectGetArea r :: Rect
r = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    CFloat
result <- Ptr Rect -> IO CFloat
graphene_rect_get_area Ptr Rect
r'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data RectGetAreaMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.MethodInfo RectGetAreaMethodInfo Rect signature where
    overloadedMethod = rectGetArea

#endif

-- method Rect::get_bottom_left
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "p"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_get_bottom_left" graphene_rect_get_bottom_left :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Graphene.Point.Point ->             -- p : TInterface (Name {namespace = "Graphene", name = "Point"})
    IO ()

-- | Retrieves the coordinates of the bottom-left corner of the given rectangle.
-- 
-- /Since: 1.0/
rectGetBottomLeft ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m (Graphene.Point.Point)
rectGetBottomLeft :: Rect -> m Point
rectGetBottomLeft r :: Rect
r = IO Point -> m Point
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point -> m Point) -> IO Point -> m Point
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Point
p <- Int -> IO (Ptr Point)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 8 :: IO (Ptr Graphene.Point.Point)
    Ptr Rect -> Ptr Point -> IO ()
graphene_rect_get_bottom_left Ptr Rect
r' Ptr Point
p
    Point
p' <- ((ManagedPtr Point -> Point) -> Ptr Point -> IO Point
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Point -> Point
Graphene.Point.Point) Ptr Point
p
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Point -> IO Point
forall (m :: * -> *) a. Monad m => a -> m a
return Point
p'

#if defined(ENABLE_OVERLOADING)
data RectGetBottomLeftMethodInfo
instance (signature ~ (m (Graphene.Point.Point)), MonadIO m) => O.MethodInfo RectGetBottomLeftMethodInfo Rect signature where
    overloadedMethod = rectGetBottomLeft

#endif

-- method Rect::get_bottom_right
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "p"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_get_bottom_right" graphene_rect_get_bottom_right :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Graphene.Point.Point ->             -- p : TInterface (Name {namespace = "Graphene", name = "Point"})
    IO ()

-- | Retrieves the coordinates of the bottom-right corner of the given rectangle.
-- 
-- /Since: 1.0/
rectGetBottomRight ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m (Graphene.Point.Point)
rectGetBottomRight :: Rect -> m Point
rectGetBottomRight r :: Rect
r = IO Point -> m Point
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point -> m Point) -> IO Point -> m Point
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Point
p <- Int -> IO (Ptr Point)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 8 :: IO (Ptr Graphene.Point.Point)
    Ptr Rect -> Ptr Point -> IO ()
graphene_rect_get_bottom_right Ptr Rect
r' Ptr Point
p
    Point
p' <- ((ManagedPtr Point -> Point) -> Ptr Point -> IO Point
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Point -> Point
Graphene.Point.Point) Ptr Point
p
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Point -> IO Point
forall (m :: * -> *) a. Monad m => a -> m a
return Point
p'

#if defined(ENABLE_OVERLOADING)
data RectGetBottomRightMethodInfo
instance (signature ~ (m (Graphene.Point.Point)), MonadIO m) => O.MethodInfo RectGetBottomRightMethodInfo Rect signature where
    overloadedMethod = rectGetBottomRight

#endif

-- method Rect::get_center
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "p"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_get_center" graphene_rect_get_center :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Graphene.Point.Point ->             -- p : TInterface (Name {namespace = "Graphene", name = "Point"})
    IO ()

-- | Retrieves the coordinates of the center of the given rectangle.
-- 
-- /Since: 1.0/
rectGetCenter ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m (Graphene.Point.Point)
rectGetCenter :: Rect -> m Point
rectGetCenter r :: Rect
r = IO Point -> m Point
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point -> m Point) -> IO Point -> m Point
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Point
p <- Int -> IO (Ptr Point)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 8 :: IO (Ptr Graphene.Point.Point)
    Ptr Rect -> Ptr Point -> IO ()
graphene_rect_get_center Ptr Rect
r' Ptr Point
p
    Point
p' <- ((ManagedPtr Point -> Point) -> Ptr Point -> IO Point
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Point -> Point
Graphene.Point.Point) Ptr Point
p
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Point -> IO Point
forall (m :: * -> *) a. Monad m => a -> m a
return Point
p'

#if defined(ENABLE_OVERLOADING)
data RectGetCenterMethodInfo
instance (signature ~ (m (Graphene.Point.Point)), MonadIO m) => O.MethodInfo RectGetCenterMethodInfo Rect signature where
    overloadedMethod = rectGetCenter

#endif

-- method Rect::get_height
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TFloat)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_get_height" graphene_rect_get_height :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO CFloat

-- | Retrieves the normalized height of the given rectangle.
-- 
-- /Since: 1.0/
rectGetHeight ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m Float
    -- ^ __Returns:__ the normalized height of the rectangle
rectGetHeight :: Rect -> m Float
rectGetHeight r :: Rect
r = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    CFloat
result <- Ptr Rect -> IO CFloat
graphene_rect_get_height Ptr Rect
r'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data RectGetHeightMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.MethodInfo RectGetHeightMethodInfo Rect signature where
    overloadedMethod = rectGetHeight

#endif

-- method Rect::get_top_left
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "p"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_get_top_left" graphene_rect_get_top_left :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Graphene.Point.Point ->             -- p : TInterface (Name {namespace = "Graphene", name = "Point"})
    IO ()

-- | Retrieves the coordinates of the top-left corner of the given rectangle.
-- 
-- /Since: 1.0/
rectGetTopLeft ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m (Graphene.Point.Point)
rectGetTopLeft :: Rect -> m Point
rectGetTopLeft r :: Rect
r = IO Point -> m Point
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point -> m Point) -> IO Point -> m Point
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Point
p <- Int -> IO (Ptr Point)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 8 :: IO (Ptr Graphene.Point.Point)
    Ptr Rect -> Ptr Point -> IO ()
graphene_rect_get_top_left Ptr Rect
r' Ptr Point
p
    Point
p' <- ((ManagedPtr Point -> Point) -> Ptr Point -> IO Point
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Point -> Point
Graphene.Point.Point) Ptr Point
p
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Point -> IO Point
forall (m :: * -> *) a. Monad m => a -> m a
return Point
p'

#if defined(ENABLE_OVERLOADING)
data RectGetTopLeftMethodInfo
instance (signature ~ (m (Graphene.Point.Point)), MonadIO m) => O.MethodInfo RectGetTopLeftMethodInfo Rect signature where
    overloadedMethod = rectGetTopLeft

#endif

-- method Rect::get_top_right
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "p"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Point" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for a #graphene_point_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_get_top_right" graphene_rect_get_top_right :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Graphene.Point.Point ->             -- p : TInterface (Name {namespace = "Graphene", name = "Point"})
    IO ()

-- | Retrieves the coordinates of the top-right corner of the given rectangle.
-- 
-- /Since: 1.0/
rectGetTopRight ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m (Graphene.Point.Point)
rectGetTopRight :: Rect -> m Point
rectGetTopRight r :: Rect
r = IO Point -> m Point
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Point -> m Point) -> IO Point -> m Point
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Point
p <- Int -> IO (Ptr Point)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 8 :: IO (Ptr Graphene.Point.Point)
    Ptr Rect -> Ptr Point -> IO ()
graphene_rect_get_top_right Ptr Rect
r' Ptr Point
p
    Point
p' <- ((ManagedPtr Point -> Point) -> Ptr Point -> IO Point
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Point -> Point
Graphene.Point.Point) Ptr Point
p
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Point -> IO Point
forall (m :: * -> *) a. Monad m => a -> m a
return Point
p'

#if defined(ENABLE_OVERLOADING)
data RectGetTopRightMethodInfo
instance (signature ~ (m (Graphene.Point.Point)), MonadIO m) => O.MethodInfo RectGetTopRightMethodInfo Rect signature where
    overloadedMethod = rectGetTopRight

#endif

-- XXX Could not generate method Rect::get_vertices
-- Error was : Not implemented: "Don't know how to allocate \"vertices\" of type TCArray False 4 (-1) (TInterface (Name {namespace = \"Graphene\", name = \"Vec2\"}))"
-- method Rect::get_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TFloat)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_get_width" graphene_rect_get_width :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO CFloat

-- | Retrieves the normalized width of the given rectangle.
-- 
-- /Since: 1.0/
rectGetWidth ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m Float
    -- ^ __Returns:__ the normalized width of the rectangle
rectGetWidth :: Rect -> m Float
rectGetWidth r :: Rect
r = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    CFloat
result <- Ptr Rect -> IO CFloat
graphene_rect_get_width Ptr Rect
r'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data RectGetWidthMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.MethodInfo RectGetWidthMethodInfo Rect signature where
    overloadedMethod = rectGetWidth

#endif

-- method Rect::get_x
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TFloat)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_get_x" graphene_rect_get_x :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO CFloat

-- | Retrieves the normalized X coordinate of the origin of the given
-- rectangle.
-- 
-- /Since: 1.0/
rectGetX ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m Float
    -- ^ __Returns:__ the normalized X coordinate of the rectangle
rectGetX :: Rect -> m Float
rectGetX r :: Rect
r = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    CFloat
result <- Ptr Rect -> IO CFloat
graphene_rect_get_x Ptr Rect
r'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data RectGetXMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.MethodInfo RectGetXMethodInfo Rect signature where
    overloadedMethod = rectGetX

#endif

-- method Rect::get_y
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TFloat)
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_get_y" graphene_rect_get_y :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO CFloat

-- | Retrieves the normalized Y coordinate of the origin of the given
-- rectangle.
-- 
-- /Since: 1.0/
rectGetY ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m Float
    -- ^ __Returns:__ the normalized Y coordinate of the rectangle
rectGetY :: Rect -> m Float
rectGetY r :: Rect
r = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    CFloat
result <- Ptr Rect -> IO CFloat
graphene_rect_get_y Ptr Rect
r'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data RectGetYMethodInfo
instance (signature ~ (m Float), MonadIO m) => O.MethodInfo RectGetYMethodInfo Rect signature where
    overloadedMethod = rectGetY

#endif

-- method Rect::init
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the X coordinate of the @graphene_rect_t.origin"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the Y coordinate of the @graphene_rect_t.origin"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the width of the @graphene_rect_t.size"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the height of the @graphene_rect_t.size"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Rect" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_init" graphene_rect_init :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    CFloat ->                               -- x : TBasicType TFloat
    CFloat ->                               -- y : TBasicType TFloat
    CFloat ->                               -- width : TBasicType TFloat
    CFloat ->                               -- height : TBasicType TFloat
    IO (Ptr Rect)

-- | Initializes the given t'GI.Graphene.Structs.Rect.Rect' with the given values.
-- 
-- This function will implicitly normalize the t'GI.Graphene.Structs.Rect.Rect'
-- before returning.
-- 
-- /Since: 1.0/
rectInit ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> Float
    -- ^ /@x@/: the X coordinate of the /@grapheneRectT@/.origin
    -> Float
    -- ^ /@y@/: the Y coordinate of the /@grapheneRectT@/.origin
    -> Float
    -- ^ /@width@/: the width of the /@grapheneRectT@/.size
    -> Float
    -- ^ /@height@/: the height of the /@grapheneRectT@/.size
    -> m Rect
    -- ^ __Returns:__ the initialized rectangle
rectInit :: Rect -> Float -> Float -> Float -> Float -> m Rect
rectInit r :: Rect
r x :: Float
x y :: Float
y width :: Float
width height :: Float
height = IO Rect -> m Rect
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rect -> m Rect) -> IO Rect -> m Rect
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    let x' :: CFloat
x' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
x
    let y' :: CFloat
y' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
y
    let width' :: CFloat
width' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
width
    let height' :: CFloat
height' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
height
    Ptr Rect
result <- Ptr Rect -> CFloat -> CFloat -> CFloat -> CFloat -> IO (Ptr Rect)
graphene_rect_init Ptr Rect
r' CFloat
x' CFloat
y' CFloat
width' CFloat
height'
    Text -> Ptr Rect -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "rectInit" Ptr Rect
result
    Rect
result' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Rect -> Rect
Rect) Ptr Rect
result
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Rect -> IO Rect
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
result'

#if defined(ENABLE_OVERLOADING)
data RectInitMethodInfo
instance (signature ~ (Float -> Float -> Float -> Float -> m Rect), MonadIO m) => O.MethodInfo RectInitMethodInfo Rect signature where
    overloadedMethod = rectInit

#endif

-- method Rect::init_from_rect
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "src"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Rect" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_init_from_rect" graphene_rect_init_from_rect :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Rect ->                             -- src : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO (Ptr Rect)

-- | Initializes /@r@/ using the given /@src@/ rectangle.
-- 
-- This function will implicitly normalize the t'GI.Graphene.Structs.Rect.Rect'
-- before returning.
-- 
-- /Since: 1.0/
rectInitFromRect ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> Rect
    -- ^ /@src@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m Rect
    -- ^ __Returns:__ the initialized rectangle
rectInitFromRect :: Rect -> Rect -> m Rect
rectInitFromRect r :: Rect
r src :: Rect
src = IO Rect -> m Rect
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rect -> m Rect) -> IO Rect -> m Rect
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Rect
src' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
src
    Ptr Rect
result <- Ptr Rect -> Ptr Rect -> IO (Ptr Rect)
graphene_rect_init_from_rect Ptr Rect
r' Ptr Rect
src'
    Text -> Ptr Rect -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "rectInitFromRect" Ptr Rect
result
    Rect
result' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Rect -> Rect
Rect) Ptr Rect
result
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
src
    Rect -> IO Rect
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
result'

#if defined(ENABLE_OVERLOADING)
data RectInitFromRectMethodInfo
instance (signature ~ (Rect -> m Rect), MonadIO m) => O.MethodInfo RectInitFromRectMethodInfo Rect signature where
    overloadedMethod = rectInitFromRect

#endif

-- method Rect::inset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "d_x"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the horizontal inset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "d_y"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the vertical inset" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Rect" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_inset" graphene_rect_inset :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    CFloat ->                               -- d_x : TBasicType TFloat
    CFloat ->                               -- d_y : TBasicType TFloat
    IO (Ptr Rect)

-- | Changes the given rectangle to be smaller, or larger depending on the
-- given inset parameters.
-- 
-- To create an inset rectangle, use positive /@dX@/ or /@dY@/ values; to
-- create a larger, encompassing rectangle, use negative /@dX@/ or /@dY@/
-- values.
-- 
-- The origin of the rectangle is offset by /@dX@/ and /@dY@/, while the size
-- is adjusted by @(2 * \@d_x, 2 * \@d_y)@. If /@dX@/ and /@dY@/ are positive
-- values, the size of the rectangle is decreased; if /@dX@/ and /@dY@/ are
-- negative values, the size of the rectangle is increased.
-- 
-- If the size of the resulting inset rectangle has a negative width or
-- height then the size will be set to zero.
-- 
-- /Since: 1.0/
rectInset ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> Float
    -- ^ /@dX@/: the horizontal inset
    -> Float
    -- ^ /@dY@/: the vertical inset
    -> m Rect
    -- ^ __Returns:__ the inset rectangle
rectInset :: Rect -> Float -> Float -> m Rect
rectInset r :: Rect
r dX :: Float
dX dY :: Float
dY = IO Rect -> m Rect
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rect -> m Rect) -> IO Rect -> m Rect
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    let dX' :: CFloat
dX' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
dX
    let dY' :: CFloat
dY' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
dY
    Ptr Rect
result <- Ptr Rect -> CFloat -> CFloat -> IO (Ptr Rect)
graphene_rect_inset Ptr Rect
r' CFloat
dX' CFloat
dY'
    Text -> Ptr Rect -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "rectInset" Ptr Rect
result
    Rect
result' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Rect -> Rect
Rect) Ptr Rect
result
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Rect -> IO Rect
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
result'

#if defined(ENABLE_OVERLOADING)
data RectInsetMethodInfo
instance (signature ~ (Float -> Float -> m Rect), MonadIO m) => O.MethodInfo RectInsetMethodInfo Rect signature where
    overloadedMethod = rectInset

#endif

-- method Rect::inset_r
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "d_x"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the horizontal inset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "d_y"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the vertical inset" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the inset rectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_inset_r" graphene_rect_inset_r :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    CFloat ->                               -- d_x : TBasicType TFloat
    CFloat ->                               -- d_y : TBasicType TFloat
    Ptr Rect ->                             -- res : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO ()

-- | Changes the given rectangle to be smaller, or larger depending on the
-- given inset parameters.
-- 
-- To create an inset rectangle, use positive /@dX@/ or /@dY@/ values; to
-- create a larger, encompassing rectangle, use negative /@dX@/ or /@dY@/
-- values.
-- 
-- The origin of the rectangle is offset by /@dX@/ and /@dY@/, while the size
-- is adjusted by @(2 * \@d_x, 2 * \@d_y)@. If /@dX@/ and /@dY@/ are positive
-- values, the size of the rectangle is decreased; if /@dX@/ and /@dY@/ are
-- negative values, the size of the rectangle is increased.
-- 
-- If the size of the resulting inset rectangle has a negative width or
-- height then the size will be set to zero.
-- 
-- /Since: 1.4/
rectInsetR ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> Float
    -- ^ /@dX@/: the horizontal inset
    -> Float
    -- ^ /@dY@/: the vertical inset
    -> m (Rect)
rectInsetR :: Rect -> Float -> Float -> m Rect
rectInsetR r :: Rect
r dX :: Float
dX dY :: Float
dY = IO Rect -> m Rect
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rect -> m Rect) -> IO Rect -> m Rect
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    let dX' :: CFloat
dX' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
dX
    let dY' :: CFloat
dY' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
dY
    Ptr Rect
res <- Int -> IO (Ptr Rect)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 16 :: IO (Ptr Rect)
    Ptr Rect -> CFloat -> CFloat -> Ptr Rect -> IO ()
graphene_rect_inset_r Ptr Rect
r' CFloat
dX' CFloat
dY' Ptr Rect
res
    Rect
res' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rect -> Rect
Rect) Ptr Rect
res
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Rect -> IO Rect
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
res'

#if defined(ENABLE_OVERLOADING)
data RectInsetRMethodInfo
instance (signature ~ (Float -> Float -> m (Rect)), MonadIO m) => O.MethodInfo RectInsetRMethodInfo Rect signature where
    overloadedMethod = rectInsetR

#endif

-- method Rect::interpolate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "factor"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the linear interpolation factor"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the\n  interpolated rectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_interpolate" graphene_rect_interpolate :: 
    Ptr Rect ->                             -- a : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Rect ->                             -- b : TInterface (Name {namespace = "Graphene", name = "Rect"})
    CDouble ->                              -- factor : TBasicType TDouble
    Ptr Rect ->                             -- res : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO ()

-- | Linearly interpolates the origin and size of the two given
-- rectangles.
-- 
-- /Since: 1.0/
rectInterpolate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@a@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> Rect
    -- ^ /@b@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> Double
    -- ^ /@factor@/: the linear interpolation factor
    -> m (Rect)
rectInterpolate :: Rect -> Rect -> Double -> m Rect
rectInterpolate a :: Rect
a b :: Rect
b factor :: Double
factor = IO Rect -> m Rect
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rect -> m Rect) -> IO Rect -> m Rect
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
a' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
a
    Ptr Rect
b' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
b
    let factor' :: CDouble
factor' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
factor
    Ptr Rect
res <- Int -> IO (Ptr Rect)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 16 :: IO (Ptr Rect)
    Ptr Rect -> Ptr Rect -> CDouble -> Ptr Rect -> IO ()
graphene_rect_interpolate Ptr Rect
a' Ptr Rect
b' CDouble
factor' Ptr Rect
res
    Rect
res' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rect -> Rect
Rect) Ptr Rect
res
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
a
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
b
    Rect -> IO Rect
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
res'

#if defined(ENABLE_OVERLOADING)
data RectInterpolateMethodInfo
instance (signature ~ (Rect -> Double -> m (Rect)), MonadIO m) => O.MethodInfo RectInterpolateMethodInfo Rect signature where
    overloadedMethod = rectInterpolate

#endif

-- method Rect::intersection
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for\n  a #graphene_rect_t"
--                 , 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 "graphene_rect_intersection" graphene_rect_intersection :: 
    Ptr Rect ->                             -- a : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Rect ->                             -- b : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Rect ->                             -- res : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO CInt

-- | Computes the intersection of the two given rectangles.
-- 
-- <<http://developer.gnome.org/graphene/stable/rectangle-intersection.png>>
-- 
-- The intersection in the image above is the blue outline.
-- 
-- If the two rectangles do not intersect, /@res@/ will contain
-- a degenerate rectangle with origin in (0, 0) and a size of 0.
-- 
-- /Since: 1.0/
rectIntersection ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@a@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> Rect
    -- ^ /@b@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m ((Bool, Rect))
    -- ^ __Returns:__ @true@ if the two rectangles intersect
rectIntersection :: Rect -> Rect -> m (Bool, Rect)
rectIntersection a :: Rect
a b :: Rect
b = IO (Bool, Rect) -> m (Bool, Rect)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Rect) -> m (Bool, Rect))
-> IO (Bool, Rect) -> m (Bool, Rect)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
a' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
a
    Ptr Rect
b' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
b
    Ptr Rect
res <- Int -> IO (Ptr Rect)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 16 :: IO (Ptr Rect)
    CInt
result <- Ptr Rect -> Ptr Rect -> Ptr Rect -> IO CInt
graphene_rect_intersection Ptr Rect
a' Ptr Rect
b' Ptr Rect
res
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Rect
res' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rect -> Rect
Rect) Ptr Rect
res
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
a
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
b
    (Bool, Rect) -> IO (Bool, Rect)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Rect
res')

#if defined(ENABLE_OVERLOADING)
data RectIntersectionMethodInfo
instance (signature ~ (Rect -> m ((Bool, Rect))), MonadIO m) => O.MethodInfo RectIntersectionMethodInfo Rect signature where
    overloadedMethod = rectIntersection

#endif

-- method Rect::normalize
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Rect" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_normalize" graphene_rect_normalize :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO (Ptr Rect)

-- | Normalizes the passed rectangle.
-- 
-- This function ensures that the size of the rectangle is made of
-- positive values, and that the origin is the top-left corner of
-- the rectangle.
-- 
-- /Since: 1.0/
rectNormalize ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m Rect
    -- ^ __Returns:__ the normalized rectangle
rectNormalize :: Rect -> m Rect
rectNormalize r :: Rect
r = IO Rect -> m Rect
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rect -> m Rect) -> IO Rect -> m Rect
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Rect
result <- Ptr Rect -> IO (Ptr Rect)
graphene_rect_normalize Ptr Rect
r'
    Text -> Ptr Rect -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "rectNormalize" Ptr Rect
result
    Rect
result' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Rect -> Rect
Rect) Ptr Rect
result
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Rect -> IO Rect
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
result'

#if defined(ENABLE_OVERLOADING)
data RectNormalizeMethodInfo
instance (signature ~ (m Rect), MonadIO m) => O.MethodInfo RectNormalizeMethodInfo Rect signature where
    overloadedMethod = rectNormalize

#endif

-- method Rect::normalize_r
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the return location for the\n  normalized rectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_normalize_r" graphene_rect_normalize_r :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Rect ->                             -- res : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO ()

-- | Normalizes the passed rectangle.
-- 
-- This function ensures that the size of the rectangle is made of
-- positive values, and that the origin is in the top-left corner
-- of the rectangle.
-- 
-- /Since: 1.4/
rectNormalizeR ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m (Rect)
rectNormalizeR :: Rect -> m Rect
rectNormalizeR r :: Rect
r = IO Rect -> m Rect
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rect -> m Rect) -> IO Rect -> m Rect
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Rect
res <- Int -> IO (Ptr Rect)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 16 :: IO (Ptr Rect)
    Ptr Rect -> Ptr Rect -> IO ()
graphene_rect_normalize_r Ptr Rect
r' Ptr Rect
res
    Rect
res' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rect -> Rect
Rect) Ptr Rect
res
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Rect -> IO Rect
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
res'

#if defined(ENABLE_OVERLOADING)
data RectNormalizeRMethodInfo
instance (signature ~ (m (Rect)), MonadIO m) => O.MethodInfo RectNormalizeRMethodInfo Rect signature where
    overloadedMethod = rectNormalizeR

#endif

-- method Rect::offset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "d_x"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the horizontal offset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "d_y"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the vertical offset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Rect" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_offset" graphene_rect_offset :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    CFloat ->                               -- d_x : TBasicType TFloat
    CFloat ->                               -- d_y : TBasicType TFloat
    IO (Ptr Rect)

-- | Offsets the origin by /@dX@/ and /@dY@/.
-- 
-- The size of the rectangle is unchanged.
-- 
-- /Since: 1.0/
rectOffset ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> Float
    -- ^ /@dX@/: the horizontal offset
    -> Float
    -- ^ /@dY@/: the vertical offset
    -> m Rect
    -- ^ __Returns:__ the offset rectangle
rectOffset :: Rect -> Float -> Float -> m Rect
rectOffset r :: Rect
r dX :: Float
dX dY :: Float
dY = IO Rect -> m Rect
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rect -> m Rect) -> IO Rect -> m Rect
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    let dX' :: CFloat
dX' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
dX
    let dY' :: CFloat
dY' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
dY
    Ptr Rect
result <- Ptr Rect -> CFloat -> CFloat -> IO (Ptr Rect)
graphene_rect_offset Ptr Rect
r' CFloat
dX' CFloat
dY'
    Text -> Ptr Rect -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "rectOffset" Ptr Rect
result
    Rect
result' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Rect -> Rect
Rect) Ptr Rect
result
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Rect -> IO Rect
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
result'

#if defined(ENABLE_OVERLOADING)
data RectOffsetMethodInfo
instance (signature ~ (Float -> Float -> m Rect), MonadIO m) => O.MethodInfo RectOffsetMethodInfo Rect signature where
    overloadedMethod = rectOffset

#endif

-- method Rect::offset_r
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "d_x"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the horizontal offset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "d_y"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the vertical offset"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the offset\n  rectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_offset_r" graphene_rect_offset_r :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    CFloat ->                               -- d_x : TBasicType TFloat
    CFloat ->                               -- d_y : TBasicType TFloat
    Ptr Rect ->                             -- res : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO ()

-- | Offsets the origin of the given rectangle by /@dX@/ and /@dY@/.
-- 
-- The size of the rectangle is left unchanged.
-- 
-- /Since: 1.4/
rectOffsetR ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> Float
    -- ^ /@dX@/: the horizontal offset
    -> Float
    -- ^ /@dY@/: the vertical offset
    -> m (Rect)
rectOffsetR :: Rect -> Float -> Float -> m Rect
rectOffsetR r :: Rect
r dX :: Float
dX dY :: Float
dY = IO Rect -> m Rect
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rect -> m Rect) -> IO Rect -> m Rect
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    let dX' :: CFloat
dX' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
dX
    let dY' :: CFloat
dY' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
dY
    Ptr Rect
res <- Int -> IO (Ptr Rect)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 16 :: IO (Ptr Rect)
    Ptr Rect -> CFloat -> CFloat -> Ptr Rect -> IO ()
graphene_rect_offset_r Ptr Rect
r' CFloat
dX' CFloat
dY' Ptr Rect
res
    Rect
res' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rect -> Rect
Rect) Ptr Rect
res
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Rect -> IO Rect
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
res'

#if defined(ENABLE_OVERLOADING)
data RectOffsetRMethodInfo
instance (signature ~ (Float -> Float -> m (Rect)), MonadIO m) => O.MethodInfo RectOffsetRMethodInfo Rect signature where
    overloadedMethod = rectOffsetR

#endif

-- method Rect::round
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the\n  rounded rectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_round" graphene_rect_round :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Rect ->                             -- res : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO ()

{-# DEPRECATED rectRound ["(Since version 1.10)","Use 'GI.Graphene.Structs.Rect.rectRoundExtents' instead"] #-}
-- | Rounds the origin and size of the given rectangle to
-- their nearest integer values; the rounding is guaranteed
-- to be large enough to have an area bigger or equal to the
-- original rectangle, but might not fully contain its extents.
-- Use 'GI.Graphene.Structs.Rect.rectRoundExtents' in case you need to round
-- to a rectangle that covers fully the original one.
-- 
-- This function is the equivalent of calling @floor@ on
-- the coordinates of the origin, and @ceil@ on the size.
-- 
-- /Since: 1.4/
rectRound ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m (Rect)
rectRound :: Rect -> m Rect
rectRound r :: Rect
r = IO Rect -> m Rect
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rect -> m Rect) -> IO Rect -> m Rect
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Rect
res <- Int -> IO (Ptr Rect)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 16 :: IO (Ptr Rect)
    Ptr Rect -> Ptr Rect -> IO ()
graphene_rect_round Ptr Rect
r' Ptr Rect
res
    Rect
res' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rect -> Rect
Rect) Ptr Rect
res
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Rect -> IO Rect
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
res'

#if defined(ENABLE_OVERLOADING)
data RectRoundMethodInfo
instance (signature ~ (m (Rect)), MonadIO m) => O.MethodInfo RectRoundMethodInfo Rect signature where
    overloadedMethod = rectRound

#endif

-- method Rect::round_extents
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the\n  rectangle with rounded extents"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_round_extents" graphene_rect_round_extents :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Rect ->                             -- res : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO ()

-- | Rounds the origin of the given rectangle to its nearest
-- integer value and and recompute the size so that the
-- rectangle is large enough to contain all the conrners
-- of the original rectangle.
-- 
-- This function is the equivalent of calling @floor@ on
-- the coordinates of the origin, and recomputing the size
-- calling @ceil@ on the bottom-right coordinates.
-- 
-- If you want to be sure that the rounded rectangle
-- completely covers the area that was covered by the
-- original rectangle — i.e. you want to cover the area
-- including all its corners — this function will make sure
-- that the size is recomputed taking into account the ceiling
-- of the coordinates of the bottom-right corner.
-- If the difference between the original coordinates and the
-- coordinates of the rounded rectangle is greater than the
-- difference between the original size and and the rounded
-- size, then the move of the origin would not be compensated
-- by a move in the anti-origin, leaving the corners of the
-- original rectangle outside the rounded one.
-- 
-- /Since: 1.10/
rectRoundExtents ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m (Rect)
rectRoundExtents :: Rect -> m Rect
rectRoundExtents r :: Rect
r = IO Rect -> m Rect
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rect -> m Rect) -> IO Rect -> m Rect
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Rect
res <- Int -> IO (Ptr Rect)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 16 :: IO (Ptr Rect)
    Ptr Rect -> Ptr Rect -> IO ()
graphene_rect_round_extents Ptr Rect
r' Ptr Rect
res
    Rect
res' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rect -> Rect
Rect) Ptr Rect
res
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Rect -> IO Rect
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
res'

#if defined(ENABLE_OVERLOADING)
data RectRoundExtentsMethodInfo
instance (signature ~ (m (Rect)), MonadIO m) => O.MethodInfo RectRoundExtentsMethodInfo Rect signature where
    overloadedMethod = rectRoundExtents

#endif

-- method Rect::round_to_pixel
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Rect" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_round_to_pixel" graphene_rect_round_to_pixel :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO (Ptr Rect)

{-# DEPRECATED rectRoundToPixel ["(Since version 1.4)","Use 'GI.Graphene.Structs.Rect.rectRound' instead"] #-}
-- | Rounds the origin and the size of the given rectangle to
-- their nearest integer values; the rounding is guaranteed
-- to be large enough to contain the original rectangle.
-- 
-- /Since: 1.0/
rectRoundToPixel ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m Rect
    -- ^ __Returns:__ the pixel-aligned rectangle.
rectRoundToPixel :: Rect -> m Rect
rectRoundToPixel r :: Rect
r = IO Rect -> m Rect
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rect -> m Rect) -> IO Rect -> m Rect
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    Ptr Rect
result <- Ptr Rect -> IO (Ptr Rect)
graphene_rect_round_to_pixel Ptr Rect
r'
    Text -> Ptr Rect -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "rectRoundToPixel" Ptr Rect
result
    Rect
result' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Rect -> Rect
Rect) Ptr Rect
result
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Rect -> IO Rect
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
result'

#if defined(ENABLE_OVERLOADING)
data RectRoundToPixelMethodInfo
instance (signature ~ (m Rect), MonadIO m) => O.MethodInfo RectRoundToPixelMethodInfo Rect signature where
    overloadedMethod = rectRoundToPixel

#endif

-- method Rect::scale
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "r"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "s_h"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "horizontal scale factor"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "s_v"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "vertical scale factor"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the\n  scaled rectangle"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_scale" graphene_rect_scale :: 
    Ptr Rect ->                             -- r : TInterface (Name {namespace = "Graphene", name = "Rect"})
    CFloat ->                               -- s_h : TBasicType TFloat
    CFloat ->                               -- s_v : TBasicType TFloat
    Ptr Rect ->                             -- res : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO ()

-- | Scales the size and origin of a rectangle horizontaly by /@sH@/,
-- and vertically by /@sV@/. The result /@res@/ is normalized.
-- 
-- /Since: 1.10/
rectScale ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@r@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> Float
    -- ^ /@sH@/: horizontal scale factor
    -> Float
    -- ^ /@sV@/: vertical scale factor
    -> m (Rect)
rectScale :: Rect -> Float -> Float -> m Rect
rectScale r :: Rect
r sH :: Float
sH sV :: Float
sV = IO Rect -> m Rect
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rect -> m Rect) -> IO Rect -> m Rect
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
r' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
r
    let sH' :: CFloat
sH' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
sH
    let sV' :: CFloat
sV' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
sV
    Ptr Rect
res <- Int -> IO (Ptr Rect)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 16 :: IO (Ptr Rect)
    Ptr Rect -> CFloat -> CFloat -> Ptr Rect -> IO ()
graphene_rect_scale Ptr Rect
r' CFloat
sH' CFloat
sV' Ptr Rect
res
    Rect
res' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rect -> Rect
Rect) Ptr Rect
res
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
r
    Rect -> IO Rect
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
res'

#if defined(ENABLE_OVERLOADING)
data RectScaleMethodInfo
instance (signature ~ (Float -> Float -> m (Rect)), MonadIO m) => O.MethodInfo RectScaleMethodInfo Rect signature where
    overloadedMethod = rectScale

#endif

-- method Rect::union
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "a"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "b"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #graphene_rect_t" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "res"
--           , argType =
--               TInterface Name { namespace = "Graphene" , name = "Rect" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for a #graphene_rect_t"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_union" graphene_rect_union :: 
    Ptr Rect ->                             -- a : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Rect ->                             -- b : TInterface (Name {namespace = "Graphene", name = "Rect"})
    Ptr Rect ->                             -- res : TInterface (Name {namespace = "Graphene", name = "Rect"})
    IO ()

-- | Computes the union of the two given rectangles.
-- 
-- <<http://developer.gnome.org/graphene/stable/rectangle-union.png>>
-- 
-- The union in the image above is the blue outline.
-- 
-- /Since: 1.0/
rectUnion ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Rect
    -- ^ /@a@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> Rect
    -- ^ /@b@/: a t'GI.Graphene.Structs.Rect.Rect'
    -> m (Rect)
rectUnion :: Rect -> Rect -> m Rect
rectUnion a :: Rect
a b :: Rect
b = IO Rect -> m Rect
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rect -> m Rect) -> IO Rect -> m Rect
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
a' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
a
    Ptr Rect
b' <- Rect -> IO (Ptr Rect)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rect
b
    Ptr Rect
res <- Int -> IO (Ptr Rect)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 16 :: IO (Ptr Rect)
    Ptr Rect -> Ptr Rect -> Ptr Rect -> IO ()
graphene_rect_union Ptr Rect
a' Ptr Rect
b' Ptr Rect
res
    Rect
res' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rect -> Rect
Rect) Ptr Rect
res
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
a
    Rect -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Rect
b
    Rect -> IO Rect
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
res'

#if defined(ENABLE_OVERLOADING)
data RectUnionMethodInfo
instance (signature ~ (Rect -> m (Rect)), MonadIO m) => O.MethodInfo RectUnionMethodInfo Rect signature where
    overloadedMethod = rectUnion

#endif

-- method Rect::alloc
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Rect" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_alloc" graphene_rect_alloc :: 
    IO (Ptr Rect)

-- | Allocates a new t'GI.Graphene.Structs.Rect.Rect'.
-- 
-- The contents of the returned rectangle are undefined.
-- 
-- /Since: 1.0/
rectAlloc ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Rect
    -- ^ __Returns:__ the newly allocated rectangle
rectAlloc :: m Rect
rectAlloc  = IO Rect -> m Rect
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rect -> m Rect) -> IO Rect -> m Rect
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
result <- IO (Ptr Rect)
graphene_rect_alloc
    Text -> Ptr Rect -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "rectAlloc" Ptr Rect
result
    Rect
result' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Rect -> Rect
Rect) Ptr Rect
result
    Rect -> IO Rect
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Rect::zero
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Graphene" , name = "Rect" })
-- throws : False
-- Skip return : False

foreign import ccall "graphene_rect_zero" graphene_rect_zero :: 
    IO (Ptr Rect)

-- | Returns a degenerate rectangle with origin fixed at (0, 0) and
-- a size of 0, 0.
-- 
-- /Since: 1.4/
rectZero ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Rect
    -- ^ __Returns:__ a fixed rectangle
rectZero :: m Rect
rectZero  = IO Rect -> m Rect
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rect -> m Rect) -> IO Rect -> m Rect
forall a b. (a -> b) -> a -> b
$ do
    Ptr Rect
result <- IO (Ptr Rect)
graphene_rect_zero
    Text -> Ptr Rect -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "rectZero" Ptr Rect
result
    Rect
result' <- ((ManagedPtr Rect -> Rect) -> Ptr Rect -> IO Rect
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Rect -> Rect
Rect) Ptr Rect
result
    Rect -> IO Rect
forall (m :: * -> *) a. Monad m => a -> m a
return Rect
result'

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveRectMethod (t :: Symbol) (o :: *) :: * where
    ResolveRectMethod "containsPoint" o = RectContainsPointMethodInfo
    ResolveRectMethod "containsRect" o = RectContainsRectMethodInfo
    ResolveRectMethod "equal" o = RectEqualMethodInfo
    ResolveRectMethod "expand" o = RectExpandMethodInfo
    ResolveRectMethod "free" o = RectFreeMethodInfo
    ResolveRectMethod "init" o = RectInitMethodInfo
    ResolveRectMethod "initFromRect" o = RectInitFromRectMethodInfo
    ResolveRectMethod "inset" o = RectInsetMethodInfo
    ResolveRectMethod "insetR" o = RectInsetRMethodInfo
    ResolveRectMethod "interpolate" o = RectInterpolateMethodInfo
    ResolveRectMethod "intersection" o = RectIntersectionMethodInfo
    ResolveRectMethod "normalize" o = RectNormalizeMethodInfo
    ResolveRectMethod "normalizeR" o = RectNormalizeRMethodInfo
    ResolveRectMethod "offset" o = RectOffsetMethodInfo
    ResolveRectMethod "offsetR" o = RectOffsetRMethodInfo
    ResolveRectMethod "round" o = RectRoundMethodInfo
    ResolveRectMethod "roundExtents" o = RectRoundExtentsMethodInfo
    ResolveRectMethod "roundToPixel" o = RectRoundToPixelMethodInfo
    ResolveRectMethod "scale" o = RectScaleMethodInfo
    ResolveRectMethod "union" o = RectUnionMethodInfo
    ResolveRectMethod "getArea" o = RectGetAreaMethodInfo
    ResolveRectMethod "getBottomLeft" o = RectGetBottomLeftMethodInfo
    ResolveRectMethod "getBottomRight" o = RectGetBottomRightMethodInfo
    ResolveRectMethod "getCenter" o = RectGetCenterMethodInfo
    ResolveRectMethod "getHeight" o = RectGetHeightMethodInfo
    ResolveRectMethod "getTopLeft" o = RectGetTopLeftMethodInfo
    ResolveRectMethod "getTopRight" o = RectGetTopRightMethodInfo
    ResolveRectMethod "getWidth" o = RectGetWidthMethodInfo
    ResolveRectMethod "getX" o = RectGetXMethodInfo
    ResolveRectMethod "getY" o = RectGetYMethodInfo
    ResolveRectMethod l o = O.MethodResolutionFailed l o

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

#endif