{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The GtkStackSwitcher widget acts as a controller for a
-- t'GI.Gtk.Objects.Stack.Stack'; it shows a row of buttons to switch between
-- the various pages of the associated stack widget.
-- 
-- All the content for the buttons comes from the child properties
-- of the t'GI.Gtk.Objects.Stack.Stack'; the button visibility in a t'GI.Gtk.Objects.StackSwitcher.StackSwitcher'
-- widget is controlled by the visibility of the child in the
-- t'GI.Gtk.Objects.Stack.Stack'.
-- 
-- It is possible to associate multiple t'GI.Gtk.Objects.StackSwitcher.StackSwitcher' widgets
-- with the same t'GI.Gtk.Objects.Stack.Stack' widget.
-- 
-- The GtkStackSwitcher widget was added in 3.10.
-- 
-- = CSS nodes
-- 
-- GtkStackSwitcher has a single CSS node named stackswitcher and
-- style class .stack-switcher.
-- 
-- When circumstances require it, GtkStackSwitcher adds the
-- .needs-attention style class to the widgets representing the
-- stack pages.

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

module GI.Gtk.Objects.StackSwitcher
    ( 

-- * Exported types
    StackSwitcher(..)                       ,
    IsStackSwitcher                         ,
    toStackSwitcher                         ,
    noStackSwitcher                         ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveStackSwitcherMethod              ,
#endif


-- ** getStack #method:getStack#

#if defined(ENABLE_OVERLOADING)
    StackSwitcherGetStackMethodInfo         ,
#endif
    stackSwitcherGetStack                   ,


-- ** new #method:new#

    stackSwitcherNew                        ,


-- ** setStack #method:setStack#

#if defined(ENABLE_OVERLOADING)
    StackSwitcherSetStackMethodInfo         ,
#endif
    stackSwitcherSetStack                   ,




 -- * Properties
-- ** stack #attr:stack#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    StackSwitcherStackPropertyInfo          ,
#endif
    clearStackSwitcherStack                 ,
    constructStackSwitcherStack             ,
    getStackSwitcherStack                   ,
    setStackSwitcherStack                   ,
#if defined(ENABLE_OVERLOADING)
    stackSwitcherStack                      ,
#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.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 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.Orientable as Gtk.Orientable
import {-# SOURCE #-} qualified GI.Gtk.Objects.Box as Gtk.Box
import {-# SOURCE #-} qualified GI.Gtk.Objects.Container as Gtk.Container
import {-# SOURCE #-} qualified GI.Gtk.Objects.Stack as Gtk.Stack
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget

-- | Memory-managed wrapper type.
newtype StackSwitcher = StackSwitcher (ManagedPtr StackSwitcher)
    deriving (StackSwitcher -> StackSwitcher -> Bool
(StackSwitcher -> StackSwitcher -> Bool)
-> (StackSwitcher -> StackSwitcher -> Bool) -> Eq StackSwitcher
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StackSwitcher -> StackSwitcher -> Bool
$c/= :: StackSwitcher -> StackSwitcher -> Bool
== :: StackSwitcher -> StackSwitcher -> Bool
$c== :: StackSwitcher -> StackSwitcher -> Bool
Eq)
foreign import ccall "gtk_stack_switcher_get_type"
    c_gtk_stack_switcher_get_type :: IO GType

instance GObject StackSwitcher where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_stack_switcher_get_type
    

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

-- | Type class for types which can be safely cast to `StackSwitcher`, for instance with `toStackSwitcher`.
class (GObject o, O.IsDescendantOf StackSwitcher o) => IsStackSwitcher o
instance (GObject o, O.IsDescendantOf StackSwitcher o) => IsStackSwitcher o

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

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

-- | A convenience alias for `Nothing` :: `Maybe` `StackSwitcher`.
noStackSwitcher :: Maybe StackSwitcher
noStackSwitcher :: Maybe StackSwitcher
noStackSwitcher = Maybe StackSwitcher
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveStackSwitcherMethod (t :: Symbol) (o :: *) :: * where
    ResolveStackSwitcherMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveStackSwitcherMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveStackSwitcherMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveStackSwitcherMethod "add" o = Gtk.Container.ContainerAddMethodInfo
    ResolveStackSwitcherMethod "addAccelerator" o = Gtk.Widget.WidgetAddAcceleratorMethodInfo
    ResolveStackSwitcherMethod "addChild" o = Gtk.Buildable.BuildableAddChildMethodInfo
    ResolveStackSwitcherMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveStackSwitcherMethod "addMnemonicLabel" o = Gtk.Widget.WidgetAddMnemonicLabelMethodInfo
    ResolveStackSwitcherMethod "addTickCallback" o = Gtk.Widget.WidgetAddTickCallbackMethodInfo
    ResolveStackSwitcherMethod "allocate" o = Gtk.Widget.WidgetAllocateMethodInfo
    ResolveStackSwitcherMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveStackSwitcherMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveStackSwitcherMethod "canActivateAccel" o = Gtk.Widget.WidgetCanActivateAccelMethodInfo
    ResolveStackSwitcherMethod "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    ResolveStackSwitcherMethod "childType" o = Gtk.Container.ContainerChildTypeMethodInfo
    ResolveStackSwitcherMethod "computeBounds" o = Gtk.Widget.WidgetComputeBoundsMethodInfo
    ResolveStackSwitcherMethod "computeExpand" o = Gtk.Widget.WidgetComputeExpandMethodInfo
    ResolveStackSwitcherMethod "computePoint" o = Gtk.Widget.WidgetComputePointMethodInfo
    ResolveStackSwitcherMethod "computeTransform" o = Gtk.Widget.WidgetComputeTransformMethodInfo
    ResolveStackSwitcherMethod "constructChild" o = Gtk.Buildable.BuildableConstructChildMethodInfo
    ResolveStackSwitcherMethod "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveStackSwitcherMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveStackSwitcherMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveStackSwitcherMethod "customFinished" o = Gtk.Buildable.BuildableCustomFinishedMethodInfo
    ResolveStackSwitcherMethod "customTagEnd" o = Gtk.Buildable.BuildableCustomTagEndMethodInfo
    ResolveStackSwitcherMethod "customTagStart" o = Gtk.Buildable.BuildableCustomTagStartMethodInfo
    ResolveStackSwitcherMethod "destroy" o = Gtk.Widget.WidgetDestroyMethodInfo
    ResolveStackSwitcherMethod "destroyed" o = Gtk.Widget.WidgetDestroyedMethodInfo
    ResolveStackSwitcherMethod "deviceIsShadowed" o = Gtk.Widget.WidgetDeviceIsShadowedMethodInfo
    ResolveStackSwitcherMethod "dragBegin" o = Gtk.Widget.WidgetDragBeginMethodInfo
    ResolveStackSwitcherMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveStackSwitcherMethod "dragDestAddImageTargets" o = Gtk.Widget.WidgetDragDestAddImageTargetsMethodInfo
    ResolveStackSwitcherMethod "dragDestAddTextTargets" o = Gtk.Widget.WidgetDragDestAddTextTargetsMethodInfo
    ResolveStackSwitcherMethod "dragDestAddUriTargets" o = Gtk.Widget.WidgetDragDestAddUriTargetsMethodInfo
    ResolveStackSwitcherMethod "dragDestFindTarget" o = Gtk.Widget.WidgetDragDestFindTargetMethodInfo
    ResolveStackSwitcherMethod "dragDestGetTargetList" o = Gtk.Widget.WidgetDragDestGetTargetListMethodInfo
    ResolveStackSwitcherMethod "dragDestGetTrackMotion" o = Gtk.Widget.WidgetDragDestGetTrackMotionMethodInfo
    ResolveStackSwitcherMethod "dragDestSet" o = Gtk.Widget.WidgetDragDestSetMethodInfo
    ResolveStackSwitcherMethod "dragDestSetTargetList" o = Gtk.Widget.WidgetDragDestSetTargetListMethodInfo
    ResolveStackSwitcherMethod "dragDestSetTrackMotion" o = Gtk.Widget.WidgetDragDestSetTrackMotionMethodInfo
    ResolveStackSwitcherMethod "dragDestUnset" o = Gtk.Widget.WidgetDragDestUnsetMethodInfo
    ResolveStackSwitcherMethod "dragGetData" o = Gtk.Widget.WidgetDragGetDataMethodInfo
    ResolveStackSwitcherMethod "dragHighlight" o = Gtk.Widget.WidgetDragHighlightMethodInfo
    ResolveStackSwitcherMethod "dragSourceAddImageTargets" o = Gtk.Widget.WidgetDragSourceAddImageTargetsMethodInfo
    ResolveStackSwitcherMethod "dragSourceAddTextTargets" o = Gtk.Widget.WidgetDragSourceAddTextTargetsMethodInfo
    ResolveStackSwitcherMethod "dragSourceAddUriTargets" o = Gtk.Widget.WidgetDragSourceAddUriTargetsMethodInfo
    ResolveStackSwitcherMethod "dragSourceGetTargetList" o = Gtk.Widget.WidgetDragSourceGetTargetListMethodInfo
    ResolveStackSwitcherMethod "dragSourceSet" o = Gtk.Widget.WidgetDragSourceSetMethodInfo
    ResolveStackSwitcherMethod "dragSourceSetIconGicon" o = Gtk.Widget.WidgetDragSourceSetIconGiconMethodInfo
    ResolveStackSwitcherMethod "dragSourceSetIconName" o = Gtk.Widget.WidgetDragSourceSetIconNameMethodInfo
    ResolveStackSwitcherMethod "dragSourceSetIconPaintable" o = Gtk.Widget.WidgetDragSourceSetIconPaintableMethodInfo
    ResolveStackSwitcherMethod "dragSourceSetTargetList" o = Gtk.Widget.WidgetDragSourceSetTargetListMethodInfo
    ResolveStackSwitcherMethod "dragSourceUnset" o = Gtk.Widget.WidgetDragSourceUnsetMethodInfo
    ResolveStackSwitcherMethod "dragUnhighlight" o = Gtk.Widget.WidgetDragUnhighlightMethodInfo
    ResolveStackSwitcherMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveStackSwitcherMethod "event" o = Gtk.Widget.WidgetEventMethodInfo
    ResolveStackSwitcherMethod "forall" o = Gtk.Container.ContainerForallMethodInfo
    ResolveStackSwitcherMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveStackSwitcherMethod "foreach" o = Gtk.Container.ContainerForeachMethodInfo
    ResolveStackSwitcherMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveStackSwitcherMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveStackSwitcherMethod "grabAdd" o = Gtk.Widget.WidgetGrabAddMethodInfo
    ResolveStackSwitcherMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveStackSwitcherMethod "grabRemove" o = Gtk.Widget.WidgetGrabRemoveMethodInfo
    ResolveStackSwitcherMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveStackSwitcherMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    ResolveStackSwitcherMethod "hasGrab" o = Gtk.Widget.WidgetHasGrabMethodInfo
    ResolveStackSwitcherMethod "hasVisibleFocus" o = Gtk.Widget.WidgetHasVisibleFocusMethodInfo
    ResolveStackSwitcherMethod "hide" o = Gtk.Widget.WidgetHideMethodInfo
    ResolveStackSwitcherMethod "inDestruction" o = Gtk.Widget.WidgetInDestructionMethodInfo
    ResolveStackSwitcherMethod "initTemplate" o = Gtk.Widget.WidgetInitTemplateMethodInfo
    ResolveStackSwitcherMethod "inputShapeCombineRegion" o = Gtk.Widget.WidgetInputShapeCombineRegionMethodInfo
    ResolveStackSwitcherMethod "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveStackSwitcherMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveStackSwitcherMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    ResolveStackSwitcherMethod "insertChildAfter" o = Gtk.Box.BoxInsertChildAfterMethodInfo
    ResolveStackSwitcherMethod "isAncestor" o = Gtk.Widget.WidgetIsAncestorMethodInfo
    ResolveStackSwitcherMethod "isDrawable" o = Gtk.Widget.WidgetIsDrawableMethodInfo
    ResolveStackSwitcherMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveStackSwitcherMethod "isFocus" o = Gtk.Widget.WidgetIsFocusMethodInfo
    ResolveStackSwitcherMethod "isSensitive" o = Gtk.Widget.WidgetIsSensitiveMethodInfo
    ResolveStackSwitcherMethod "isToplevel" o = Gtk.Widget.WidgetIsToplevelMethodInfo
    ResolveStackSwitcherMethod "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveStackSwitcherMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    ResolveStackSwitcherMethod "listAccelClosures" o = Gtk.Widget.WidgetListAccelClosuresMethodInfo
    ResolveStackSwitcherMethod "listActionPrefixes" o = Gtk.Widget.WidgetListActionPrefixesMethodInfo
    ResolveStackSwitcherMethod "listMnemonicLabels" o = Gtk.Widget.WidgetListMnemonicLabelsMethodInfo
    ResolveStackSwitcherMethod "map" o = Gtk.Widget.WidgetMapMethodInfo
    ResolveStackSwitcherMethod "measure" o = Gtk.Widget.WidgetMeasureMethodInfo
    ResolveStackSwitcherMethod "mnemonicActivate" o = Gtk.Widget.WidgetMnemonicActivateMethodInfo
    ResolveStackSwitcherMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveStackSwitcherMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveStackSwitcherMethod "observeChildren" o = Gtk.Widget.WidgetObserveChildrenMethodInfo
    ResolveStackSwitcherMethod "observeControllers" o = Gtk.Widget.WidgetObserveControllersMethodInfo
    ResolveStackSwitcherMethod "parserFinished" o = Gtk.Buildable.BuildableParserFinishedMethodInfo
    ResolveStackSwitcherMethod "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveStackSwitcherMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveStackSwitcherMethod "queueComputeExpand" o = Gtk.Widget.WidgetQueueComputeExpandMethodInfo
    ResolveStackSwitcherMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveStackSwitcherMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveStackSwitcherMethod "queueResizeNoRedraw" o = Gtk.Widget.WidgetQueueResizeNoRedrawMethodInfo
    ResolveStackSwitcherMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveStackSwitcherMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveStackSwitcherMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveStackSwitcherMethod "registerSurface" o = Gtk.Widget.WidgetRegisterSurfaceMethodInfo
    ResolveStackSwitcherMethod "remove" o = Gtk.Container.ContainerRemoveMethodInfo
    ResolveStackSwitcherMethod "removeAccelerator" o = Gtk.Widget.WidgetRemoveAcceleratorMethodInfo
    ResolveStackSwitcherMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveStackSwitcherMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveStackSwitcherMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveStackSwitcherMethod "reorderChildAfter" o = Gtk.Box.BoxReorderChildAfterMethodInfo
    ResolveStackSwitcherMethod "resetStyle" o = Gtk.Widget.WidgetResetStyleMethodInfo
    ResolveStackSwitcherMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveStackSwitcherMethod "show" o = Gtk.Widget.WidgetShowMethodInfo
    ResolveStackSwitcherMethod "sizeAllocate" o = Gtk.Widget.WidgetSizeAllocateMethodInfo
    ResolveStackSwitcherMethod "snapshotChild" o = Gtk.Widget.WidgetSnapshotChildMethodInfo
    ResolveStackSwitcherMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveStackSwitcherMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveStackSwitcherMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveStackSwitcherMethod "translateCoordinates" o = Gtk.Widget.WidgetTranslateCoordinatesMethodInfo
    ResolveStackSwitcherMethod "triggerTooltipQuery" o = Gtk.Widget.WidgetTriggerTooltipQueryMethodInfo
    ResolveStackSwitcherMethod "unmap" o = Gtk.Widget.WidgetUnmapMethodInfo
    ResolveStackSwitcherMethod "unparent" o = Gtk.Widget.WidgetUnparentMethodInfo
    ResolveStackSwitcherMethod "unrealize" o = Gtk.Widget.WidgetUnrealizeMethodInfo
    ResolveStackSwitcherMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveStackSwitcherMethod "unregisterSurface" o = Gtk.Widget.WidgetUnregisterSurfaceMethodInfo
    ResolveStackSwitcherMethod "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveStackSwitcherMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveStackSwitcherMethod "getAccessible" o = Gtk.Widget.WidgetGetAccessibleMethodInfo
    ResolveStackSwitcherMethod "getActionGroup" o = Gtk.Widget.WidgetGetActionGroupMethodInfo
    ResolveStackSwitcherMethod "getAllocatedBaseline" o = Gtk.Widget.WidgetGetAllocatedBaselineMethodInfo
    ResolveStackSwitcherMethod "getAllocatedHeight" o = Gtk.Widget.WidgetGetAllocatedHeightMethodInfo
    ResolveStackSwitcherMethod "getAllocatedWidth" o = Gtk.Widget.WidgetGetAllocatedWidthMethodInfo
    ResolveStackSwitcherMethod "getAllocation" o = Gtk.Widget.WidgetGetAllocationMethodInfo
    ResolveStackSwitcherMethod "getAncestor" o = Gtk.Widget.WidgetGetAncestorMethodInfo
    ResolveStackSwitcherMethod "getBaselinePosition" o = Gtk.Box.BoxGetBaselinePositionMethodInfo
    ResolveStackSwitcherMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveStackSwitcherMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveStackSwitcherMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveStackSwitcherMethod "getChildren" o = Gtk.Container.ContainerGetChildrenMethodInfo
    ResolveStackSwitcherMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveStackSwitcherMethod "getCursor" o = Gtk.Widget.WidgetGetCursorMethodInfo
    ResolveStackSwitcherMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveStackSwitcherMethod "getDirection" o = Gtk.Widget.WidgetGetDirectionMethodInfo
    ResolveStackSwitcherMethod "getDisplay" o = Gtk.Widget.WidgetGetDisplayMethodInfo
    ResolveStackSwitcherMethod "getFirstChild" o = Gtk.Widget.WidgetGetFirstChildMethodInfo
    ResolveStackSwitcherMethod "getFocusChild" o = Gtk.Widget.WidgetGetFocusChildMethodInfo
    ResolveStackSwitcherMethod "getFocusHadjustment" o = Gtk.Container.ContainerGetFocusHadjustmentMethodInfo
    ResolveStackSwitcherMethod "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveStackSwitcherMethod "getFocusVadjustment" o = Gtk.Container.ContainerGetFocusVadjustmentMethodInfo
    ResolveStackSwitcherMethod "getFontMap" o = Gtk.Widget.WidgetGetFontMapMethodInfo
    ResolveStackSwitcherMethod "getFontOptions" o = Gtk.Widget.WidgetGetFontOptionsMethodInfo
    ResolveStackSwitcherMethod "getFrameClock" o = Gtk.Widget.WidgetGetFrameClockMethodInfo
    ResolveStackSwitcherMethod "getHalign" o = Gtk.Widget.WidgetGetHalignMethodInfo
    ResolveStackSwitcherMethod "getHasSurface" o = Gtk.Widget.WidgetGetHasSurfaceMethodInfo
    ResolveStackSwitcherMethod "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveStackSwitcherMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveStackSwitcherMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveStackSwitcherMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    ResolveStackSwitcherMethod "getHomogeneous" o = Gtk.Box.BoxGetHomogeneousMethodInfo
    ResolveStackSwitcherMethod "getInternalChild" o = Gtk.Buildable.BuildableGetInternalChildMethodInfo
    ResolveStackSwitcherMethod "getLastChild" o = Gtk.Widget.WidgetGetLastChildMethodInfo
    ResolveStackSwitcherMethod "getLayoutManager" o = Gtk.Widget.WidgetGetLayoutManagerMethodInfo
    ResolveStackSwitcherMethod "getMapped" o = Gtk.Widget.WidgetGetMappedMethodInfo
    ResolveStackSwitcherMethod "getMarginBottom" o = Gtk.Widget.WidgetGetMarginBottomMethodInfo
    ResolveStackSwitcherMethod "getMarginEnd" o = Gtk.Widget.WidgetGetMarginEndMethodInfo
    ResolveStackSwitcherMethod "getMarginStart" o = Gtk.Widget.WidgetGetMarginStartMethodInfo
    ResolveStackSwitcherMethod "getMarginTop" o = Gtk.Widget.WidgetGetMarginTopMethodInfo
    ResolveStackSwitcherMethod "getModifierMask" o = Gtk.Widget.WidgetGetModifierMaskMethodInfo
    ResolveStackSwitcherMethod "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveStackSwitcherMethod "getNextSibling" o = Gtk.Widget.WidgetGetNextSiblingMethodInfo
    ResolveStackSwitcherMethod "getOpacity" o = Gtk.Widget.WidgetGetOpacityMethodInfo
    ResolveStackSwitcherMethod "getOrientation" o = Gtk.Orientable.OrientableGetOrientationMethodInfo
    ResolveStackSwitcherMethod "getOverflow" o = Gtk.Widget.WidgetGetOverflowMethodInfo
    ResolveStackSwitcherMethod "getPangoContext" o = Gtk.Widget.WidgetGetPangoContextMethodInfo
    ResolveStackSwitcherMethod "getParent" o = Gtk.Widget.WidgetGetParentMethodInfo
    ResolveStackSwitcherMethod "getPath" o = Gtk.Widget.WidgetGetPathMethodInfo
    ResolveStackSwitcherMethod "getPathForChild" o = Gtk.Container.ContainerGetPathForChildMethodInfo
    ResolveStackSwitcherMethod "getPreferredSize" o = Gtk.Widget.WidgetGetPreferredSizeMethodInfo
    ResolveStackSwitcherMethod "getPrevSibling" o = Gtk.Widget.WidgetGetPrevSiblingMethodInfo
    ResolveStackSwitcherMethod "getPrimaryClipboard" o = Gtk.Widget.WidgetGetPrimaryClipboardMethodInfo
    ResolveStackSwitcherMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveStackSwitcherMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveStackSwitcherMethod "getRealized" o = Gtk.Widget.WidgetGetRealizedMethodInfo
    ResolveStackSwitcherMethod "getReceivesDefault" o = Gtk.Widget.WidgetGetReceivesDefaultMethodInfo
    ResolveStackSwitcherMethod "getRequestMode" o = Gtk.Widget.WidgetGetRequestModeMethodInfo
    ResolveStackSwitcherMethod "getRoot" o = Gtk.Widget.WidgetGetRootMethodInfo
    ResolveStackSwitcherMethod "getScaleFactor" o = Gtk.Widget.WidgetGetScaleFactorMethodInfo
    ResolveStackSwitcherMethod "getSensitive" o = Gtk.Widget.WidgetGetSensitiveMethodInfo
    ResolveStackSwitcherMethod "getSettings" o = Gtk.Widget.WidgetGetSettingsMethodInfo
    ResolveStackSwitcherMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveStackSwitcherMethod "getSpacing" o = Gtk.Box.BoxGetSpacingMethodInfo
    ResolveStackSwitcherMethod "getStack" o = StackSwitcherGetStackMethodInfo
    ResolveStackSwitcherMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveStackSwitcherMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveStackSwitcherMethod "getSupportMultidevice" o = Gtk.Widget.WidgetGetSupportMultideviceMethodInfo
    ResolveStackSwitcherMethod "getSurface" o = Gtk.Widget.WidgetGetSurfaceMethodInfo
    ResolveStackSwitcherMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveStackSwitcherMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveStackSwitcherMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    ResolveStackSwitcherMethod "getTooltipWindow" o = Gtk.Widget.WidgetGetTooltipWindowMethodInfo
    ResolveStackSwitcherMethod "getToplevel" o = Gtk.Widget.WidgetGetToplevelMethodInfo
    ResolveStackSwitcherMethod "getValign" o = Gtk.Widget.WidgetGetValignMethodInfo
    ResolveStackSwitcherMethod "getVexpand" o = Gtk.Widget.WidgetGetVexpandMethodInfo
    ResolveStackSwitcherMethod "getVexpandSet" o = Gtk.Widget.WidgetGetVexpandSetMethodInfo
    ResolveStackSwitcherMethod "getVisible" o = Gtk.Widget.WidgetGetVisibleMethodInfo
    ResolveStackSwitcherMethod "getWidth" o = Gtk.Widget.WidgetGetWidthMethodInfo
    ResolveStackSwitcherMethod "setAccelPath" o = Gtk.Widget.WidgetSetAccelPathMethodInfo
    ResolveStackSwitcherMethod "setBaselinePosition" o = Gtk.Box.BoxSetBaselinePositionMethodInfo
    ResolveStackSwitcherMethod "setBuildableProperty" o = Gtk.Buildable.BuildableSetBuildablePropertyMethodInfo
    ResolveStackSwitcherMethod "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveStackSwitcherMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveStackSwitcherMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveStackSwitcherMethod "setCursor" o = Gtk.Widget.WidgetSetCursorMethodInfo
    ResolveStackSwitcherMethod "setCursorFromName" o = Gtk.Widget.WidgetSetCursorFromNameMethodInfo
    ResolveStackSwitcherMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveStackSwitcherMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveStackSwitcherMethod "setDirection" o = Gtk.Widget.WidgetSetDirectionMethodInfo
    ResolveStackSwitcherMethod "setFocusChild" o = Gtk.Widget.WidgetSetFocusChildMethodInfo
    ResolveStackSwitcherMethod "setFocusHadjustment" o = Gtk.Container.ContainerSetFocusHadjustmentMethodInfo
    ResolveStackSwitcherMethod "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveStackSwitcherMethod "setFocusVadjustment" o = Gtk.Container.ContainerSetFocusVadjustmentMethodInfo
    ResolveStackSwitcherMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveStackSwitcherMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveStackSwitcherMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveStackSwitcherMethod "setHasSurface" o = Gtk.Widget.WidgetSetHasSurfaceMethodInfo
    ResolveStackSwitcherMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveStackSwitcherMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveStackSwitcherMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    ResolveStackSwitcherMethod "setHomogeneous" o = Gtk.Box.BoxSetHomogeneousMethodInfo
    ResolveStackSwitcherMethod "setLayoutManager" o = Gtk.Widget.WidgetSetLayoutManagerMethodInfo
    ResolveStackSwitcherMethod "setMarginBottom" o = Gtk.Widget.WidgetSetMarginBottomMethodInfo
    ResolveStackSwitcherMethod "setMarginEnd" o = Gtk.Widget.WidgetSetMarginEndMethodInfo
    ResolveStackSwitcherMethod "setMarginStart" o = Gtk.Widget.WidgetSetMarginStartMethodInfo
    ResolveStackSwitcherMethod "setMarginTop" o = Gtk.Widget.WidgetSetMarginTopMethodInfo
    ResolveStackSwitcherMethod "setName" o = Gtk.Widget.WidgetSetNameMethodInfo
    ResolveStackSwitcherMethod "setOpacity" o = Gtk.Widget.WidgetSetOpacityMethodInfo
    ResolveStackSwitcherMethod "setOrientation" o = Gtk.Orientable.OrientableSetOrientationMethodInfo
    ResolveStackSwitcherMethod "setOverflow" o = Gtk.Widget.WidgetSetOverflowMethodInfo
    ResolveStackSwitcherMethod "setParent" o = Gtk.Widget.WidgetSetParentMethodInfo
    ResolveStackSwitcherMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveStackSwitcherMethod "setReceivesDefault" o = Gtk.Widget.WidgetSetReceivesDefaultMethodInfo
    ResolveStackSwitcherMethod "setSensitive" o = Gtk.Widget.WidgetSetSensitiveMethodInfo
    ResolveStackSwitcherMethod "setSizeRequest" o = Gtk.Widget.WidgetSetSizeRequestMethodInfo
    ResolveStackSwitcherMethod "setSpacing" o = Gtk.Box.BoxSetSpacingMethodInfo
    ResolveStackSwitcherMethod "setStack" o = StackSwitcherSetStackMethodInfo
    ResolveStackSwitcherMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveStackSwitcherMethod "setSupportMultidevice" o = Gtk.Widget.WidgetSetSupportMultideviceMethodInfo
    ResolveStackSwitcherMethod "setSurface" o = Gtk.Widget.WidgetSetSurfaceMethodInfo
    ResolveStackSwitcherMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveStackSwitcherMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    ResolveStackSwitcherMethod "setTooltipWindow" o = Gtk.Widget.WidgetSetTooltipWindowMethodInfo
    ResolveStackSwitcherMethod "setValign" o = Gtk.Widget.WidgetSetValignMethodInfo
    ResolveStackSwitcherMethod "setVexpand" o = Gtk.Widget.WidgetSetVexpandMethodInfo
    ResolveStackSwitcherMethod "setVexpandSet" o = Gtk.Widget.WidgetSetVexpandSetMethodInfo
    ResolveStackSwitcherMethod "setVisible" o = Gtk.Widget.WidgetSetVisibleMethodInfo
    ResolveStackSwitcherMethod l o = O.MethodResolutionFailed l o

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

#endif

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

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

-- | Set the value of the “@stack@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' stackSwitcher [ #stack 'Data.GI.Base.Attributes.:=' value ]
-- @
setStackSwitcherStack :: (MonadIO m, IsStackSwitcher o, Gtk.Stack.IsStack a) => o -> a -> m ()
setStackSwitcherStack :: o -> a -> m ()
setStackSwitcherStack obj :: o
obj val :: a
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 a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "stack" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@stack@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructStackSwitcherStack :: (IsStackSwitcher o, Gtk.Stack.IsStack a) => a -> IO (GValueConstruct o)
constructStackSwitcherStack :: a -> IO (GValueConstruct o)
constructStackSwitcherStack val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "stack" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Set the value of the “@stack@” 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' #stack
-- @
clearStackSwitcherStack :: (MonadIO m, IsStackSwitcher o) => o -> m ()
clearStackSwitcherStack :: o -> m ()
clearStackSwitcherStack obj :: 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 Stack -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "stack" (Maybe Stack
forall a. Maybe a
Nothing :: Maybe Gtk.Stack.Stack)

#if defined(ENABLE_OVERLOADING)
data StackSwitcherStackPropertyInfo
instance AttrInfo StackSwitcherStackPropertyInfo where
    type AttrAllowedOps StackSwitcherStackPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint StackSwitcherStackPropertyInfo = IsStackSwitcher
    type AttrSetTypeConstraint StackSwitcherStackPropertyInfo = Gtk.Stack.IsStack
    type AttrTransferTypeConstraint StackSwitcherStackPropertyInfo = Gtk.Stack.IsStack
    type AttrTransferType StackSwitcherStackPropertyInfo = Gtk.Stack.Stack
    type AttrGetType StackSwitcherStackPropertyInfo = (Maybe Gtk.Stack.Stack)
    type AttrLabel StackSwitcherStackPropertyInfo = "stack"
    type AttrOrigin StackSwitcherStackPropertyInfo = StackSwitcher
    attrGet = getStackSwitcherStack
    attrSet = setStackSwitcherStack
    attrTransfer _ v = do
        unsafeCastTo Gtk.Stack.Stack v
    attrConstruct = constructStackSwitcherStack
    attrClear = clearStackSwitcherStack
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList StackSwitcher
type instance O.AttributeList StackSwitcher = StackSwitcherAttributeList
type StackSwitcherAttributeList = ('[ '("baselinePosition", Gtk.Box.BoxBaselinePositionPropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("expand", Gtk.Widget.WidgetExpandPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("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), '("isFocus", Gtk.Widget.WidgetIsFocusPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("margin", Gtk.Widget.WidgetMarginPropertyInfo), '("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), '("stack", StackSwitcherStackPropertyInfo), '("surface", Gtk.Widget.WidgetSurfacePropertyInfo), '("tooltipMarkup", Gtk.Widget.WidgetTooltipMarkupPropertyInfo), '("tooltipText", Gtk.Widget.WidgetTooltipTextPropertyInfo), '("valign", Gtk.Widget.WidgetValignPropertyInfo), '("vexpand", Gtk.Widget.WidgetVexpandPropertyInfo), '("vexpandSet", Gtk.Widget.WidgetVexpandSetPropertyInfo), '("visible", Gtk.Widget.WidgetVisiblePropertyInfo), '("widthRequest", Gtk.Widget.WidgetWidthRequestPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
stackSwitcherStack :: AttrLabelProxy "stack"
stackSwitcherStack = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList StackSwitcher = StackSwitcherSignalList
type StackSwitcherSignalList = ('[ '("accelClosuresChanged", Gtk.Widget.WidgetAccelClosuresChangedSignalInfo), '("add", Gtk.Container.ContainerAddSignalInfo), '("canActivateAccel", Gtk.Widget.WidgetCanActivateAccelSignalInfo), '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("dragBegin", Gtk.Widget.WidgetDragBeginSignalInfo), '("dragDataDelete", Gtk.Widget.WidgetDragDataDeleteSignalInfo), '("dragDataGet", Gtk.Widget.WidgetDragDataGetSignalInfo), '("dragDataReceived", Gtk.Widget.WidgetDragDataReceivedSignalInfo), '("dragDrop", Gtk.Widget.WidgetDragDropSignalInfo), '("dragEnd", Gtk.Widget.WidgetDragEndSignalInfo), '("dragFailed", Gtk.Widget.WidgetDragFailedSignalInfo), '("dragLeave", Gtk.Widget.WidgetDragLeaveSignalInfo), '("dragMotion", Gtk.Widget.WidgetDragMotionSignalInfo), '("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), '("popupMenu", Gtk.Widget.WidgetPopupMenuSignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("remove", Gtk.Container.ContainerRemoveSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("sizeAllocate", Gtk.Widget.WidgetSizeAllocateSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("styleUpdated", Gtk.Widget.WidgetStyleUpdatedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "gtk_stack_switcher_new" gtk_stack_switcher_new :: 
    IO (Ptr StackSwitcher)

-- | Create a new t'GI.Gtk.Objects.StackSwitcher.StackSwitcher'.
stackSwitcherNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m StackSwitcher
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.StackSwitcher.StackSwitcher'.
stackSwitcherNew :: m StackSwitcher
stackSwitcherNew  = IO StackSwitcher -> m StackSwitcher
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO StackSwitcher -> m StackSwitcher)
-> IO StackSwitcher -> m StackSwitcher
forall a b. (a -> b) -> a -> b
$ do
    Ptr StackSwitcher
result <- IO (Ptr StackSwitcher)
gtk_stack_switcher_new
    Text -> Ptr StackSwitcher -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "stackSwitcherNew" Ptr StackSwitcher
result
    StackSwitcher
result' <- ((ManagedPtr StackSwitcher -> StackSwitcher)
-> Ptr StackSwitcher -> IO StackSwitcher
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr StackSwitcher -> StackSwitcher
StackSwitcher) Ptr StackSwitcher
result
    StackSwitcher -> IO StackSwitcher
forall (m :: * -> *) a. Monad m => a -> m a
return StackSwitcher
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method StackSwitcher::get_stack
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "switcher"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StackSwitcher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStackSwitcher"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Stack" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_stack_switcher_get_stack" gtk_stack_switcher_get_stack :: 
    Ptr StackSwitcher ->                    -- switcher : TInterface (Name {namespace = "Gtk", name = "StackSwitcher"})
    IO (Ptr Gtk.Stack.Stack)

-- | Retrieves the stack.
-- See 'GI.Gtk.Objects.StackSwitcher.stackSwitcherSetStack'.
stackSwitcherGetStack ::
    (B.CallStack.HasCallStack, MonadIO m, IsStackSwitcher a) =>
    a
    -- ^ /@switcher@/: a t'GI.Gtk.Objects.StackSwitcher.StackSwitcher'
    -> m (Maybe Gtk.Stack.Stack)
    -- ^ __Returns:__ the stack, or 'P.Nothing' if
    --    none has been set explicitly.
stackSwitcherGetStack :: a -> m (Maybe Stack)
stackSwitcherGetStack switcher :: a
switcher = IO (Maybe Stack) -> m (Maybe Stack)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Stack) -> m (Maybe Stack))
-> IO (Maybe Stack) -> m (Maybe Stack)
forall a b. (a -> b) -> a -> b
$ do
    Ptr StackSwitcher
switcher' <- a -> IO (Ptr StackSwitcher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
switcher
    Ptr Stack
result <- Ptr StackSwitcher -> IO (Ptr Stack)
gtk_stack_switcher_get_stack Ptr StackSwitcher
switcher'
    Maybe Stack
maybeResult <- Ptr Stack -> (Ptr Stack -> IO Stack) -> IO (Maybe Stack)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Stack
result ((Ptr Stack -> IO Stack) -> IO (Maybe Stack))
-> (Ptr Stack -> IO Stack) -> IO (Maybe Stack)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Stack
result' -> do
        Stack
result'' <- ((ManagedPtr Stack -> Stack) -> Ptr Stack -> IO Stack
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Stack -> Stack
Gtk.Stack.Stack) Ptr Stack
result'
        Stack -> IO Stack
forall (m :: * -> *) a. Monad m => a -> m a
return Stack
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
switcher
    Maybe Stack -> IO (Maybe Stack)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Stack
maybeResult

#if defined(ENABLE_OVERLOADING)
data StackSwitcherGetStackMethodInfo
instance (signature ~ (m (Maybe Gtk.Stack.Stack)), MonadIO m, IsStackSwitcher a) => O.MethodInfo StackSwitcherGetStackMethodInfo a signature where
    overloadedMethod = stackSwitcherGetStack

#endif

-- method StackSwitcher::set_stack
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "switcher"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StackSwitcher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStackSwitcher"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "stack"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Stack" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStack" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_stack_switcher_set_stack" gtk_stack_switcher_set_stack :: 
    Ptr StackSwitcher ->                    -- switcher : TInterface (Name {namespace = "Gtk", name = "StackSwitcher"})
    Ptr Gtk.Stack.Stack ->                  -- stack : TInterface (Name {namespace = "Gtk", name = "Stack"})
    IO ()

-- | Sets the stack to control.
stackSwitcherSetStack ::
    (B.CallStack.HasCallStack, MonadIO m, IsStackSwitcher a, Gtk.Stack.IsStack b) =>
    a
    -- ^ /@switcher@/: a t'GI.Gtk.Objects.StackSwitcher.StackSwitcher'
    -> Maybe (b)
    -- ^ /@stack@/: a t'GI.Gtk.Objects.Stack.Stack'
    -> m ()
stackSwitcherSetStack :: a -> Maybe b -> m ()
stackSwitcherSetStack switcher :: a
switcher stack :: Maybe b
stack = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr StackSwitcher
switcher' <- a -> IO (Ptr StackSwitcher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
switcher
    Ptr Stack
maybeStack <- case Maybe b
stack of
        Nothing -> Ptr Stack -> IO (Ptr Stack)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Stack
forall a. Ptr a
nullPtr
        Just jStack :: b
jStack -> do
            Ptr Stack
jStack' <- b -> IO (Ptr Stack)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jStack
            Ptr Stack -> IO (Ptr Stack)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Stack
jStack'
    Ptr StackSwitcher -> Ptr Stack -> IO ()
gtk_stack_switcher_set_stack Ptr StackSwitcher
switcher' Ptr Stack
maybeStack
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
switcher
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
stack b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StackSwitcherSetStackMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsStackSwitcher a, Gtk.Stack.IsStack b) => O.MethodInfo StackSwitcherSetStackMethodInfo a signature where
    overloadedMethod = stackSwitcherSetStack

#endif