{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A GtkShortcutsGroup represents a group of related keyboard shortcuts
-- or gestures. The group has a title. It may optionally be associated with
-- a view of the application, which can be used to show only relevant shortcuts
-- depending on the application context.
-- 
-- This widget is only meant to be used with t'GI.Gtk.Objects.ShortcutsWindow.ShortcutsWindow'.

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

module GI.Gtk.Objects.ShortcutsGroup
    ( 

-- * Exported types
    ShortcutsGroup(..)                      ,
    IsShortcutsGroup                        ,
    toShortcutsGroup                        ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [actionSetEnabled]("GI.Gtk.Objects.Widget#g:method:actionSetEnabled"), [activate]("GI.Gtk.Objects.Widget#g:method:activate"), [activateAction]("GI.Gtk.Objects.Widget#g:method:activateAction"), [activateDefault]("GI.Gtk.Objects.Widget#g:method:activateDefault"), [addController]("GI.Gtk.Objects.Widget#g:method:addController"), [addCssClass]("GI.Gtk.Objects.Widget#g:method:addCssClass"), [addMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:addMnemonicLabel"), [addTickCallback]("GI.Gtk.Objects.Widget#g:method:addTickCallback"), [allocate]("GI.Gtk.Objects.Widget#g:method:allocate"), [append]("GI.Gtk.Objects.Box#g:method:append"), [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"), [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"), [insertChildAfter]("GI.Gtk.Objects.Box#g:method:insertChildAfter"), [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"), [prepend]("GI.Gtk.Objects.Box#g:method:prepend"), [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.Gtk.Objects.Box#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"), [reorderChildAfter]("GI.Gtk.Objects.Box#g:method:reorderChildAfter"), [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"), [getBaselinePosition]("GI.Gtk.Objects.Box#g:method:getBaselinePosition"), [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"), [getDirection]("GI.Gtk.Objects.Widget#g:method:getDirection"), [getDisplay]("GI.Gtk.Objects.Widget#g:method:getDisplay"), [getFirstChild]("GI.Gtk.Objects.Widget#g:method:getFirstChild"), [getFocusChild]("GI.Gtk.Objects.Widget#g:method:getFocusChild"), [getFocusOnClick]("GI.Gtk.Objects.Widget#g:method:getFocusOnClick"), [getFocusable]("GI.Gtk.Objects.Widget#g:method:getFocusable"), [getFontMap]("GI.Gtk.Objects.Widget#g:method:getFontMap"), [getFontOptions]("GI.Gtk.Objects.Widget#g:method:getFontOptions"), [getFrameClock]("GI.Gtk.Objects.Widget#g:method:getFrameClock"), [getHalign]("GI.Gtk.Objects.Widget#g:method:getHalign"), [getHasTooltip]("GI.Gtk.Objects.Widget#g:method:getHasTooltip"), [getHeight]("GI.Gtk.Objects.Widget#g:method:getHeight"), [getHexpand]("GI.Gtk.Objects.Widget#g:method:getHexpand"), [getHexpandSet]("GI.Gtk.Objects.Widget#g:method:getHexpandSet"), [getHomogeneous]("GI.Gtk.Objects.Box#g:method:getHomogeneous"), [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"), [getOrientation]("GI.Gtk.Interfaces.Orientable#g:method:getOrientation"), [getOverflow]("GI.Gtk.Objects.Widget#g:method:getOverflow"), [getPangoContext]("GI.Gtk.Objects.Widget#g:method:getPangoContext"), [getParent]("GI.Gtk.Objects.Widget#g:method:getParent"), [getPreferredSize]("GI.Gtk.Objects.Widget#g:method:getPreferredSize"), [getPrevSibling]("GI.Gtk.Objects.Widget#g:method:getPrevSibling"), [getPrimaryClipboard]("GI.Gtk.Objects.Widget#g:method:getPrimaryClipboard"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRealized]("GI.Gtk.Objects.Widget#g:method:getRealized"), [getReceivesDefault]("GI.Gtk.Objects.Widget#g:method:getReceivesDefault"), [getRequestMode]("GI.Gtk.Objects.Widget#g:method:getRequestMode"), [getRoot]("GI.Gtk.Objects.Widget#g:method:getRoot"), [getScaleFactor]("GI.Gtk.Objects.Widget#g:method:getScaleFactor"), [getSensitive]("GI.Gtk.Objects.Widget#g:method:getSensitive"), [getSettings]("GI.Gtk.Objects.Widget#g:method:getSettings"), [getSize]("GI.Gtk.Objects.Widget#g:method:getSize"), [getSizeRequest]("GI.Gtk.Objects.Widget#g:method:getSizeRequest"), [getSpacing]("GI.Gtk.Objects.Box#g:method:getSpacing"), [getStateFlags]("GI.Gtk.Objects.Widget#g:method:getStateFlags"), [getStyleContext]("GI.Gtk.Objects.Widget#g:method:getStyleContext"), [getTemplateChild]("GI.Gtk.Objects.Widget#g:method:getTemplateChild"), [getTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:getTooltipMarkup"), [getTooltipText]("GI.Gtk.Objects.Widget#g:method:getTooltipText"), [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
-- [setBaselinePosition]("GI.Gtk.Objects.Box#g:method:setBaselinePosition"), [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [setChildVisible]("GI.Gtk.Objects.Widget#g:method:setChildVisible"), [setCssClasses]("GI.Gtk.Objects.Widget#g:method:setCssClasses"), [setCursor]("GI.Gtk.Objects.Widget#g:method:setCursor"), [setCursorFromName]("GI.Gtk.Objects.Widget#g:method:setCursorFromName"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDirection]("GI.Gtk.Objects.Widget#g:method:setDirection"), [setFocusChild]("GI.Gtk.Objects.Widget#g:method:setFocusChild"), [setFocusOnClick]("GI.Gtk.Objects.Widget#g:method:setFocusOnClick"), [setFocusable]("GI.Gtk.Objects.Widget#g:method:setFocusable"), [setFontMap]("GI.Gtk.Objects.Widget#g:method:setFontMap"), [setFontOptions]("GI.Gtk.Objects.Widget#g:method:setFontOptions"), [setHalign]("GI.Gtk.Objects.Widget#g:method:setHalign"), [setHasTooltip]("GI.Gtk.Objects.Widget#g:method:setHasTooltip"), [setHexpand]("GI.Gtk.Objects.Widget#g:method:setHexpand"), [setHexpandSet]("GI.Gtk.Objects.Widget#g:method:setHexpandSet"), [setHomogeneous]("GI.Gtk.Objects.Box#g:method:setHomogeneous"), [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"), [setOrientation]("GI.Gtk.Interfaces.Orientable#g:method:setOrientation"), [setOverflow]("GI.Gtk.Objects.Widget#g:method:setOverflow"), [setParent]("GI.Gtk.Objects.Widget#g:method:setParent"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setReceivesDefault]("GI.Gtk.Objects.Widget#g:method:setReceivesDefault"), [setSensitive]("GI.Gtk.Objects.Widget#g:method:setSensitive"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setSpacing]("GI.Gtk.Objects.Box#g:method:setSpacing"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [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)
    ResolveShortcutsGroupMethod             ,
#endif



 -- * Properties


-- ** accelSizeGroup #attr:accelSizeGroup#
-- | The size group for the accelerator portion of shortcuts in this group.
-- 
-- This is used internally by GTK, and must not be modified by applications.

#if defined(ENABLE_OVERLOADING)
    ShortcutsGroupAccelSizeGroupPropertyInfo,
#endif
    clearShortcutsGroupAccelSizeGroup       ,
    constructShortcutsGroupAccelSizeGroup   ,
    setShortcutsGroupAccelSizeGroup         ,
#if defined(ENABLE_OVERLOADING)
    shortcutsGroupAccelSizeGroup            ,
#endif


-- ** height #attr:height#
-- | A rough measure for the number of lines in this group.
-- 
-- This is used internally by GTK, and is not useful for applications.

#if defined(ENABLE_OVERLOADING)
    ShortcutsGroupHeightPropertyInfo        ,
#endif
    getShortcutsGroupHeight                 ,
#if defined(ENABLE_OVERLOADING)
    shortcutsGroupHeight                    ,
#endif


-- ** title #attr:title#
-- | The title for this group of shortcuts.

#if defined(ENABLE_OVERLOADING)
    ShortcutsGroupTitlePropertyInfo         ,
#endif
    clearShortcutsGroupTitle                ,
    constructShortcutsGroupTitle            ,
    getShortcutsGroupTitle                  ,
    setShortcutsGroupTitle                  ,
#if defined(ENABLE_OVERLOADING)
    shortcutsGroupTitle                     ,
#endif


-- ** titleSizeGroup #attr:titleSizeGroup#
-- | The size group for the textual portion of shortcuts in this group.
-- 
-- This is used internally by GTK, and must not be modified by applications.

#if defined(ENABLE_OVERLOADING)
    ShortcutsGroupTitleSizeGroupPropertyInfo,
#endif
    clearShortcutsGroupTitleSizeGroup       ,
    constructShortcutsGroupTitleSizeGroup   ,
    setShortcutsGroupTitleSizeGroup         ,
#if defined(ENABLE_OVERLOADING)
    shortcutsGroupTitleSizeGroup            ,
#endif


-- ** view #attr:view#
-- | An optional view that the shortcuts in this group are relevant for.
-- The group will be hidden if the t'GI.Gtk.Objects.ShortcutsWindow.ShortcutsWindow':@/view-name/@ property
-- does not match the view of this group.
-- 
-- Set this to 'P.Nothing' to make the group always visible.

#if defined(ENABLE_OVERLOADING)
    ShortcutsGroupViewPropertyInfo          ,
#endif
    clearShortcutsGroupView                 ,
    constructShortcutsGroupView             ,
    getShortcutsGroupView                   ,
    setShortcutsGroupView                   ,
#if defined(ENABLE_OVERLOADING)
    shortcutsGroupView                      ,
#endif




    ) where

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

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

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Orientable as Gtk.Orientable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Box as Gtk.Box
import {-# SOURCE #-} qualified GI.Gtk.Objects.SizeGroup as Gtk.SizeGroup
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

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

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

foreign import ccall "gtk_shortcuts_group_get_type"
    c_gtk_shortcuts_group_get_type :: IO B.Types.GType

instance B.Types.TypedObject ShortcutsGroup where
    glibType :: IO GType
glibType = IO GType
c_gtk_shortcuts_group_get_type

instance B.Types.GObject ShortcutsGroup

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

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

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

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

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

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

#endif

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

#endif

-- VVV Prop "accel-size-group"
   -- Type: TInterface (Name {namespace = "Gtk", name = "SizeGroup"})
   -- Flags: [PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

-- | Construct a `GValueConstruct` with valid value for the “@accel-size-group@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructShortcutsGroupAccelSizeGroup :: (IsShortcutsGroup o, MIO.MonadIO m, Gtk.SizeGroup.IsSizeGroup a) => a -> m (GValueConstruct o)
constructShortcutsGroupAccelSizeGroup :: forall o (m :: * -> *) a.
(IsShortcutsGroup o, MonadIO m, IsSizeGroup a) =>
a -> m (GValueConstruct o)
constructShortcutsGroupAccelSizeGroup a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"accel-size-group" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@accel-size-group@” 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' #accelSizeGroup
-- @
clearShortcutsGroupAccelSizeGroup :: (MonadIO m, IsShortcutsGroup o) => o -> m ()
clearShortcutsGroupAccelSizeGroup :: forall (m :: * -> *) o.
(MonadIO m, IsShortcutsGroup o) =>
o -> m ()
clearShortcutsGroupAccelSizeGroup o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe SizeGroup -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"accel-size-group" (Maybe SizeGroup
forall a. Maybe a
Nothing :: Maybe Gtk.SizeGroup.SizeGroup)

#if defined(ENABLE_OVERLOADING)
data ShortcutsGroupAccelSizeGroupPropertyInfo
instance AttrInfo ShortcutsGroupAccelSizeGroupPropertyInfo where
    type AttrAllowedOps ShortcutsGroupAccelSizeGroupPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrClear]
    type AttrBaseTypeConstraint ShortcutsGroupAccelSizeGroupPropertyInfo = IsShortcutsGroup
    type AttrSetTypeConstraint ShortcutsGroupAccelSizeGroupPropertyInfo = Gtk.SizeGroup.IsSizeGroup
    type AttrTransferTypeConstraint ShortcutsGroupAccelSizeGroupPropertyInfo = Gtk.SizeGroup.IsSizeGroup
    type AttrTransferType ShortcutsGroupAccelSizeGroupPropertyInfo = Gtk.SizeGroup.SizeGroup
    type AttrGetType ShortcutsGroupAccelSizeGroupPropertyInfo = ()
    type AttrLabel ShortcutsGroupAccelSizeGroupPropertyInfo = "accel-size-group"
    type AttrOrigin ShortcutsGroupAccelSizeGroupPropertyInfo = ShortcutsGroup
    attrGet = undefined
    attrSet = setShortcutsGroupAccelSizeGroup
    attrTransfer _ v = do
        unsafeCastTo Gtk.SizeGroup.SizeGroup v
    attrConstruct = constructShortcutsGroupAccelSizeGroup
    attrClear = clearShortcutsGroupAccelSizeGroup
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data ShortcutsGroupHeightPropertyInfo
instance AttrInfo ShortcutsGroupHeightPropertyInfo where
    type AttrAllowedOps ShortcutsGroupHeightPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint ShortcutsGroupHeightPropertyInfo = IsShortcutsGroup
    type AttrSetTypeConstraint ShortcutsGroupHeightPropertyInfo = (~) ()
    type AttrTransferTypeConstraint ShortcutsGroupHeightPropertyInfo = (~) ()
    type AttrTransferType ShortcutsGroupHeightPropertyInfo = ()
    type AttrGetType ShortcutsGroupHeightPropertyInfo = Word32
    type AttrLabel ShortcutsGroupHeightPropertyInfo = "height"
    type AttrOrigin ShortcutsGroupHeightPropertyInfo = ShortcutsGroup
    attrGet = getShortcutsGroupHeight
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

-- | 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' shortcutsGroup #title
-- @
getShortcutsGroupTitle :: (MonadIO m, IsShortcutsGroup o) => o -> m (Maybe T.Text)
getShortcutsGroupTitle :: forall (m :: * -> *) o.
(MonadIO m, IsShortcutsGroup o) =>
o -> m (Maybe Text)
getShortcutsGroupTitle o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"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' shortcutsGroup [ #title 'Data.GI.Base.Attributes.:=' value ]
-- @
setShortcutsGroupTitle :: (MonadIO m, IsShortcutsGroup o) => o -> T.Text -> m ()
setShortcutsGroupTitle :: forall (m :: * -> *) o.
(MonadIO m, IsShortcutsGroup o) =>
o -> Text -> m ()
setShortcutsGroupTitle o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"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`.
constructShortcutsGroupTitle :: (IsShortcutsGroup o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructShortcutsGroupTitle :: forall o (m :: * -> *).
(IsShortcutsGroup o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructShortcutsGroupTitle Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"title" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

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

#if defined(ENABLE_OVERLOADING)
data ShortcutsGroupTitlePropertyInfo
instance AttrInfo ShortcutsGroupTitlePropertyInfo where
    type AttrAllowedOps ShortcutsGroupTitlePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ShortcutsGroupTitlePropertyInfo = IsShortcutsGroup
    type AttrSetTypeConstraint ShortcutsGroupTitlePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ShortcutsGroupTitlePropertyInfo = (~) T.Text
    type AttrTransferType ShortcutsGroupTitlePropertyInfo = T.Text
    type AttrGetType ShortcutsGroupTitlePropertyInfo = (Maybe T.Text)
    type AttrLabel ShortcutsGroupTitlePropertyInfo = "title"
    type AttrOrigin ShortcutsGroupTitlePropertyInfo = ShortcutsGroup
    attrGet = getShortcutsGroupTitle
    attrSet = setShortcutsGroupTitle
    attrTransfer _ v = do
        return v
    attrConstruct = constructShortcutsGroupTitle
    attrClear = clearShortcutsGroupTitle
#endif

-- VVV Prop "title-size-group"
   -- Type: TInterface (Name {namespace = "Gtk", name = "SizeGroup"})
   -- Flags: [PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

-- | Construct a `GValueConstruct` with valid value for the “@title-size-group@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructShortcutsGroupTitleSizeGroup :: (IsShortcutsGroup o, MIO.MonadIO m, Gtk.SizeGroup.IsSizeGroup a) => a -> m (GValueConstruct o)
constructShortcutsGroupTitleSizeGroup :: forall o (m :: * -> *) a.
(IsShortcutsGroup o, MonadIO m, IsSizeGroup a) =>
a -> m (GValueConstruct o)
constructShortcutsGroupTitleSizeGroup a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"title-size-group" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@title-size-group@” 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' #titleSizeGroup
-- @
clearShortcutsGroupTitleSizeGroup :: (MonadIO m, IsShortcutsGroup o) => o -> m ()
clearShortcutsGroupTitleSizeGroup :: forall (m :: * -> *) o.
(MonadIO m, IsShortcutsGroup o) =>
o -> m ()
clearShortcutsGroupTitleSizeGroup o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe SizeGroup -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"title-size-group" (Maybe SizeGroup
forall a. Maybe a
Nothing :: Maybe Gtk.SizeGroup.SizeGroup)

#if defined(ENABLE_OVERLOADING)
data ShortcutsGroupTitleSizeGroupPropertyInfo
instance AttrInfo ShortcutsGroupTitleSizeGroupPropertyInfo where
    type AttrAllowedOps ShortcutsGroupTitleSizeGroupPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrClear]
    type AttrBaseTypeConstraint ShortcutsGroupTitleSizeGroupPropertyInfo = IsShortcutsGroup
    type AttrSetTypeConstraint ShortcutsGroupTitleSizeGroupPropertyInfo = Gtk.SizeGroup.IsSizeGroup
    type AttrTransferTypeConstraint ShortcutsGroupTitleSizeGroupPropertyInfo = Gtk.SizeGroup.IsSizeGroup
    type AttrTransferType ShortcutsGroupTitleSizeGroupPropertyInfo = Gtk.SizeGroup.SizeGroup
    type AttrGetType ShortcutsGroupTitleSizeGroupPropertyInfo = ()
    type AttrLabel ShortcutsGroupTitleSizeGroupPropertyInfo = "title-size-group"
    type AttrOrigin ShortcutsGroupTitleSizeGroupPropertyInfo = ShortcutsGroup
    attrGet = undefined
    attrSet = setShortcutsGroupTitleSizeGroup
    attrTransfer _ v = do
        unsafeCastTo Gtk.SizeGroup.SizeGroup v
    attrConstruct = constructShortcutsGroupTitleSizeGroup
    attrClear = clearShortcutsGroupTitleSizeGroup
#endif

-- VVV Prop "view"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data ShortcutsGroupViewPropertyInfo
instance AttrInfo ShortcutsGroupViewPropertyInfo where
    type AttrAllowedOps ShortcutsGroupViewPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ShortcutsGroupViewPropertyInfo = IsShortcutsGroup
    type AttrSetTypeConstraint ShortcutsGroupViewPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ShortcutsGroupViewPropertyInfo = (~) T.Text
    type AttrTransferType ShortcutsGroupViewPropertyInfo = T.Text
    type AttrGetType ShortcutsGroupViewPropertyInfo = (Maybe T.Text)
    type AttrLabel ShortcutsGroupViewPropertyInfo = "view"
    type AttrOrigin ShortcutsGroupViewPropertyInfo = ShortcutsGroup
    attrGet = getShortcutsGroupView
    attrSet = setShortcutsGroupView
    attrTransfer _ v = do
        return v
    attrConstruct = constructShortcutsGroupView
    attrClear = clearShortcutsGroupView
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ShortcutsGroup
type instance O.AttributeList ShortcutsGroup = ShortcutsGroupAttributeList
type ShortcutsGroupAttributeList = ('[ '("accelSizeGroup", ShortcutsGroupAccelSizeGroupPropertyInfo), '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("baselinePosition", Gtk.Box.BoxBaselinePositionPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusable", Gtk.Widget.WidgetFocusablePropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("height", ShortcutsGroupHeightPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("homogeneous", Gtk.Box.BoxHomogeneousPropertyInfo), '("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), '("orientation", Gtk.Orientable.OrientableOrientationPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("spacing", Gtk.Box.BoxSpacingPropertyInfo), '("title", ShortcutsGroupTitlePropertyInfo), '("titleSizeGroup", ShortcutsGroupTitleSizeGroupPropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("view", ShortcutsGroupViewPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
shortcutsGroupAccelSizeGroup :: AttrLabelProxy "accelSizeGroup"
shortcutsGroupAccelSizeGroup = AttrLabelProxy

shortcutsGroupHeight :: AttrLabelProxy "height"
shortcutsGroupHeight = AttrLabelProxy

shortcutsGroupTitle :: AttrLabelProxy "title"
shortcutsGroupTitle = AttrLabelProxy

shortcutsGroupTitleSizeGroup :: AttrLabelProxy "titleSizeGroup"
shortcutsGroupTitleSizeGroup = AttrLabelProxy

shortcutsGroupView :: AttrLabelProxy "view"
shortcutsGroupView = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ShortcutsGroup = ShortcutsGroupSignalList
type ShortcutsGroupSignalList = ('[ '("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