{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A widget constraining its child to a given size.
-- 
-- \<picture>
--   \<source srcset=\"clamp-wide-dark.png\" media=\"(prefers-color-scheme: dark)\">
--   \<img src=\"clamp-wide.png\" alt=\"clamp-wide\">
-- \<\/picture>
-- \<picture>
--   \<source srcset=\"clamp-narrow-dark.png\" media=\"(prefers-color-scheme: dark)\">
--   \<img src=\"clamp-narrow.png\" alt=\"clamp-narrow\">
-- \<\/picture>
-- 
-- The @AdwClamp@ widget constrains the size of the widget it contains to a
-- given maximum size. It will constrain the width if it is horizontal, or the
-- height if it is vertical. The expansion of the child from its minimum to its
-- maximum size is eased out for a smooth transition.
-- 
-- If the child requires more than the requested maximum size, it will be
-- allocated the minimum size it can fit in instead.
-- 
-- == CSS nodes
-- 
-- @AdwClamp@ has a single CSS node with name @clamp@.
-- 
-- Its children will receive the style classes @.large@ when the child reached
-- its maximum size, @.small@ when the clamp allocates its full size to the
-- child, @.medium@ in-between, or none if it hasn\'t computed its size yet.
-- 
-- /Since: 1.0/

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

module GI.Adw.Objects.Clamp
    ( 

-- * Exported types
    Clamp(..)                               ,
    IsClamp                                 ,
    toClamp                                 ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [actionSetEnabled]("GI.Gtk.Objects.Widget#g:method:actionSetEnabled"), [activate]("GI.Gtk.Objects.Widget#g:method:activate"), [activateAction]("GI.Gtk.Objects.Widget#g:method:activateAction"), [activateDefault]("GI.Gtk.Objects.Widget#g:method:activateDefault"), [addController]("GI.Gtk.Objects.Widget#g:method:addController"), [addCssClass]("GI.Gtk.Objects.Widget#g:method:addCssClass"), [addMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:addMnemonicLabel"), [addTickCallback]("GI.Gtk.Objects.Widget#g:method:addTickCallback"), [allocate]("GI.Gtk.Objects.Widget#g:method:allocate"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [childFocus]("GI.Gtk.Objects.Widget#g:method:childFocus"), [computeBounds]("GI.Gtk.Objects.Widget#g:method:computeBounds"), [computeExpand]("GI.Gtk.Objects.Widget#g:method:computeExpand"), [computePoint]("GI.Gtk.Objects.Widget#g:method:computePoint"), [computeTransform]("GI.Gtk.Objects.Widget#g:method:computeTransform"), [contains]("GI.Gtk.Objects.Widget#g:method:contains"), [createPangoContext]("GI.Gtk.Objects.Widget#g:method:createPangoContext"), [createPangoLayout]("GI.Gtk.Objects.Widget#g:method:createPangoLayout"), [disposeTemplate]("GI.Gtk.Objects.Widget#g:method:disposeTemplate"), [dragCheckThreshold]("GI.Gtk.Objects.Widget#g:method:dragCheckThreshold"), [errorBell]("GI.Gtk.Objects.Widget#g:method:errorBell"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [grabFocus]("GI.Gtk.Objects.Widget#g:method:grabFocus"), [hasCssClass]("GI.Gtk.Objects.Widget#g:method:hasCssClass"), [hasDefault]("GI.Gtk.Objects.Widget#g:method:hasDefault"), [hasFocus]("GI.Gtk.Objects.Widget#g:method:hasFocus"), [hasVisibleFocus]("GI.Gtk.Objects.Widget#g:method:hasVisibleFocus"), [hide]("GI.Gtk.Objects.Widget#g:method:hide"), [inDestruction]("GI.Gtk.Objects.Widget#g:method:inDestruction"), [initTemplate]("GI.Gtk.Objects.Widget#g:method:initTemplate"), [insertActionGroup]("GI.Gtk.Objects.Widget#g:method:insertActionGroup"), [insertAfter]("GI.Gtk.Objects.Widget#g:method:insertAfter"), [insertBefore]("GI.Gtk.Objects.Widget#g:method:insertBefore"), [isAncestor]("GI.Gtk.Objects.Widget#g:method:isAncestor"), [isDrawable]("GI.Gtk.Objects.Widget#g:method:isDrawable"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isFocus]("GI.Gtk.Objects.Widget#g:method:isFocus"), [isSensitive]("GI.Gtk.Objects.Widget#g:method:isSensitive"), [isVisible]("GI.Gtk.Objects.Widget#g:method:isVisible"), [keynavFailed]("GI.Gtk.Objects.Widget#g:method:keynavFailed"), [listMnemonicLabels]("GI.Gtk.Objects.Widget#g:method:listMnemonicLabels"), [map]("GI.Gtk.Objects.Widget#g:method:map"), [measure]("GI.Gtk.Objects.Widget#g:method:measure"), [mnemonicActivate]("GI.Gtk.Objects.Widget#g:method:mnemonicActivate"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [observeChildren]("GI.Gtk.Objects.Widget#g:method:observeChildren"), [observeControllers]("GI.Gtk.Objects.Widget#g:method:observeControllers"), [pick]("GI.Gtk.Objects.Widget#g:method:pick"), [queueAllocate]("GI.Gtk.Objects.Widget#g:method:queueAllocate"), [queueDraw]("GI.Gtk.Objects.Widget#g:method:queueDraw"), [queueResize]("GI.Gtk.Objects.Widget#g:method:queueResize"), [realize]("GI.Gtk.Objects.Widget#g:method:realize"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeController]("GI.Gtk.Objects.Widget#g:method:removeController"), [removeCssClass]("GI.Gtk.Objects.Widget#g:method:removeCssClass"), [removeMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:removeMnemonicLabel"), [removeTickCallback]("GI.Gtk.Objects.Widget#g:method:removeTickCallback"), [resetProperty]("GI.Gtk.Interfaces.Accessible#g:method:resetProperty"), [resetRelation]("GI.Gtk.Interfaces.Accessible#g:method:resetRelation"), [resetState]("GI.Gtk.Interfaces.Accessible#g:method:resetState"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [shouldLayout]("GI.Gtk.Objects.Widget#g:method:shouldLayout"), [show]("GI.Gtk.Objects.Widget#g:method:show"), [sizeAllocate]("GI.Gtk.Objects.Widget#g:method:sizeAllocate"), [snapshotChild]("GI.Gtk.Objects.Widget#g:method:snapshotChild"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [translateCoordinates]("GI.Gtk.Objects.Widget#g:method:translateCoordinates"), [triggerTooltipQuery]("GI.Gtk.Objects.Widget#g:method:triggerTooltipQuery"), [unmap]("GI.Gtk.Objects.Widget#g:method:unmap"), [unparent]("GI.Gtk.Objects.Widget#g:method:unparent"), [unrealize]("GI.Gtk.Objects.Widget#g:method:unrealize"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unsetStateFlags]("GI.Gtk.Objects.Widget#g:method:unsetStateFlags"), [updateProperty]("GI.Gtk.Interfaces.Accessible#g:method:updateProperty"), [updateRelation]("GI.Gtk.Interfaces.Accessible#g:method:updateRelation"), [updateState]("GI.Gtk.Interfaces.Accessible#g:method:updateState"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccessibleRole]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleRole"), [getAllocatedBaseline]("GI.Gtk.Objects.Widget#g:method:getAllocatedBaseline"), [getAllocatedHeight]("GI.Gtk.Objects.Widget#g:method:getAllocatedHeight"), [getAllocatedWidth]("GI.Gtk.Objects.Widget#g:method:getAllocatedWidth"), [getAllocation]("GI.Gtk.Objects.Widget#g:method:getAllocation"), [getAncestor]("GI.Gtk.Objects.Widget#g:method:getAncestor"), [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [getCanFocus]("GI.Gtk.Objects.Widget#g:method:getCanFocus"), [getCanTarget]("GI.Gtk.Objects.Widget#g:method:getCanTarget"), [getChild]("GI.Adw.Objects.Clamp#g:method:getChild"), [getChildVisible]("GI.Gtk.Objects.Widget#g:method:getChildVisible"), [getClipboard]("GI.Gtk.Objects.Widget#g:method:getClipboard"), [getCssClasses]("GI.Gtk.Objects.Widget#g:method:getCssClasses"), [getCssName]("GI.Gtk.Objects.Widget#g:method:getCssName"), [getCursor]("GI.Gtk.Objects.Widget#g:method:getCursor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDirection]("GI.Gtk.Objects.Widget#g:method:getDirection"), [getDisplay]("GI.Gtk.Objects.Widget#g:method:getDisplay"), [getFirstChild]("GI.Gtk.Objects.Widget#g:method:getFirstChild"), [getFocusChild]("GI.Gtk.Objects.Widget#g:method:getFocusChild"), [getFocusOnClick]("GI.Gtk.Objects.Widget#g:method:getFocusOnClick"), [getFocusable]("GI.Gtk.Objects.Widget#g:method:getFocusable"), [getFontMap]("GI.Gtk.Objects.Widget#g:method:getFontMap"), [getFontOptions]("GI.Gtk.Objects.Widget#g:method:getFontOptions"), [getFrameClock]("GI.Gtk.Objects.Widget#g:method:getFrameClock"), [getHalign]("GI.Gtk.Objects.Widget#g:method:getHalign"), [getHasTooltip]("GI.Gtk.Objects.Widget#g:method:getHasTooltip"), [getHeight]("GI.Gtk.Objects.Widget#g:method:getHeight"), [getHexpand]("GI.Gtk.Objects.Widget#g:method:getHexpand"), [getHexpandSet]("GI.Gtk.Objects.Widget#g:method:getHexpandSet"), [getLastChild]("GI.Gtk.Objects.Widget#g:method:getLastChild"), [getLayoutManager]("GI.Gtk.Objects.Widget#g:method:getLayoutManager"), [getMapped]("GI.Gtk.Objects.Widget#g:method:getMapped"), [getMarginBottom]("GI.Gtk.Objects.Widget#g:method:getMarginBottom"), [getMarginEnd]("GI.Gtk.Objects.Widget#g:method:getMarginEnd"), [getMarginStart]("GI.Gtk.Objects.Widget#g:method:getMarginStart"), [getMarginTop]("GI.Gtk.Objects.Widget#g:method:getMarginTop"), [getMaximumSize]("GI.Adw.Objects.Clamp#g:method:getMaximumSize"), [getName]("GI.Gtk.Objects.Widget#g:method:getName"), [getNative]("GI.Gtk.Objects.Widget#g:method:getNative"), [getNextSibling]("GI.Gtk.Objects.Widget#g:method:getNextSibling"), [getOpacity]("GI.Gtk.Objects.Widget#g:method:getOpacity"), [getOrientation]("GI.Gtk.Interfaces.Orientable#g:method:getOrientation"), [getOverflow]("GI.Gtk.Objects.Widget#g:method:getOverflow"), [getPangoContext]("GI.Gtk.Objects.Widget#g:method:getPangoContext"), [getParent]("GI.Gtk.Objects.Widget#g:method:getParent"), [getPreferredSize]("GI.Gtk.Objects.Widget#g:method:getPreferredSize"), [getPrevSibling]("GI.Gtk.Objects.Widget#g:method:getPrevSibling"), [getPrimaryClipboard]("GI.Gtk.Objects.Widget#g:method:getPrimaryClipboard"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRealized]("GI.Gtk.Objects.Widget#g:method:getRealized"), [getReceivesDefault]("GI.Gtk.Objects.Widget#g:method:getReceivesDefault"), [getRequestMode]("GI.Gtk.Objects.Widget#g:method:getRequestMode"), [getRoot]("GI.Gtk.Objects.Widget#g:method:getRoot"), [getScaleFactor]("GI.Gtk.Objects.Widget#g:method:getScaleFactor"), [getSensitive]("GI.Gtk.Objects.Widget#g:method:getSensitive"), [getSettings]("GI.Gtk.Objects.Widget#g:method:getSettings"), [getSize]("GI.Gtk.Objects.Widget#g:method:getSize"), [getSizeRequest]("GI.Gtk.Objects.Widget#g:method:getSizeRequest"), [getStateFlags]("GI.Gtk.Objects.Widget#g:method:getStateFlags"), [getStyleContext]("GI.Gtk.Objects.Widget#g:method:getStyleContext"), [getTemplateChild]("GI.Gtk.Objects.Widget#g:method:getTemplateChild"), [getTighteningThreshold]("GI.Adw.Objects.Clamp#g:method:getTighteningThreshold"), [getTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:getTooltipMarkup"), [getTooltipText]("GI.Gtk.Objects.Widget#g:method:getTooltipText"), [getValign]("GI.Gtk.Objects.Widget#g:method:getValign"), [getVexpand]("GI.Gtk.Objects.Widget#g:method:getVexpand"), [getVexpandSet]("GI.Gtk.Objects.Widget#g:method:getVexpandSet"), [getVisible]("GI.Gtk.Objects.Widget#g:method:getVisible"), [getWidth]("GI.Gtk.Objects.Widget#g:method:getWidth").
-- 
-- ==== Setters
-- [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [setChild]("GI.Adw.Objects.Clamp#g:method:setChild"), [setChildVisible]("GI.Gtk.Objects.Widget#g:method:setChildVisible"), [setCssClasses]("GI.Gtk.Objects.Widget#g:method:setCssClasses"), [setCursor]("GI.Gtk.Objects.Widget#g:method:setCursor"), [setCursorFromName]("GI.Gtk.Objects.Widget#g:method:setCursorFromName"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDirection]("GI.Gtk.Objects.Widget#g:method:setDirection"), [setFocusChild]("GI.Gtk.Objects.Widget#g:method:setFocusChild"), [setFocusOnClick]("GI.Gtk.Objects.Widget#g:method:setFocusOnClick"), [setFocusable]("GI.Gtk.Objects.Widget#g:method:setFocusable"), [setFontMap]("GI.Gtk.Objects.Widget#g:method:setFontMap"), [setFontOptions]("GI.Gtk.Objects.Widget#g:method:setFontOptions"), [setHalign]("GI.Gtk.Objects.Widget#g:method:setHalign"), [setHasTooltip]("GI.Gtk.Objects.Widget#g:method:setHasTooltip"), [setHexpand]("GI.Gtk.Objects.Widget#g:method:setHexpand"), [setHexpandSet]("GI.Gtk.Objects.Widget#g:method:setHexpandSet"), [setLayoutManager]("GI.Gtk.Objects.Widget#g:method:setLayoutManager"), [setMarginBottom]("GI.Gtk.Objects.Widget#g:method:setMarginBottom"), [setMarginEnd]("GI.Gtk.Objects.Widget#g:method:setMarginEnd"), [setMarginStart]("GI.Gtk.Objects.Widget#g:method:setMarginStart"), [setMarginTop]("GI.Gtk.Objects.Widget#g:method:setMarginTop"), [setMaximumSize]("GI.Adw.Objects.Clamp#g:method:setMaximumSize"), [setName]("GI.Gtk.Objects.Widget#g:method:setName"), [setOpacity]("GI.Gtk.Objects.Widget#g:method:setOpacity"), [setOrientation]("GI.Gtk.Interfaces.Orientable#g:method:setOrientation"), [setOverflow]("GI.Gtk.Objects.Widget#g:method:setOverflow"), [setParent]("GI.Gtk.Objects.Widget#g:method:setParent"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setReceivesDefault]("GI.Gtk.Objects.Widget#g:method:setReceivesDefault"), [setSensitive]("GI.Gtk.Objects.Widget#g:method:setSensitive"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [setTighteningThreshold]("GI.Adw.Objects.Clamp#g:method:setTighteningThreshold"), [setTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:setTooltipMarkup"), [setTooltipText]("GI.Gtk.Objects.Widget#g:method:setTooltipText"), [setValign]("GI.Gtk.Objects.Widget#g:method:setValign"), [setVexpand]("GI.Gtk.Objects.Widget#g:method:setVexpand"), [setVexpandSet]("GI.Gtk.Objects.Widget#g:method:setVexpandSet"), [setVisible]("GI.Gtk.Objects.Widget#g:method:setVisible").

#if defined(ENABLE_OVERLOADING)
    ResolveClampMethod                      ,
#endif

-- ** getChild #method:getChild#

#if defined(ENABLE_OVERLOADING)
    ClampGetChildMethodInfo                 ,
#endif
    clampGetChild                           ,


-- ** getMaximumSize #method:getMaximumSize#

#if defined(ENABLE_OVERLOADING)
    ClampGetMaximumSizeMethodInfo           ,
#endif
    clampGetMaximumSize                     ,


-- ** getTighteningThreshold #method:getTighteningThreshold#

#if defined(ENABLE_OVERLOADING)
    ClampGetTighteningThresholdMethodInfo   ,
#endif
    clampGetTighteningThreshold             ,


-- ** new #method:new#

    clampNew                                ,


-- ** setChild #method:setChild#

#if defined(ENABLE_OVERLOADING)
    ClampSetChildMethodInfo                 ,
#endif
    clampSetChild                           ,


-- ** setMaximumSize #method:setMaximumSize#

#if defined(ENABLE_OVERLOADING)
    ClampSetMaximumSizeMethodInfo           ,
#endif
    clampSetMaximumSize                     ,


-- ** setTighteningThreshold #method:setTighteningThreshold#

#if defined(ENABLE_OVERLOADING)
    ClampSetTighteningThresholdMethodInfo   ,
#endif
    clampSetTighteningThreshold             ,




 -- * Properties


-- ** child #attr:child#
-- | The child widget of the @AdwClamp@.
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    ClampChildPropertyInfo                  ,
#endif
#if defined(ENABLE_OVERLOADING)
    clampChild                              ,
#endif
    clearClampChild                         ,
    constructClampChild                     ,
    getClampChild                           ,
    setClampChild                           ,


-- ** maximumSize #attr:maximumSize#
-- | The maximum size allocated to the child.
-- 
-- It is the width if the clamp is horizontal, or the height if it is vertical.
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    ClampMaximumSizePropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    clampMaximumSize                        ,
#endif
    constructClampMaximumSize               ,
    getClampMaximumSize                     ,
    setClampMaximumSize                     ,


-- ** tighteningThreshold #attr:tighteningThreshold#
-- | The size above which the child is clamped.
-- 
-- Starting from this size, the clamp will tighten its grip on the child,
-- slowly allocating less and less of the available size up to the maximum
-- allocated size. Below that threshold and below the maximum size, the child
-- will be allocated all the available size.
-- 
-- If the threshold is greater than the maximum size to allocate to the child,
-- the child will be allocated all the size up to the maximum.
-- If the threshold is lower than the minimum size to allocate to the child,
-- that size will be used as the tightening threshold.
-- 
-- Effectively, tightening the grip on the child before it reaches its maximum
-- size makes transitions to and from the maximum size smoother when resizing.
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    ClampTighteningThresholdPropertyInfo    ,
#endif
#if defined(ENABLE_OVERLOADING)
    clampTighteningThreshold                ,
#endif
    constructClampTighteningThreshold       ,
    getClampTighteningThreshold             ,
    setClampTighteningThreshold             ,




    ) where

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

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

import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import qualified GI.Gtk.Interfaces.Orientable as Gtk.Orientable
import qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "adw_clamp_get_type"
    c_adw_clamp_get_type :: IO B.Types.GType

instance B.Types.TypedObject Clamp where
    glibType :: IO GType
glibType = IO GType
c_adw_clamp_get_type

instance B.Types.GObject Clamp

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

instance O.HasParentTypes Clamp
type instance O.ParentTypes Clamp = '[Gtk.Widget.Widget, GObject.Object.Object, Gtk.Accessible.Accessible, Gtk.Buildable.Buildable, Gtk.ConstraintTarget.ConstraintTarget, Gtk.Orientable.Orientable]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveClampMethod (t :: Symbol) (o :: *) :: * where
    ResolveClampMethod "actionSetEnabled" o = Gtk.Widget.WidgetActionSetEnabledMethodInfo
    ResolveClampMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveClampMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveClampMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveClampMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveClampMethod "addCssClass" o = Gtk.Widget.WidgetAddCssClassMethodInfo
    ResolveClampMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveClampMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveClampMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveClampMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveClampMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveClampMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveClampMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveClampMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveClampMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveClampMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveClampMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveClampMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveClampMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveClampMethod "disposeTemplate" o = Gtk.Widget.WidgetDisposeTemplateMethodInfo
    ResolveClampMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveClampMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveClampMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveClampMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveClampMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveClampMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveClampMethod "hasCssClass" o = Gtk.Widget.WidgetHasCssClassMethodInfo
    ResolveClampMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveClampMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveClampMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveClampMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveClampMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveClampMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveClampMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveClampMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveClampMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveClampMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveClampMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveClampMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveClampMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveClampMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveClampMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveClampMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveClampMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveClampMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveClampMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveClampMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveClampMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveClampMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveClampMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveClampMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveClampMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveClampMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveClampMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveClampMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveClampMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveClampMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveClampMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveClampMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveClampMethod "removeCssClass" o = Gtk.Widget.WidgetRemoveCssClassMethodInfo
    ResolveClampMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveClampMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveClampMethod "resetProperty" o = Gtk.Accessible.AccessibleResetPropertyMethodInfo
    ResolveClampMethod "resetRelation" o = Gtk.Accessible.AccessibleResetRelationMethodInfo
    ResolveClampMethod "resetState" o = Gtk.Accessible.AccessibleResetStateMethodInfo
    ResolveClampMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveClampMethod "shouldLayout" o = Gtk.Widget.WidgetShouldLayoutMethodInfo
    ResolveClampMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveClampMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveClampMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveClampMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveClampMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveClampMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveClampMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveClampMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveClampMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveClampMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveClampMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveClampMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveClampMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveClampMethod "updateProperty" o = Gtk.Accessible.AccessibleUpdatePropertyMethodInfo
    ResolveClampMethod "updateRelation" o = Gtk.Accessible.AccessibleUpdateRelationMethodInfo
    ResolveClampMethod "updateState" o = Gtk.Accessible.AccessibleUpdateStateMethodInfo
    ResolveClampMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveClampMethod "getAccessibleRole" o = Gtk.Accessible.AccessibleGetAccessibleRoleMethodInfo
    ResolveClampMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveClampMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveClampMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveClampMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveClampMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveClampMethod "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
    ResolveClampMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveClampMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveClampMethod "getChild" o = ClampGetChildMethodInfo
    ResolveClampMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveClampMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveClampMethod "getCssClasses" o = Gtk.Widget.WidgetGetCssClassesMethodInfo
    ResolveClampMethod "getCssName" o = Gtk.Widget.WidgetGetCssNameMethodInfo
    ResolveClampMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveClampMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveClampMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveClampMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveClampMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveClampMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveClampMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveClampMethod "getFocusable" o = Gtk.Widget.WidgetGetFocusableMethodInfo
    ResolveClampMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveClampMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveClampMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveClampMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveClampMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveClampMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveClampMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveClampMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveClampMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveClampMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveClampMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveClampMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveClampMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveClampMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveClampMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveClampMethod "getMaximumSize" o = ClampGetMaximumSizeMethodInfo
    ResolveClampMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveClampMethod "getNative" o = Gtk.Widget.WidgetGetNativeMethodInfo
    ResolveClampMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveClampMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveClampMethod "getOrientation" o = Gtk.Orientable.OrientableGetOrientationMethodInfo
    ResolveClampMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveClampMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveClampMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveClampMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveClampMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveClampMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveClampMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveClampMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveClampMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveClampMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveClampMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveClampMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveClampMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveClampMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveClampMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveClampMethod "getSize" o = Gtk.Widget.WidgetGetSizeMethodInfo
    ResolveClampMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveClampMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveClampMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveClampMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveClampMethod "getTighteningThreshold" o = ClampGetTighteningThresholdMethodInfo
    ResolveClampMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveClampMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveClampMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveClampMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveClampMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveClampMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveClampMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveClampMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveClampMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveClampMethod "setChild" o = ClampSetChildMethodInfo
    ResolveClampMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveClampMethod "setCssClasses" o = Gtk.Widget.WidgetSetCssClassesMethodInfo
    ResolveClampMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveClampMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveClampMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveClampMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveClampMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveClampMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveClampMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveClampMethod "setFocusable" o = Gtk.Widget.WidgetSetFocusableMethodInfo
    ResolveClampMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveClampMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveClampMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveClampMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveClampMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveClampMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveClampMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveClampMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveClampMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveClampMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveClampMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveClampMethod "setMaximumSize" o = ClampSetMaximumSizeMethodInfo
    ResolveClampMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveClampMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveClampMethod "setOrientation" o = Gtk.Orientable.OrientableSetOrientationMethodInfo
    ResolveClampMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveClampMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveClampMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveClampMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveClampMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveClampMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveClampMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveClampMethod "setTighteningThreshold" o = ClampSetTighteningThresholdMethodInfo
    ResolveClampMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveClampMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveClampMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveClampMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveClampMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveClampMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveClampMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

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

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

-- | Construct a `GValueConstruct` with valid value for the “@child@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructClampChild :: (IsClamp o, MIO.MonadIO m, Gtk.Widget.IsWidget a) => a -> m (GValueConstruct o)
constructClampChild :: forall o (m :: * -> *) a.
(IsClamp o, MonadIO m, IsWidget a) =>
a -> m (GValueConstruct o)
constructClampChild 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
"child" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

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

#if defined(ENABLE_OVERLOADING)
data ClampChildPropertyInfo
instance AttrInfo ClampChildPropertyInfo where
    type AttrAllowedOps ClampChildPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ClampChildPropertyInfo = IsClamp
    type AttrSetTypeConstraint ClampChildPropertyInfo = Gtk.Widget.IsWidget
    type AttrTransferTypeConstraint ClampChildPropertyInfo = Gtk.Widget.IsWidget
    type AttrTransferType ClampChildPropertyInfo = Gtk.Widget.Widget
    type AttrGetType ClampChildPropertyInfo = (Maybe Gtk.Widget.Widget)
    type AttrLabel ClampChildPropertyInfo = "child"
    type AttrOrigin ClampChildPropertyInfo = Clamp
    attrGet = getClampChild
    attrSet = setClampChild
    attrTransfer _ v = do
        unsafeCastTo Gtk.Widget.Widget v
    attrConstruct = constructClampChild
    attrClear = clearClampChild
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.Clamp.child"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.3/docs/GI-Adw-Objects-Clamp.html#g:attr:child"
        })
#endif

-- VVV Prop "maximum-size"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@maximum-size@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' clamp #maximumSize
-- @
getClampMaximumSize :: (MonadIO m, IsClamp o) => o -> m Int32
getClampMaximumSize :: forall (m :: * -> *) o. (MonadIO m, IsClamp o) => o -> m Int32
getClampMaximumSize 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
"maximum-size"

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

-- | Construct a `GValueConstruct` with valid value for the “@maximum-size@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructClampMaximumSize :: (IsClamp o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructClampMaximumSize :: forall o (m :: * -> *).
(IsClamp o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructClampMaximumSize 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
"maximum-size" Int32
val

#if defined(ENABLE_OVERLOADING)
data ClampMaximumSizePropertyInfo
instance AttrInfo ClampMaximumSizePropertyInfo where
    type AttrAllowedOps ClampMaximumSizePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ClampMaximumSizePropertyInfo = IsClamp
    type AttrSetTypeConstraint ClampMaximumSizePropertyInfo = (~) Int32
    type AttrTransferTypeConstraint ClampMaximumSizePropertyInfo = (~) Int32
    type AttrTransferType ClampMaximumSizePropertyInfo = Int32
    type AttrGetType ClampMaximumSizePropertyInfo = Int32
    type AttrLabel ClampMaximumSizePropertyInfo = "maximum-size"
    type AttrOrigin ClampMaximumSizePropertyInfo = Clamp
    attrGet = getClampMaximumSize
    attrSet = setClampMaximumSize
    attrTransfer _ v = do
        return v
    attrConstruct = constructClampMaximumSize
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.Clamp.maximumSize"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.3/docs/GI-Adw-Objects-Clamp.html#g:attr:maximumSize"
        })
#endif

-- VVV Prop "tightening-threshold"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@tightening-threshold@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' clamp #tighteningThreshold
-- @
getClampTighteningThreshold :: (MonadIO m, IsClamp o) => o -> m Int32
getClampTighteningThreshold :: forall (m :: * -> *) o. (MonadIO m, IsClamp o) => o -> m Int32
getClampTighteningThreshold 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
"tightening-threshold"

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

-- | Construct a `GValueConstruct` with valid value for the “@tightening-threshold@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructClampTighteningThreshold :: (IsClamp o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructClampTighteningThreshold :: forall o (m :: * -> *).
(IsClamp o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructClampTighteningThreshold 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
"tightening-threshold" Int32
val

#if defined(ENABLE_OVERLOADING)
data ClampTighteningThresholdPropertyInfo
instance AttrInfo ClampTighteningThresholdPropertyInfo where
    type AttrAllowedOps ClampTighteningThresholdPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ClampTighteningThresholdPropertyInfo = IsClamp
    type AttrSetTypeConstraint ClampTighteningThresholdPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint ClampTighteningThresholdPropertyInfo = (~) Int32
    type AttrTransferType ClampTighteningThresholdPropertyInfo = Int32
    type AttrGetType ClampTighteningThresholdPropertyInfo = Int32
    type AttrLabel ClampTighteningThresholdPropertyInfo = "tightening-threshold"
    type AttrOrigin ClampTighteningThresholdPropertyInfo = Clamp
    attrGet = getClampTighteningThreshold
    attrSet = setClampTighteningThreshold
    attrTransfer _ v = do
        return v
    attrConstruct = constructClampTighteningThreshold
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.Clamp.tighteningThreshold"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.3/docs/GI-Adw-Objects-Clamp.html#g:attr:tighteningThreshold"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Clamp
type instance O.AttributeList Clamp = ClampAttributeList
type ClampAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("child", ClampChildPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusable", Gtk.Widget.WidgetFocusablePropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("maximumSize", ClampMaximumSizePropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("orientation", Gtk.Orientable.OrientableOrientationPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("tighteningThreshold", ClampTighteningThresholdPropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
clampChild :: AttrLabelProxy "child"
clampChild = AttrLabelProxy

clampMaximumSize :: AttrLabelProxy "maximumSize"
clampMaximumSize = AttrLabelProxy

clampTighteningThreshold :: AttrLabelProxy "tighteningThreshold"
clampTighteningThreshold = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Clamp = ClampSignalList
type ClampSignalList = ('[ '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "adw_clamp_new" adw_clamp_new :: 
    IO (Ptr Clamp)

-- | Creates a new @AdwClamp@.
-- 
-- /Since: 1.0/
clampNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Clamp
    -- ^ __Returns:__ the newly created @AdwClamp@
clampNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Clamp
clampNew  = IO Clamp -> m Clamp
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Clamp -> m Clamp) -> IO Clamp -> m Clamp
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clamp
result <- IO (Ptr Clamp)
adw_clamp_new
    Text -> Ptr Clamp -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"clampNew" Ptr Clamp
result
    Clamp
result' <- ((ManagedPtr Clamp -> Clamp) -> Ptr Clamp -> IO Clamp
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Clamp -> Clamp
Clamp) Ptr Clamp
result
    Clamp -> IO Clamp
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Clamp
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Clamp::get_child
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Adw" , name = "Clamp" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a clamp" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Widget" })
-- throws : False
-- Skip return : False

foreign import ccall "adw_clamp_get_child" adw_clamp_get_child :: 
    Ptr Clamp ->                            -- self : TInterface (Name {namespace = "Adw", name = "Clamp"})
    IO (Ptr Gtk.Widget.Widget)

-- | Gets the child widget of /@self@/.
-- 
-- /Since: 1.0/
clampGetChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsClamp a) =>
    a
    -- ^ /@self@/: a clamp
    -> m (Maybe Gtk.Widget.Widget)
    -- ^ __Returns:__ the child widget of /@self@/
clampGetChild :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsClamp a) =>
a -> m (Maybe Widget)
clampGetChild a
self = IO (Maybe Widget) -> m (Maybe Widget)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Widget) -> m (Maybe Widget))
-> IO (Maybe Widget) -> m (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clamp
self' <- a -> IO (Ptr Clamp)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
result <- Ptr Clamp -> IO (Ptr Widget)
adw_clamp_get_child Ptr Clamp
self'
    Maybe Widget
maybeResult <- Ptr Widget -> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Widget
result ((Ptr Widget -> IO Widget) -> IO (Maybe Widget))
-> (Ptr Widget -> IO Widget) -> IO (Maybe Widget)
forall a b. (a -> b) -> a -> b
$ \Ptr Widget
result' -> do
        Widget
result'' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result'
        Widget -> IO Widget
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Widget -> IO (Maybe Widget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Widget
maybeResult

#if defined(ENABLE_OVERLOADING)
data ClampGetChildMethodInfo
instance (signature ~ (m (Maybe Gtk.Widget.Widget)), MonadIO m, IsClamp a) => O.OverloadedMethod ClampGetChildMethodInfo a signature where
    overloadedMethod = clampGetChild

instance O.OverloadedMethodInfo ClampGetChildMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.Clamp.clampGetChild",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.3/docs/GI-Adw-Objects-Clamp.html#v:clampGetChild"
        })


#endif

-- method Clamp::get_maximum_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Adw" , name = "Clamp" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a clamp" , 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 "adw_clamp_get_maximum_size" adw_clamp_get_maximum_size :: 
    Ptr Clamp ->                            -- self : TInterface (Name {namespace = "Adw", name = "Clamp"})
    IO Int32

-- | Gets the maximum size allocated to the child.
-- 
-- /Since: 1.0/
clampGetMaximumSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsClamp a) =>
    a
    -- ^ /@self@/: a clamp
    -> m Int32
    -- ^ __Returns:__ the maximum size to allocate to the child
clampGetMaximumSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsClamp a) =>
a -> m Int32
clampGetMaximumSize a
self = 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 Clamp
self' <- a -> IO (Ptr Clamp)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Int32
result <- Ptr Clamp -> IO Int32
adw_clamp_get_maximum_size Ptr Clamp
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data ClampGetMaximumSizeMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsClamp a) => O.OverloadedMethod ClampGetMaximumSizeMethodInfo a signature where
    overloadedMethod = clampGetMaximumSize

instance O.OverloadedMethodInfo ClampGetMaximumSizeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.Clamp.clampGetMaximumSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.3/docs/GI-Adw-Objects-Clamp.html#v:clampGetMaximumSize"
        })


#endif

-- method Clamp::get_tightening_threshold
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Adw" , name = "Clamp" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a clamp" , 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 "adw_clamp_get_tightening_threshold" adw_clamp_get_tightening_threshold :: 
    Ptr Clamp ->                            -- self : TInterface (Name {namespace = "Adw", name = "Clamp"})
    IO Int32

-- | Gets the size above which the child is clamped.
-- 
-- /Since: 1.0/
clampGetTighteningThreshold ::
    (B.CallStack.HasCallStack, MonadIO m, IsClamp a) =>
    a
    -- ^ /@self@/: a clamp
    -> m Int32
    -- ^ __Returns:__ the size above which the child is clamped
clampGetTighteningThreshold :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsClamp a) =>
a -> m Int32
clampGetTighteningThreshold a
self = 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 Clamp
self' <- a -> IO (Ptr Clamp)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Int32
result <- Ptr Clamp -> IO Int32
adw_clamp_get_tightening_threshold Ptr Clamp
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data ClampGetTighteningThresholdMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsClamp a) => O.OverloadedMethod ClampGetTighteningThresholdMethodInfo a signature where
    overloadedMethod = clampGetTighteningThreshold

instance O.OverloadedMethodInfo ClampGetTighteningThresholdMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.Clamp.clampGetTighteningThreshold",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.3/docs/GI-Adw-Objects-Clamp.html#v:clampGetTighteningThreshold"
        })


#endif

-- method Clamp::set_child
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Adw" , name = "Clamp" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a clamp" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "child"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Widget" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the child widget" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "adw_clamp_set_child" adw_clamp_set_child :: 
    Ptr Clamp ->                            -- self : TInterface (Name {namespace = "Adw", name = "Clamp"})
    Ptr Gtk.Widget.Widget ->                -- child : TInterface (Name {namespace = "Gtk", name = "Widget"})
    IO ()

-- | Sets the child widget of /@self@/.
-- 
-- /Since: 1.0/
clampSetChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsClamp a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@self@/: a clamp
    -> Maybe (b)
    -- ^ /@child@/: the child widget
    -> m ()
clampSetChild :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsClamp a, IsWidget b) =>
a -> Maybe b -> m ()
clampSetChild a
self Maybe b
child = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clamp
self' <- a -> IO (Ptr Clamp)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
maybeChild <- case Maybe b
child of
        Maybe b
Nothing -> Ptr Widget -> IO (Ptr Widget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
forall a. Ptr a
nullPtr
        Just b
jChild -> do
            Ptr Widget
jChild' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jChild
            Ptr Widget -> IO (Ptr Widget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jChild'
    Ptr Clamp -> Ptr Widget -> IO ()
adw_clamp_set_child Ptr Clamp
self' Ptr Widget
maybeChild
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
child b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClampSetChildMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsClamp a, Gtk.Widget.IsWidget b) => O.OverloadedMethod ClampSetChildMethodInfo a signature where
    overloadedMethod = clampSetChild

instance O.OverloadedMethodInfo ClampSetChildMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.Clamp.clampSetChild",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.3/docs/GI-Adw-Objects-Clamp.html#v:clampSetChild"
        })


#endif

-- method Clamp::set_maximum_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Adw" , name = "Clamp" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a clamp" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "maximum_size"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the maximum size" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "adw_clamp_set_maximum_size" adw_clamp_set_maximum_size :: 
    Ptr Clamp ->                            -- self : TInterface (Name {namespace = "Adw", name = "Clamp"})
    Int32 ->                                -- maximum_size : TBasicType TInt
    IO ()

-- | Sets the maximum size allocated to the child.
-- 
-- It is the width if the clamp is horizontal, or the height if it is vertical.
-- 
-- /Since: 1.0/
clampSetMaximumSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsClamp a) =>
    a
    -- ^ /@self@/: a clamp
    -> Int32
    -- ^ /@maximumSize@/: the maximum size
    -> m ()
clampSetMaximumSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsClamp a) =>
a -> Int32 -> m ()
clampSetMaximumSize a
self Int32
maximumSize = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clamp
self' <- a -> IO (Ptr Clamp)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Clamp -> Int32 -> IO ()
adw_clamp_set_maximum_size Ptr Clamp
self' Int32
maximumSize
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClampSetMaximumSizeMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsClamp a) => O.OverloadedMethod ClampSetMaximumSizeMethodInfo a signature where
    overloadedMethod = clampSetMaximumSize

instance O.OverloadedMethodInfo ClampSetMaximumSizeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.Clamp.clampSetMaximumSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.3/docs/GI-Adw-Objects-Clamp.html#v:clampSetMaximumSize"
        })


#endif

-- method Clamp::set_tightening_threshold
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType = TInterface Name { namespace = "Adw" , name = "Clamp" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a clamp" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "tightening_threshold"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the tightening threshold"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "adw_clamp_set_tightening_threshold" adw_clamp_set_tightening_threshold :: 
    Ptr Clamp ->                            -- self : TInterface (Name {namespace = "Adw", name = "Clamp"})
    Int32 ->                                -- tightening_threshold : TBasicType TInt
    IO ()

-- | Sets the size above which the child is clamped.
-- 
-- Starting from this size, the clamp will tighten its grip on the child, slowly
-- allocating less and less of the available size up to the maximum allocated
-- size. Below that threshold and below the maximum size, the child will be
-- allocated all the available size.
-- 
-- If the threshold is greater than the maximum size to allocate to the child,
-- the child will be allocated all the size up to the maximum. If the threshold
-- is lower than the minimum size to allocate to the child, that size will be
-- used as the tightening threshold.
-- 
-- Effectively, tightening the grip on the child before it reaches its maximum
-- size makes transitions to and from the maximum size smoother when resizing.
-- 
-- /Since: 1.0/
clampSetTighteningThreshold ::
    (B.CallStack.HasCallStack, MonadIO m, IsClamp a) =>
    a
    -- ^ /@self@/: a clamp
    -> Int32
    -- ^ /@tighteningThreshold@/: the tightening threshold
    -> m ()
clampSetTighteningThreshold :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsClamp a) =>
a -> Int32 -> m ()
clampSetTighteningThreshold a
self Int32
tighteningThreshold = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Clamp
self' <- a -> IO (Ptr Clamp)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Clamp -> Int32 -> IO ()
adw_clamp_set_tightening_threshold Ptr Clamp
self' Int32
tighteningThreshold
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ClampSetTighteningThresholdMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsClamp a) => O.OverloadedMethod ClampSetTighteningThresholdMethodInfo a signature where
    overloadedMethod = clampSetTighteningThreshold

instance O.OverloadedMethodInfo ClampSetTighteningThresholdMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.Clamp.clampSetTighteningThreshold",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.3/docs/GI-Adw-Objects-Clamp.html#v:clampSetTighteningThreshold"
        })


#endif