{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkConstraint@ describes a constraint between attributes of two widgets,
--  expressed as a linear equation.
-- 
-- The typical equation for a constraint is:
-- 
-- >  target.target_attr = source.source_attr × multiplier + constant
-- 
-- 
-- Each @GtkConstraint@ is part of a system that will be solved by a
-- t'GI.Gtk.Objects.ConstraintLayout.ConstraintLayout' in order to allocate and position each
-- child widget or guide.
-- 
-- The source and target, as well as their attributes, of a @GtkConstraint@
-- instance are immutable after creation.

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

module GI.Gtk.Objects.Constraint
    ( 

-- * Exported types
    Constraint(..)                          ,
    IsConstraint                            ,
    toConstraint                            ,


 -- * 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"), [isAttached]("GI.Gtk.Objects.Constraint#g:method:isAttached"), [isConstant]("GI.Gtk.Objects.Constraint#g:method:isConstant"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isRequired]("GI.Gtk.Objects.Constraint#g:method:isRequired"), [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
-- [getConstant]("GI.Gtk.Objects.Constraint#g:method:getConstant"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getMultiplier]("GI.Gtk.Objects.Constraint#g:method:getMultiplier"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRelation]("GI.Gtk.Objects.Constraint#g:method:getRelation"), [getSource]("GI.Gtk.Objects.Constraint#g:method:getSource"), [getSourceAttribute]("GI.Gtk.Objects.Constraint#g:method:getSourceAttribute"), [getStrength]("GI.Gtk.Objects.Constraint#g:method:getStrength"), [getTarget]("GI.Gtk.Objects.Constraint#g:method:getTarget"), [getTargetAttribute]("GI.Gtk.Objects.Constraint#g:method:getTargetAttribute").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveConstraintMethod                 ,
#endif

-- ** getConstant #method:getConstant#

#if defined(ENABLE_OVERLOADING)
    ConstraintGetConstantMethodInfo         ,
#endif
    constraintGetConstant                   ,


-- ** getMultiplier #method:getMultiplier#

#if defined(ENABLE_OVERLOADING)
    ConstraintGetMultiplierMethodInfo       ,
#endif
    constraintGetMultiplier                 ,


-- ** getRelation #method:getRelation#

#if defined(ENABLE_OVERLOADING)
    ConstraintGetRelationMethodInfo         ,
#endif
    constraintGetRelation                   ,


-- ** getSource #method:getSource#

#if defined(ENABLE_OVERLOADING)
    ConstraintGetSourceMethodInfo           ,
#endif
    constraintGetSource                     ,


-- ** getSourceAttribute #method:getSourceAttribute#

#if defined(ENABLE_OVERLOADING)
    ConstraintGetSourceAttributeMethodInfo  ,
#endif
    constraintGetSourceAttribute            ,


-- ** getStrength #method:getStrength#

#if defined(ENABLE_OVERLOADING)
    ConstraintGetStrengthMethodInfo         ,
#endif
    constraintGetStrength                   ,


-- ** getTarget #method:getTarget#

#if defined(ENABLE_OVERLOADING)
    ConstraintGetTargetMethodInfo           ,
#endif
    constraintGetTarget                     ,


-- ** getTargetAttribute #method:getTargetAttribute#

#if defined(ENABLE_OVERLOADING)
    ConstraintGetTargetAttributeMethodInfo  ,
#endif
    constraintGetTargetAttribute            ,


-- ** isAttached #method:isAttached#

#if defined(ENABLE_OVERLOADING)
    ConstraintIsAttachedMethodInfo          ,
#endif
    constraintIsAttached                    ,


-- ** isConstant #method:isConstant#

#if defined(ENABLE_OVERLOADING)
    ConstraintIsConstantMethodInfo          ,
#endif
    constraintIsConstant                    ,


-- ** isRequired #method:isRequired#

#if defined(ENABLE_OVERLOADING)
    ConstraintIsRequiredMethodInfo          ,
#endif
    constraintIsRequired                    ,


-- ** new #method:new#

    constraintNew                           ,


-- ** newConstant #method:newConstant#

    constraintNewConstant                   ,




 -- * Properties


-- ** constant #attr:constant#
-- | The constant value to be added to the [Constraint:sourceAttribute]("GI.Gtk.Objects.Constraint#g:attr:sourceAttribute").

#if defined(ENABLE_OVERLOADING)
    ConstraintConstantPropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    constraintConstant                      ,
#endif
    constructConstraintConstant             ,
    getConstraintConstant                   ,


-- ** multiplier #attr:multiplier#
-- | The multiplication factor to be applied to
-- the [Constraint:sourceAttribute]("GI.Gtk.Objects.Constraint#g:attr:sourceAttribute").

#if defined(ENABLE_OVERLOADING)
    ConstraintMultiplierPropertyInfo        ,
#endif
#if defined(ENABLE_OVERLOADING)
    constraintMultiplier                    ,
#endif
    constructConstraintMultiplier           ,
    getConstraintMultiplier                 ,


-- ** relation #attr:relation#
-- | The order relation between the terms of the constraint.

#if defined(ENABLE_OVERLOADING)
    ConstraintRelationPropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    constraintRelation                      ,
#endif
    constructConstraintRelation             ,
    getConstraintRelation                   ,


-- ** source #attr:source#
-- | The source of the constraint.
-- 
-- The constraint will set the [Constraint:targetAttribute]("GI.Gtk.Objects.Constraint#g:attr:targetAttribute")
-- property of the target using the [Constraint:sourceAttribute]("GI.Gtk.Objects.Constraint#g:attr:sourceAttribute")
-- property of the source.

#if defined(ENABLE_OVERLOADING)
    ConstraintSourcePropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    constraintSource                        ,
#endif
    constructConstraintSource               ,
    getConstraintSource                     ,


-- ** sourceAttribute #attr:sourceAttribute#
-- | The attribute of the [Constraint:source]("GI.Gtk.Objects.Constraint#g:attr:source") read by the
-- constraint.

#if defined(ENABLE_OVERLOADING)
    ConstraintSourceAttributePropertyInfo   ,
#endif
#if defined(ENABLE_OVERLOADING)
    constraintSourceAttribute               ,
#endif
    constructConstraintSourceAttribute      ,
    getConstraintSourceAttribute            ,


-- ** strength #attr:strength#
-- | The strength of the constraint.
-- 
-- The strength can be expressed either using one of the symbolic values
-- of the t'GI.Gtk.Enums.ConstraintStrength' enumeration, or any positive integer
-- value.

#if defined(ENABLE_OVERLOADING)
    ConstraintStrengthPropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    constraintStrength                      ,
#endif
    constructConstraintStrength             ,
    getConstraintStrength                   ,


-- ** target #attr:target#
-- | The target of the constraint.
-- 
-- The constraint will set the [Constraint:targetAttribute]("GI.Gtk.Objects.Constraint#g:attr:targetAttribute")
-- property of the target using the [Constraint:sourceAttribute]("GI.Gtk.Objects.Constraint#g:attr:sourceAttribute")
-- property of the source widget.

#if defined(ENABLE_OVERLOADING)
    ConstraintTargetPropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    constraintTarget                        ,
#endif
    constructConstraintTarget               ,
    getConstraintTarget                     ,


-- ** targetAttribute #attr:targetAttribute#
-- | The attribute of the [Constraint:target]("GI.Gtk.Objects.Constraint#g:attr:target") set by the constraint.

#if defined(ENABLE_OVERLOADING)
    ConstraintTargetAttributePropertyInfo   ,
#endif
#if defined(ENABLE_OVERLOADING)
    constraintTargetAttribute               ,
#endif
    constructConstraintTargetAttribute      ,
    getConstraintTargetAttribute            ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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 Constraint = Constraint (SP.ManagedPtr Constraint)
    deriving (Constraint -> Constraint -> Bool
(Constraint -> Constraint -> Bool)
-> (Constraint -> Constraint -> Bool) -> Eq Constraint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Constraint -> Constraint -> Bool
== :: Constraint -> Constraint -> Bool
$c/= :: Constraint -> Constraint -> Bool
/= :: Constraint -> Constraint -> Bool
Eq)

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

foreign import ccall "gtk_constraint_get_type"
    c_gtk_constraint_get_type :: IO B.Types.GType

instance B.Types.TypedObject Constraint where
    glibType :: IO GType
glibType = IO GType
c_gtk_constraint_get_type

instance B.Types.GObject Constraint

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

instance O.HasParentTypes Constraint
type instance O.ParentTypes Constraint = '[GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveConstraintMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveConstraintMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveConstraintMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveConstraintMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveConstraintMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveConstraintMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveConstraintMethod "isAttached" o = ConstraintIsAttachedMethodInfo
    ResolveConstraintMethod "isConstant" o = ConstraintIsConstantMethodInfo
    ResolveConstraintMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveConstraintMethod "isRequired" o = ConstraintIsRequiredMethodInfo
    ResolveConstraintMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveConstraintMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveConstraintMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveConstraintMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveConstraintMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveConstraintMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveConstraintMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveConstraintMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveConstraintMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveConstraintMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveConstraintMethod "getConstant" o = ConstraintGetConstantMethodInfo
    ResolveConstraintMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveConstraintMethod "getMultiplier" o = ConstraintGetMultiplierMethodInfo
    ResolveConstraintMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveConstraintMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveConstraintMethod "getRelation" o = ConstraintGetRelationMethodInfo
    ResolveConstraintMethod "getSource" o = ConstraintGetSourceMethodInfo
    ResolveConstraintMethod "getSourceAttribute" o = ConstraintGetSourceAttributeMethodInfo
    ResolveConstraintMethod "getStrength" o = ConstraintGetStrengthMethodInfo
    ResolveConstraintMethod "getTarget" o = ConstraintGetTargetMethodInfo
    ResolveConstraintMethod "getTargetAttribute" o = ConstraintGetTargetAttributeMethodInfo
    ResolveConstraintMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveConstraintMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveConstraintMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveConstraintMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "constant"
   -- Type: TBasicType TDouble
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

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

-- | Construct a `GValueConstruct` with valid value for the “@constant@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructConstraintConstant :: (IsConstraint o, MIO.MonadIO m) => Double -> m (GValueConstruct o)
constructConstraintConstant :: forall o (m :: * -> *).
(IsConstraint o, MonadIO m) =>
Double -> m (GValueConstruct o)
constructConstraintConstant Double
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 -> Double -> IO (GValueConstruct o)
forall o. String -> Double -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyDouble String
"constant" Double
val

#if defined(ENABLE_OVERLOADING)
data ConstraintConstantPropertyInfo
instance AttrInfo ConstraintConstantPropertyInfo where
    type AttrAllowedOps ConstraintConstantPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ConstraintConstantPropertyInfo = IsConstraint
    type AttrSetTypeConstraint ConstraintConstantPropertyInfo = (~) Double
    type AttrTransferTypeConstraint ConstraintConstantPropertyInfo = (~) Double
    type AttrTransferType ConstraintConstantPropertyInfo = Double
    type AttrGetType ConstraintConstantPropertyInfo = Double
    type AttrLabel ConstraintConstantPropertyInfo = "constant"
    type AttrOrigin ConstraintConstantPropertyInfo = Constraint
    attrGet = getConstraintConstant
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructConstraintConstant
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Constraint.constant"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Constraint.html#g:attr:constant"
        })
#endif

-- VVV Prop "multiplier"
   -- Type: TBasicType TDouble
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

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

-- | Construct a `GValueConstruct` with valid value for the “@multiplier@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructConstraintMultiplier :: (IsConstraint o, MIO.MonadIO m) => Double -> m (GValueConstruct o)
constructConstraintMultiplier :: forall o (m :: * -> *).
(IsConstraint o, MonadIO m) =>
Double -> m (GValueConstruct o)
constructConstraintMultiplier Double
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 -> Double -> IO (GValueConstruct o)
forall o. String -> Double -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyDouble String
"multiplier" Double
val

#if defined(ENABLE_OVERLOADING)
data ConstraintMultiplierPropertyInfo
instance AttrInfo ConstraintMultiplierPropertyInfo where
    type AttrAllowedOps ConstraintMultiplierPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ConstraintMultiplierPropertyInfo = IsConstraint
    type AttrSetTypeConstraint ConstraintMultiplierPropertyInfo = (~) Double
    type AttrTransferTypeConstraint ConstraintMultiplierPropertyInfo = (~) Double
    type AttrTransferType ConstraintMultiplierPropertyInfo = Double
    type AttrGetType ConstraintMultiplierPropertyInfo = Double
    type AttrLabel ConstraintMultiplierPropertyInfo = "multiplier"
    type AttrOrigin ConstraintMultiplierPropertyInfo = Constraint
    attrGet = getConstraintMultiplier
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructConstraintMultiplier
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Constraint.multiplier"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Constraint.html#g:attr:multiplier"
        })
#endif

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

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

-- | Construct a `GValueConstruct` with valid value for the “@relation@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructConstraintRelation :: (IsConstraint o, MIO.MonadIO m) => Gtk.Enums.ConstraintRelation -> m (GValueConstruct o)
constructConstraintRelation :: forall o (m :: * -> *).
(IsConstraint o, MonadIO m) =>
ConstraintRelation -> m (GValueConstruct o)
constructConstraintRelation ConstraintRelation
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 -> ConstraintRelation -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"relation" ConstraintRelation
val

#if defined(ENABLE_OVERLOADING)
data ConstraintRelationPropertyInfo
instance AttrInfo ConstraintRelationPropertyInfo where
    type AttrAllowedOps ConstraintRelationPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ConstraintRelationPropertyInfo = IsConstraint
    type AttrSetTypeConstraint ConstraintRelationPropertyInfo = (~) Gtk.Enums.ConstraintRelation
    type AttrTransferTypeConstraint ConstraintRelationPropertyInfo = (~) Gtk.Enums.ConstraintRelation
    type AttrTransferType ConstraintRelationPropertyInfo = Gtk.Enums.ConstraintRelation
    type AttrGetType ConstraintRelationPropertyInfo = Gtk.Enums.ConstraintRelation
    type AttrLabel ConstraintRelationPropertyInfo = "relation"
    type AttrOrigin ConstraintRelationPropertyInfo = Constraint
    attrGet = getConstraintRelation
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructConstraintRelation
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Constraint.relation"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Constraint.html#g:attr:relation"
        })
#endif

-- VVV Prop "source"
   -- Type: TInterface (Name {namespace = "Gtk", name = "ConstraintTarget"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just True,Nothing)

-- | Get the value of the “@source@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' constraint #source
-- @
getConstraintSource :: (MonadIO m, IsConstraint o) => o -> m (Maybe Gtk.ConstraintTarget.ConstraintTarget)
getConstraintSource :: forall (m :: * -> *) o.
(MonadIO m, IsConstraint o) =>
o -> m (Maybe ConstraintTarget)
getConstraintSource o
obj = IO (Maybe ConstraintTarget) -> m (Maybe ConstraintTarget)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe ConstraintTarget) -> m (Maybe ConstraintTarget))
-> IO (Maybe ConstraintTarget) -> m (Maybe ConstraintTarget)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr ConstraintTarget -> ConstraintTarget)
-> IO (Maybe ConstraintTarget)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"source" ManagedPtr ConstraintTarget -> ConstraintTarget
Gtk.ConstraintTarget.ConstraintTarget

-- | Construct a `GValueConstruct` with valid value for the “@source@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructConstraintSource :: (IsConstraint o, MIO.MonadIO m, Gtk.ConstraintTarget.IsConstraintTarget a) => a -> m (GValueConstruct o)
constructConstraintSource :: forall o (m :: * -> *) a.
(IsConstraint o, MonadIO m, IsConstraintTarget a) =>
a -> m (GValueConstruct o)
constructConstraintSource a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"source" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data ConstraintSourcePropertyInfo
instance AttrInfo ConstraintSourcePropertyInfo where
    type AttrAllowedOps ConstraintSourcePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ConstraintSourcePropertyInfo = IsConstraint
    type AttrSetTypeConstraint ConstraintSourcePropertyInfo = Gtk.ConstraintTarget.IsConstraintTarget
    type AttrTransferTypeConstraint ConstraintSourcePropertyInfo = Gtk.ConstraintTarget.IsConstraintTarget
    type AttrTransferType ConstraintSourcePropertyInfo = Gtk.ConstraintTarget.ConstraintTarget
    type AttrGetType ConstraintSourcePropertyInfo = (Maybe Gtk.ConstraintTarget.ConstraintTarget)
    type AttrLabel ConstraintSourcePropertyInfo = "source"
    type AttrOrigin ConstraintSourcePropertyInfo = Constraint
    attrGet = getConstraintSource
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gtk.ConstraintTarget.ConstraintTarget v
    attrConstruct = constructConstraintSource
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Constraint.source"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Constraint.html#g:attr:source"
        })
#endif

-- VVV Prop "source-attribute"
   -- Type: TInterface (Name {namespace = "Gtk", name = "ConstraintAttribute"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

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

-- | Construct a `GValueConstruct` with valid value for the “@source-attribute@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructConstraintSourceAttribute :: (IsConstraint o, MIO.MonadIO m) => Gtk.Enums.ConstraintAttribute -> m (GValueConstruct o)
constructConstraintSourceAttribute :: forall o (m :: * -> *).
(IsConstraint o, MonadIO m) =>
ConstraintAttribute -> m (GValueConstruct o)
constructConstraintSourceAttribute ConstraintAttribute
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 -> ConstraintAttribute -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"source-attribute" ConstraintAttribute
val

#if defined(ENABLE_OVERLOADING)
data ConstraintSourceAttributePropertyInfo
instance AttrInfo ConstraintSourceAttributePropertyInfo where
    type AttrAllowedOps ConstraintSourceAttributePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ConstraintSourceAttributePropertyInfo = IsConstraint
    type AttrSetTypeConstraint ConstraintSourceAttributePropertyInfo = (~) Gtk.Enums.ConstraintAttribute
    type AttrTransferTypeConstraint ConstraintSourceAttributePropertyInfo = (~) Gtk.Enums.ConstraintAttribute
    type AttrTransferType ConstraintSourceAttributePropertyInfo = Gtk.Enums.ConstraintAttribute
    type AttrGetType ConstraintSourceAttributePropertyInfo = Gtk.Enums.ConstraintAttribute
    type AttrLabel ConstraintSourceAttributePropertyInfo = "source-attribute"
    type AttrOrigin ConstraintSourceAttributePropertyInfo = Constraint
    attrGet = getConstraintSourceAttribute
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructConstraintSourceAttribute
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Constraint.sourceAttribute"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Constraint.html#g:attr:sourceAttribute"
        })
#endif

-- VVV Prop "strength"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | 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' constraint #strength
-- @
getConstraintStrength :: (MonadIO m, IsConstraint o) => o -> m Int32
getConstraintStrength :: forall (m :: * -> *) o. (MonadIO m, IsConstraint o) => o -> m Int32
getConstraintStrength o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
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
"strength"

-- | 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`.
constructConstraintStrength :: (IsConstraint o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructConstraintStrength :: forall o (m :: * -> *).
(IsConstraint o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructConstraintStrength Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
"strength" Int32
val

#if defined(ENABLE_OVERLOADING)
data ConstraintStrengthPropertyInfo
instance AttrInfo ConstraintStrengthPropertyInfo where
    type AttrAllowedOps ConstraintStrengthPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ConstraintStrengthPropertyInfo = IsConstraint
    type AttrSetTypeConstraint ConstraintStrengthPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint ConstraintStrengthPropertyInfo = (~) Int32
    type AttrTransferType ConstraintStrengthPropertyInfo = Int32
    type AttrGetType ConstraintStrengthPropertyInfo = Int32
    type AttrLabel ConstraintStrengthPropertyInfo = "strength"
    type AttrOrigin ConstraintStrengthPropertyInfo = Constraint
    attrGet = getConstraintStrength
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructConstraintStrength
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Constraint.strength"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Constraint.html#g:attr:strength"
        })
#endif

-- VVV Prop "target"
   -- Type: TInterface (Name {namespace = "Gtk", name = "ConstraintTarget"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just True,Nothing)

-- | Get the value of the “@target@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' constraint #target
-- @
getConstraintTarget :: (MonadIO m, IsConstraint o) => o -> m (Maybe Gtk.ConstraintTarget.ConstraintTarget)
getConstraintTarget :: forall (m :: * -> *) o.
(MonadIO m, IsConstraint o) =>
o -> m (Maybe ConstraintTarget)
getConstraintTarget o
obj = IO (Maybe ConstraintTarget) -> m (Maybe ConstraintTarget)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe ConstraintTarget) -> m (Maybe ConstraintTarget))
-> IO (Maybe ConstraintTarget) -> m (Maybe ConstraintTarget)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr ConstraintTarget -> ConstraintTarget)
-> IO (Maybe ConstraintTarget)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"target" ManagedPtr ConstraintTarget -> ConstraintTarget
Gtk.ConstraintTarget.ConstraintTarget

-- | Construct a `GValueConstruct` with valid value for the “@target@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructConstraintTarget :: (IsConstraint o, MIO.MonadIO m, Gtk.ConstraintTarget.IsConstraintTarget a) => a -> m (GValueConstruct o)
constructConstraintTarget :: forall o (m :: * -> *) a.
(IsConstraint o, MonadIO m, IsConstraintTarget a) =>
a -> m (GValueConstruct o)
constructConstraintTarget a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"target" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data ConstraintTargetPropertyInfo
instance AttrInfo ConstraintTargetPropertyInfo where
    type AttrAllowedOps ConstraintTargetPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ConstraintTargetPropertyInfo = IsConstraint
    type AttrSetTypeConstraint ConstraintTargetPropertyInfo = Gtk.ConstraintTarget.IsConstraintTarget
    type AttrTransferTypeConstraint ConstraintTargetPropertyInfo = Gtk.ConstraintTarget.IsConstraintTarget
    type AttrTransferType ConstraintTargetPropertyInfo = Gtk.ConstraintTarget.ConstraintTarget
    type AttrGetType ConstraintTargetPropertyInfo = (Maybe Gtk.ConstraintTarget.ConstraintTarget)
    type AttrLabel ConstraintTargetPropertyInfo = "target"
    type AttrOrigin ConstraintTargetPropertyInfo = Constraint
    attrGet = getConstraintTarget
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gtk.ConstraintTarget.ConstraintTarget v
    attrConstruct = constructConstraintTarget
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Constraint.target"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Constraint.html#g:attr:target"
        })
#endif

-- VVV Prop "target-attribute"
   -- Type: TInterface (Name {namespace = "Gtk", name = "ConstraintAttribute"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

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

-- | Construct a `GValueConstruct` with valid value for the “@target-attribute@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructConstraintTargetAttribute :: (IsConstraint o, MIO.MonadIO m) => Gtk.Enums.ConstraintAttribute -> m (GValueConstruct o)
constructConstraintTargetAttribute :: forall o (m :: * -> *).
(IsConstraint o, MonadIO m) =>
ConstraintAttribute -> m (GValueConstruct o)
constructConstraintTargetAttribute ConstraintAttribute
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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 -> ConstraintAttribute -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"target-attribute" ConstraintAttribute
val

#if defined(ENABLE_OVERLOADING)
data ConstraintTargetAttributePropertyInfo
instance AttrInfo ConstraintTargetAttributePropertyInfo where
    type AttrAllowedOps ConstraintTargetAttributePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ConstraintTargetAttributePropertyInfo = IsConstraint
    type AttrSetTypeConstraint ConstraintTargetAttributePropertyInfo = (~) Gtk.Enums.ConstraintAttribute
    type AttrTransferTypeConstraint ConstraintTargetAttributePropertyInfo = (~) Gtk.Enums.ConstraintAttribute
    type AttrTransferType ConstraintTargetAttributePropertyInfo = Gtk.Enums.ConstraintAttribute
    type AttrGetType ConstraintTargetAttributePropertyInfo = Gtk.Enums.ConstraintAttribute
    type AttrLabel ConstraintTargetAttributePropertyInfo = "target-attribute"
    type AttrOrigin ConstraintTargetAttributePropertyInfo = Constraint
    attrGet = getConstraintTargetAttribute
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructConstraintTargetAttribute
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.Constraint.targetAttribute"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-Constraint.html#g:attr:targetAttribute"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Constraint
type instance O.AttributeList Constraint = ConstraintAttributeList
type ConstraintAttributeList = ('[ '("constant", ConstraintConstantPropertyInfo), '("multiplier", ConstraintMultiplierPropertyInfo), '("relation", ConstraintRelationPropertyInfo), '("source", ConstraintSourcePropertyInfo), '("sourceAttribute", ConstraintSourceAttributePropertyInfo), '("strength", ConstraintStrengthPropertyInfo), '("target", ConstraintTargetPropertyInfo), '("targetAttribute", ConstraintTargetAttributePropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
constraintConstant :: AttrLabelProxy "constant"
constraintConstant = AttrLabelProxy

constraintMultiplier :: AttrLabelProxy "multiplier"
constraintMultiplier = AttrLabelProxy

constraintRelation :: AttrLabelProxy "relation"
constraintRelation = AttrLabelProxy

constraintSource :: AttrLabelProxy "source"
constraintSource = AttrLabelProxy

constraintSourceAttribute :: AttrLabelProxy "sourceAttribute"
constraintSourceAttribute = AttrLabelProxy

constraintStrength :: AttrLabelProxy "strength"
constraintStrength = AttrLabelProxy

constraintTarget :: AttrLabelProxy "target"
constraintTarget = AttrLabelProxy

constraintTargetAttribute :: AttrLabelProxy "targetAttribute"
constraintTargetAttribute = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Constraint = ConstraintSignalList
type ConstraintSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method Constraint::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "target"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ConstraintTarget" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the target of the constraint"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target_attribute"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "ConstraintAttribute" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the attribute of `target` to be set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "relation"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ConstraintRelation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the relation equivalence between `target_attribute` and `source_attribute`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "source"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ConstraintTarget" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the source of the constraint"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "source_attribute"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "ConstraintAttribute" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the attribute of `source` to be read"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "multiplier"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a multiplication factor to be applied to `source_attribute`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "constant"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a constant factor to be added to `source_attribute`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "strength"
--           , argType = TBasicType TInt
--           , 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: Just (TInterface Name { namespace = "Gtk" , name = "Constraint" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_constraint_new" gtk_constraint_new :: 
    Ptr Gtk.ConstraintTarget.ConstraintTarget -> -- target : TInterface (Name {namespace = "Gtk", name = "ConstraintTarget"})
    CUInt ->                                -- target_attribute : TInterface (Name {namespace = "Gtk", name = "ConstraintAttribute"})
    CInt ->                                 -- relation : TInterface (Name {namespace = "Gtk", name = "ConstraintRelation"})
    Ptr Gtk.ConstraintTarget.ConstraintTarget -> -- source : TInterface (Name {namespace = "Gtk", name = "ConstraintTarget"})
    CUInt ->                                -- source_attribute : TInterface (Name {namespace = "Gtk", name = "ConstraintAttribute"})
    CDouble ->                              -- multiplier : TBasicType TDouble
    CDouble ->                              -- constant : TBasicType TDouble
    Int32 ->                                -- strength : TBasicType TInt
    IO (Ptr Constraint)

-- | Creates a new constraint representing a relation between a layout
-- attribute on a source and a layout attribute on a target.
constraintNew ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.ConstraintTarget.IsConstraintTarget a, Gtk.ConstraintTarget.IsConstraintTarget b) =>
    Maybe (a)
    -- ^ /@target@/: the target of the constraint
    -> Gtk.Enums.ConstraintAttribute
    -- ^ /@targetAttribute@/: the attribute of @target@ to be set
    -> Gtk.Enums.ConstraintRelation
    -- ^ /@relation@/: the relation equivalence between @target_attribute@ and @source_attribute@
    -> Maybe (b)
    -- ^ /@source@/: the source of the constraint
    -> Gtk.Enums.ConstraintAttribute
    -- ^ /@sourceAttribute@/: the attribute of @source@ to be read
    -> Double
    -- ^ /@multiplier@/: a multiplication factor to be applied to @source_attribute@
    -> Double
    -- ^ /@constant@/: a constant factor to be added to @source_attribute@
    -> Int32
    -- ^ /@strength@/: the strength of the constraint
    -> m Constraint
    -- ^ __Returns:__ the newly created constraint
constraintNew :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsConstraintTarget a,
 IsConstraintTarget b) =>
Maybe a
-> ConstraintAttribute
-> ConstraintRelation
-> Maybe b
-> ConstraintAttribute
-> Double
-> Double
-> Int32
-> m Constraint
constraintNew Maybe a
target ConstraintAttribute
targetAttribute ConstraintRelation
relation Maybe b
source ConstraintAttribute
sourceAttribute Double
multiplier Double
constant Int32
strength = IO Constraint -> m Constraint
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Constraint -> m Constraint) -> IO Constraint -> m Constraint
forall a b. (a -> b) -> a -> b
$ do
    Ptr ConstraintTarget
maybeTarget <- case Maybe a
target of
        Maybe a
Nothing -> Ptr ConstraintTarget -> IO (Ptr ConstraintTarget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ConstraintTarget
forall a. Ptr a
nullPtr
        Just a
jTarget -> do
            Ptr ConstraintTarget
jTarget' <- a -> IO (Ptr ConstraintTarget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jTarget
            Ptr ConstraintTarget -> IO (Ptr ConstraintTarget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ConstraintTarget
jTarget'
    let targetAttribute' :: CUInt
targetAttribute' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (ConstraintAttribute -> Int) -> ConstraintAttribute -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstraintAttribute -> Int
forall a. Enum a => a -> Int
fromEnum) ConstraintAttribute
targetAttribute
    let relation' :: CInt
relation' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt)
-> (ConstraintRelation -> Int) -> ConstraintRelation -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstraintRelation -> Int
forall a. Enum a => a -> Int
fromEnum) ConstraintRelation
relation
    Ptr ConstraintTarget
maybeSource <- case Maybe b
source of
        Maybe b
Nothing -> Ptr ConstraintTarget -> IO (Ptr ConstraintTarget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ConstraintTarget
forall a. Ptr a
nullPtr
        Just b
jSource -> do
            Ptr ConstraintTarget
jSource' <- b -> IO (Ptr ConstraintTarget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jSource
            Ptr ConstraintTarget -> IO (Ptr ConstraintTarget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ConstraintTarget
jSource'
    let sourceAttribute' :: CUInt
sourceAttribute' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (ConstraintAttribute -> Int) -> ConstraintAttribute -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstraintAttribute -> Int
forall a. Enum a => a -> Int
fromEnum) ConstraintAttribute
sourceAttribute
    let multiplier' :: CDouble
multiplier' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
multiplier
    let constant' :: CDouble
constant' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
constant
    Ptr Constraint
result <- Ptr ConstraintTarget
-> CUInt
-> CInt
-> Ptr ConstraintTarget
-> CUInt
-> CDouble
-> CDouble
-> Int32
-> IO (Ptr Constraint)
gtk_constraint_new Ptr ConstraintTarget
maybeTarget CUInt
targetAttribute' CInt
relation' Ptr ConstraintTarget
maybeSource CUInt
sourceAttribute' CDouble
multiplier' CDouble
constant' Int32
strength
    Text -> Ptr Constraint -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"constraintNew" Ptr Constraint
result
    Constraint
result' <- ((ManagedPtr Constraint -> Constraint)
-> Ptr Constraint -> IO Constraint
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Constraint -> Constraint
Constraint) Ptr Constraint
result
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
target a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
source b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Constraint -> IO Constraint
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Constraint
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Constraint::new_constant
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "target"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ConstraintTarget" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a the target of the constraint"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target_attribute"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "ConstraintAttribute" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the attribute of `target` to be set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "relation"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ConstraintRelation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the relation equivalence between `target_attribute` and `constant`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "constant"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a constant factor to be set on `target_attribute`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "strength"
--           , argType = TBasicType TInt
--           , 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: Just (TInterface Name { namespace = "Gtk" , name = "Constraint" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_constraint_new_constant" gtk_constraint_new_constant :: 
    Ptr Gtk.ConstraintTarget.ConstraintTarget -> -- target : TInterface (Name {namespace = "Gtk", name = "ConstraintTarget"})
    CUInt ->                                -- target_attribute : TInterface (Name {namespace = "Gtk", name = "ConstraintAttribute"})
    CInt ->                                 -- relation : TInterface (Name {namespace = "Gtk", name = "ConstraintRelation"})
    CDouble ->                              -- constant : TBasicType TDouble
    Int32 ->                                -- strength : TBasicType TInt
    IO (Ptr Constraint)

-- | Creates a new constraint representing a relation between a layout
-- attribute on a target and a constant value.
constraintNewConstant ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.ConstraintTarget.IsConstraintTarget a) =>
    Maybe (a)
    -- ^ /@target@/: a the target of the constraint
    -> Gtk.Enums.ConstraintAttribute
    -- ^ /@targetAttribute@/: the attribute of @target@ to be set
    -> Gtk.Enums.ConstraintRelation
    -- ^ /@relation@/: the relation equivalence between @target_attribute@ and @constant@
    -> Double
    -- ^ /@constant@/: a constant factor to be set on @target_attribute@
    -> Int32
    -- ^ /@strength@/: the strength of the constraint
    -> m Constraint
    -- ^ __Returns:__ the newly created constraint
constraintNewConstant :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraintTarget a) =>
Maybe a
-> ConstraintAttribute
-> ConstraintRelation
-> Double
-> Int32
-> m Constraint
constraintNewConstant Maybe a
target ConstraintAttribute
targetAttribute ConstraintRelation
relation Double
constant Int32
strength = IO Constraint -> m Constraint
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Constraint -> m Constraint) -> IO Constraint -> m Constraint
forall a b. (a -> b) -> a -> b
$ do
    Ptr ConstraintTarget
maybeTarget <- case Maybe a
target of
        Maybe a
Nothing -> Ptr ConstraintTarget -> IO (Ptr ConstraintTarget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ConstraintTarget
forall a. Ptr a
nullPtr
        Just a
jTarget -> do
            Ptr ConstraintTarget
jTarget' <- a -> IO (Ptr ConstraintTarget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jTarget
            Ptr ConstraintTarget -> IO (Ptr ConstraintTarget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ConstraintTarget
jTarget'
    let targetAttribute' :: CUInt
targetAttribute' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (ConstraintAttribute -> Int) -> ConstraintAttribute -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstraintAttribute -> Int
forall a. Enum a => a -> Int
fromEnum) ConstraintAttribute
targetAttribute
    let relation' :: CInt
relation' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt)
-> (ConstraintRelation -> Int) -> ConstraintRelation -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstraintRelation -> Int
forall a. Enum a => a -> Int
fromEnum) ConstraintRelation
relation
    let constant' :: CDouble
constant' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
constant
    Ptr Constraint
result <- Ptr ConstraintTarget
-> CUInt -> CInt -> CDouble -> Int32 -> IO (Ptr Constraint)
gtk_constraint_new_constant Ptr ConstraintTarget
maybeTarget CUInt
targetAttribute' CInt
relation' CDouble
constant' Int32
strength
    Text -> Ptr Constraint -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"constraintNewConstant" Ptr Constraint
result
    Constraint
result' <- ((ManagedPtr Constraint -> Constraint)
-> Ptr Constraint -> IO Constraint
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Constraint -> Constraint
Constraint) Ptr Constraint
result
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
target a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Constraint -> IO Constraint
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Constraint
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "gtk_constraint_get_constant" gtk_constraint_get_constant :: 
    Ptr Constraint ->                       -- constraint : TInterface (Name {namespace = "Gtk", name = "Constraint"})
    IO CDouble

-- | Retrieves the constant factor added to the source attributes\' value.
constraintGetConstant ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraint a) =>
    a
    -- ^ /@constraint@/: a @GtkConstraint@
    -> m Double
    -- ^ __Returns:__ a constant factor
constraintGetConstant :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraint a) =>
a -> m Double
constraintGetConstant a
constraint = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr Constraint
constraint' <- a -> IO (Ptr Constraint)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
constraint
    CDouble
result <- Ptr Constraint -> IO CDouble
gtk_constraint_get_constant Ptr Constraint
constraint'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
constraint
    Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data ConstraintGetConstantMethodInfo
instance (signature ~ (m Double), MonadIO m, IsConstraint a) => O.OverloadedMethod ConstraintGetConstantMethodInfo a signature where
    overloadedMethod = constraintGetConstant

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


#endif

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

foreign import ccall "gtk_constraint_get_multiplier" gtk_constraint_get_multiplier :: 
    Ptr Constraint ->                       -- constraint : TInterface (Name {namespace = "Gtk", name = "Constraint"})
    IO CDouble

-- | Retrieves the multiplication factor applied to the source
-- attribute\'s value.
constraintGetMultiplier ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraint a) =>
    a
    -- ^ /@constraint@/: a @GtkConstraint@
    -> m Double
    -- ^ __Returns:__ a multiplication factor
constraintGetMultiplier :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraint a) =>
a -> m Double
constraintGetMultiplier a
constraint = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr Constraint
constraint' <- a -> IO (Ptr Constraint)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
constraint
    CDouble
result <- Ptr Constraint -> IO CDouble
gtk_constraint_get_multiplier Ptr Constraint
constraint'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
constraint
    Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data ConstraintGetMultiplierMethodInfo
instance (signature ~ (m Double), MonadIO m, IsConstraint a) => O.OverloadedMethod ConstraintGetMultiplierMethodInfo a signature where
    overloadedMethod = constraintGetMultiplier

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


#endif

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

foreign import ccall "gtk_constraint_get_relation" gtk_constraint_get_relation :: 
    Ptr Constraint ->                       -- constraint : TInterface (Name {namespace = "Gtk", name = "Constraint"})
    IO CInt

-- | The order relation between the terms of the constraint.
constraintGetRelation ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraint a) =>
    a
    -- ^ /@constraint@/: a @GtkConstraint@
    -> m Gtk.Enums.ConstraintRelation
    -- ^ __Returns:__ a relation type
constraintGetRelation :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraint a) =>
a -> m ConstraintRelation
constraintGetRelation a
constraint = IO ConstraintRelation -> m ConstraintRelation
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ConstraintRelation -> m ConstraintRelation)
-> IO ConstraintRelation -> m ConstraintRelation
forall a b. (a -> b) -> a -> b
$ do
    Ptr Constraint
constraint' <- a -> IO (Ptr Constraint)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
constraint
    CInt
result <- Ptr Constraint -> IO CInt
gtk_constraint_get_relation Ptr Constraint
constraint'
    let result' :: ConstraintRelation
result' = (Int -> ConstraintRelation
forall a. Enum a => Int -> a
toEnum (Int -> ConstraintRelation)
-> (CInt -> Int) -> CInt -> ConstraintRelation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
constraint
    ConstraintRelation -> IO ConstraintRelation
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ConstraintRelation
result'

#if defined(ENABLE_OVERLOADING)
data ConstraintGetRelationMethodInfo
instance (signature ~ (m Gtk.Enums.ConstraintRelation), MonadIO m, IsConstraint a) => O.OverloadedMethod ConstraintGetRelationMethodInfo a signature where
    overloadedMethod = constraintGetRelation

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


#endif

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

foreign import ccall "gtk_constraint_get_source" gtk_constraint_get_source :: 
    Ptr Constraint ->                       -- constraint : TInterface (Name {namespace = "Gtk", name = "Constraint"})
    IO (Ptr Gtk.ConstraintTarget.ConstraintTarget)

-- | Retrieves the t'GI.Gtk.Interfaces.ConstraintTarget.ConstraintTarget' used as the source for the
-- constraint.
-- 
-- If the source is set to @NULL@ at creation, the constraint will use
-- the widget using the t'GI.Gtk.Objects.ConstraintLayout.ConstraintLayout' as the source.
constraintGetSource ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraint a) =>
    a
    -- ^ /@constraint@/: a @GtkConstraint@
    -> m (Maybe Gtk.ConstraintTarget.ConstraintTarget)
    -- ^ __Returns:__ the source of the constraint
constraintGetSource :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraint a) =>
a -> m (Maybe ConstraintTarget)
constraintGetSource a
constraint = IO (Maybe ConstraintTarget) -> m (Maybe ConstraintTarget)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ConstraintTarget) -> m (Maybe ConstraintTarget))
-> IO (Maybe ConstraintTarget) -> m (Maybe ConstraintTarget)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Constraint
constraint' <- a -> IO (Ptr Constraint)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
constraint
    Ptr ConstraintTarget
result <- Ptr Constraint -> IO (Ptr ConstraintTarget)
gtk_constraint_get_source Ptr Constraint
constraint'
    Maybe ConstraintTarget
maybeResult <- Ptr ConstraintTarget
-> (Ptr ConstraintTarget -> IO ConstraintTarget)
-> IO (Maybe ConstraintTarget)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr ConstraintTarget
result ((Ptr ConstraintTarget -> IO ConstraintTarget)
 -> IO (Maybe ConstraintTarget))
-> (Ptr ConstraintTarget -> IO ConstraintTarget)
-> IO (Maybe ConstraintTarget)
forall a b. (a -> b) -> a -> b
$ \Ptr ConstraintTarget
result' -> do
        ConstraintTarget
result'' <- ((ManagedPtr ConstraintTarget -> ConstraintTarget)
-> Ptr ConstraintTarget -> IO ConstraintTarget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ConstraintTarget -> ConstraintTarget
Gtk.ConstraintTarget.ConstraintTarget) Ptr ConstraintTarget
result'
        ConstraintTarget -> IO ConstraintTarget
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ConstraintTarget
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
constraint
    Maybe ConstraintTarget -> IO (Maybe ConstraintTarget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ConstraintTarget
maybeResult

#if defined(ENABLE_OVERLOADING)
data ConstraintGetSourceMethodInfo
instance (signature ~ (m (Maybe Gtk.ConstraintTarget.ConstraintTarget)), MonadIO m, IsConstraint a) => O.OverloadedMethod ConstraintGetSourceMethodInfo a signature where
    overloadedMethod = constraintGetSource

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


#endif

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

foreign import ccall "gtk_constraint_get_source_attribute" gtk_constraint_get_source_attribute :: 
    Ptr Constraint ->                       -- constraint : TInterface (Name {namespace = "Gtk", name = "Constraint"})
    IO CUInt

-- | Retrieves the attribute of the source to be read by the constraint.
constraintGetSourceAttribute ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraint a) =>
    a
    -- ^ /@constraint@/: a @GtkConstraint@
    -> m Gtk.Enums.ConstraintAttribute
    -- ^ __Returns:__ the source\'s attribute
constraintGetSourceAttribute :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraint a) =>
a -> m ConstraintAttribute
constraintGetSourceAttribute a
constraint = IO ConstraintAttribute -> m ConstraintAttribute
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ConstraintAttribute -> m ConstraintAttribute)
-> IO ConstraintAttribute -> m ConstraintAttribute
forall a b. (a -> b) -> a -> b
$ do
    Ptr Constraint
constraint' <- a -> IO (Ptr Constraint)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
constraint
    CUInt
result <- Ptr Constraint -> IO CUInt
gtk_constraint_get_source_attribute Ptr Constraint
constraint'
    let result' :: ConstraintAttribute
result' = (Int -> ConstraintAttribute
forall a. Enum a => Int -> a
toEnum (Int -> ConstraintAttribute)
-> (CUInt -> Int) -> CUInt -> ConstraintAttribute
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
constraint
    ConstraintAttribute -> IO ConstraintAttribute
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ConstraintAttribute
result'

#if defined(ENABLE_OVERLOADING)
data ConstraintGetSourceAttributeMethodInfo
instance (signature ~ (m Gtk.Enums.ConstraintAttribute), MonadIO m, IsConstraint a) => O.OverloadedMethod ConstraintGetSourceAttributeMethodInfo a signature where
    overloadedMethod = constraintGetSourceAttribute

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


#endif

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

foreign import ccall "gtk_constraint_get_strength" gtk_constraint_get_strength :: 
    Ptr Constraint ->                       -- constraint : TInterface (Name {namespace = "Gtk", name = "Constraint"})
    IO Int32

-- | Retrieves the strength of the constraint.
constraintGetStrength ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraint a) =>
    a
    -- ^ /@constraint@/: a @GtkConstraint@
    -> m Int32
    -- ^ __Returns:__ the strength value
constraintGetStrength :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraint a) =>
a -> m Int32
constraintGetStrength a
constraint = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Constraint
constraint' <- a -> IO (Ptr Constraint)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
constraint
    Int32
result <- Ptr Constraint -> IO Int32
gtk_constraint_get_strength Ptr Constraint
constraint'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
constraint
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data ConstraintGetStrengthMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsConstraint a) => O.OverloadedMethod ConstraintGetStrengthMethodInfo a signature where
    overloadedMethod = constraintGetStrength

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


#endif

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

foreign import ccall "gtk_constraint_get_target" gtk_constraint_get_target :: 
    Ptr Constraint ->                       -- constraint : TInterface (Name {namespace = "Gtk", name = "Constraint"})
    IO (Ptr Gtk.ConstraintTarget.ConstraintTarget)

-- | Retrieves the t'GI.Gtk.Interfaces.ConstraintTarget.ConstraintTarget' used as the target for
-- the constraint.
-- 
-- If the targe is set to @NULL@ at creation, the constraint will use
-- the widget using the t'GI.Gtk.Objects.ConstraintLayout.ConstraintLayout' as the target.
constraintGetTarget ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraint a) =>
    a
    -- ^ /@constraint@/: a @GtkConstraint@
    -> m (Maybe Gtk.ConstraintTarget.ConstraintTarget)
    -- ^ __Returns:__ a @GtkConstraintTarget@
constraintGetTarget :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraint a) =>
a -> m (Maybe ConstraintTarget)
constraintGetTarget a
constraint = IO (Maybe ConstraintTarget) -> m (Maybe ConstraintTarget)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ConstraintTarget) -> m (Maybe ConstraintTarget))
-> IO (Maybe ConstraintTarget) -> m (Maybe ConstraintTarget)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Constraint
constraint' <- a -> IO (Ptr Constraint)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
constraint
    Ptr ConstraintTarget
result <- Ptr Constraint -> IO (Ptr ConstraintTarget)
gtk_constraint_get_target Ptr Constraint
constraint'
    Maybe ConstraintTarget
maybeResult <- Ptr ConstraintTarget
-> (Ptr ConstraintTarget -> IO ConstraintTarget)
-> IO (Maybe ConstraintTarget)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr ConstraintTarget
result ((Ptr ConstraintTarget -> IO ConstraintTarget)
 -> IO (Maybe ConstraintTarget))
-> (Ptr ConstraintTarget -> IO ConstraintTarget)
-> IO (Maybe ConstraintTarget)
forall a b. (a -> b) -> a -> b
$ \Ptr ConstraintTarget
result' -> do
        ConstraintTarget
result'' <- ((ManagedPtr ConstraintTarget -> ConstraintTarget)
-> Ptr ConstraintTarget -> IO ConstraintTarget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ConstraintTarget -> ConstraintTarget
Gtk.ConstraintTarget.ConstraintTarget) Ptr ConstraintTarget
result'
        ConstraintTarget -> IO ConstraintTarget
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ConstraintTarget
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
constraint
    Maybe ConstraintTarget -> IO (Maybe ConstraintTarget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ConstraintTarget
maybeResult

#if defined(ENABLE_OVERLOADING)
data ConstraintGetTargetMethodInfo
instance (signature ~ (m (Maybe Gtk.ConstraintTarget.ConstraintTarget)), MonadIO m, IsConstraint a) => O.OverloadedMethod ConstraintGetTargetMethodInfo a signature where
    overloadedMethod = constraintGetTarget

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


#endif

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

foreign import ccall "gtk_constraint_get_target_attribute" gtk_constraint_get_target_attribute :: 
    Ptr Constraint ->                       -- constraint : TInterface (Name {namespace = "Gtk", name = "Constraint"})
    IO CUInt

-- | Retrieves the attribute of the target to be set by the constraint.
constraintGetTargetAttribute ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraint a) =>
    a
    -- ^ /@constraint@/: a @GtkConstraint@
    -> m Gtk.Enums.ConstraintAttribute
    -- ^ __Returns:__ the target\'s attribute
constraintGetTargetAttribute :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraint a) =>
a -> m ConstraintAttribute
constraintGetTargetAttribute a
constraint = IO ConstraintAttribute -> m ConstraintAttribute
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ConstraintAttribute -> m ConstraintAttribute)
-> IO ConstraintAttribute -> m ConstraintAttribute
forall a b. (a -> b) -> a -> b
$ do
    Ptr Constraint
constraint' <- a -> IO (Ptr Constraint)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
constraint
    CUInt
result <- Ptr Constraint -> IO CUInt
gtk_constraint_get_target_attribute Ptr Constraint
constraint'
    let result' :: ConstraintAttribute
result' = (Int -> ConstraintAttribute
forall a. Enum a => Int -> a
toEnum (Int -> ConstraintAttribute)
-> (CUInt -> Int) -> CUInt -> ConstraintAttribute
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
constraint
    ConstraintAttribute -> IO ConstraintAttribute
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ConstraintAttribute
result'

#if defined(ENABLE_OVERLOADING)
data ConstraintGetTargetAttributeMethodInfo
instance (signature ~ (m Gtk.Enums.ConstraintAttribute), MonadIO m, IsConstraint a) => O.OverloadedMethod ConstraintGetTargetAttributeMethodInfo a signature where
    overloadedMethod = constraintGetTargetAttribute

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


#endif

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

foreign import ccall "gtk_constraint_is_attached" gtk_constraint_is_attached :: 
    Ptr Constraint ->                       -- constraint : TInterface (Name {namespace = "Gtk", name = "Constraint"})
    IO CInt

-- | Checks whether the constraint is attached to a t'GI.Gtk.Objects.ConstraintLayout.ConstraintLayout',
-- and it is contributing to the layout.
constraintIsAttached ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraint a) =>
    a
    -- ^ /@constraint@/: a @GtkConstraint@
    -> m Bool
    -- ^ __Returns:__ @TRUE@ if the constraint is attached
constraintIsAttached :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraint a) =>
a -> m Bool
constraintIsAttached a
constraint = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Constraint
constraint' <- a -> IO (Ptr Constraint)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
constraint
    CInt
result <- Ptr Constraint -> IO CInt
gtk_constraint_is_attached Ptr Constraint
constraint'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
constraint
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ConstraintIsAttachedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsConstraint a) => O.OverloadedMethod ConstraintIsAttachedMethodInfo a signature where
    overloadedMethod = constraintIsAttached

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


#endif

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

foreign import ccall "gtk_constraint_is_constant" gtk_constraint_is_constant :: 
    Ptr Constraint ->                       -- constraint : TInterface (Name {namespace = "Gtk", name = "Constraint"})
    IO CInt

-- | Checks whether the constraint describes a relation between an attribute
-- on the [Constraint:target]("GI.Gtk.Objects.Constraint#g:attr:target") and a constant value.
constraintIsConstant ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraint a) =>
    a
    -- ^ /@constraint@/: a @GtkConstraint@
    -> m Bool
    -- ^ __Returns:__ @TRUE@ if the constraint is a constant relation
constraintIsConstant :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraint a) =>
a -> m Bool
constraintIsConstant a
constraint = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Constraint
constraint' <- a -> IO (Ptr Constraint)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
constraint
    CInt
result <- Ptr Constraint -> IO CInt
gtk_constraint_is_constant Ptr Constraint
constraint'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
constraint
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ConstraintIsConstantMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsConstraint a) => O.OverloadedMethod ConstraintIsConstantMethodInfo a signature where
    overloadedMethod = constraintIsConstant

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


#endif

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

foreign import ccall "gtk_constraint_is_required" gtk_constraint_is_required :: 
    Ptr Constraint ->                       -- constraint : TInterface (Name {namespace = "Gtk", name = "Constraint"})
    IO CInt

-- | Checks whether the constraint is a required relation for solving the
-- constraint layout.
constraintIsRequired ::
    (B.CallStack.HasCallStack, MonadIO m, IsConstraint a) =>
    a
    -- ^ /@constraint@/: a @GtkConstraint@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the constraint is required
constraintIsRequired :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsConstraint a) =>
a -> m Bool
constraintIsRequired a
constraint = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Constraint
constraint' <- a -> IO (Ptr Constraint)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
constraint
    CInt
result <- Ptr Constraint -> IO CInt
gtk_constraint_is_required Ptr Constraint
constraint'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
constraint
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ConstraintIsRequiredMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsConstraint a) => O.OverloadedMethod ConstraintIsRequiredMethodInfo a signature where
    overloadedMethod = constraintIsRequired

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


#endif