{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A GtkShortcutsSection collects all the keyboard shortcuts and gestures
-- for a major application mode. If your application needs multiple sections,
-- you should give each section a unique t'GI.Gtk.Objects.ShortcutsSection.ShortcutsSection':@/section-name/@ and
-- a t'GI.Gtk.Objects.ShortcutsSection.ShortcutsSection':@/title/@ that can be shown in the section selector of
-- the GtkShortcutsWindow.
-- 
-- The t'GI.Gtk.Objects.ShortcutsSection.ShortcutsSection':@/max-height/@ property can be used to influence how
-- the groups in the section are distributed over pages and columns.
-- 
-- 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.ShortcutsSection
    ( 

-- * Exported types
    ShortcutsSection(..)                    ,
    IsShortcutsSection                      ,
    toShortcutsSection                      ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveShortcutsSectionMethod           ,
#endif




 -- * Properties
-- ** maxHeight #attr:maxHeight#
-- | The maximum number of lines to allow per column. This property can
-- be used to influence how the groups in this section are distributed
-- across pages and columns. The default value of 15 should work in
-- most cases.

#if defined(ENABLE_OVERLOADING)
    ShortcutsSectionMaxHeightPropertyInfo   ,
#endif
    constructShortcutsSectionMaxHeight      ,
    getShortcutsSectionMaxHeight            ,
    setShortcutsSectionMaxHeight            ,
#if defined(ENABLE_OVERLOADING)
    shortcutsSectionMaxHeight               ,
#endif


-- ** sectionName #attr:sectionName#
-- | A unique name to identify this section among the sections
-- added to the GtkShortcutsWindow. Setting the t'GI.Gtk.Objects.ShortcutsWindow.ShortcutsWindow':@/section-name/@
-- property to this string will make this section shown in the
-- GtkShortcutsWindow.

#if defined(ENABLE_OVERLOADING)
    ShortcutsSectionSectionNamePropertyInfo ,
#endif
    clearShortcutsSectionSectionName        ,
    constructShortcutsSectionSectionName    ,
    getShortcutsSectionSectionName          ,
    setShortcutsSectionSectionName          ,
#if defined(ENABLE_OVERLOADING)
    shortcutsSectionSectionName             ,
#endif


-- ** title #attr:title#
-- | The string to show in the section selector of the GtkShortcutsWindow
-- for this section. If there is only one section, you don\'t need to
-- set a title, since the section selector will not be shown in this case.

#if defined(ENABLE_OVERLOADING)
    ShortcutsSectionTitlePropertyInfo       ,
#endif
    clearShortcutsSectionTitle              ,
    constructShortcutsSectionTitle          ,
    getShortcutsSectionTitle                ,
    setShortcutsSectionTitle                ,
#if defined(ENABLE_OVERLOADING)
    shortcutsSectionTitle                   ,
#endif


-- ** viewName #attr:viewName#
-- | A view name to filter the groups in this section by.
-- See t'GI.Gtk.Objects.ShortcutsGroup.ShortcutsGroup':@/view/@.
-- 
-- Applications are expected to use the t'GI.Gtk.Objects.ShortcutsWindow.ShortcutsWindow':@/view-name/@
-- property for this purpose.

#if defined(ENABLE_OVERLOADING)
    ShortcutsSectionViewNamePropertyInfo    ,
#endif
    clearShortcutsSectionViewName           ,
    constructShortcutsSectionViewName       ,
    getShortcutsSectionViewName             ,
    setShortcutsSectionViewName             ,
#if defined(ENABLE_OVERLOADING)
    shortcutsSectionViewName                ,
#endif




 -- * Signals
-- ** changeCurrentPage #signal:changeCurrentPage#

    C_ShortcutsSectionChangeCurrentPageCallback,
    ShortcutsSectionChangeCurrentPageCallback,
#if defined(ENABLE_OVERLOADING)
    ShortcutsSectionChangeCurrentPageSignalInfo,
#endif
    afterShortcutsSectionChangeCurrentPage  ,
    genClosure_ShortcutsSectionChangeCurrentPage,
    mk_ShortcutsSectionChangeCurrentPageCallback,
    noShortcutsSectionChangeCurrentPageCallback,
    onShortcutsSectionChangeCurrentPage     ,
    wrap_ShortcutsSectionChangeCurrentPageCallback,




    ) 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.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 GI.Atk.Interfaces.ImplementorIface as Atk.ImplementorIface
import qualified GI.GObject.Objects.Object as GObject.Object
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.Widget as Gtk.Widget

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

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

foreign import ccall "gtk_shortcuts_section_get_type"
    c_gtk_shortcuts_section_get_type :: IO B.Types.GType

instance B.Types.TypedObject ShortcutsSection where
    glibType :: IO GType
glibType = IO GType
c_gtk_shortcuts_section_get_type

instance B.Types.GObject ShortcutsSection

-- | Convert 'ShortcutsSection' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue ShortcutsSection where
    toGValue :: ShortcutsSection -> IO GValue
toGValue ShortcutsSection
o = do
        GType
gtype <- IO GType
c_gtk_shortcuts_section_get_type
        ShortcutsSection
-> (Ptr ShortcutsSection -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ShortcutsSection
o (GType
-> (GValue -> Ptr ShortcutsSection -> IO ())
-> Ptr ShortcutsSection
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr ShortcutsSection -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO ShortcutsSection
fromGValue GValue
gv = do
        Ptr ShortcutsSection
ptr <- GValue -> IO (Ptr ShortcutsSection)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr ShortcutsSection)
        (ManagedPtr ShortcutsSection -> ShortcutsSection)
-> Ptr ShortcutsSection -> IO ShortcutsSection
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr ShortcutsSection -> ShortcutsSection
ShortcutsSection Ptr ShortcutsSection
ptr
        
    

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

instance O.HasParentTypes ShortcutsSection
type instance O.ParentTypes ShortcutsSection = '[Gtk.Box.Box, Gtk.Widget.Widget, GObject.Object.Object, Atk.ImplementorIface.ImplementorIface, Gtk.Buildable.Buildable, Gtk.ConstraintTarget.ConstraintTarget, Gtk.Orientable.Orientable]

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

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

instance (info ~ ResolveShortcutsSectionMethod t ShortcutsSection, O.MethodInfo info ShortcutsSection p) => OL.IsLabel t (ShortcutsSection -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- signal ShortcutsSection::change-current-page
-- | /No description available in the introspection data./
type ShortcutsSectionChangeCurrentPageCallback =
    Int32
    -> IO Bool

-- | A convenience synonym for @`Nothing` :: `Maybe` `ShortcutsSectionChangeCurrentPageCallback`@.
noShortcutsSectionChangeCurrentPageCallback :: Maybe ShortcutsSectionChangeCurrentPageCallback
noShortcutsSectionChangeCurrentPageCallback :: Maybe ShortcutsSectionChangeCurrentPageCallback
noShortcutsSectionChangeCurrentPageCallback = Maybe ShortcutsSectionChangeCurrentPageCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_ShortcutsSectionChangeCurrentPageCallback =
    Ptr () ->                               -- object
    Int32 ->
    Ptr () ->                               -- user_data
    IO CInt

-- | Generate a function pointer callable from C code, from a `C_ShortcutsSectionChangeCurrentPageCallback`.
foreign import ccall "wrapper"
    mk_ShortcutsSectionChangeCurrentPageCallback :: C_ShortcutsSectionChangeCurrentPageCallback -> IO (FunPtr C_ShortcutsSectionChangeCurrentPageCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_ShortcutsSectionChangeCurrentPage :: MonadIO m => ShortcutsSectionChangeCurrentPageCallback -> m (GClosure C_ShortcutsSectionChangeCurrentPageCallback)
genClosure_ShortcutsSectionChangeCurrentPage :: ShortcutsSectionChangeCurrentPageCallback
-> m (GClosure C_ShortcutsSectionChangeCurrentPageCallback)
genClosure_ShortcutsSectionChangeCurrentPage ShortcutsSectionChangeCurrentPageCallback
cb = IO (GClosure C_ShortcutsSectionChangeCurrentPageCallback)
-> m (GClosure C_ShortcutsSectionChangeCurrentPageCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ShortcutsSectionChangeCurrentPageCallback)
 -> m (GClosure C_ShortcutsSectionChangeCurrentPageCallback))
-> IO (GClosure C_ShortcutsSectionChangeCurrentPageCallback)
-> m (GClosure C_ShortcutsSectionChangeCurrentPageCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ShortcutsSectionChangeCurrentPageCallback
cb' = ShortcutsSectionChangeCurrentPageCallback
-> C_ShortcutsSectionChangeCurrentPageCallback
wrap_ShortcutsSectionChangeCurrentPageCallback ShortcutsSectionChangeCurrentPageCallback
cb
    C_ShortcutsSectionChangeCurrentPageCallback
-> IO (FunPtr C_ShortcutsSectionChangeCurrentPageCallback)
mk_ShortcutsSectionChangeCurrentPageCallback C_ShortcutsSectionChangeCurrentPageCallback
cb' IO (FunPtr C_ShortcutsSectionChangeCurrentPageCallback)
-> (FunPtr C_ShortcutsSectionChangeCurrentPageCallback
    -> IO (GClosure C_ShortcutsSectionChangeCurrentPageCallback))
-> IO (GClosure C_ShortcutsSectionChangeCurrentPageCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ShortcutsSectionChangeCurrentPageCallback
-> IO (GClosure C_ShortcutsSectionChangeCurrentPageCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `ShortcutsSectionChangeCurrentPageCallback` into a `C_ShortcutsSectionChangeCurrentPageCallback`.
wrap_ShortcutsSectionChangeCurrentPageCallback ::
    ShortcutsSectionChangeCurrentPageCallback ->
    C_ShortcutsSectionChangeCurrentPageCallback
wrap_ShortcutsSectionChangeCurrentPageCallback :: ShortcutsSectionChangeCurrentPageCallback
-> C_ShortcutsSectionChangeCurrentPageCallback
wrap_ShortcutsSectionChangeCurrentPageCallback ShortcutsSectionChangeCurrentPageCallback
_cb Ptr ()
_ Int32
object Ptr ()
_ = do
    Bool
result <- ShortcutsSectionChangeCurrentPageCallback
_cb  Int32
object
    let result' :: CInt
result' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
result
    CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'


-- | Connect a signal handler for the [changeCurrentPage](#signal:changeCurrentPage) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' shortcutsSection #changeCurrentPage callback
-- @
-- 
-- 
onShortcutsSectionChangeCurrentPage :: (IsShortcutsSection a, MonadIO m) => a -> ShortcutsSectionChangeCurrentPageCallback -> m SignalHandlerId
onShortcutsSectionChangeCurrentPage :: a -> ShortcutsSectionChangeCurrentPageCallback -> m SignalHandlerId
onShortcutsSectionChangeCurrentPage a
obj ShortcutsSectionChangeCurrentPageCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ShortcutsSectionChangeCurrentPageCallback
cb' = ShortcutsSectionChangeCurrentPageCallback
-> C_ShortcutsSectionChangeCurrentPageCallback
wrap_ShortcutsSectionChangeCurrentPageCallback ShortcutsSectionChangeCurrentPageCallback
cb
    FunPtr C_ShortcutsSectionChangeCurrentPageCallback
cb'' <- C_ShortcutsSectionChangeCurrentPageCallback
-> IO (FunPtr C_ShortcutsSectionChangeCurrentPageCallback)
mk_ShortcutsSectionChangeCurrentPageCallback C_ShortcutsSectionChangeCurrentPageCallback
cb'
    a
-> Text
-> FunPtr C_ShortcutsSectionChangeCurrentPageCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"change-current-page" FunPtr C_ShortcutsSectionChangeCurrentPageCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [changeCurrentPage](#signal:changeCurrentPage) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' shortcutsSection #changeCurrentPage callback
-- @
-- 
-- 
afterShortcutsSectionChangeCurrentPage :: (IsShortcutsSection a, MonadIO m) => a -> ShortcutsSectionChangeCurrentPageCallback -> m SignalHandlerId
afterShortcutsSectionChangeCurrentPage :: a -> ShortcutsSectionChangeCurrentPageCallback -> m SignalHandlerId
afterShortcutsSectionChangeCurrentPage a
obj ShortcutsSectionChangeCurrentPageCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ShortcutsSectionChangeCurrentPageCallback
cb' = ShortcutsSectionChangeCurrentPageCallback
-> C_ShortcutsSectionChangeCurrentPageCallback
wrap_ShortcutsSectionChangeCurrentPageCallback ShortcutsSectionChangeCurrentPageCallback
cb
    FunPtr C_ShortcutsSectionChangeCurrentPageCallback
cb'' <- C_ShortcutsSectionChangeCurrentPageCallback
-> IO (FunPtr C_ShortcutsSectionChangeCurrentPageCallback)
mk_ShortcutsSectionChangeCurrentPageCallback C_ShortcutsSectionChangeCurrentPageCallback
cb'
    a
-> Text
-> FunPtr C_ShortcutsSectionChangeCurrentPageCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"change-current-page" FunPtr C_ShortcutsSectionChangeCurrentPageCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data ShortcutsSectionChangeCurrentPageSignalInfo
instance SignalInfo ShortcutsSectionChangeCurrentPageSignalInfo where
    type HaskellCallbackType ShortcutsSectionChangeCurrentPageSignalInfo = ShortcutsSectionChangeCurrentPageCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ShortcutsSectionChangeCurrentPageCallback cb
        cb'' <- mk_ShortcutsSectionChangeCurrentPageCallback cb'
        connectSignalFunPtr obj "change-current-page" cb'' connectMode detail

#endif

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

-- | Get the value of the “@max-height@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' shortcutsSection #maxHeight
-- @
getShortcutsSectionMaxHeight :: (MonadIO m, IsShortcutsSection o) => o -> m Word32
getShortcutsSectionMaxHeight :: o -> m Word32
getShortcutsSectionMaxHeight o
obj = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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
"max-height"

-- | Set the value of the “@max-height@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' shortcutsSection [ #maxHeight 'Data.GI.Base.Attributes.:=' value ]
-- @
setShortcutsSectionMaxHeight :: (MonadIO m, IsShortcutsSection o) => o -> Word32 -> m ()
setShortcutsSectionMaxHeight :: o -> Word32 -> m ()
setShortcutsSectionMaxHeight o
obj Word32
val = 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 -> Word32 -> IO ()
forall a. GObject a => a -> String -> Word32 -> IO ()
B.Properties.setObjectPropertyUInt32 o
obj String
"max-height" Word32
val

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

#if defined(ENABLE_OVERLOADING)
data ShortcutsSectionMaxHeightPropertyInfo
instance AttrInfo ShortcutsSectionMaxHeightPropertyInfo where
    type AttrAllowedOps ShortcutsSectionMaxHeightPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ShortcutsSectionMaxHeightPropertyInfo = IsShortcutsSection
    type AttrSetTypeConstraint ShortcutsSectionMaxHeightPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint ShortcutsSectionMaxHeightPropertyInfo = (~) Word32
    type AttrTransferType ShortcutsSectionMaxHeightPropertyInfo = Word32
    type AttrGetType ShortcutsSectionMaxHeightPropertyInfo = Word32
    type AttrLabel ShortcutsSectionMaxHeightPropertyInfo = "max-height"
    type AttrOrigin ShortcutsSectionMaxHeightPropertyInfo = ShortcutsSection
    attrGet = getShortcutsSectionMaxHeight
    attrSet = setShortcutsSectionMaxHeight
    attrTransfer _ v = do
        return v
    attrConstruct = constructShortcutsSectionMaxHeight
    attrClear = undefined
#endif

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

-- | Get the value of the “@section-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' shortcutsSection #sectionName
-- @
getShortcutsSectionSectionName :: (MonadIO m, IsShortcutsSection o) => o -> m (Maybe T.Text)
getShortcutsSectionSectionName :: o -> m (Maybe Text)
getShortcutsSectionSectionName o
obj = IO (Maybe Text) -> m (Maybe Text)
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
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"section-name"

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

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

-- | Set the value of the “@section-name@” 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' #sectionName
-- @
clearShortcutsSectionSectionName :: (MonadIO m, IsShortcutsSection o) => o -> m ()
clearShortcutsSectionSectionName :: o -> m ()
clearShortcutsSectionSectionName 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
"section-name" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data ShortcutsSectionSectionNamePropertyInfo
instance AttrInfo ShortcutsSectionSectionNamePropertyInfo where
    type AttrAllowedOps ShortcutsSectionSectionNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ShortcutsSectionSectionNamePropertyInfo = IsShortcutsSection
    type AttrSetTypeConstraint ShortcutsSectionSectionNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ShortcutsSectionSectionNamePropertyInfo = (~) T.Text
    type AttrTransferType ShortcutsSectionSectionNamePropertyInfo = T.Text
    type AttrGetType ShortcutsSectionSectionNamePropertyInfo = (Maybe T.Text)
    type AttrLabel ShortcutsSectionSectionNamePropertyInfo = "section-name"
    type AttrOrigin ShortcutsSectionSectionNamePropertyInfo = ShortcutsSection
    attrGet = getShortcutsSectionSectionName
    attrSet = setShortcutsSectionSectionName
    attrTransfer _ v = do
        return v
    attrConstruct = constructShortcutsSectionSectionName
    attrClear = clearShortcutsSectionSectionName
#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' shortcutsSection #title
-- @
getShortcutsSectionTitle :: (MonadIO m, IsShortcutsSection o) => o -> m (Maybe T.Text)
getShortcutsSectionTitle :: o -> m (Maybe Text)
getShortcutsSectionTitle o
obj = IO (Maybe Text) -> m (Maybe Text)
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
$ 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' shortcutsSection [ #title 'Data.GI.Base.Attributes.:=' value ]
-- @
setShortcutsSectionTitle :: (MonadIO m, IsShortcutsSection o) => o -> T.Text -> m ()
setShortcutsSectionTitle :: o -> Text -> m ()
setShortcutsSectionTitle o
obj Text
val = 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" (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`.
constructShortcutsSectionTitle :: (IsShortcutsSection o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructShortcutsSectionTitle :: Text -> m (GValueConstruct o)
constructShortcutsSectionTitle 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
$ 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
-- @
clearShortcutsSectionTitle :: (MonadIO m, IsShortcutsSection o) => o -> m ()
clearShortcutsSectionTitle :: o -> m ()
clearShortcutsSectionTitle 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 ShortcutsSectionTitlePropertyInfo
instance AttrInfo ShortcutsSectionTitlePropertyInfo where
    type AttrAllowedOps ShortcutsSectionTitlePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ShortcutsSectionTitlePropertyInfo = IsShortcutsSection
    type AttrSetTypeConstraint ShortcutsSectionTitlePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ShortcutsSectionTitlePropertyInfo = (~) T.Text
    type AttrTransferType ShortcutsSectionTitlePropertyInfo = T.Text
    type AttrGetType ShortcutsSectionTitlePropertyInfo = (Maybe T.Text)
    type AttrLabel ShortcutsSectionTitlePropertyInfo = "title"
    type AttrOrigin ShortcutsSectionTitlePropertyInfo = ShortcutsSection
    attrGet = getShortcutsSectionTitle
    attrSet = setShortcutsSectionTitle
    attrTransfer _ v = do
        return v
    attrConstruct = constructShortcutsSectionTitle
    attrClear = clearShortcutsSectionTitle
#endif

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

-- | Get the value of the “@view-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' shortcutsSection #viewName
-- @
getShortcutsSectionViewName :: (MonadIO m, IsShortcutsSection o) => o -> m (Maybe T.Text)
getShortcutsSectionViewName :: o -> m (Maybe Text)
getShortcutsSectionViewName o
obj = IO (Maybe Text) -> m (Maybe Text)
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
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"view-name"

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

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

-- | Set the value of the “@view-name@” 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' #viewName
-- @
clearShortcutsSectionViewName :: (MonadIO m, IsShortcutsSection o) => o -> m ()
clearShortcutsSectionViewName :: o -> m ()
clearShortcutsSectionViewName 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-name" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data ShortcutsSectionViewNamePropertyInfo
instance AttrInfo ShortcutsSectionViewNamePropertyInfo where
    type AttrAllowedOps ShortcutsSectionViewNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ShortcutsSectionViewNamePropertyInfo = IsShortcutsSection
    type AttrSetTypeConstraint ShortcutsSectionViewNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ShortcutsSectionViewNamePropertyInfo = (~) T.Text
    type AttrTransferType ShortcutsSectionViewNamePropertyInfo = T.Text
    type AttrGetType ShortcutsSectionViewNamePropertyInfo = (Maybe T.Text)
    type AttrLabel ShortcutsSectionViewNamePropertyInfo = "view-name"
    type AttrOrigin ShortcutsSectionViewNamePropertyInfo = ShortcutsSection
    attrGet = getShortcutsSectionViewName
    attrSet = setShortcutsSectionViewName
    attrTransfer _ v = do
        return v
    attrConstruct = constructShortcutsSectionViewName
    attrClear = clearShortcutsSectionViewName
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ShortcutsSection
type instance O.AttributeList ShortcutsSection = ShortcutsSectionAttributeList
type ShortcutsSectionAttributeList = ('[ '("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), '("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), '("maxHeight", ShortcutsSectionMaxHeightPropertyInfo), '("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), '("sectionName", ShortcutsSectionSectionNamePropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("spacing", Gtk.Box.BoxSpacingPropertyInfo), '("title", ShortcutsSectionTitlePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("viewName", ShortcutsSectionViewNamePropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
shortcutsSectionMaxHeight :: AttrLabelProxy "maxHeight"
shortcutsSectionMaxHeight = AttrLabelProxy

shortcutsSectionSectionName :: AttrLabelProxy "sectionName"
shortcutsSectionSectionName = AttrLabelProxy

shortcutsSectionTitle :: AttrLabelProxy "title"
shortcutsSectionTitle = AttrLabelProxy

shortcutsSectionViewName :: AttrLabelProxy "viewName"
shortcutsSectionViewName = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ShortcutsSection = ShortcutsSectionSignalList
type ShortcutsSectionSignalList = ('[ '("changeCurrentPage", ShortcutsSectionChangeCurrentPageSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("grabNotify", Gtk.Widget.WidgetGrabNotifySignalInfo), '("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