{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Gdk.Structs.Geometry.Geometry' struct gives the window manager information about
-- a window’s geometry constraints. Normally you would set these on
-- the GTK+ level using @/gtk_window_set_geometry_hints()/@. @/GtkWindow/@
-- then sets the hints on the t'GI.Gdk.Objects.Window.Window' it creates.
-- 
-- 'GI.Gdk.Objects.Window.windowSetGeometryHints' expects the hints to be fully valid already
-- and simply passes them to the window manager; in contrast,
-- @/gtk_window_set_geometry_hints()/@ performs some interpretation. For example,
-- @/GtkWindow/@ will apply the hints to the geometry widget instead of the
-- toplevel window, if you set a geometry widget. Also, the
-- /@minWidth@/\//@minHeight@/\//@maxWidth@/\//@maxHeight@/ fields may be set to -1, and
-- @/GtkWindow/@ will substitute the size request of the window or geometry widget.
-- If the minimum size hint is not provided, @/GtkWindow/@ will use its requisition
-- as the minimum size. If the minimum size is provided and a geometry widget is
-- set, @/GtkWindow/@ will take the minimum size as the minimum size of the
-- geometry widget rather than the entire window. The base size is treated
-- similarly.
-- 
-- The canonical use-case for @/gtk_window_set_geometry_hints()/@ is to get a
-- terminal widget to resize properly. Here, the terminal text area should be
-- the geometry widget; @/GtkWindow/@ will then automatically set the base size to
-- the size of other widgets in the terminal window, such as the menubar and
-- scrollbar. Then, the /@widthInc@/ and /@heightInc@/ fields should be set to the
-- size of one character in the terminal. Finally, the base size should be set
-- to the size of one character. The net effect is that the minimum size of the
-- terminal will have a 1x1 character terminal area, and only terminal sizes on
-- the “character grid” will be allowed.
-- 
-- Here’s an example of how the terminal example would be implemented, assuming
-- a terminal area widget called “terminal” and a toplevel window “toplevel”:
-- 
-- 
-- === /C code/
-- >
-- >	GdkGeometry hints;
-- >
-- >	hints.base_width = terminal->char_width;
-- >        hints.base_height = terminal->char_height;
-- >        hints.min_width = terminal->char_width;
-- >        hints.min_height = terminal->char_height;
-- >        hints.width_inc = terminal->char_width;
-- >        hints.height_inc = terminal->char_height;
-- >
-- > gtk_window_set_geometry_hints (GTK_WINDOW (toplevel),
-- >                                GTK_WIDGET (terminal),
-- >                                &hints,
-- >                                GDK_HINT_RESIZE_INC |
-- >                                GDK_HINT_MIN_SIZE |
-- >                                GDK_HINT_BASE_SIZE);
-- 
-- 
-- The other useful fields are the /@minAspect@/ and /@maxAspect@/ fields; these
-- contain a width\/height ratio as a floating point number. If a geometry widget
-- is set, the aspect applies to the geometry widget rather than the entire
-- window. The most common use of these hints is probably to set /@minAspect@/ and
-- /@maxAspect@/ to the same value, thus forcing the window to keep a constant
-- aspect ratio.

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

module GI.Gdk.Structs.Geometry
    ( 

-- * Exported types
    Geometry(..)                            ,
    newZeroGeometry                         ,
    noGeometry                              ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveGeometryMethod                   ,
#endif




 -- * Properties
-- ** baseHeight #attr:baseHeight#
-- | allowed window widths are /@baseHeight@/ + /@heightInc@/ * N where
--  N is any integer (-1 allowed with @/GtkWindow/@)

#if defined(ENABLE_OVERLOADING)
    geometry_baseHeight                     ,
#endif
    getGeometryBaseHeight                   ,
    setGeometryBaseHeight                   ,


-- ** baseWidth #attr:baseWidth#
-- | allowed window widths are /@baseWidth@/ + /@widthInc@/ * N where N
--  is any integer (-1 allowed with @/GtkWindow/@)

#if defined(ENABLE_OVERLOADING)
    geometry_baseWidth                      ,
#endif
    getGeometryBaseWidth                    ,
    setGeometryBaseWidth                    ,


-- ** heightInc #attr:heightInc#
-- | height resize increment

#if defined(ENABLE_OVERLOADING)
    geometry_heightInc                      ,
#endif
    getGeometryHeightInc                    ,
    setGeometryHeightInc                    ,


-- ** maxAspect #attr:maxAspect#
-- | maximum width\/height ratio

#if defined(ENABLE_OVERLOADING)
    geometry_maxAspect                      ,
#endif
    getGeometryMaxAspect                    ,
    setGeometryMaxAspect                    ,


-- ** maxHeight #attr:maxHeight#
-- | maximum height of window (or -1 to use requisition, with
--  @/GtkWindow/@ only)

#if defined(ENABLE_OVERLOADING)
    geometry_maxHeight                      ,
#endif
    getGeometryMaxHeight                    ,
    setGeometryMaxHeight                    ,


-- ** maxWidth #attr:maxWidth#
-- | maximum width of window (or -1 to use requisition, with
--  @/GtkWindow/@ only)

#if defined(ENABLE_OVERLOADING)
    geometry_maxWidth                       ,
#endif
    getGeometryMaxWidth                     ,
    setGeometryMaxWidth                     ,


-- ** minAspect #attr:minAspect#
-- | minimum width\/height ratio

#if defined(ENABLE_OVERLOADING)
    geometry_minAspect                      ,
#endif
    getGeometryMinAspect                    ,
    setGeometryMinAspect                    ,


-- ** minHeight #attr:minHeight#
-- | minimum height of window (or -1 to use requisition, with
--  @/GtkWindow/@ only)

#if defined(ENABLE_OVERLOADING)
    geometry_minHeight                      ,
#endif
    getGeometryMinHeight                    ,
    setGeometryMinHeight                    ,


-- ** minWidth #attr:minWidth#
-- | minimum width of window (or -1 to use requisition, with
--  @/GtkWindow/@ only)

#if defined(ENABLE_OVERLOADING)
    geometry_minWidth                       ,
#endif
    getGeometryMinWidth                     ,
    setGeometryMinWidth                     ,


-- ** widthInc #attr:widthInc#
-- | width resize increment

#if defined(ENABLE_OVERLOADING)
    geometry_widthInc                       ,
#endif
    getGeometryWidthInc                     ,
    setGeometryWidthInc                     ,


-- ** winGravity #attr:winGravity#
-- | window gravity, see @/gtk_window_set_gravity()/@

#if defined(ENABLE_OVERLOADING)
    geometry_winGravity                     ,
#endif
    getGeometryWinGravity                   ,
    setGeometryWinGravity                   ,




    ) 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.Gdk.Enums as Gdk.Enums

-- | Memory-managed wrapper type.
newtype Geometry = Geometry (ManagedPtr Geometry)
    deriving (Geometry -> Geometry -> Bool
(Geometry -> Geometry -> Bool)
-> (Geometry -> Geometry -> Bool) -> Eq Geometry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Geometry -> Geometry -> Bool
$c/= :: Geometry -> Geometry -> Bool
== :: Geometry -> Geometry -> Bool
$c== :: Geometry -> Geometry -> Bool
Eq)
instance WrappedPtr Geometry where
    wrappedPtrCalloc :: IO (Ptr Geometry)
wrappedPtrCalloc = Int -> IO (Ptr Geometry)
forall a. Int -> IO (Ptr a)
callocBytes 56
    wrappedPtrCopy :: Geometry -> IO Geometry
wrappedPtrCopy = \p :: Geometry
p -> Geometry -> (Ptr Geometry -> IO Geometry) -> IO Geometry
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Geometry
p (Int -> Ptr Geometry -> IO (Ptr Geometry)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 56 (Ptr Geometry -> IO (Ptr Geometry))
-> (Ptr Geometry -> IO Geometry) -> Ptr Geometry -> IO Geometry
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr Geometry -> Geometry) -> Ptr Geometry -> IO Geometry
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Geometry -> Geometry
Geometry)
    wrappedPtrFree :: Maybe (GDestroyNotify Geometry)
wrappedPtrFree = GDestroyNotify Geometry -> Maybe (GDestroyNotify Geometry)
forall a. a -> Maybe a
Just GDestroyNotify Geometry
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free

-- | Construct a `Geometry` struct initialized to zero.
newZeroGeometry :: MonadIO m => m Geometry
newZeroGeometry :: m Geometry
newZeroGeometry = IO Geometry -> m Geometry
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Geometry -> m Geometry) -> IO Geometry -> m Geometry
forall a b. (a -> b) -> a -> b
$ IO (Ptr Geometry)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr Geometry) -> (Ptr Geometry -> IO Geometry) -> IO Geometry
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr Geometry -> Geometry) -> Ptr Geometry -> IO Geometry
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Geometry -> Geometry
Geometry

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


-- | A convenience alias for `Nothing` :: `Maybe` `Geometry`.
noGeometry :: Maybe Geometry
noGeometry :: Maybe Geometry
noGeometry = Maybe Geometry
forall a. Maybe a
Nothing

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

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

#if defined(ENABLE_OVERLOADING)
data GeometryMinWidthFieldInfo
instance AttrInfo GeometryMinWidthFieldInfo where
    type AttrBaseTypeConstraint GeometryMinWidthFieldInfo = (~) Geometry
    type AttrAllowedOps GeometryMinWidthFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GeometryMinWidthFieldInfo = (~) Int32
    type AttrTransferTypeConstraint GeometryMinWidthFieldInfo = (~)Int32
    type AttrTransferType GeometryMinWidthFieldInfo = Int32
    type AttrGetType GeometryMinWidthFieldInfo = Int32
    type AttrLabel GeometryMinWidthFieldInfo = "min_width"
    type AttrOrigin GeometryMinWidthFieldInfo = Geometry
    attrGet = getGeometryMinWidth
    attrSet = setGeometryMinWidth
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

geometry_minWidth :: AttrLabelProxy "minWidth"
geometry_minWidth = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data GeometryMinHeightFieldInfo
instance AttrInfo GeometryMinHeightFieldInfo where
    type AttrBaseTypeConstraint GeometryMinHeightFieldInfo = (~) Geometry
    type AttrAllowedOps GeometryMinHeightFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GeometryMinHeightFieldInfo = (~) Int32
    type AttrTransferTypeConstraint GeometryMinHeightFieldInfo = (~)Int32
    type AttrTransferType GeometryMinHeightFieldInfo = Int32
    type AttrGetType GeometryMinHeightFieldInfo = Int32
    type AttrLabel GeometryMinHeightFieldInfo = "min_height"
    type AttrOrigin GeometryMinHeightFieldInfo = Geometry
    attrGet = getGeometryMinHeight
    attrSet = setGeometryMinHeight
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

geometry_minHeight :: AttrLabelProxy "minHeight"
geometry_minHeight = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data GeometryMaxWidthFieldInfo
instance AttrInfo GeometryMaxWidthFieldInfo where
    type AttrBaseTypeConstraint GeometryMaxWidthFieldInfo = (~) Geometry
    type AttrAllowedOps GeometryMaxWidthFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GeometryMaxWidthFieldInfo = (~) Int32
    type AttrTransferTypeConstraint GeometryMaxWidthFieldInfo = (~)Int32
    type AttrTransferType GeometryMaxWidthFieldInfo = Int32
    type AttrGetType GeometryMaxWidthFieldInfo = Int32
    type AttrLabel GeometryMaxWidthFieldInfo = "max_width"
    type AttrOrigin GeometryMaxWidthFieldInfo = Geometry
    attrGet = getGeometryMaxWidth
    attrSet = setGeometryMaxWidth
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

geometry_maxWidth :: AttrLabelProxy "maxWidth"
geometry_maxWidth = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data GeometryMaxHeightFieldInfo
instance AttrInfo GeometryMaxHeightFieldInfo where
    type AttrBaseTypeConstraint GeometryMaxHeightFieldInfo = (~) Geometry
    type AttrAllowedOps GeometryMaxHeightFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GeometryMaxHeightFieldInfo = (~) Int32
    type AttrTransferTypeConstraint GeometryMaxHeightFieldInfo = (~)Int32
    type AttrTransferType GeometryMaxHeightFieldInfo = Int32
    type AttrGetType GeometryMaxHeightFieldInfo = Int32
    type AttrLabel GeometryMaxHeightFieldInfo = "max_height"
    type AttrOrigin GeometryMaxHeightFieldInfo = Geometry
    attrGet = getGeometryMaxHeight
    attrSet = setGeometryMaxHeight
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

geometry_maxHeight :: AttrLabelProxy "maxHeight"
geometry_maxHeight = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data GeometryBaseWidthFieldInfo
instance AttrInfo GeometryBaseWidthFieldInfo where
    type AttrBaseTypeConstraint GeometryBaseWidthFieldInfo = (~) Geometry
    type AttrAllowedOps GeometryBaseWidthFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GeometryBaseWidthFieldInfo = (~) Int32
    type AttrTransferTypeConstraint GeometryBaseWidthFieldInfo = (~)Int32
    type AttrTransferType GeometryBaseWidthFieldInfo = Int32
    type AttrGetType GeometryBaseWidthFieldInfo = Int32
    type AttrLabel GeometryBaseWidthFieldInfo = "base_width"
    type AttrOrigin GeometryBaseWidthFieldInfo = Geometry
    attrGet = getGeometryBaseWidth
    attrSet = setGeometryBaseWidth
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

geometry_baseWidth :: AttrLabelProxy "baseWidth"
geometry_baseWidth = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data GeometryBaseHeightFieldInfo
instance AttrInfo GeometryBaseHeightFieldInfo where
    type AttrBaseTypeConstraint GeometryBaseHeightFieldInfo = (~) Geometry
    type AttrAllowedOps GeometryBaseHeightFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GeometryBaseHeightFieldInfo = (~) Int32
    type AttrTransferTypeConstraint GeometryBaseHeightFieldInfo = (~)Int32
    type AttrTransferType GeometryBaseHeightFieldInfo = Int32
    type AttrGetType GeometryBaseHeightFieldInfo = Int32
    type AttrLabel GeometryBaseHeightFieldInfo = "base_height"
    type AttrOrigin GeometryBaseHeightFieldInfo = Geometry
    attrGet = getGeometryBaseHeight
    attrSet = setGeometryBaseHeight
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

geometry_baseHeight :: AttrLabelProxy "baseHeight"
geometry_baseHeight = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data GeometryWidthIncFieldInfo
instance AttrInfo GeometryWidthIncFieldInfo where
    type AttrBaseTypeConstraint GeometryWidthIncFieldInfo = (~) Geometry
    type AttrAllowedOps GeometryWidthIncFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GeometryWidthIncFieldInfo = (~) Int32
    type AttrTransferTypeConstraint GeometryWidthIncFieldInfo = (~)Int32
    type AttrTransferType GeometryWidthIncFieldInfo = Int32
    type AttrGetType GeometryWidthIncFieldInfo = Int32
    type AttrLabel GeometryWidthIncFieldInfo = "width_inc"
    type AttrOrigin GeometryWidthIncFieldInfo = Geometry
    attrGet = getGeometryWidthInc
    attrSet = setGeometryWidthInc
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

geometry_widthInc :: AttrLabelProxy "widthInc"
geometry_widthInc = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data GeometryHeightIncFieldInfo
instance AttrInfo GeometryHeightIncFieldInfo where
    type AttrBaseTypeConstraint GeometryHeightIncFieldInfo = (~) Geometry
    type AttrAllowedOps GeometryHeightIncFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GeometryHeightIncFieldInfo = (~) Int32
    type AttrTransferTypeConstraint GeometryHeightIncFieldInfo = (~)Int32
    type AttrTransferType GeometryHeightIncFieldInfo = Int32
    type AttrGetType GeometryHeightIncFieldInfo = Int32
    type AttrLabel GeometryHeightIncFieldInfo = "height_inc"
    type AttrOrigin GeometryHeightIncFieldInfo = Geometry
    attrGet = getGeometryHeightInc
    attrSet = setGeometryHeightInc
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

geometry_heightInc :: AttrLabelProxy "heightInc"
geometry_heightInc = AttrLabelProxy

#endif


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

-- | Set the value of the “@min_aspect@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' geometry [ #minAspect 'Data.GI.Base.Attributes.:=' value ]
-- @
setGeometryMinAspect :: MonadIO m => Geometry -> Double -> m ()
setGeometryMinAspect :: Geometry -> Double -> m ()
setGeometryMinAspect s :: Geometry
s val :: Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Geometry -> (Ptr Geometry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Geometry
s ((Ptr Geometry -> IO ()) -> IO ())
-> (Ptr Geometry -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Geometry
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 Geometry
ptr Ptr Geometry -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data GeometryMinAspectFieldInfo
instance AttrInfo GeometryMinAspectFieldInfo where
    type AttrBaseTypeConstraint GeometryMinAspectFieldInfo = (~) Geometry
    type AttrAllowedOps GeometryMinAspectFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GeometryMinAspectFieldInfo = (~) Double
    type AttrTransferTypeConstraint GeometryMinAspectFieldInfo = (~)Double
    type AttrTransferType GeometryMinAspectFieldInfo = Double
    type AttrGetType GeometryMinAspectFieldInfo = Double
    type AttrLabel GeometryMinAspectFieldInfo = "min_aspect"
    type AttrOrigin GeometryMinAspectFieldInfo = Geometry
    attrGet = getGeometryMinAspect
    attrSet = setGeometryMinAspect
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

geometry_minAspect :: AttrLabelProxy "minAspect"
geometry_minAspect = AttrLabelProxy

#endif


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

-- | Set the value of the “@max_aspect@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' geometry [ #maxAspect 'Data.GI.Base.Attributes.:=' value ]
-- @
setGeometryMaxAspect :: MonadIO m => Geometry -> Double -> m ()
setGeometryMaxAspect :: Geometry -> Double -> m ()
setGeometryMaxAspect s :: Geometry
s val :: Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Geometry -> (Ptr Geometry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Geometry
s ((Ptr Geometry -> IO ()) -> IO ())
-> (Ptr Geometry -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Geometry
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 Geometry
ptr Ptr Geometry -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data GeometryMaxAspectFieldInfo
instance AttrInfo GeometryMaxAspectFieldInfo where
    type AttrBaseTypeConstraint GeometryMaxAspectFieldInfo = (~) Geometry
    type AttrAllowedOps GeometryMaxAspectFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GeometryMaxAspectFieldInfo = (~) Double
    type AttrTransferTypeConstraint GeometryMaxAspectFieldInfo = (~)Double
    type AttrTransferType GeometryMaxAspectFieldInfo = Double
    type AttrGetType GeometryMaxAspectFieldInfo = Double
    type AttrLabel GeometryMaxAspectFieldInfo = "max_aspect"
    type AttrOrigin GeometryMaxAspectFieldInfo = Geometry
    attrGet = getGeometryMaxAspect
    attrSet = setGeometryMaxAspect
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

geometry_maxAspect :: AttrLabelProxy "maxAspect"
geometry_maxAspect = AttrLabelProxy

#endif


-- | Get the value of the “@win_gravity@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' geometry #winGravity
-- @
getGeometryWinGravity :: MonadIO m => Geometry -> m Gdk.Enums.Gravity
getGeometryWinGravity :: Geometry -> m Gravity
getGeometryWinGravity s :: Geometry
s = IO Gravity -> m Gravity
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Gravity -> m Gravity) -> IO Gravity -> m Gravity
forall a b. (a -> b) -> a -> b
$ Geometry -> (Ptr Geometry -> IO Gravity) -> IO Gravity
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Geometry
s ((Ptr Geometry -> IO Gravity) -> IO Gravity)
-> (Ptr Geometry -> IO Gravity) -> IO Gravity
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Geometry
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr Geometry
ptr Ptr Geometry -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48) :: IO CUInt
    let val' :: Gravity
val' = (Int -> Gravity
forall a. Enum a => Int -> a
toEnum (Int -> Gravity) -> (CUInt -> Int) -> CUInt -> Gravity
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
val
    Gravity -> IO Gravity
forall (m :: * -> *) a. Monad m => a -> m a
return Gravity
val'

-- | Set the value of the “@win_gravity@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' geometry [ #winGravity 'Data.GI.Base.Attributes.:=' value ]
-- @
setGeometryWinGravity :: MonadIO m => Geometry -> Gdk.Enums.Gravity -> m ()
setGeometryWinGravity :: Geometry -> Gravity -> m ()
setGeometryWinGravity s :: Geometry
s val :: Gravity
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Geometry -> (Ptr Geometry -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Geometry
s ((Ptr Geometry -> IO ()) -> IO ())
-> (Ptr Geometry -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr Geometry
ptr -> do
    let val' :: CUInt
val' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Gravity -> Int) -> Gravity -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Gravity -> Int
forall a. Enum a => a -> Int
fromEnum) Gravity
val
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Geometry
ptr Ptr Geometry -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48) (CUInt
val' :: CUInt)

#if defined(ENABLE_OVERLOADING)
data GeometryWinGravityFieldInfo
instance AttrInfo GeometryWinGravityFieldInfo where
    type AttrBaseTypeConstraint GeometryWinGravityFieldInfo = (~) Geometry
    type AttrAllowedOps GeometryWinGravityFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GeometryWinGravityFieldInfo = (~) Gdk.Enums.Gravity
    type AttrTransferTypeConstraint GeometryWinGravityFieldInfo = (~)Gdk.Enums.Gravity
    type AttrTransferType GeometryWinGravityFieldInfo = Gdk.Enums.Gravity
    type AttrGetType GeometryWinGravityFieldInfo = Gdk.Enums.Gravity
    type AttrLabel GeometryWinGravityFieldInfo = "win_gravity"
    type AttrOrigin GeometryWinGravityFieldInfo = Geometry
    attrGet = getGeometryWinGravity
    attrSet = setGeometryWinGravity
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

geometry_winGravity :: AttrLabelProxy "winGravity"
geometry_winGravity = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Geometry
type instance O.AttributeList Geometry = GeometryAttributeList
type GeometryAttributeList = ('[ '("minWidth", GeometryMinWidthFieldInfo), '("minHeight", GeometryMinHeightFieldInfo), '("maxWidth", GeometryMaxWidthFieldInfo), '("maxHeight", GeometryMaxHeightFieldInfo), '("baseWidth", GeometryBaseWidthFieldInfo), '("baseHeight", GeometryBaseHeightFieldInfo), '("widthInc", GeometryWidthIncFieldInfo), '("heightInc", GeometryHeightIncFieldInfo), '("minAspect", GeometryMinAspectFieldInfo), '("maxAspect", GeometryMaxAspectFieldInfo), '("winGravity", GeometryWinGravityFieldInfo)] :: [(Symbol, *)])
#endif

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

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

#endif