{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A group of preference rows.
-- 
-- \<picture>
--   \<source srcset=\"preferences-group-dark.png\" media=\"(prefers-color-scheme: dark)\">
--   \<img src=\"preferences-group.png\" alt=\"preferences-group\">
-- \<\/picture>
-- 
-- An @AdwPreferencesGroup@ represents a group or tightly related preferences,
-- which in turn are represented by [class/@preferencesRow@/].
-- 
-- To summarize the role of the preferences it gathers, a group can have both a
-- title and a description. The title will be used by [class/@preferencesWindow@/]
-- to let the user look for a preference.
-- 
-- == AdwPreferencesGroup as GtkBuildable
-- 
-- The @AdwPreferencesGroup@ implementation of the t'GI.Gtk.Interfaces.Buildable.Buildable' interface
-- supports adding [class/@preferencesRow@/]s to the list by omitting \"type\". If \"type\"
-- is omitted and the widget isn\'t a [class/@preferencesRow@/] the child is added to
-- a box below the list.
-- 
-- When the \"type\" attribute of a child is @header-suffix@, the child
-- is set as the suffix on the end of the title and description.
-- 
-- == CSS nodes
-- 
-- @AdwPreferencesGroup@ has a single CSS node with name @preferencesgroup@.
-- 
-- == Accessibility
-- 
-- @AdwPreferencesGroup@ uses the @GTK_ACCESSIBLE_ROLE_GROUP@ role.
-- 
-- /Since: 1.0/

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

module GI.Adw.Objects.PreferencesGroup
    ( 

-- * Exported types
    PreferencesGroup(..)                    ,
    IsPreferencesGroup                      ,
    toPreferencesGroup                      ,


 -- * 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"), [add]("GI.Adw.Objects.PreferencesGroup#g:method:add"), [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"), [remove]("GI.Adw.Objects.PreferencesGroup#g:method:remove"), [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"), [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"), [getDescription]("GI.Adw.Objects.PreferencesGroup#g:method:getDescription"), [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"), [getHeaderSuffix]("GI.Adw.Objects.PreferencesGroup#g:method:getHeaderSuffix"), [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"), [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"), [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"), [getTitle]("GI.Adw.Objects.PreferencesGroup#g:method:getTitle"), [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"), [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"), [setDescription]("GI.Adw.Objects.PreferencesGroup#g:method:setDescription"), [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"), [setHeaderSuffix]("GI.Adw.Objects.PreferencesGroup#g:method:setHeaderSuffix"), [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"), [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"), [setTitle]("GI.Adw.Objects.PreferencesGroup#g:method:setTitle"), [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)
    ResolvePreferencesGroupMethod           ,
#endif

-- ** add #method:add#

#if defined(ENABLE_OVERLOADING)
    PreferencesGroupAddMethodInfo           ,
#endif
    preferencesGroupAdd                     ,


-- ** getDescription #method:getDescription#

#if defined(ENABLE_OVERLOADING)
    PreferencesGroupGetDescriptionMethodInfo,
#endif
    preferencesGroupGetDescription          ,


-- ** getHeaderSuffix #method:getHeaderSuffix#

#if defined(ENABLE_OVERLOADING)
    PreferencesGroupGetHeaderSuffixMethodInfo,
#endif
    preferencesGroupGetHeaderSuffix         ,


-- ** getTitle #method:getTitle#

#if defined(ENABLE_OVERLOADING)
    PreferencesGroupGetTitleMethodInfo      ,
#endif
    preferencesGroupGetTitle                ,


-- ** new #method:new#

    preferencesGroupNew                     ,


-- ** remove #method:remove#

#if defined(ENABLE_OVERLOADING)
    PreferencesGroupRemoveMethodInfo        ,
#endif
    preferencesGroupRemove                  ,


-- ** setDescription #method:setDescription#

#if defined(ENABLE_OVERLOADING)
    PreferencesGroupSetDescriptionMethodInfo,
#endif
    preferencesGroupSetDescription          ,


-- ** setHeaderSuffix #method:setHeaderSuffix#

#if defined(ENABLE_OVERLOADING)
    PreferencesGroupSetHeaderSuffixMethodInfo,
#endif
    preferencesGroupSetHeaderSuffix         ,


-- ** setTitle #method:setTitle#

#if defined(ENABLE_OVERLOADING)
    PreferencesGroupSetTitleMethodInfo      ,
#endif
    preferencesGroupSetTitle                ,




 -- * Properties


-- ** description #attr:description#
-- | The description for this group of preferences.
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    PreferencesGroupDescriptionPropertyInfo ,
#endif
    clearPreferencesGroupDescription        ,
    constructPreferencesGroupDescription    ,
    getPreferencesGroupDescription          ,
#if defined(ENABLE_OVERLOADING)
    preferencesGroupDescription             ,
#endif
    setPreferencesGroupDescription          ,


-- ** headerSuffix #attr:headerSuffix#
-- | The header suffix widget.
-- 
-- Displayed above the list, next to the title and description.
-- 
-- Suffixes are commonly used to show a button or a spinner for the whole
-- group.
-- 
-- /Since: 1.1/

#if defined(ENABLE_OVERLOADING)
    PreferencesGroupHeaderSuffixPropertyInfo,
#endif
    clearPreferencesGroupHeaderSuffix       ,
    constructPreferencesGroupHeaderSuffix   ,
    getPreferencesGroupHeaderSuffix         ,
#if defined(ENABLE_OVERLOADING)
    preferencesGroupHeaderSuffix            ,
#endif
    setPreferencesGroupHeaderSuffix         ,


-- ** title #attr:title#
-- | The title for this group of preferences.
-- 
-- /Since: 1.0/

#if defined(ENABLE_OVERLOADING)
    PreferencesGroupTitlePropertyInfo       ,
#endif
    constructPreferencesGroupTitle          ,
    getPreferencesGroupTitle                ,
#if defined(ENABLE_OVERLOADING)
    preferencesGroupTitle                   ,
#endif
    setPreferencesGroupTitle                ,




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

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

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

foreign import ccall "adw_preferences_group_get_type"
    c_adw_preferences_group_get_type :: IO B.Types.GType

instance B.Types.TypedObject PreferencesGroup where
    glibType :: IO GType
glibType = IO GType
c_adw_preferences_group_get_type

instance B.Types.GObject PreferencesGroup

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

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

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

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

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

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

#endif

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

#endif

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

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

-- | Set the value of the “@description@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' preferencesGroup [ #description 'Data.GI.Base.Attributes.:=' value ]
-- @
setPreferencesGroupDescription :: (MonadIO m, IsPreferencesGroup o) => o -> T.Text -> m ()
setPreferencesGroupDescription :: forall (m :: * -> *) o.
(MonadIO m, IsPreferencesGroup o) =>
o -> Text -> m ()
setPreferencesGroupDescription 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
"description" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

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

-- | Set the value of the “@description@” 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' #description
-- @
clearPreferencesGroupDescription :: (MonadIO m, IsPreferencesGroup o) => o -> m ()
clearPreferencesGroupDescription :: forall (m :: * -> *) o.
(MonadIO m, IsPreferencesGroup o) =>
o -> m ()
clearPreferencesGroupDescription 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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"description" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data PreferencesGroupDescriptionPropertyInfo
instance AttrInfo PreferencesGroupDescriptionPropertyInfo where
    type AttrAllowedOps PreferencesGroupDescriptionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PreferencesGroupDescriptionPropertyInfo = IsPreferencesGroup
    type AttrSetTypeConstraint PreferencesGroupDescriptionPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint PreferencesGroupDescriptionPropertyInfo = (~) T.Text
    type AttrTransferType PreferencesGroupDescriptionPropertyInfo = T.Text
    type AttrGetType PreferencesGroupDescriptionPropertyInfo = (Maybe T.Text)
    type AttrLabel PreferencesGroupDescriptionPropertyInfo = "description"
    type AttrOrigin PreferencesGroupDescriptionPropertyInfo = PreferencesGroup
    attrGet = getPreferencesGroupDescription
    attrSet = setPreferencesGroupDescription
    attrTransfer _ v = do
        return v
    attrConstruct = constructPreferencesGroupDescription
    attrClear = clearPreferencesGroupDescription
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.PreferencesGroup.description"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.3/docs/GI-Adw-Objects-PreferencesGroup.html#g:attr:description"
        })
#endif

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

-- | Get the value of the “@header-suffix@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' preferencesGroup #headerSuffix
-- @
getPreferencesGroupHeaderSuffix :: (MonadIO m, IsPreferencesGroup o) => o -> m (Maybe Gtk.Widget.Widget)
getPreferencesGroupHeaderSuffix :: forall (m :: * -> *) o.
(MonadIO m, IsPreferencesGroup o) =>
o -> m (Maybe Widget)
getPreferencesGroupHeaderSuffix 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
"header-suffix" ManagedPtr Widget -> Widget
Gtk.Widget.Widget

-- | Set the value of the “@header-suffix@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' preferencesGroup [ #headerSuffix 'Data.GI.Base.Attributes.:=' value ]
-- @
setPreferencesGroupHeaderSuffix :: (MonadIO m, IsPreferencesGroup o, Gtk.Widget.IsWidget a) => o -> a -> m ()
setPreferencesGroupHeaderSuffix :: forall (m :: * -> *) o a.
(MonadIO m, IsPreferencesGroup o, IsWidget a) =>
o -> a -> m ()
setPreferencesGroupHeaderSuffix 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
"header-suffix" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

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

-- | Set the value of the “@header-suffix@” 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' #headerSuffix
-- @
clearPreferencesGroupHeaderSuffix :: (MonadIO m, IsPreferencesGroup o) => o -> m ()
clearPreferencesGroupHeaderSuffix :: forall (m :: * -> *) o.
(MonadIO m, IsPreferencesGroup o) =>
o -> m ()
clearPreferencesGroupHeaderSuffix 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
"header-suffix" (Maybe Widget
forall a. Maybe a
Nothing :: Maybe Gtk.Widget.Widget)

#if defined(ENABLE_OVERLOADING)
data PreferencesGroupHeaderSuffixPropertyInfo
instance AttrInfo PreferencesGroupHeaderSuffixPropertyInfo where
    type AttrAllowedOps PreferencesGroupHeaderSuffixPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PreferencesGroupHeaderSuffixPropertyInfo = IsPreferencesGroup
    type AttrSetTypeConstraint PreferencesGroupHeaderSuffixPropertyInfo = Gtk.Widget.IsWidget
    type AttrTransferTypeConstraint PreferencesGroupHeaderSuffixPropertyInfo = Gtk.Widget.IsWidget
    type AttrTransferType PreferencesGroupHeaderSuffixPropertyInfo = Gtk.Widget.Widget
    type AttrGetType PreferencesGroupHeaderSuffixPropertyInfo = (Maybe Gtk.Widget.Widget)
    type AttrLabel PreferencesGroupHeaderSuffixPropertyInfo = "header-suffix"
    type AttrOrigin PreferencesGroupHeaderSuffixPropertyInfo = PreferencesGroup
    attrGet = getPreferencesGroupHeaderSuffix
    attrSet = setPreferencesGroupHeaderSuffix
    attrTransfer _ v = do
        unsafeCastTo Gtk.Widget.Widget v
    attrConstruct = constructPreferencesGroupHeaderSuffix
    attrClear = clearPreferencesGroupHeaderSuffix
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Adw.Objects.PreferencesGroup.headerSuffix"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-adwaita-1.0.3/docs/GI-Adw-Objects-PreferencesGroup.html#g:attr:headerSuffix"
        })
#endif

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

-- | Get the value of the “@title@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' preferencesGroup #title
-- @
getPreferencesGroupTitle :: (MonadIO m, IsPreferencesGroup o) => o -> m T.Text
getPreferencesGroupTitle :: forall (m :: * -> *) o.
(MonadIO m, IsPreferencesGroup o) =>
o -> m Text
getPreferencesGroupTitle 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
"getPreferencesGroupTitle" (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
"title"

-- | Set the value of the “@title@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' preferencesGroup [ #title 'Data.GI.Base.Attributes.:=' value ]
-- @
setPreferencesGroupTitle :: (MonadIO m, IsPreferencesGroup o) => o -> T.Text -> m ()
setPreferencesGroupTitle :: forall (m :: * -> *) o.
(MonadIO m, IsPreferencesGroup o) =>
o -> Text -> m ()
setPreferencesGroupTitle 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
"title" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

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

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PreferencesGroup
type instance O.AttributeList PreferencesGroup = PreferencesGroupAttributeList
type PreferencesGroupAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("description", PreferencesGroupDescriptionPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusable", Gtk.Widget.WidgetFocusablePropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("headerSuffix", PreferencesGroupHeaderSuffixPropertyInfo), '("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), '("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), '("title", PreferencesGroupTitlePropertyInfo), '("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)
preferencesGroupDescription :: AttrLabelProxy "description"
preferencesGroupDescription = AttrLabelProxy

preferencesGroupHeaderSuffix :: AttrLabelProxy "headerSuffix"
preferencesGroupHeaderSuffix = AttrLabelProxy

preferencesGroupTitle :: AttrLabelProxy "title"
preferencesGroupTitle = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList PreferencesGroup = PreferencesGroupSignalList
type PreferencesGroupSignalList = ('[ '("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 PreferencesGroup::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Adw" , name = "PreferencesGroup" })
-- throws : False
-- Skip return : False

foreign import ccall "adw_preferences_group_new" adw_preferences_group_new :: 
    IO (Ptr PreferencesGroup)

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

#if defined(ENABLE_OVERLOADING)
#endif

-- method PreferencesGroup::add
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Adw" , name = "PreferencesGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a preferences group"
--                 , 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 = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the widget to add" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Adds a child to /@self@/.
-- 
-- /Since: 1.0/
preferencesGroupAdd ::
    (B.CallStack.HasCallStack, MonadIO m, IsPreferencesGroup a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@self@/: a preferences group
    -> b
    -- ^ /@child@/: the widget to add
    -> m ()
preferencesGroupAdd :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPreferencesGroup a, IsWidget b) =>
a -> b -> m ()
preferencesGroupAdd a
self 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 PreferencesGroup
self' <- a -> IO (Ptr PreferencesGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
child' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    Ptr PreferencesGroup -> Ptr Widget -> IO ()
adw_preferences_group_add Ptr PreferencesGroup
self' Ptr Widget
child'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PreferencesGroupAddMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsPreferencesGroup a, Gtk.Widget.IsWidget b) => O.OverloadedMethod PreferencesGroupAddMethodInfo a signature where
    overloadedMethod = preferencesGroupAdd

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


#endif

-- method PreferencesGroup::get_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Adw" , name = "PreferencesGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a preferences group"
--                 , 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_preferences_group_get_description" adw_preferences_group_get_description :: 
    Ptr PreferencesGroup ->                 -- self : TInterface (Name {namespace = "Adw", name = "PreferencesGroup"})
    IO CString

-- | Gets the description of /@self@/.
-- 
-- /Since: 1.0/
preferencesGroupGetDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsPreferencesGroup a) =>
    a
    -- ^ /@self@/: a preferences group
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the description of /@self@/
preferencesGroupGetDescription :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPreferencesGroup a) =>
a -> m (Maybe Text)
preferencesGroupGetDescription a
self = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr PreferencesGroup
self' <- a -> IO (Ptr PreferencesGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr PreferencesGroup -> IO CString
adw_preferences_group_get_description Ptr PreferencesGroup
self'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

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

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


#endif

-- method PreferencesGroup::get_header_suffix
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Adw" , name = "PreferencesGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `AdwPreferencesGroup`"
--                 , 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_preferences_group_get_header_suffix" adw_preferences_group_get_header_suffix :: 
    Ptr PreferencesGroup ->                 -- self : TInterface (Name {namespace = "Adw", name = "PreferencesGroup"})
    IO (Ptr Gtk.Widget.Widget)

-- | Gets the suffix for /@self@/\'s header.
-- 
-- /Since: 1.1/
preferencesGroupGetHeaderSuffix ::
    (B.CallStack.HasCallStack, MonadIO m, IsPreferencesGroup a) =>
    a
    -- ^ /@self@/: a @AdwPreferencesGroup@
    -> m (Maybe Gtk.Widget.Widget)
    -- ^ __Returns:__ the suffix for /@self@/\'s header.
preferencesGroupGetHeaderSuffix :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPreferencesGroup a) =>
a -> m (Maybe Widget)
preferencesGroupGetHeaderSuffix 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 PreferencesGroup
self' <- a -> IO (Ptr PreferencesGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
result <- Ptr PreferencesGroup -> IO (Ptr Widget)
adw_preferences_group_get_header_suffix Ptr PreferencesGroup
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 PreferencesGroupGetHeaderSuffixMethodInfo
instance (signature ~ (m (Maybe Gtk.Widget.Widget)), MonadIO m, IsPreferencesGroup a) => O.OverloadedMethod PreferencesGroupGetHeaderSuffixMethodInfo a signature where
    overloadedMethod = preferencesGroupGetHeaderSuffix

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


#endif

-- method PreferencesGroup::get_title
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Adw" , name = "PreferencesGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a preferences group"
--                 , 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_preferences_group_get_title" adw_preferences_group_get_title :: 
    Ptr PreferencesGroup ->                 -- self : TInterface (Name {namespace = "Adw", name = "PreferencesGroup"})
    IO CString

-- | Gets the title of /@self@/.
-- 
-- /Since: 1.0/
preferencesGroupGetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsPreferencesGroup a) =>
    a
    -- ^ /@self@/: a preferences group
    -> m T.Text
    -- ^ __Returns:__ the title of /@self@/
preferencesGroupGetTitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPreferencesGroup a) =>
a -> m Text
preferencesGroupGetTitle 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 PreferencesGroup
self' <- a -> IO (Ptr PreferencesGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr PreferencesGroup -> IO CString
adw_preferences_group_get_title Ptr PreferencesGroup
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"preferencesGroupGetTitle" 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 PreferencesGroupGetTitleMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPreferencesGroup a) => O.OverloadedMethod PreferencesGroupGetTitleMethodInfo a signature where
    overloadedMethod = preferencesGroupGetTitle

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


#endif

-- method PreferencesGroup::remove
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Adw" , name = "PreferencesGroup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a preferences group"
--                 , 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 = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the child to remove"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Removes a child from /@self@/.
-- 
-- /Since: 1.0/
preferencesGroupRemove ::
    (B.CallStack.HasCallStack, MonadIO m, IsPreferencesGroup a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@self@/: a preferences group
    -> b
    -- ^ /@child@/: the child to remove
    -> m ()
preferencesGroupRemove :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPreferencesGroup a, IsWidget b) =>
a -> b -> m ()
preferencesGroupRemove a
self 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 PreferencesGroup
self' <- a -> IO (Ptr PreferencesGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
child' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
child
    Ptr PreferencesGroup -> Ptr Widget -> IO ()
adw_preferences_group_remove Ptr PreferencesGroup
self' Ptr Widget
child'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
child
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PreferencesGroupRemoveMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsPreferencesGroup a, Gtk.Widget.IsWidget b) => O.OverloadedMethod PreferencesGroupRemoveMethodInfo a signature where
    overloadedMethod = preferencesGroupRemove

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


#endif

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

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

-- | Sets the description for /@self@/.
-- 
-- /Since: 1.0/
preferencesGroupSetDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsPreferencesGroup a) =>
    a
    -- ^ /@self@/: a preferences group
    -> Maybe (T.Text)
    -- ^ /@description@/: the description
    -> m ()
preferencesGroupSetDescription :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPreferencesGroup a) =>
a -> Maybe Text -> m ()
preferencesGroupSetDescription a
self Maybe Text
description = 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 PreferencesGroup
self' <- a -> IO (Ptr PreferencesGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
maybeDescription <- case Maybe Text
description of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jDescription -> do
            CString
jDescription' <- Text -> IO CString
textToCString Text
jDescription
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jDescription'
    Ptr PreferencesGroup -> CString -> IO ()
adw_preferences_group_set_description Ptr PreferencesGroup
self' CString
maybeDescription
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeDescription
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

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


#endif

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

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

-- | Sets the suffix for /@self@/\'s header.
-- 
-- Displayed above the list, next to the title and description.
-- 
-- Suffixes are commonly used to show a button or a spinner for the whole group.
-- 
-- /Since: 1.1/
preferencesGroupSetHeaderSuffix ::
    (B.CallStack.HasCallStack, MonadIO m, IsPreferencesGroup a, Gtk.Widget.IsWidget b) =>
    a
    -- ^ /@self@/: a @AdwPreferencesGroup@
    -> Maybe (b)
    -- ^ /@suffix@/: the suffix to set
    -> m ()
preferencesGroupSetHeaderSuffix :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPreferencesGroup a, IsWidget b) =>
a -> Maybe b -> m ()
preferencesGroupSetHeaderSuffix a
self Maybe b
suffix = 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 PreferencesGroup
self' <- a -> IO (Ptr PreferencesGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
maybeSuffix <- case Maybe b
suffix 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
jSuffix -> do
            Ptr Widget
jSuffix' <- b -> IO (Ptr Widget)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jSuffix
            Ptr Widget -> IO (Ptr Widget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Widget
jSuffix'
    Ptr PreferencesGroup -> Ptr Widget -> IO ()
adw_preferences_group_set_header_suffix Ptr PreferencesGroup
self' Ptr Widget
maybeSuffix
    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
suffix 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 PreferencesGroupSetHeaderSuffixMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsPreferencesGroup a, Gtk.Widget.IsWidget b) => O.OverloadedMethod PreferencesGroupSetHeaderSuffixMethodInfo a signature where
    overloadedMethod = preferencesGroupSetHeaderSuffix

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


#endif

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

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

-- | Sets the title for /@self@/.
-- 
-- /Since: 1.0/
preferencesGroupSetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsPreferencesGroup a) =>
    a
    -- ^ /@self@/: a preferences group
    -> T.Text
    -- ^ /@title@/: the title
    -> m ()
preferencesGroupSetTitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPreferencesGroup a) =>
a -> Text -> m ()
preferencesGroupSetTitle a
self Text
title = 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 PreferencesGroup
self' <- a -> IO (Ptr PreferencesGroup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
title' <- Text -> IO CString
textToCString Text
title
    Ptr PreferencesGroup -> CString -> IO ()
adw_preferences_group_set_title Ptr PreferencesGroup
self' CString
title'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
title'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

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


#endif