{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A @GtkConstraintGuide@ is an invisible layout element in a
-- @GtkConstraintLayout@.
-- 
-- The @GtkConstraintLayout@ treats guides like widgets. They
-- can be used as the source or target of a @GtkConstraint@.
-- 
-- Guides have a minimum, maximum and natural size. Depending
-- on the constraints that are applied, they can act like a
-- guideline that widgets can be aligned to, or like *flexible
-- space*.
-- 
-- Unlike a @GtkWidget@, a @GtkConstraintGuide@ will not be drawn.

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

module GI.Gtk.Objects.ConstraintGuide
    ( 

-- * Exported types
    ConstraintGuide(..)                     ,
    IsConstraintGuide                       ,
    toConstraintGuide                       ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getMaxSize]("GI.Gtk.Objects.ConstraintGuide#g:method:getMaxSize"), [getMinSize]("GI.Gtk.Objects.ConstraintGuide#g:method:getMinSize"), [getName]("GI.Gtk.Objects.ConstraintGuide#g:method:getName"), [getNatSize]("GI.Gtk.Objects.ConstraintGuide#g:method:getNatSize"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getStrength]("GI.Gtk.Objects.ConstraintGuide#g:method:getStrength").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setMaxSize]("GI.Gtk.Objects.ConstraintGuide#g:method:setMaxSize"), [setMinSize]("GI.Gtk.Objects.ConstraintGuide#g:method:setMinSize"), [setName]("GI.Gtk.Objects.ConstraintGuide#g:method:setName"), [setNatSize]("GI.Gtk.Objects.ConstraintGuide#g:method:setNatSize"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setStrength]("GI.Gtk.Objects.ConstraintGuide#g:method:setStrength").

#if defined(ENABLE_OVERLOADING)
    ResolveConstraintGuideMethod            ,
#endif

-- ** getMaxSize #method:getMaxSize#

#if defined(ENABLE_OVERLOADING)
    ConstraintGuideGetMaxSizeMethodInfo     ,
#endif
    constraintGuideGetMaxSize               ,


-- ** getMinSize #method:getMinSize#

#if defined(ENABLE_OVERLOADING)
    ConstraintGuideGetMinSizeMethodInfo     ,
#endif
    constraintGuideGetMinSize               ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    ConstraintGuideGetNameMethodInfo        ,
#endif
    constraintGuideGetName                  ,


-- ** getNatSize #method:getNatSize#

#if defined(ENABLE_OVERLOADING)
    ConstraintGuideGetNatSizeMethodInfo     ,
#endif
    constraintGuideGetNatSize               ,


-- ** getStrength #method:getStrength#

#if defined(ENABLE_OVERLOADING)
    ConstraintGuideGetStrengthMethodInfo    ,
#endif
    constraintGuideGetStrength              ,


-- ** new #method:new#

    constraintGuideNew                      ,


-- ** setMaxSize #method:setMaxSize#

#if defined(ENABLE_OVERLOADING)
    ConstraintGuideSetMaxSizeMethodInfo     ,
#endif
    constraintGuideSetMaxSize               ,


-- ** setMinSize #method:setMinSize#

#if defined(ENABLE_OVERLOADING)
    ConstraintGuideSetMinSizeMethodInfo     ,
#endif
    constraintGuideSetMinSize               ,


-- ** setName #method:setName#

#if defined(ENABLE_OVERLOADING)
    ConstraintGuideSetNameMethodInfo        ,
#endif
    constraintGuideSetName                  ,


-- ** setNatSize #method:setNatSize#

#if defined(ENABLE_OVERLOADING)
    ConstraintGuideSetNatSizeMethodInfo     ,
#endif
    constraintGuideSetNatSize               ,


-- ** setStrength #method:setStrength#

#if defined(ENABLE_OVERLOADING)
    ConstraintGuideSetStrengthMethodInfo    ,
#endif
    constraintGuideSetStrength              ,




 -- * Properties


-- ** maxHeight #attr:maxHeight#
-- | The maximum height of the guide.

#if defined(ENABLE_OVERLOADING)
    ConstraintGuideMaxHeightPropertyInfo    ,
#endif
#if defined(ENABLE_OVERLOADING)
    constraintGuideMaxHeight                ,
#endif
    constructConstraintGuideMaxHeight       ,
    getConstraintGuideMaxHeight             ,
    setConstraintGuideMaxHeight             ,


-- ** maxWidth #attr:maxWidth#
-- | The maximum width of the guide.

#if defined(ENABLE_OVERLOADING)
    ConstraintGuideMaxWidthPropertyInfo     ,
#endif
#if defined(ENABLE_OVERLOADING)
    constraintGuideMaxWidth                 ,
#endif
    constructConstraintGuideMaxWidth        ,
    getConstraintGuideMaxWidth              ,
    setConstraintGuideMaxWidth              ,


-- ** minHeight #attr:minHeight#
-- | The minimum height of the guide.

#if defined(ENABLE_OVERLOADING)
    ConstraintGuideMinHeightPropertyInfo    ,
#endif
#if defined(ENABLE_OVERLOADING)
    constraintGuideMinHeight                ,
#endif
    constructConstraintGuideMinHeight       ,
    getConstraintGuideMinHeight             ,
    setConstraintGuideMinHeight             ,


-- ** minWidth #attr:minWidth#
-- | The minimum width of the guide.

#if defined(ENABLE_OVERLOADING)
    ConstraintGuideMinWidthPropertyInfo     ,
#endif
#if defined(ENABLE_OVERLOADING)
    constraintGuideMinWidth                 ,
#endif
    constructConstraintGuideMinWidth        ,
    getConstraintGuideMinWidth              ,
    setConstraintGuideMinWidth              ,


-- ** name #attr:name#
-- | A name that identifies the @GtkConstraintGuide@, for debugging.

#if defined(ENABLE_OVERLOADING)
    ConstraintGuideNamePropertyInfo         ,
#endif
    clearConstraintGuideName                ,
#if defined(ENABLE_OVERLOADING)
    constraintGuideName                     ,
#endif
    constructConstraintGuideName            ,
    getConstraintGuideName                  ,
    setConstraintGuideName                  ,


-- ** natHeight #attr:natHeight#
-- | The preferred, or natural, height of the guide.

#if defined(ENABLE_OVERLOADING)
    ConstraintGuideNatHeightPropertyInfo    ,
#endif
#if defined(ENABLE_OVERLOADING)
    constraintGuideNatHeight                ,
#endif
    constructConstraintGuideNatHeight       ,
    getConstraintGuideNatHeight             ,
    setConstraintGuideNatHeight             ,


-- ** natWidth #attr:natWidth#
-- | The preferred, or natural, width of the guide.

#if defined(ENABLE_OVERLOADING)
    ConstraintGuideNatWidthPropertyInfo     ,
#endif
#if defined(ENABLE_OVERLOADING)
    constraintGuideNatWidth                 ,
#endif
    constructConstraintGuideNatWidth        ,
    getConstraintGuideNatWidth              ,
    setConstraintGuideNatWidth              ,


-- ** strength #attr:strength#
-- | The @GtkConstraintStrength@ to be used for the constraint on
-- the natural size of the guide.

#if defined(ENABLE_OVERLOADING)
    ConstraintGuideStrengthPropertyInfo     ,
#endif
#if defined(ENABLE_OVERLOADING)
    constraintGuideStrength                 ,
#endif
    constructConstraintGuideStrength        ,
    getConstraintGuideStrength              ,
    setConstraintGuideStrength              ,




    ) 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.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

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget

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

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

foreign import ccall "gtk_constraint_guide_get_type"
    c_gtk_constraint_guide_get_type :: IO B.Types.GType

instance B.Types.TypedObject ConstraintGuide where
    glibType :: IO GType
glibType = IO GType
c_gtk_constraint_guide_get_type

instance B.Types.GObject ConstraintGuide

-- | Type class for types which can be safely cast to `ConstraintGuide`, for instance with `toConstraintGuide`.
class (SP.GObject o, O.IsDescendantOf ConstraintGuide o) => IsConstraintGuide o
instance (SP.GObject o, O.IsDescendantOf ConstraintGuide o) => IsConstraintGuide o

instance O.HasParentTypes ConstraintGuide
type instance O.ParentTypes ConstraintGuide = '[GObject.Object.Object, Gtk.ConstraintTarget.ConstraintTarget]

-- | Cast to `ConstraintGuide`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toConstraintGuide :: (MIO.MonadIO m, IsConstraintGuide o) => o -> m ConstraintGuide
toConstraintGuide :: forall (m :: * -> *) o.
(MonadIO m, IsConstraintGuide o) =>
o -> m ConstraintGuide
toConstraintGuide = IO ConstraintGuide -> m ConstraintGuide
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ConstraintGuide -> m ConstraintGuide)
-> (o -> IO ConstraintGuide) -> o -> m ConstraintGuide
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr ConstraintGuide -> ConstraintGuide)
-> o -> IO ConstraintGuide
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr ConstraintGuide -> ConstraintGuide
ConstraintGuide

-- | Convert 'ConstraintGuide' 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 ConstraintGuide) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_constraint_guide_get_type
    gvalueSet_ :: Ptr GValue -> Maybe ConstraintGuide -> IO ()
gvalueSet_ Ptr GValue
gv Maybe ConstraintGuide
P.Nothing = Ptr GValue -> Ptr ConstraintGuide -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr ConstraintGuide
forall a. Ptr a
FP.nullPtr :: FP.Ptr ConstraintGuide)
    gvalueSet_ Ptr GValue
gv (P.Just ConstraintGuide
obj) = ConstraintGuide -> (Ptr ConstraintGuide -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ConstraintGuide
obj (Ptr GValue -> Ptr ConstraintGuide -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe ConstraintGuide)
gvalueGet_ Ptr GValue
gv = do
        Ptr ConstraintGuide
ptr <- Ptr GValue -> IO (Ptr ConstraintGuide)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr ConstraintGuide)
        if Ptr ConstraintGuide
ptr Ptr ConstraintGuide -> Ptr ConstraintGuide -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr ConstraintGuide
forall a. Ptr a
FP.nullPtr
        then ConstraintGuide -> Maybe ConstraintGuide
forall a. a -> Maybe a
P.Just (ConstraintGuide -> Maybe ConstraintGuide)
-> IO ConstraintGuide -> IO (Maybe ConstraintGuide)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr ConstraintGuide -> ConstraintGuide)
-> Ptr ConstraintGuide -> IO ConstraintGuide
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr ConstraintGuide -> ConstraintGuide
ConstraintGuide Ptr ConstraintGuide
ptr
        else Maybe ConstraintGuide -> IO (Maybe ConstraintGuide)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ConstraintGuide
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveConstraintGuideMethod (t :: Symbol) (o :: *) :: * where
    ResolveConstraintGuideMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveConstraintGuideMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveConstraintGuideMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveConstraintGuideMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveConstraintGuideMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveConstraintGuideMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveConstraintGuideMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveConstraintGuideMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveConstraintGuideMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveConstraintGuideMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveConstraintGuideMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveConstraintGuideMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveConstraintGuideMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveConstraintGuideMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveConstraintGuideMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveConstraintGuideMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveConstraintGuideMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveConstraintGuideMethod "getMaxSize" o = ConstraintGuideGetMaxSizeMethodInfo
    ResolveConstraintGuideMethod "getMinSize" o = ConstraintGuideGetMinSizeMethodInfo
    ResolveConstraintGuideMethod "getName" o = ConstraintGuideGetNameMethodInfo
    ResolveConstraintGuideMethod "getNatSize" o = ConstraintGuideGetNatSizeMethodInfo
    ResolveConstraintGuideMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveConstraintGuideMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveConstraintGuideMethod "getStrength" o = ConstraintGuideGetStrengthMethodInfo
    ResolveConstraintGuideMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveConstraintGuideMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveConstraintGuideMethod "setMaxSize" o = ConstraintGuideSetMaxSizeMethodInfo
    ResolveConstraintGuideMethod "setMinSize" o = ConstraintGuideSetMinSizeMethodInfo
    ResolveConstraintGuideMethod "setName" o = ConstraintGuideSetNameMethodInfo
    ResolveConstraintGuideMethod "setNatSize" o = ConstraintGuideSetNatSizeMethodInfo
    ResolveConstraintGuideMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveConstraintGuideMethod "setStrength" o = ConstraintGuideSetStrengthMethodInfo
    ResolveConstraintGuideMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveConstraintGuideMethod t ConstraintGuide, O.OverloadedMethod info ConstraintGuide p) => OL.IsLabel t (ConstraintGuide -> 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 ~ ResolveConstraintGuideMethod t ConstraintGuide, O.OverloadedMethod info ConstraintGuide p, R.HasField t ConstraintGuide p) => R.HasField t ConstraintGuide p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- VVV Prop "max-height"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@max-height@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' constraintGuide #maxHeight
-- @
getConstraintGuideMaxHeight :: (MonadIO m, IsConstraintGuide o) => o -> m Int32
getConstraintGuideMaxHeight :: forall (m :: * -> *) o.
(MonadIO m, IsConstraintGuide o) =>
o -> m Int32
getConstraintGuideMaxHeight o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"max-height"

-- | Set the value of the “@max-height@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' constraintGuide [ #maxHeight 'Data.GI.Base.Attributes.:=' value ]
-- @
setConstraintGuideMaxHeight :: (MonadIO m, IsConstraintGuide o) => o -> Int32 -> m ()
setConstraintGuideMaxHeight :: forall (m :: * -> *) o.
(MonadIO m, IsConstraintGuide o) =>
o -> Int32 -> m ()
setConstraintGuideMaxHeight o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"max-height" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@max-height@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructConstraintGuideMaxHeight :: (IsConstraintGuide o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructConstraintGuideMaxHeight :: forall o (m :: * -> *).
(IsConstraintGuide o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructConstraintGuideMaxHeight Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"max-height" Int32
val

#if defined(ENABLE_OVERLOADING)
data ConstraintGuideMaxHeightPropertyInfo
instance AttrInfo ConstraintGuideMaxHeightPropertyInfo where
    type AttrAllowedOps ConstraintGuideMaxHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ConstraintGuideMaxHeightPropertyInfo = IsConstraintGuide
    type AttrSetTypeConstraint ConstraintGuideMaxHeightPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint ConstraintGuideMaxHeightPropertyInfo = (~) Int32
    type AttrTransferType ConstraintGuideMaxHeightPropertyInfo = Int32
    type AttrGetType ConstraintGuideMaxHeightPropertyInfo = Int32
    type AttrLabel ConstraintGuideMaxHeightPropertyInfo = "max-height"
    type AttrOrigin ConstraintGuideMaxHeightPropertyInfo = ConstraintGuide
    attrGet = getConstraintGuideMaxHeight
    attrSet = setConstraintGuideMaxHeight
    attrTransfer _ v = do
        return v
    attrConstruct = constructConstraintGuideMaxHeight
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ConstraintGuide.maxHeight"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ConstraintGuide.html#g:attr:maxHeight"
        })
#endif

-- VVV Prop "max-width"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@max-width@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' constraintGuide #maxWidth
-- @
getConstraintGuideMaxWidth :: (MonadIO m, IsConstraintGuide o) => o -> m Int32
getConstraintGuideMaxWidth :: forall (m :: * -> *) o.
(MonadIO m, IsConstraintGuide o) =>
o -> m Int32
getConstraintGuideMaxWidth o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"max-width"

-- | Set the value of the “@max-width@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' constraintGuide [ #maxWidth 'Data.GI.Base.Attributes.:=' value ]
-- @
setConstraintGuideMaxWidth :: (MonadIO m, IsConstraintGuide o) => o -> Int32 -> m ()
setConstraintGuideMaxWidth :: forall (m :: * -> *) o.
(MonadIO m, IsConstraintGuide o) =>
o -> Int32 -> m ()
setConstraintGuideMaxWidth o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"max-width" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@max-width@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructConstraintGuideMaxWidth :: (IsConstraintGuide o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructConstraintGuideMaxWidth :: forall o (m :: * -> *).
(IsConstraintGuide o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructConstraintGuideMaxWidth Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"max-width" Int32
val

#if defined(ENABLE_OVERLOADING)
data ConstraintGuideMaxWidthPropertyInfo
instance AttrInfo ConstraintGuideMaxWidthPropertyInfo where
    type AttrAllowedOps ConstraintGuideMaxWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ConstraintGuideMaxWidthPropertyInfo = IsConstraintGuide
    type AttrSetTypeConstraint ConstraintGuideMaxWidthPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint ConstraintGuideMaxWidthPropertyInfo = (~) Int32
    type AttrTransferType ConstraintGuideMaxWidthPropertyInfo = Int32
    type AttrGetType ConstraintGuideMaxWidthPropertyInfo = Int32
    type AttrLabel ConstraintGuideMaxWidthPropertyInfo = "max-width"
    type AttrOrigin ConstraintGuideMaxWidthPropertyInfo = ConstraintGuide
    attrGet = getConstraintGuideMaxWidth
    attrSet = setConstraintGuideMaxWidth
    attrTransfer _ v = do
        return v
    attrConstruct = constructConstraintGuideMaxWidth
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ConstraintGuide.maxWidth"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ConstraintGuide.html#g:attr:maxWidth"
        })
#endif

-- VVV Prop "min-height"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@min-height@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' constraintGuide #minHeight
-- @
getConstraintGuideMinHeight :: (MonadIO m, IsConstraintGuide o) => o -> m Int32
getConstraintGuideMinHeight :: forall (m :: * -> *) o.
(MonadIO m, IsConstraintGuide o) =>
o -> m Int32
getConstraintGuideMinHeight o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"min-height"

-- | Set the value of the “@min-height@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' constraintGuide [ #minHeight 'Data.GI.Base.Attributes.:=' value ]
-- @
setConstraintGuideMinHeight :: (MonadIO m, IsConstraintGuide o) => o -> Int32 -> m ()
setConstraintGuideMinHeight :: forall (m :: * -> *) o.
(MonadIO m, IsConstraintGuide o) =>
o -> Int32 -> m ()
setConstraintGuideMinHeight o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"min-height" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@min-height@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructConstraintGuideMinHeight :: (IsConstraintGuide o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructConstraintGuideMinHeight :: forall o (m :: * -> *).
(IsConstraintGuide o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructConstraintGuideMinHeight Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"min-height" Int32
val

#if defined(ENABLE_OVERLOADING)
data ConstraintGuideMinHeightPropertyInfo
instance AttrInfo ConstraintGuideMinHeightPropertyInfo where
    type AttrAllowedOps ConstraintGuideMinHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ConstraintGuideMinHeightPropertyInfo = IsConstraintGuide
    type AttrSetTypeConstraint ConstraintGuideMinHeightPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint ConstraintGuideMinHeightPropertyInfo = (~) Int32
    type AttrTransferType ConstraintGuideMinHeightPropertyInfo = Int32
    type AttrGetType ConstraintGuideMinHeightPropertyInfo = Int32
    type AttrLabel ConstraintGuideMinHeightPropertyInfo = "min-height"
    type AttrOrigin ConstraintGuideMinHeightPropertyInfo = ConstraintGuide
    attrGet = getConstraintGuideMinHeight
    attrSet = setConstraintGuideMinHeight
    attrTransfer _ v = do
        return v
    attrConstruct = constructConstraintGuideMinHeight
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ConstraintGuide.minHeight"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ConstraintGuide.html#g:attr:minHeight"
        })
#endif

-- VVV Prop "min-width"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@min-width@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' constraintGuide #minWidth
-- @
getConstraintGuideMinWidth :: (MonadIO m, IsConstraintGuide o) => o -> m Int32
getConstraintGuideMinWidth :: forall (m :: * -> *) o.
(MonadIO m, IsConstraintGuide o) =>
o -> m Int32
getConstraintGuideMinWidth o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"min-width"

-- | Set the value of the “@min-width@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' constraintGuide [ #minWidth 'Data.GI.Base.Attributes.:=' value ]
-- @
setConstraintGuideMinWidth :: (MonadIO m, IsConstraintGuide o) => o -> Int32 -> m ()
setConstraintGuideMinWidth :: forall (m :: * -> *) o.
(MonadIO m, IsConstraintGuide o) =>
o -> Int32 -> m ()
setConstraintGuideMinWidth o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"min-width" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@min-width@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructConstraintGuideMinWidth :: (IsConstraintGuide o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructConstraintGuideMinWidth :: forall o (m :: * -> *).
(IsConstraintGuide o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructConstraintGuideMinWidth Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"min-width" Int32
val

#if defined(ENABLE_OVERLOADING)
data ConstraintGuideMinWidthPropertyInfo
instance AttrInfo ConstraintGuideMinWidthPropertyInfo where
    type AttrAllowedOps ConstraintGuideMinWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ConstraintGuideMinWidthPropertyInfo = IsConstraintGuide
    type AttrSetTypeConstraint ConstraintGuideMinWidthPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint ConstraintGuideMinWidthPropertyInfo = (~) Int32
    type AttrTransferType ConstraintGuideMinWidthPropertyInfo = Int32
    type AttrGetType ConstraintGuideMinWidthPropertyInfo = Int32
    type AttrLabel ConstraintGuideMinWidthPropertyInfo = "min-width"
    type AttrOrigin ConstraintGuideMinWidthPropertyInfo = ConstraintGuide
    attrGet = getConstraintGuideMinWidth
    attrSet = setConstraintGuideMinWidth
    attrTransfer _ v = do
        return v
    attrConstruct = constructConstraintGuideMinWidth
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ConstraintGuide.minWidth"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ConstraintGuide.html#g:attr:minWidth"
        })
#endif

-- VVV Prop "name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,Just True)

-- | Get the value of the “@name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' constraintGuide #name
-- @
getConstraintGuideName :: (MonadIO m, IsConstraintGuide o) => o -> m (Maybe T.Text)
getConstraintGuideName :: forall (m :: * -> *) o.
(MonadIO m, IsConstraintGuide o) =>
o -> m (Maybe Text)
getConstraintGuideName o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"name"

-- | Set the value of the “@name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' constraintGuide [ #name 'Data.GI.Base.Attributes.:=' value ]
-- @
setConstraintGuideName :: (MonadIO m, IsConstraintGuide o) => o -> T.Text -> m ()
setConstraintGuideName :: forall (m :: * -> *) o.
(MonadIO m, IsConstraintGuide o) =>
o -> Text -> m ()
setConstraintGuideName o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructConstraintGuideName :: (IsConstraintGuide o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructConstraintGuideName :: forall o (m :: * -> *).
(IsConstraintGuide o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructConstraintGuideName Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

-- | Set the value of the “@name@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #name
-- @
clearConstraintGuideName :: (MonadIO m, IsConstraintGuide o) => o -> m ()
clearConstraintGuideName :: forall (m :: * -> *) o.
(MonadIO m, IsConstraintGuide o) =>
o -> m ()
clearConstraintGuideName o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"name" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data ConstraintGuideNamePropertyInfo
instance AttrInfo ConstraintGuideNamePropertyInfo where
    type AttrAllowedOps ConstraintGuideNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ConstraintGuideNamePropertyInfo = IsConstraintGuide
    type AttrSetTypeConstraint ConstraintGuideNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ConstraintGuideNamePropertyInfo = (~) T.Text
    type AttrTransferType ConstraintGuideNamePropertyInfo = T.Text
    type AttrGetType ConstraintGuideNamePropertyInfo = (Maybe T.Text)
    type AttrLabel ConstraintGuideNamePropertyInfo = "name"
    type AttrOrigin ConstraintGuideNamePropertyInfo = ConstraintGuide
    attrGet = getConstraintGuideName
    attrSet = setConstraintGuideName
    attrTransfer _ v = do
        return v
    attrConstruct = constructConstraintGuideName
    attrClear = clearConstraintGuideName
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ConstraintGuide.name"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ConstraintGuide.html#g:attr:name"
        })
#endif

-- VVV Prop "nat-height"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@nat-height@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' constraintGuide #natHeight
-- @
getConstraintGuideNatHeight :: (MonadIO m, IsConstraintGuide o) => o -> m Int32
getConstraintGuideNatHeight :: forall (m :: * -> *) o.
(MonadIO m, IsConstraintGuide o) =>
o -> m Int32
getConstraintGuideNatHeight o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"nat-height"

-- | Set the value of the “@nat-height@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' constraintGuide [ #natHeight 'Data.GI.Base.Attributes.:=' value ]
-- @
setConstraintGuideNatHeight :: (MonadIO m, IsConstraintGuide o) => o -> Int32 -> m ()
setConstraintGuideNatHeight :: forall (m :: * -> *) o.
(MonadIO m, IsConstraintGuide o) =>
o -> Int32 -> m ()
setConstraintGuideNatHeight o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"nat-height" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@nat-height@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructConstraintGuideNatHeight :: (IsConstraintGuide o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructConstraintGuideNatHeight :: forall o (m :: * -> *).
(IsConstraintGuide o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructConstraintGuideNatHeight Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"nat-height" Int32
val

#if defined(ENABLE_OVERLOADING)
data ConstraintGuideNatHeightPropertyInfo
instance AttrInfo ConstraintGuideNatHeightPropertyInfo where
    type AttrAllowedOps ConstraintGuideNatHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ConstraintGuideNatHeightPropertyInfo = IsConstraintGuide
    type AttrSetTypeConstraint ConstraintGuideNatHeightPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint ConstraintGuideNatHeightPropertyInfo = (~) Int32
    type AttrTransferType ConstraintGuideNatHeightPropertyInfo = Int32
    type AttrGetType ConstraintGuideNatHeightPropertyInfo = Int32
    type AttrLabel ConstraintGuideNatHeightPropertyInfo = "nat-height"
    type AttrOrigin ConstraintGuideNatHeightPropertyInfo = ConstraintGuide
    attrGet = getConstraintGuideNatHeight
    attrSet = setConstraintGuideNatHeight
    attrTransfer _ v = do
        return v
    attrConstruct = constructConstraintGuideNatHeight
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ConstraintGuide.natHeight"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ConstraintGuide.html#g:attr:natHeight"
        })
#endif

-- VVV Prop "nat-width"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@nat-width@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' constraintGuide #natWidth
-- @
getConstraintGuideNatWidth :: (MonadIO m, IsConstraintGuide o) => o -> m Int32
getConstraintGuideNatWidth :: forall (m :: * -> *) o.
(MonadIO m, IsConstraintGuide o) =>
o -> m Int32
getConstraintGuideNatWidth o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"nat-width"

-- | Set the value of the “@nat-width@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' constraintGuide [ #natWidth 'Data.GI.Base.Attributes.:=' value ]
-- @
setConstraintGuideNatWidth :: (MonadIO m, IsConstraintGuide o) => o -> Int32 -> m ()
setConstraintGuideNatWidth :: forall (m :: * -> *) o.
(MonadIO m, IsConstraintGuide o) =>
o -> Int32 -> m ()
setConstraintGuideNatWidth o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"nat-width" Int32
val

-- | Construct a `GValueConstruct` with valid value for the “@nat-width@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructConstraintGuideNatWidth :: (IsConstraintGuide o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructConstraintGuideNatWidth :: forall o (m :: * -> *).
(IsConstraintGuide o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructConstraintGuideNatWidth Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"nat-width" Int32
val

#if defined(ENABLE_OVERLOADING)
data ConstraintGuideNatWidthPropertyInfo
instance AttrInfo ConstraintGuideNatWidthPropertyInfo where
    type AttrAllowedOps ConstraintGuideNatWidthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ConstraintGuideNatWidthPropertyInfo = IsConstraintGuide
    type AttrSetTypeConstraint ConstraintGuideNatWidthPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint ConstraintGuideNatWidthPropertyInfo = (~) Int32
    type AttrTransferType ConstraintGuideNatWidthPropertyInfo = Int32
    type AttrGetType ConstraintGuideNatWidthPropertyInfo = Int32
    type AttrLabel ConstraintGuideNatWidthPropertyInfo = "nat-width"
    type AttrOrigin ConstraintGuideNatWidthPropertyInfo = ConstraintGuide
    attrGet = getConstraintGuideNatWidth
    attrSet = setConstraintGuideNatWidth
    attrTransfer _ v = do
        return v
    attrConstruct = constructConstraintGuideNatWidth
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ConstraintGuide.natWidth"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ConstraintGuide.html#g:attr:natWidth"
        })
#endif

-- VVV Prop "strength"
   -- Type: TInterface (Name {namespace = "Gtk", name = "ConstraintStrength"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@strength@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' constraintGuide #strength
-- @
getConstraintGuideStrength :: (MonadIO m, IsConstraintGuide o) => o -> m Gtk.Enums.ConstraintStrength
getConstraintGuideStrength :: forall (m :: * -> *) o.
(MonadIO m, IsConstraintGuide o) =>
o -> m ConstraintStrength
getConstraintGuideStrength o
obj = IO ConstraintStrength -> m ConstraintStrength
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ConstraintStrength -> m ConstraintStrength)
-> IO ConstraintStrength -> m ConstraintStrength
forall a b. (a -> b) -> a -> b
$ o -> String -> IO ConstraintStrength
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"strength"

-- | Set the value of the “@strength@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' constraintGuide [ #strength 'Data.GI.Base.Attributes.:=' value ]
-- @
setConstraintGuideStrength :: (MonadIO m, IsConstraintGuide o) => o -> Gtk.Enums.ConstraintStrength -> m ()
setConstraintGuideStrength :: forall (m :: * -> *) o.
(MonadIO m, IsConstraintGuide o) =>
o -> ConstraintStrength -> m ()
setConstraintGuideStrength o
obj ConstraintStrength
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> ConstraintStrength -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"strength" ConstraintStrength
val

-- | Construct a `GValueConstruct` with valid value for the “@strength@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructConstraintGuideStrength :: (IsConstraintGuide o, MIO.MonadIO m) => Gtk.Enums.ConstraintStrength -> m (GValueConstruct o)
constructConstraintGuideStrength :: forall o (m :: * -> *).
(IsConstraintGuide o, MonadIO m) =>
ConstraintStrength -> m (GValueConstruct o)
constructConstraintGuideStrength ConstraintStrength
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> ConstraintStrength -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"strength" ConstraintStrength
val

#if defined(ENABLE_OVERLOADING)
data ConstraintGuideStrengthPropertyInfo
instance AttrInfo ConstraintGuideStrengthPropertyInfo where
    type AttrAllowedOps ConstraintGuideStrengthPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ConstraintGuideStrengthPropertyInfo = IsConstraintGuide
    type AttrSetTypeConstraint ConstraintGuideStrengthPropertyInfo = (~) Gtk.Enums.ConstraintStrength
    type AttrTransferTypeConstraint ConstraintGuideStrengthPropertyInfo = (~) Gtk.Enums.ConstraintStrength
    type AttrTransferType ConstraintGuideStrengthPropertyInfo = Gtk.Enums.ConstraintStrength
    type AttrGetType ConstraintGuideStrengthPropertyInfo = Gtk.Enums.ConstraintStrength
    type AttrLabel ConstraintGuideStrengthPropertyInfo = "strength"
    type AttrOrigin ConstraintGuideStrengthPropertyInfo = ConstraintGuide
    attrGet = getConstraintGuideStrength
    attrSet = setConstraintGuideStrength
    attrTransfer _ v = do
        return v
    attrConstruct = constructConstraintGuideStrength
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ConstraintGuide.strength"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ConstraintGuide.html#g:attr:strength"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ConstraintGuide
type instance O.AttributeList ConstraintGuide = ConstraintGuideAttributeList
type ConstraintGuideAttributeList = ('[ '("maxHeight", ConstraintGuideMaxHeightPropertyInfo), '("maxWidth", ConstraintGuideMaxWidthPropertyInfo), '("minHeight", ConstraintGuideMinHeightPropertyInfo), '("minWidth", ConstraintGuideMinWidthPropertyInfo), '("name", ConstraintGuideNamePropertyInfo), '("natHeight", ConstraintGuideNatHeightPropertyInfo), '("natWidth", ConstraintGuideNatWidthPropertyInfo), '("strength", ConstraintGuideStrengthPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
constraintGuideMaxHeight :: AttrLabelProxy "maxHeight"
constraintGuideMaxHeight = AttrLabelProxy

constraintGuideMaxWidth :: AttrLabelProxy "maxWidth"
constraintGuideMaxWidth = AttrLabelProxy

constraintGuideMinHeight :: AttrLabelProxy "minHeight"
constraintGuideMinHeight = AttrLabelProxy

constraintGuideMinWidth :: AttrLabelProxy "minWidth"
constraintGuideMinWidth = AttrLabelProxy

constraintGuideName :: AttrLabelProxy "name"
constraintGuideName = AttrLabelProxy

constraintGuideNatHeight :: AttrLabelProxy "natHeight"
constraintGuideNatHeight = AttrLabelProxy

constraintGuideNatWidth :: AttrLabelProxy "natWidth"
constraintGuideNatWidth = AttrLabelProxy

constraintGuideStrength :: AttrLabelProxy "strength"
constraintGuideStrength = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ConstraintGuide = ConstraintGuideSignalList
type ConstraintGuideSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method ConstraintGuide::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "ConstraintGuide" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_constraint_guide_new" gtk_constraint_guide_new :: 
    IO (Ptr ConstraintGuide)

-- | Creates a new @GtkConstraintGuide@ object.
constraintGuideNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m ConstraintGuide
    -- ^ __Returns:__ a new @GtkConstraintGuide@ object.
constraintGuideNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m ConstraintGuide
constraintGuideNew  = IO ConstraintGuide -> m ConstraintGuide
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ConstraintGuide -> m ConstraintGuide)
-> IO ConstraintGuide -> m ConstraintGuide
forall a b. (a -> b) -> a -> b
$ do
    Ptr ConstraintGuide
result <- IO (Ptr ConstraintGuide)
gtk_constraint_guide_new
    Text -> Ptr ConstraintGuide -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"constraintGuideNew" Ptr ConstraintGuide
result
    ConstraintGuide
result' <- ((ManagedPtr ConstraintGuide -> ConstraintGuide)
-> Ptr ConstraintGuide -> IO ConstraintGuide
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ConstraintGuide -> ConstraintGuide
ConstraintGuide) Ptr ConstraintGuide
result
    ConstraintGuide -> IO ConstraintGuide
forall (m :: * -> *) a. Monad m => a -> m a
return ConstraintGuide
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method ConstraintGuide::get_max_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "guide"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ConstraintGuide" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkConstraintGuide` object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the maximum width"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the maximum height"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_constraint_guide_get_max_size" gtk_constraint_guide_get_max_size :: 
    Ptr ConstraintGuide ->                  -- guide : TInterface (Name {namespace = "Gtk", name = "ConstraintGuide"})
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    IO ()

-- | Gets the maximum size of /@guide@/.
constraintGuideGetMaxSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraintGuide a) =>
    a
    -- ^ /@guide@/: a @GtkConstraintGuide@ object
    -> Int32
    -- ^ /@width@/: return location for the maximum width
    -> Int32
    -- ^ /@height@/: return location for the maximum height
    -> m ()
constraintGuideGetMaxSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraintGuide a) =>
a -> Int32 -> Int32 -> m ()
constraintGuideGetMaxSize a
guide Int32
width Int32
height = 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 ConstraintGuide
guide' <- a -> IO (Ptr ConstraintGuide)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
guide
    Ptr ConstraintGuide -> Int32 -> Int32 -> IO ()
gtk_constraint_guide_get_max_size Ptr ConstraintGuide
guide' Int32
width Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
guide
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ConstraintGuideGetMaxSizeMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m, IsConstraintGuide a) => O.OverloadedMethod ConstraintGuideGetMaxSizeMethodInfo a signature where
    overloadedMethod = constraintGuideGetMaxSize

instance O.OverloadedMethodInfo ConstraintGuideGetMaxSizeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ConstraintGuide.constraintGuideGetMaxSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ConstraintGuide.html#v:constraintGuideGetMaxSize"
        })


#endif

-- method ConstraintGuide::get_min_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "guide"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ConstraintGuide" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkConstraintGuide` object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the minimum width"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the minimum height"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_constraint_guide_get_min_size" gtk_constraint_guide_get_min_size :: 
    Ptr ConstraintGuide ->                  -- guide : TInterface (Name {namespace = "Gtk", name = "ConstraintGuide"})
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    IO ()

-- | Gets the minimum size of /@guide@/.
constraintGuideGetMinSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraintGuide a) =>
    a
    -- ^ /@guide@/: a @GtkConstraintGuide@ object
    -> Int32
    -- ^ /@width@/: return location for the minimum width
    -> Int32
    -- ^ /@height@/: return location for the minimum height
    -> m ()
constraintGuideGetMinSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraintGuide a) =>
a -> Int32 -> Int32 -> m ()
constraintGuideGetMinSize a
guide Int32
width Int32
height = 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 ConstraintGuide
guide' <- a -> IO (Ptr ConstraintGuide)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
guide
    Ptr ConstraintGuide -> Int32 -> Int32 -> IO ()
gtk_constraint_guide_get_min_size Ptr ConstraintGuide
guide' Int32
width Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
guide
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ConstraintGuideGetMinSizeMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m, IsConstraintGuide a) => O.OverloadedMethod ConstraintGuideGetMinSizeMethodInfo a signature where
    overloadedMethod = constraintGuideGetMinSize

instance O.OverloadedMethodInfo ConstraintGuideGetMinSizeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ConstraintGuide.constraintGuideGetMinSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ConstraintGuide.html#v:constraintGuideGetMinSize"
        })


#endif

-- method ConstraintGuide::get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "guide"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ConstraintGuide" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkConstraintGuide`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_constraint_guide_get_name" gtk_constraint_guide_get_name :: 
    Ptr ConstraintGuide ->                  -- guide : TInterface (Name {namespace = "Gtk", name = "ConstraintGuide"})
    IO CString

-- | Retrieves the name set using 'GI.Gtk.Objects.ConstraintGuide.constraintGuideSetName'.
constraintGuideGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraintGuide a) =>
    a
    -- ^ /@guide@/: a @GtkConstraintGuide@
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the name of the guide
constraintGuideGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraintGuide a) =>
a -> m (Maybe Text)
constraintGuideGetName a
guide = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr ConstraintGuide
guide' <- a -> IO (Ptr ConstraintGuide)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
guide
    CString
result <- Ptr ConstraintGuide -> IO CString
gtk_constraint_guide_get_name Ptr ConstraintGuide
guide'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
guide
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data ConstraintGuideGetNameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsConstraintGuide a) => O.OverloadedMethod ConstraintGuideGetNameMethodInfo a signature where
    overloadedMethod = constraintGuideGetName

instance O.OverloadedMethodInfo ConstraintGuideGetNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ConstraintGuide.constraintGuideGetName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ConstraintGuide.html#v:constraintGuideGetName"
        })


#endif

-- method ConstraintGuide::get_nat_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "guide"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ConstraintGuide" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkConstraintGuide` object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the natural width"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the natural height"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_constraint_guide_get_nat_size" gtk_constraint_guide_get_nat_size :: 
    Ptr ConstraintGuide ->                  -- guide : TInterface (Name {namespace = "Gtk", name = "ConstraintGuide"})
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    IO ()

-- | Gets the natural size of /@guide@/.
constraintGuideGetNatSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraintGuide a) =>
    a
    -- ^ /@guide@/: a @GtkConstraintGuide@ object
    -> Int32
    -- ^ /@width@/: return location for the natural width
    -> Int32
    -- ^ /@height@/: return location for the natural height
    -> m ()
constraintGuideGetNatSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraintGuide a) =>
a -> Int32 -> Int32 -> m ()
constraintGuideGetNatSize a
guide Int32
width Int32
height = 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 ConstraintGuide
guide' <- a -> IO (Ptr ConstraintGuide)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
guide
    Ptr ConstraintGuide -> Int32 -> Int32 -> IO ()
gtk_constraint_guide_get_nat_size Ptr ConstraintGuide
guide' Int32
width Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
guide
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ConstraintGuideGetNatSizeMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m, IsConstraintGuide a) => O.OverloadedMethod ConstraintGuideGetNatSizeMethodInfo a signature where
    overloadedMethod = constraintGuideGetNatSize

instance O.OverloadedMethodInfo ConstraintGuideGetNatSizeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ConstraintGuide.constraintGuideGetNatSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ConstraintGuide.html#v:constraintGuideGetNatSize"
        })


#endif

-- method ConstraintGuide::get_strength
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "guide"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ConstraintGuide" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkConstraintGuide`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gtk" , name = "ConstraintStrength" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_constraint_guide_get_strength" gtk_constraint_guide_get_strength :: 
    Ptr ConstraintGuide ->                  -- guide : TInterface (Name {namespace = "Gtk", name = "ConstraintGuide"})
    IO CUInt

-- | Retrieves the strength set using 'GI.Gtk.Objects.ConstraintGuide.constraintGuideSetStrength'.
constraintGuideGetStrength ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraintGuide a) =>
    a
    -- ^ /@guide@/: a @GtkConstraintGuide@
    -> m Gtk.Enums.ConstraintStrength
    -- ^ __Returns:__ the strength of the constraint on the natural size
constraintGuideGetStrength :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraintGuide a) =>
a -> m ConstraintStrength
constraintGuideGetStrength a
guide = IO ConstraintStrength -> m ConstraintStrength
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ConstraintStrength -> m ConstraintStrength)
-> IO ConstraintStrength -> m ConstraintStrength
forall a b. (a -> b) -> a -> b
$ do
    Ptr ConstraintGuide
guide' <- a -> IO (Ptr ConstraintGuide)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
guide
    CUInt
result <- Ptr ConstraintGuide -> IO CUInt
gtk_constraint_guide_get_strength Ptr ConstraintGuide
guide'
    let result' :: ConstraintStrength
result' = (Int -> ConstraintStrength
forall a. Enum a => Int -> a
toEnum (Int -> ConstraintStrength)
-> (CUInt -> Int) -> CUInt -> ConstraintStrength
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
guide
    ConstraintStrength -> IO ConstraintStrength
forall (m :: * -> *) a. Monad m => a -> m a
return ConstraintStrength
result'

#if defined(ENABLE_OVERLOADING)
data ConstraintGuideGetStrengthMethodInfo
instance (signature ~ (m Gtk.Enums.ConstraintStrength), MonadIO m, IsConstraintGuide a) => O.OverloadedMethod ConstraintGuideGetStrengthMethodInfo a signature where
    overloadedMethod = constraintGuideGetStrength

instance O.OverloadedMethodInfo ConstraintGuideGetStrengthMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ConstraintGuide.constraintGuideGetStrength",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ConstraintGuide.html#v:constraintGuideGetStrength"
        })


#endif

-- method ConstraintGuide::set_max_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "guide"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ConstraintGuide" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkConstraintGuide` object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new maximum width, or -1 to not change it"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the new maximum height, or -1 to not change it"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_constraint_guide_set_max_size" gtk_constraint_guide_set_max_size :: 
    Ptr ConstraintGuide ->                  -- guide : TInterface (Name {namespace = "Gtk", name = "ConstraintGuide"})
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    IO ()

-- | Sets the maximum size of /@guide@/.
-- 
-- If /@guide@/ is attached to a @GtkConstraintLayout@,
-- the constraints will be updated to reflect the new size.
constraintGuideSetMaxSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraintGuide a) =>
    a
    -- ^ /@guide@/: a @GtkConstraintGuide@ object
    -> Int32
    -- ^ /@width@/: the new maximum width, or -1 to not change it
    -> Int32
    -- ^ /@height@/: the new maximum height, or -1 to not change it
    -> m ()
constraintGuideSetMaxSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraintGuide a) =>
a -> Int32 -> Int32 -> m ()
constraintGuideSetMaxSize a
guide Int32
width Int32
height = 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 ConstraintGuide
guide' <- a -> IO (Ptr ConstraintGuide)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
guide
    Ptr ConstraintGuide -> Int32 -> Int32 -> IO ()
gtk_constraint_guide_set_max_size Ptr ConstraintGuide
guide' Int32
width Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
guide
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ConstraintGuideSetMaxSizeMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m, IsConstraintGuide a) => O.OverloadedMethod ConstraintGuideSetMaxSizeMethodInfo a signature where
    overloadedMethod = constraintGuideSetMaxSize

instance O.OverloadedMethodInfo ConstraintGuideSetMaxSizeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ConstraintGuide.constraintGuideSetMaxSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ConstraintGuide.html#v:constraintGuideSetMaxSize"
        })


#endif

-- method ConstraintGuide::set_min_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "guide"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ConstraintGuide" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkConstraintGuide` object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new minimum width, or -1 to not change it"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the new minimum height, or -1 to not change it"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_constraint_guide_set_min_size" gtk_constraint_guide_set_min_size :: 
    Ptr ConstraintGuide ->                  -- guide : TInterface (Name {namespace = "Gtk", name = "ConstraintGuide"})
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    IO ()

-- | Sets the minimum size of /@guide@/.
-- 
-- If /@guide@/ is attached to a @GtkConstraintLayout@,
-- the constraints will be updated to reflect the new size.
constraintGuideSetMinSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraintGuide a) =>
    a
    -- ^ /@guide@/: a @GtkConstraintGuide@ object
    -> Int32
    -- ^ /@width@/: the new minimum width, or -1 to not change it
    -> Int32
    -- ^ /@height@/: the new minimum height, or -1 to not change it
    -> m ()
constraintGuideSetMinSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraintGuide a) =>
a -> Int32 -> Int32 -> m ()
constraintGuideSetMinSize a
guide Int32
width Int32
height = 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 ConstraintGuide
guide' <- a -> IO (Ptr ConstraintGuide)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
guide
    Ptr ConstraintGuide -> Int32 -> Int32 -> IO ()
gtk_constraint_guide_set_min_size Ptr ConstraintGuide
guide' Int32
width Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
guide
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ConstraintGuideSetMinSizeMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m, IsConstraintGuide a) => O.OverloadedMethod ConstraintGuideSetMinSizeMethodInfo a signature where
    overloadedMethod = constraintGuideSetMinSize

instance O.OverloadedMethodInfo ConstraintGuideSetMinSizeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ConstraintGuide.constraintGuideSetMinSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ConstraintGuide.html#v:constraintGuideSetMinSize"
        })


#endif

-- method ConstraintGuide::set_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "guide"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ConstraintGuide" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkConstraintGuide`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a name for the @guide"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_constraint_guide_set_name" gtk_constraint_guide_set_name :: 
    Ptr ConstraintGuide ->                  -- guide : TInterface (Name {namespace = "Gtk", name = "ConstraintGuide"})
    CString ->                              -- name : TBasicType TUTF8
    IO ()

-- | Sets a name for the given @GtkConstraintGuide@.
-- 
-- The name is useful for debugging purposes.
constraintGuideSetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraintGuide a) =>
    a
    -- ^ /@guide@/: a @GtkConstraintGuide@
    -> Maybe (T.Text)
    -- ^ /@name@/: a name for the /@guide@/
    -> m ()
constraintGuideSetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraintGuide a) =>
a -> Maybe Text -> m ()
constraintGuideSetName a
guide Maybe Text
name = 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 ConstraintGuide
guide' <- a -> IO (Ptr ConstraintGuide)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
guide
    CString
maybeName <- case Maybe Text
name of
        Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jName -> do
            CString
jName' <- Text -> IO CString
textToCString Text
jName
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jName'
    Ptr ConstraintGuide -> CString -> IO ()
gtk_constraint_guide_set_name Ptr ConstraintGuide
guide' CString
maybeName
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
guide
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeName
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ConstraintGuideSetNameMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsConstraintGuide a) => O.OverloadedMethod ConstraintGuideSetNameMethodInfo a signature where
    overloadedMethod = constraintGuideSetName

instance O.OverloadedMethodInfo ConstraintGuideSetNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ConstraintGuide.constraintGuideSetName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ConstraintGuide.html#v:constraintGuideSetName"
        })


#endif

-- method ConstraintGuide::set_nat_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "guide"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ConstraintGuide" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkConstraintGuide` object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new natural width, or -1 to not change it"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the new natural height, or -1 to not change it"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_constraint_guide_set_nat_size" gtk_constraint_guide_set_nat_size :: 
    Ptr ConstraintGuide ->                  -- guide : TInterface (Name {namespace = "Gtk", name = "ConstraintGuide"})
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    IO ()

-- | Sets the natural size of /@guide@/.
-- 
-- If /@guide@/ is attached to a @GtkConstraintLayout@,
-- the constraints will be updated to reflect the new size.
constraintGuideSetNatSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraintGuide a) =>
    a
    -- ^ /@guide@/: a @GtkConstraintGuide@ object
    -> Int32
    -- ^ /@width@/: the new natural width, or -1 to not change it
    -> Int32
    -- ^ /@height@/: the new natural height, or -1 to not change it
    -> m ()
constraintGuideSetNatSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraintGuide a) =>
a -> Int32 -> Int32 -> m ()
constraintGuideSetNatSize a
guide Int32
width Int32
height = 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 ConstraintGuide
guide' <- a -> IO (Ptr ConstraintGuide)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
guide
    Ptr ConstraintGuide -> Int32 -> Int32 -> IO ()
gtk_constraint_guide_set_nat_size Ptr ConstraintGuide
guide' Int32
width Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
guide
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ConstraintGuideSetNatSizeMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m, IsConstraintGuide a) => O.OverloadedMethod ConstraintGuideSetNatSizeMethodInfo a signature where
    overloadedMethod = constraintGuideSetNatSize

instance O.OverloadedMethodInfo ConstraintGuideSetNatSizeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ConstraintGuide.constraintGuideSetNatSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ConstraintGuide.html#v:constraintGuideSetNatSize"
        })


#endif

-- method ConstraintGuide::set_strength
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "guide"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ConstraintGuide" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkConstraintGuide`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "strength"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ConstraintStrength" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the strength of the constraint"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_constraint_guide_set_strength" gtk_constraint_guide_set_strength :: 
    Ptr ConstraintGuide ->                  -- guide : TInterface (Name {namespace = "Gtk", name = "ConstraintGuide"})
    CUInt ->                                -- strength : TInterface (Name {namespace = "Gtk", name = "ConstraintStrength"})
    IO ()

-- | Sets the strength of the constraint on the natural size of the
-- given @GtkConstraintGuide@.
constraintGuideSetStrength ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraintGuide a) =>
    a
    -- ^ /@guide@/: a @GtkConstraintGuide@
    -> Gtk.Enums.ConstraintStrength
    -- ^ /@strength@/: the strength of the constraint
    -> m ()
constraintGuideSetStrength :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraintGuide a) =>
a -> ConstraintStrength -> m ()
constraintGuideSetStrength a
guide ConstraintStrength
strength = 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 ConstraintGuide
guide' <- a -> IO (Ptr ConstraintGuide)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
guide
    let strength' :: CUInt
strength' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (ConstraintStrength -> Int) -> ConstraintStrength -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstraintStrength -> Int
forall a. Enum a => a -> Int
fromEnum) ConstraintStrength
strength
    Ptr ConstraintGuide -> CUInt -> IO ()
gtk_constraint_guide_set_strength Ptr ConstraintGuide
guide' CUInt
strength'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
guide
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ConstraintGuideSetStrengthMethodInfo
instance (signature ~ (Gtk.Enums.ConstraintStrength -> m ()), MonadIO m, IsConstraintGuide a) => O.OverloadedMethod ConstraintGuideSetStrengthMethodInfo a signature where
    overloadedMethod = constraintGuideSetStrength

instance O.OverloadedMethodInfo ConstraintGuideSetStrengthMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ConstraintGuide.constraintGuideSetStrength",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Objects-ConstraintGuide.html#v:constraintGuideSetStrength"
        })


#endif