{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A helper widget for creating buttons.
-- 
-- \<picture>
--   \<source srcset=\"button-content-dark.png\" media=\"(prefers-color-scheme: dark)\">
--   \<img src=\"button-content.png\" alt=\"button-content\">
-- \<\/picture>
-- 
-- @AdwButtonContent@ is a box-like widget with an icon and a label.
-- 
-- It\'s intended to be used as a direct child of t'GI.Gtk.Objects.Button.Button',
-- t'GI.Gtk.Objects.MenuButton.MenuButton' or [class/@splitButton@/], when they need to have both an
-- icon and a label, as follows:
-- 
-- 
-- === /xml code/
-- ><object class="GtkButton">
-- >  <property name="child">
-- >    <object class="AdwButtonContent">
-- >      <property name="icon-name">document-open-symbolic</property>
-- >      <property name="label" translatable="yes">_Open</property>
-- >      <property name="use-underline">True</property>
-- >    </object>
-- >  </property>
-- ></object>
-- 
-- 
-- @AdwButtonContent@ handles style classes and connecting the mnemonic to the
-- button automatically.
-- 
-- == CSS nodes
-- 
-- >buttoncontent
-- >├── image
-- >╰── label
-- 
-- 
-- @AdwButtonContent@\'s CSS node is called @buttoncontent@. It contains the
-- subnodes @image@ and @label@.
-- 
-- When inside a @GtkButton@ or @AdwSplitButton@, the button will receive the
-- @.image-text-button@ style class. When inside a @GtkMenuButton@, the
-- internal @GtkButton@ will receive it instead.
-- 
-- == Accessibility
-- 
-- @AdwButtonContent@ uses the @GTK_ACCESSIBLE_ROLE_GROUP@ role.

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

module GI.Adw.Objects.ButtonContent
    ( 

-- * Exported types
    ButtonContent(..)                       ,
    IsButtonContent                         ,
    toButtonContent                         ,


 -- * 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"), [updateNextAccessibleSibling]("GI.Gtk.Interfaces.Accessible#g:method:updateNextAccessibleSibling"), [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
-- [getAccessibleParent]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleParent"), [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"), [getAtContext]("GI.Gtk.Interfaces.Accessible#g:method:getAtContext"), [getBounds]("GI.Gtk.Interfaces.Accessible#g:method:getBounds"), [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [getCanFocus]("GI.Gtk.Objects.Widget#g:method:getCanFocus"), [getCanTarget]("GI.Gtk.Objects.Widget#g:method:getCanTarget"), [getChildVisible]("GI.Gtk.Objects.Widget#g:method:getChildVisible"), [getClipboard]("GI.Gtk.Objects.Widget#g:method:getClipboard"), [getColor]("GI.Gtk.Objects.Widget#g:method:getColor"), [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"), [getFirstAccessibleChild]("GI.Gtk.Interfaces.Accessible#g:method:getFirstAccessibleChild"), [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"), [getIconName]("GI.Adw.Objects.ButtonContent#g:method:getIconName"), [getLabel]("GI.Adw.Objects.ButtonContent#g:method:getLabel"), [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"), [getName]("GI.Gtk.Objects.Widget#g:method:getName"), [getNative]("GI.Gtk.Objects.Widget#g:method:getNative"), [getNextAccessibleSibling]("GI.Gtk.Interfaces.Accessible#g:method:getNextAccessibleSibling"), [getNextSibling]("GI.Gtk.Objects.Widget#g:method:getNextSibling"), [getOpacity]("GI.Gtk.Objects.Widget#g:method:getOpacity"), [getOverflow]("GI.Gtk.Objects.Widget#g:method:getOverflow"), [getPangoContext]("GI.Gtk.Objects.Widget#g:method:getPangoContext"), [getParent]("GI.Gtk.Objects.Widget#g:method:getParent"), [getPlatformState]("GI.Gtk.Interfaces.Accessible#g:method:getPlatformState"), [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"), [getTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:getTooltipMarkup"), [getTooltipText]("GI.Gtk.Objects.Widget#g:method:getTooltipText"), [getUseUnderline]("GI.Adw.Objects.ButtonContent#g:method:getUseUnderline"), [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
-- [setAccessibleParent]("GI.Gtk.Interfaces.Accessible#g:method:setAccessibleParent"), [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [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"), [setIconName]("GI.Adw.Objects.ButtonContent#g:method:setIconName"), [setLabel]("GI.Adw.Objects.ButtonContent#g:method:setLabel"), [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"), [setName]("GI.Gtk.Objects.Widget#g:method:setName"), [setOpacity]("GI.Gtk.Objects.Widget#g:method:setOpacity"), [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"), [setTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:setTooltipMarkup"), [setTooltipText]("GI.Gtk.Objects.Widget#g:method:setTooltipText"), [setUseUnderline]("GI.Adw.Objects.ButtonContent#g:method:setUseUnderline"), [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)
    ResolveButtonContentMethod              ,
#endif

-- ** getIconName #method:getIconName#

#if defined(ENABLE_OVERLOADING)
    ButtonContentGetIconNameMethodInfo      ,
#endif
    buttonContentGetIconName                ,


-- ** getLabel #method:getLabel#

#if defined(ENABLE_OVERLOADING)
    ButtonContentGetLabelMethodInfo         ,
#endif
    buttonContentGetLabel                   ,


-- ** getUseUnderline #method:getUseUnderline#

#if defined(ENABLE_OVERLOADING)
    ButtonContentGetUseUnderlineMethodInfo  ,
#endif
    buttonContentGetUseUnderline            ,


-- ** new #method:new#

    buttonContentNew                        ,


-- ** setIconName #method:setIconName#

#if defined(ENABLE_OVERLOADING)
    ButtonContentSetIconNameMethodInfo      ,
#endif
    buttonContentSetIconName                ,


-- ** setLabel #method:setLabel#

#if defined(ENABLE_OVERLOADING)
    ButtonContentSetLabelMethodInfo         ,
#endif
    buttonContentSetLabel                   ,


-- ** setUseUnderline #method:setUseUnderline#

#if defined(ENABLE_OVERLOADING)
    ButtonContentSetUseUnderlineMethodInfo  ,
#endif
    buttonContentSetUseUnderline            ,




 -- * Properties


-- ** iconName #attr:iconName#
-- | The name of the displayed icon.
-- 
-- If empty, the icon is not shown.

#if defined(ENABLE_OVERLOADING)
    ButtonContentIconNamePropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    buttonContentIconName                   ,
#endif
    constructButtonContentIconName          ,
    getButtonContentIconName                ,
    setButtonContentIconName                ,


-- ** label #attr:label#
-- | The displayed label.

#if defined(ENABLE_OVERLOADING)
    ButtonContentLabelPropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    buttonContentLabel                      ,
#endif
    constructButtonContentLabel             ,
    getButtonContentLabel                   ,
    setButtonContentLabel                   ,


-- ** useUnderline #attr:useUnderline#
-- | Whether an underline in the text indicates a mnemonic.
-- 
-- The mnemonic can be used to activate the parent button.
-- 
-- See [property/@buttonContent@/:label].

#if defined(ENABLE_OVERLOADING)
    ButtonContentUseUnderlinePropertyInfo   ,
#endif
#if defined(ENABLE_OVERLOADING)
    buttonContentUseUnderline               ,
#endif
    constructButtonContentUseUnderline      ,
    getButtonContentUseUnderline            ,
    setButtonContentUseUnderline            ,




    ) 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 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.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "adw_button_content_get_type"
    c_adw_button_content_get_type :: IO B.Types.GType

instance B.Types.TypedObject ButtonContent where
    glibType :: IO GType
glibType = IO GType
c_adw_button_content_get_type

instance B.Types.GObject ButtonContent

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

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

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

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

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

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

#endif

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

#endif

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

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

-- | Set the value of the “@icon-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' buttonContent [ #iconName 'Data.GI.Base.Attributes.:=' value ]
-- @
setButtonContentIconName :: (MonadIO m, IsButtonContent o) => o -> T.Text -> m ()
setButtonContentIconName :: forall (m :: * -> *) o.
(MonadIO m, IsButtonContent o) =>
o -> Text -> m ()
setButtonContentIconName o
obj Text
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"icon-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@icon-name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructButtonContentIconName :: (IsButtonContent o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructButtonContentIconName :: forall o (m :: * -> *).
(IsButtonContent o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructButtonContentIconName Text
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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"icon-name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data ButtonContentIconNamePropertyInfo
instance AttrInfo ButtonContentIconNamePropertyInfo where
    type AttrAllowedOps ButtonContentIconNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ButtonContentIconNamePropertyInfo = IsButtonContent
    type AttrSetTypeConstraint ButtonContentIconNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ButtonContentIconNamePropertyInfo = (~) T.Text
    type AttrTransferType ButtonContentIconNamePropertyInfo = T.Text
    type AttrGetType ButtonContentIconNamePropertyInfo = T.Text
    type AttrLabel ButtonContentIconNamePropertyInfo = "icon-name"
    type AttrOrigin ButtonContentIconNamePropertyInfo = ButtonContent
    attrGet = getButtonContentIconName
    attrSet = setButtonContentIconName
    attrTransfer _ v = do
        return v
    attrConstruct = constructButtonContentIconName
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.ButtonContent.iconName"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.5/docs/GI-Adw-Objects-ButtonContent.html#g:attr:iconName"
        })
#endif

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

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

-- | Set the value of the “@label@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' buttonContent [ #label 'Data.GI.Base.Attributes.:=' value ]
-- @
setButtonContentLabel :: (MonadIO m, IsButtonContent o) => o -> T.Text -> m ()
setButtonContentLabel :: forall (m :: * -> *) o.
(MonadIO m, IsButtonContent o) =>
o -> Text -> m ()
setButtonContentLabel o
obj Text
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"label" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

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

#if defined(ENABLE_OVERLOADING)
data ButtonContentLabelPropertyInfo
instance AttrInfo ButtonContentLabelPropertyInfo where
    type AttrAllowedOps ButtonContentLabelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ButtonContentLabelPropertyInfo = IsButtonContent
    type AttrSetTypeConstraint ButtonContentLabelPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ButtonContentLabelPropertyInfo = (~) T.Text
    type AttrTransferType ButtonContentLabelPropertyInfo = T.Text
    type AttrGetType ButtonContentLabelPropertyInfo = T.Text
    type AttrLabel ButtonContentLabelPropertyInfo = "label"
    type AttrOrigin ButtonContentLabelPropertyInfo = ButtonContent
    attrGet = getButtonContentLabel
    attrSet = setButtonContentLabel
    attrTransfer _ v = do
        return v
    attrConstruct = constructButtonContentLabel
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.ButtonContent.label"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.5/docs/GI-Adw-Objects-ButtonContent.html#g:attr:label"
        })
#endif

-- VVV Prop "use-underline"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

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

-- | Set the value of the “@use-underline@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' buttonContent [ #useUnderline 'Data.GI.Base.Attributes.:=' value ]
-- @
setButtonContentUseUnderline :: (MonadIO m, IsButtonContent o) => o -> Bool -> m ()
setButtonContentUseUnderline :: forall (m :: * -> *) o.
(MonadIO m, IsButtonContent o) =>
o -> Bool -> m ()
setButtonContentUseUnderline o
obj Bool
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"use-underline" Bool
val

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

#if defined(ENABLE_OVERLOADING)
data ButtonContentUseUnderlinePropertyInfo
instance AttrInfo ButtonContentUseUnderlinePropertyInfo where
    type AttrAllowedOps ButtonContentUseUnderlinePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ButtonContentUseUnderlinePropertyInfo = IsButtonContent
    type AttrSetTypeConstraint ButtonContentUseUnderlinePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint ButtonContentUseUnderlinePropertyInfo = (~) Bool
    type AttrTransferType ButtonContentUseUnderlinePropertyInfo = Bool
    type AttrGetType ButtonContentUseUnderlinePropertyInfo = Bool
    type AttrLabel ButtonContentUseUnderlinePropertyInfo = "use-underline"
    type AttrOrigin ButtonContentUseUnderlinePropertyInfo = ButtonContent
    attrGet = getButtonContentUseUnderline
    attrSet = setButtonContentUseUnderline
    attrTransfer _ v = do
        return v
    attrConstruct = constructButtonContentUseUnderline
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.ButtonContent.useUnderline"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.5/docs/GI-Adw-Objects-ButtonContent.html#g:attr:useUnderline"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ButtonContent
type instance O.AttributeList ButtonContent = ButtonContentAttributeList
type ButtonContentAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("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), '("iconName", ButtonContentIconNamePropertyInfo), '("label", ButtonContentLabelPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("useUnderline", ButtonContentUseUnderlinePropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
buttonContentIconName :: AttrLabelProxy "iconName"
buttonContentIconName = AttrLabelProxy

buttonContentLabel :: AttrLabelProxy "label"
buttonContentLabel = AttrLabelProxy

buttonContentUseUnderline :: AttrLabelProxy "useUnderline"
buttonContentUseUnderline = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ButtonContent = ButtonContentSignalList
type ButtonContentSignalList = ('[ '("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, DK.Type)])

#endif

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

foreign import ccall "adw_button_content_new" adw_button_content_new :: 
    IO (Ptr ButtonContent)

-- | Creates a new @AdwButtonContent@.
buttonContentNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m ButtonContent
    -- ^ __Returns:__ the new created @AdwButtonContent@
buttonContentNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m ButtonContent
buttonContentNew  = IO ButtonContent -> m ButtonContent
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ButtonContent -> m ButtonContent)
-> IO ButtonContent -> m ButtonContent
forall a b. (a -> b) -> a -> b
$ do
    Ptr ButtonContent
result <- IO (Ptr ButtonContent)
adw_button_content_new
    Text -> Ptr ButtonContent -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"buttonContentNew" Ptr ButtonContent
result
    ButtonContent
result' <- ((ManagedPtr ButtonContent -> ButtonContent)
-> Ptr ButtonContent -> IO ButtonContent
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ButtonContent -> ButtonContent
ButtonContent) Ptr ButtonContent
result
    ButtonContent -> IO ButtonContent
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ButtonContent
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "adw_button_content_get_icon_name" adw_button_content_get_icon_name :: 
    Ptr ButtonContent ->                    -- self : TInterface (Name {namespace = "Adw", name = "ButtonContent"})
    IO CString

-- | Gets the name of the displayed icon.
buttonContentGetIconName ::
    (B.CallStack.HasCallStack, MonadIO m, IsButtonContent a) =>
    a
    -- ^ /@self@/: a button content
    -> m T.Text
    -- ^ __Returns:__ the icon name
buttonContentGetIconName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButtonContent a) =>
a -> m Text
buttonContentGetIconName a
self = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr ButtonContent
self' <- a -> IO (Ptr ButtonContent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr ButtonContent -> IO CString
adw_button_content_get_icon_name Ptr ButtonContent
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"buttonContentGetIconName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ButtonContentGetIconNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsButtonContent a) => O.OverloadedMethod ButtonContentGetIconNameMethodInfo a signature where
    overloadedMethod = buttonContentGetIconName

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


#endif

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

foreign import ccall "adw_button_content_get_label" adw_button_content_get_label :: 
    Ptr ButtonContent ->                    -- self : TInterface (Name {namespace = "Adw", name = "ButtonContent"})
    IO CString

-- | Gets the displayed label.
buttonContentGetLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsButtonContent a) =>
    a
    -- ^ /@self@/: a button content
    -> m T.Text
    -- ^ __Returns:__ the label
buttonContentGetLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButtonContent a) =>
a -> m Text
buttonContentGetLabel a
self = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr ButtonContent
self' <- a -> IO (Ptr ButtonContent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr ButtonContent -> IO CString
adw_button_content_get_label Ptr ButtonContent
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"buttonContentGetLabel" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ButtonContentGetLabelMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsButtonContent a) => O.OverloadedMethod ButtonContentGetLabelMethodInfo a signature where
    overloadedMethod = buttonContentGetLabel

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


#endif

-- method ButtonContent::get_use_underline
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Adw" , name = "ButtonContent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a button content" , 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 "adw_button_content_get_use_underline" adw_button_content_get_use_underline :: 
    Ptr ButtonContent ->                    -- self : TInterface (Name {namespace = "Adw", name = "ButtonContent"})
    IO CInt

-- | Gets whether an underline in the text indicates a mnemonic.
buttonContentGetUseUnderline ::
    (B.CallStack.HasCallStack, MonadIO m, IsButtonContent a) =>
    a
    -- ^ /@self@/: a button content
    -> m Bool
    -- ^ __Returns:__ whether an underline in the text indicates a mnemonic
buttonContentGetUseUnderline :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButtonContent a) =>
a -> m Bool
buttonContentGetUseUnderline a
self = 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 ButtonContent
self' <- a -> IO (Ptr ButtonContent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr ButtonContent -> IO CInt
adw_button_content_get_use_underline Ptr ButtonContent
self'
    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
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data ButtonContentGetUseUnderlineMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsButtonContent a) => O.OverloadedMethod ButtonContentGetUseUnderlineMethodInfo a signature where
    overloadedMethod = buttonContentGetUseUnderline

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


#endif

-- method ButtonContent::set_icon_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Adw" , name = "ButtonContent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a button content" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new icon name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "adw_button_content_set_icon_name" adw_button_content_set_icon_name :: 
    Ptr ButtonContent ->                    -- self : TInterface (Name {namespace = "Adw", name = "ButtonContent"})
    CString ->                              -- icon_name : TBasicType TUTF8
    IO ()

-- | Sets the name of the displayed icon.
-- 
-- If empty, the icon is not shown.
buttonContentSetIconName ::
    (B.CallStack.HasCallStack, MonadIO m, IsButtonContent a) =>
    a
    -- ^ /@self@/: a button content
    -> T.Text
    -- ^ /@iconName@/: the new icon name
    -> m ()
buttonContentSetIconName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButtonContent a) =>
a -> Text -> m ()
buttonContentSetIconName a
self Text
iconName = 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 ButtonContent
self' <- a -> IO (Ptr ButtonContent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
iconName' <- Text -> IO CString
textToCString Text
iconName
    Ptr ButtonContent -> CString -> IO ()
adw_button_content_set_icon_name Ptr ButtonContent
self' CString
iconName'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
iconName'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ButtonContentSetIconNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsButtonContent a) => O.OverloadedMethod ButtonContentSetIconNameMethodInfo a signature where
    overloadedMethod = buttonContentSetIconName

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


#endif

-- method ButtonContent::set_label
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Adw" , name = "ButtonContent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a button content" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "label"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new label" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "adw_button_content_set_label" adw_button_content_set_label :: 
    Ptr ButtonContent ->                    -- self : TInterface (Name {namespace = "Adw", name = "ButtonContent"})
    CString ->                              -- label : TBasicType TUTF8
    IO ()

-- | Sets the displayed label.
buttonContentSetLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsButtonContent a) =>
    a
    -- ^ /@self@/: a button content
    -> T.Text
    -- ^ /@label@/: the new label
    -> m ()
buttonContentSetLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButtonContent a) =>
a -> Text -> m ()
buttonContentSetLabel a
self Text
label = 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 ButtonContent
self' <- a -> IO (Ptr ButtonContent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
label' <- Text -> IO CString
textToCString Text
label
    Ptr ButtonContent -> CString -> IO ()
adw_button_content_set_label Ptr ButtonContent
self' CString
label'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
label'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ButtonContentSetLabelMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsButtonContent a) => O.OverloadedMethod ButtonContentSetLabelMethodInfo a signature where
    overloadedMethod = buttonContentSetLabel

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


#endif

-- method ButtonContent::set_use_underline
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Adw" , name = "ButtonContent" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a button content" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "use_underline"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "whether an underline in the text indicates a mnemonic"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "adw_button_content_set_use_underline" adw_button_content_set_use_underline :: 
    Ptr ButtonContent ->                    -- self : TInterface (Name {namespace = "Adw", name = "ButtonContent"})
    CInt ->                                 -- use_underline : TBasicType TBoolean
    IO ()

-- | Sets whether an underline in the text indicates a mnemonic.
-- 
-- The mnemonic can be used to activate the parent button.
-- 
-- See [property/@buttonContent@/:label].
buttonContentSetUseUnderline ::
    (B.CallStack.HasCallStack, MonadIO m, IsButtonContent a) =>
    a
    -- ^ /@self@/: a button content
    -> Bool
    -- ^ /@useUnderline@/: whether an underline in the text indicates a mnemonic
    -> m ()
buttonContentSetUseUnderline :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsButtonContent a) =>
a -> Bool -> m ()
buttonContentSetUseUnderline a
self Bool
useUnderline = 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 ButtonContent
self' <- a -> IO (Ptr ButtonContent)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let useUnderline' :: CInt
useUnderline' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
useUnderline
    Ptr ButtonContent -> CInt -> IO ()
adw_button_content_set_use_underline Ptr ButtonContent
self' CInt
useUnderline'
    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 ButtonContentSetUseUnderlineMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsButtonContent a) => O.OverloadedMethod ButtonContentSetUseUnderlineMethodInfo a signature where
    overloadedMethod = buttonContentSetUseUnderline

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


#endif