{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A data structure for holding a rectangle.
-- 
-- /Since: 2.46/

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

module GI.Rsvg.Structs.Rectangle
    ( 

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


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveRectangleMethod                  ,
#endif



 -- * Properties


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

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


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

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


-- ** x #attr:x#
-- | X coordinate of the left side of the rectangle

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


-- ** y #attr:y#
-- | Y coordinate of the the top side of the rectangle

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




    ) where

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

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


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

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

instance BoxedPtr Rectangle where
    boxedPtrCopy :: Rectangle -> IO Rectangle
boxedPtrCopy = \Rectangle
p -> Rectangle -> (Ptr Rectangle -> IO Rectangle) -> IO Rectangle
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Rectangle
p (Int -> Ptr Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
32 (Ptr Rectangle -> IO (Ptr Rectangle))
-> (Ptr Rectangle -> IO Rectangle) -> Ptr Rectangle -> IO Rectangle
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr Rectangle -> Rectangle
Rectangle)
    boxedPtrFree :: Rectangle -> IO ()
boxedPtrFree = \Rectangle
x -> Rectangle -> (Ptr Rectangle -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr Rectangle
x Ptr Rectangle -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr Rectangle where
    boxedPtrCalloc :: IO (Ptr Rectangle)
boxedPtrCalloc = Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
callocBytes Int
32


-- | Construct a `Rectangle` struct initialized to zero.
newZeroRectangle :: MonadIO m => m Rectangle
newZeroRectangle :: forall (m :: * -> *). MonadIO m => m Rectangle
newZeroRectangle = IO Rectangle -> m Rectangle
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rectangle -> m Rectangle) -> IO Rectangle -> m Rectangle
forall a b. (a -> b) -> a -> b
$ IO (Ptr Rectangle)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr Rectangle)
-> (Ptr Rectangle -> IO Rectangle) -> IO Rectangle
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Rectangle -> Rectangle
Rectangle

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


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

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

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

rectangle_x :: AttrLabelProxy "x"
rectangle_x = AttrLabelProxy

#endif


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

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

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

rectangle_y :: AttrLabelProxy "y"
rectangle_y = AttrLabelProxy

#endif


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

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

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

rectangle_width :: AttrLabelProxy "width"
rectangle_width = AttrLabelProxy

#endif


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

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

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

rectangle_height :: AttrLabelProxy "height"
rectangle_height = AttrLabelProxy

#endif



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

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

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

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

#endif

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

#endif