{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.Cairo.Structs.RectangleInt
    ( 

-- * Exported types
    RectangleInt(..)                        ,
    newZeroRectangleInt                     ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveRectangleIntMethod               ,
#endif



 -- * Properties


-- ** height #attr:height#
-- | /No description available in the introspection data./

    getRectangleIntHeight                   ,
#if defined(ENABLE_OVERLOADING)
    rectangleInt_height                     ,
#endif
    setRectangleIntHeight                   ,


-- ** width #attr:width#
-- | /No description available in the introspection data./

    getRectangleIntWidth                    ,
#if defined(ENABLE_OVERLOADING)
    rectangleInt_width                      ,
#endif
    setRectangleIntWidth                    ,


-- ** x #attr:x#
-- | /No description available in the introspection data./

    getRectangleIntX                        ,
#if defined(ENABLE_OVERLOADING)
    rectangleInt_x                          ,
#endif
    setRectangleIntX                        ,


-- ** y #attr:y#
-- | /No description available in the introspection data./

    getRectangleIntY                        ,
#if defined(ENABLE_OVERLOADING)
    rectangleInt_y                          ,
#endif
    setRectangleIntY                        ,




    ) where

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

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


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

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

foreign import ccall "cairo_gobject_rectangle_int_get_type" c_cairo_gobject_rectangle_int_get_type :: 
    IO GType

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

instance B.Types.TypedObject RectangleInt where
    glibType :: IO GType
glibType = IO GType
c_cairo_gobject_rectangle_int_get_type

instance B.Types.GBoxed RectangleInt

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

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

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


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

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

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

rectangleInt_x :: AttrLabelProxy "x"
rectangleInt_x = AttrLabelProxy

#endif


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

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

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

rectangleInt_y :: AttrLabelProxy "y"
rectangleInt_y = AttrLabelProxy

#endif


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

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

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

rectangleInt_width :: AttrLabelProxy "width"
rectangleInt_width = AttrLabelProxy

#endif


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

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

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

rectangleInt_height :: AttrLabelProxy "height"
rectangleInt_height = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList RectangleInt
type instance O.AttributeList RectangleInt = RectangleIntAttributeList
type RectangleIntAttributeList = ('[ '("x", RectangleIntXFieldInfo), '("y", RectangleIntYFieldInfo), '("width", RectangleIntWidthFieldInfo), '("height", RectangleIntHeightFieldInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveRectangleIntMethod (t :: Symbol) (o :: *) :: * where
    ResolveRectangleIntMethod l o = O.MethodResolutionFailed l o

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

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

#endif

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

#endif