{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The @GtkStackSwitcher@ shows a row of buttons to switch between @GtkStack@
-- pages.
-- 
-- <<https://docs.gtk.org/gtk4/stackswitcher.png An example GtkStackSwitcher>>
-- 
-- It acts as a controller for the associated @GtkStack@.
-- 
-- All the content for the buttons comes from the properties of the stacks
-- t'GI.Gtk.Objects.StackPage.StackPage' objects; the button visibility in a @GtkStackSwitcher@
-- widget is controlled by the visibility of the child in the @GtkStack@.
-- 
-- It is possible to associate multiple @GtkStackSwitcher@ widgets
-- with the same @GtkStack@ widget.
-- 
-- = 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.
-- 
-- = Accessibility
-- 
-- @GtkStackSwitcher@ uses the 'GI.Gtk.Enums.AccessibleRoleTabList' role
-- and uses the 'GI.Gtk.Enums.AccessibleRoleTab' for its buttons.
-- 
-- = Orientable
-- 
-- Since GTK 4.4, @GtkStackSwitcher@ implements @GtkOrientable@ allowing
-- the stack switcher to be made vertical with
-- @gtk_orientable_set_orientation()@.

#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                         ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [actionSetEnabled]("GI.Gtk.Objects.Widget#g:method:actionSetEnabled"), [activate]("GI.Gtk.Objects.Widget#g:method:activate"), [activateAction]("GI.Gtk.Objects.Widget#g:method:activateAction"), [activateDefault]("GI.Gtk.Objects.Widget#g:method:activateDefault"), [addController]("GI.Gtk.Objects.Widget#g:method:addController"), [addCssClass]("GI.Gtk.Objects.Widget#g:method:addCssClass"), [addMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:addMnemonicLabel"), [addTickCallback]("GI.Gtk.Objects.Widget#g:method:addTickCallback"), [allocate]("GI.Gtk.Objects.Widget#g:method:allocate"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [childFocus]("GI.Gtk.Objects.Widget#g:method:childFocus"), [computeBounds]("GI.Gtk.Objects.Widget#g:method:computeBounds"), [computeExpand]("GI.Gtk.Objects.Widget#g:method:computeExpand"), [computePoint]("GI.Gtk.Objects.Widget#g:method:computePoint"), [computeTransform]("GI.Gtk.Objects.Widget#g:method:computeTransform"), [contains]("GI.Gtk.Objects.Widget#g:method:contains"), [createPangoContext]("GI.Gtk.Objects.Widget#g:method:createPangoContext"), [createPangoLayout]("GI.Gtk.Objects.Widget#g:method:createPangoLayout"), [disposeTemplate]("GI.Gtk.Objects.Widget#g:method:disposeTemplate"), [dragCheckThreshold]("GI.Gtk.Objects.Widget#g:method:dragCheckThreshold"), [errorBell]("GI.Gtk.Objects.Widget#g:method:errorBell"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [grabFocus]("GI.Gtk.Objects.Widget#g:method:grabFocus"), [hasCssClass]("GI.Gtk.Objects.Widget#g:method:hasCssClass"), [hasDefault]("GI.Gtk.Objects.Widget#g:method:hasDefault"), [hasFocus]("GI.Gtk.Objects.Widget#g:method:hasFocus"), [hasVisibleFocus]("GI.Gtk.Objects.Widget#g:method:hasVisibleFocus"), [hide]("GI.Gtk.Objects.Widget#g:method:hide"), [inDestruction]("GI.Gtk.Objects.Widget#g:method:inDestruction"), [initTemplate]("GI.Gtk.Objects.Widget#g:method:initTemplate"), [insertActionGroup]("GI.Gtk.Objects.Widget#g:method:insertActionGroup"), [insertAfter]("GI.Gtk.Objects.Widget#g:method:insertAfter"), [insertBefore]("GI.Gtk.Objects.Widget#g:method:insertBefore"), [isAncestor]("GI.Gtk.Objects.Widget#g:method:isAncestor"), [isDrawable]("GI.Gtk.Objects.Widget#g:method:isDrawable"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isFocus]("GI.Gtk.Objects.Widget#g:method:isFocus"), [isSensitive]("GI.Gtk.Objects.Widget#g:method:isSensitive"), [isVisible]("GI.Gtk.Objects.Widget#g:method:isVisible"), [keynavFailed]("GI.Gtk.Objects.Widget#g:method:keynavFailed"), [listMnemonicLabels]("GI.Gtk.Objects.Widget#g:method:listMnemonicLabels"), [map]("GI.Gtk.Objects.Widget#g:method:map"), [measure]("GI.Gtk.Objects.Widget#g:method:measure"), [mnemonicActivate]("GI.Gtk.Objects.Widget#g:method:mnemonicActivate"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [observeChildren]("GI.Gtk.Objects.Widget#g:method:observeChildren"), [observeControllers]("GI.Gtk.Objects.Widget#g:method:observeControllers"), [pick]("GI.Gtk.Objects.Widget#g:method:pick"), [queueAllocate]("GI.Gtk.Objects.Widget#g:method:queueAllocate"), [queueDraw]("GI.Gtk.Objects.Widget#g:method:queueDraw"), [queueResize]("GI.Gtk.Objects.Widget#g:method:queueResize"), [realize]("GI.Gtk.Objects.Widget#g:method:realize"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [removeController]("GI.Gtk.Objects.Widget#g:method:removeController"), [removeCssClass]("GI.Gtk.Objects.Widget#g:method:removeCssClass"), [removeMnemonicLabel]("GI.Gtk.Objects.Widget#g:method:removeMnemonicLabel"), [removeTickCallback]("GI.Gtk.Objects.Widget#g:method:removeTickCallback"), [resetProperty]("GI.Gtk.Interfaces.Accessible#g:method:resetProperty"), [resetRelation]("GI.Gtk.Interfaces.Accessible#g:method:resetRelation"), [resetState]("GI.Gtk.Interfaces.Accessible#g:method:resetState"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [shouldLayout]("GI.Gtk.Objects.Widget#g:method:shouldLayout"), [show]("GI.Gtk.Objects.Widget#g:method:show"), [sizeAllocate]("GI.Gtk.Objects.Widget#g:method:sizeAllocate"), [snapshotChild]("GI.Gtk.Objects.Widget#g:method:snapshotChild"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [translateCoordinates]("GI.Gtk.Objects.Widget#g:method:translateCoordinates"), [triggerTooltipQuery]("GI.Gtk.Objects.Widget#g:method:triggerTooltipQuery"), [unmap]("GI.Gtk.Objects.Widget#g:method:unmap"), [unparent]("GI.Gtk.Objects.Widget#g:method:unparent"), [unrealize]("GI.Gtk.Objects.Widget#g:method:unrealize"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unsetStateFlags]("GI.Gtk.Objects.Widget#g:method:unsetStateFlags"), [updateProperty]("GI.Gtk.Interfaces.Accessible#g:method:updateProperty"), [updateRelation]("GI.Gtk.Interfaces.Accessible#g:method:updateRelation"), [updateState]("GI.Gtk.Interfaces.Accessible#g:method:updateState"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccessibleRole]("GI.Gtk.Interfaces.Accessible#g:method:getAccessibleRole"), [getAllocatedBaseline]("GI.Gtk.Objects.Widget#g:method:getAllocatedBaseline"), [getAllocatedHeight]("GI.Gtk.Objects.Widget#g:method:getAllocatedHeight"), [getAllocatedWidth]("GI.Gtk.Objects.Widget#g:method:getAllocatedWidth"), [getAllocation]("GI.Gtk.Objects.Widget#g:method:getAllocation"), [getAncestor]("GI.Gtk.Objects.Widget#g:method:getAncestor"), [getBuildableId]("GI.Gtk.Interfaces.Buildable#g:method:getBuildableId"), [getCanFocus]("GI.Gtk.Objects.Widget#g:method:getCanFocus"), [getCanTarget]("GI.Gtk.Objects.Widget#g:method:getCanTarget"), [getChildVisible]("GI.Gtk.Objects.Widget#g:method:getChildVisible"), [getClipboard]("GI.Gtk.Objects.Widget#g:method:getClipboard"), [getCssClasses]("GI.Gtk.Objects.Widget#g:method:getCssClasses"), [getCssName]("GI.Gtk.Objects.Widget#g:method:getCssName"), [getCursor]("GI.Gtk.Objects.Widget#g:method:getCursor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDirection]("GI.Gtk.Objects.Widget#g:method:getDirection"), [getDisplay]("GI.Gtk.Objects.Widget#g:method:getDisplay"), [getFirstChild]("GI.Gtk.Objects.Widget#g:method:getFirstChild"), [getFocusChild]("GI.Gtk.Objects.Widget#g:method:getFocusChild"), [getFocusOnClick]("GI.Gtk.Objects.Widget#g:method:getFocusOnClick"), [getFocusable]("GI.Gtk.Objects.Widget#g:method:getFocusable"), [getFontMap]("GI.Gtk.Objects.Widget#g:method:getFontMap"), [getFontOptions]("GI.Gtk.Objects.Widget#g:method:getFontOptions"), [getFrameClock]("GI.Gtk.Objects.Widget#g:method:getFrameClock"), [getHalign]("GI.Gtk.Objects.Widget#g:method:getHalign"), [getHasTooltip]("GI.Gtk.Objects.Widget#g:method:getHasTooltip"), [getHeight]("GI.Gtk.Objects.Widget#g:method:getHeight"), [getHexpand]("GI.Gtk.Objects.Widget#g:method:getHexpand"), [getHexpandSet]("GI.Gtk.Objects.Widget#g:method:getHexpandSet"), [getLastChild]("GI.Gtk.Objects.Widget#g:method:getLastChild"), [getLayoutManager]("GI.Gtk.Objects.Widget#g:method:getLayoutManager"), [getMapped]("GI.Gtk.Objects.Widget#g:method:getMapped"), [getMarginBottom]("GI.Gtk.Objects.Widget#g:method:getMarginBottom"), [getMarginEnd]("GI.Gtk.Objects.Widget#g:method:getMarginEnd"), [getMarginStart]("GI.Gtk.Objects.Widget#g:method:getMarginStart"), [getMarginTop]("GI.Gtk.Objects.Widget#g:method:getMarginTop"), [getName]("GI.Gtk.Objects.Widget#g:method:getName"), [getNative]("GI.Gtk.Objects.Widget#g:method:getNative"), [getNextSibling]("GI.Gtk.Objects.Widget#g:method:getNextSibling"), [getOpacity]("GI.Gtk.Objects.Widget#g:method:getOpacity"), [getOrientation]("GI.Gtk.Interfaces.Orientable#g:method:getOrientation"), [getOverflow]("GI.Gtk.Objects.Widget#g:method:getOverflow"), [getPangoContext]("GI.Gtk.Objects.Widget#g:method:getPangoContext"), [getParent]("GI.Gtk.Objects.Widget#g:method:getParent"), [getPreferredSize]("GI.Gtk.Objects.Widget#g:method:getPreferredSize"), [getPrevSibling]("GI.Gtk.Objects.Widget#g:method:getPrevSibling"), [getPrimaryClipboard]("GI.Gtk.Objects.Widget#g:method:getPrimaryClipboard"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRealized]("GI.Gtk.Objects.Widget#g:method:getRealized"), [getReceivesDefault]("GI.Gtk.Objects.Widget#g:method:getReceivesDefault"), [getRequestMode]("GI.Gtk.Objects.Widget#g:method:getRequestMode"), [getRoot]("GI.Gtk.Objects.Widget#g:method:getRoot"), [getScaleFactor]("GI.Gtk.Objects.Widget#g:method:getScaleFactor"), [getSensitive]("GI.Gtk.Objects.Widget#g:method:getSensitive"), [getSettings]("GI.Gtk.Objects.Widget#g:method:getSettings"), [getSize]("GI.Gtk.Objects.Widget#g:method:getSize"), [getSizeRequest]("GI.Gtk.Objects.Widget#g:method:getSizeRequest"), [getStack]("GI.Gtk.Objects.StackSwitcher#g:method:getStack"), [getStateFlags]("GI.Gtk.Objects.Widget#g:method:getStateFlags"), [getStyleContext]("GI.Gtk.Objects.Widget#g:method:getStyleContext"), [getTemplateChild]("GI.Gtk.Objects.Widget#g:method:getTemplateChild"), [getTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:getTooltipMarkup"), [getTooltipText]("GI.Gtk.Objects.Widget#g:method:getTooltipText"), [getValign]("GI.Gtk.Objects.Widget#g:method:getValign"), [getVexpand]("GI.Gtk.Objects.Widget#g:method:getVexpand"), [getVexpandSet]("GI.Gtk.Objects.Widget#g:method:getVexpandSet"), [getVisible]("GI.Gtk.Objects.Widget#g:method:getVisible"), [getWidth]("GI.Gtk.Objects.Widget#g:method:getWidth").
-- 
-- ==== Setters
-- [setCanFocus]("GI.Gtk.Objects.Widget#g:method:setCanFocus"), [setCanTarget]("GI.Gtk.Objects.Widget#g:method:setCanTarget"), [setChildVisible]("GI.Gtk.Objects.Widget#g:method:setChildVisible"), [setCssClasses]("GI.Gtk.Objects.Widget#g:method:setCssClasses"), [setCursor]("GI.Gtk.Objects.Widget#g:method:setCursor"), [setCursorFromName]("GI.Gtk.Objects.Widget#g:method:setCursorFromName"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDirection]("GI.Gtk.Objects.Widget#g:method:setDirection"), [setFocusChild]("GI.Gtk.Objects.Widget#g:method:setFocusChild"), [setFocusOnClick]("GI.Gtk.Objects.Widget#g:method:setFocusOnClick"), [setFocusable]("GI.Gtk.Objects.Widget#g:method:setFocusable"), [setFontMap]("GI.Gtk.Objects.Widget#g:method:setFontMap"), [setFontOptions]("GI.Gtk.Objects.Widget#g:method:setFontOptions"), [setHalign]("GI.Gtk.Objects.Widget#g:method:setHalign"), [setHasTooltip]("GI.Gtk.Objects.Widget#g:method:setHasTooltip"), [setHexpand]("GI.Gtk.Objects.Widget#g:method:setHexpand"), [setHexpandSet]("GI.Gtk.Objects.Widget#g:method:setHexpandSet"), [setLayoutManager]("GI.Gtk.Objects.Widget#g:method:setLayoutManager"), [setMarginBottom]("GI.Gtk.Objects.Widget#g:method:setMarginBottom"), [setMarginEnd]("GI.Gtk.Objects.Widget#g:method:setMarginEnd"), [setMarginStart]("GI.Gtk.Objects.Widget#g:method:setMarginStart"), [setMarginTop]("GI.Gtk.Objects.Widget#g:method:setMarginTop"), [setName]("GI.Gtk.Objects.Widget#g:method:setName"), [setOpacity]("GI.Gtk.Objects.Widget#g:method:setOpacity"), [setOrientation]("GI.Gtk.Interfaces.Orientable#g:method:setOrientation"), [setOverflow]("GI.Gtk.Objects.Widget#g:method:setOverflow"), [setParent]("GI.Gtk.Objects.Widget#g:method:setParent"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setReceivesDefault]("GI.Gtk.Objects.Widget#g:method:setReceivesDefault"), [setSensitive]("GI.Gtk.Objects.Widget#g:method:setSensitive"), [setSizeRequest]("GI.Gtk.Objects.Widget#g:method:setSizeRequest"), [setStack]("GI.Gtk.Objects.StackSwitcher#g:method:setStack"), [setStateFlags]("GI.Gtk.Objects.Widget#g:method:setStateFlags"), [setTooltipMarkup]("GI.Gtk.Objects.Widget#g:method:setTooltipMarkup"), [setTooltipText]("GI.Gtk.Objects.Widget#g:method:setTooltipText"), [setValign]("GI.Gtk.Objects.Widget#g:method:setValign"), [setVexpand]("GI.Gtk.Objects.Widget#g:method:setVexpand"), [setVexpandSet]("GI.Gtk.Objects.Widget#g:method:setVexpandSet"), [setVisible]("GI.Gtk.Objects.Widget#g:method:setVisible").

#if defined(ENABLE_OVERLOADING)
    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#
-- | The stack.

#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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

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

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

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

foreign import ccall "gtk_stack_switcher_get_type"
    c_gtk_stack_switcher_get_type :: IO B.Types.GType

instance B.Types.TypedObject StackSwitcher where
    glibType :: IO GType
glibType = IO GType
c_gtk_stack_switcher_get_type

instance B.Types.GObject StackSwitcher

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

instance O.HasParentTypes StackSwitcher
type instance O.ParentTypes StackSwitcher = '[Gtk.Widget.Widget, GObject.Object.Object, Gtk.Accessible.Accessible, Gtk.Buildable.Buildable, Gtk.ConstraintTarget.ConstraintTarget, 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 :: (MIO.MonadIO m, IsStackSwitcher o) => o -> m StackSwitcher
toStackSwitcher :: forall (m :: * -> *) o.
(MonadIO m, IsStackSwitcher o) =>
o -> m StackSwitcher
toStackSwitcher = IO StackSwitcher -> m StackSwitcher
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr StackSwitcher -> StackSwitcher
StackSwitcher

-- | Convert 'StackSwitcher' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe StackSwitcher) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_stack_switcher_get_type
    gvalueSet_ :: Ptr GValue -> Maybe StackSwitcher -> IO ()
gvalueSet_ Ptr GValue
gv Maybe StackSwitcher
P.Nothing = Ptr GValue -> Ptr StackSwitcher -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr StackSwitcher
forall a. Ptr a
FP.nullPtr :: FP.Ptr StackSwitcher)
    gvalueSet_ Ptr GValue
gv (P.Just StackSwitcher
obj) = StackSwitcher -> (Ptr StackSwitcher -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr StackSwitcher
obj (Ptr GValue -> Ptr StackSwitcher -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe StackSwitcher)
gvalueGet_ Ptr GValue
gv = do
        Ptr StackSwitcher
ptr <- Ptr GValue -> IO (Ptr StackSwitcher)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr StackSwitcher)
        if Ptr StackSwitcher
ptr Ptr StackSwitcher -> Ptr StackSwitcher -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr StackSwitcher
forall a. Ptr a
FP.nullPtr
        then StackSwitcher -> Maybe StackSwitcher
forall a. a -> Maybe a
P.Just (StackSwitcher -> Maybe StackSwitcher)
-> IO StackSwitcher -> IO (Maybe StackSwitcher)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
        else Maybe StackSwitcher -> IO (Maybe StackSwitcher)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe StackSwitcher
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveStackSwitcherMethod (t :: Symbol) (o :: *) :: * where
    ResolveStackSwitcherMethod "actionSetEnabled" o = Gtk.Widget.WidgetActionSetEnabledMethodInfo
    ResolveStackSwitcherMethod "activate" o = Gtk.Widget.WidgetActivateMethodInfo
    ResolveStackSwitcherMethod "activateAction" o = Gtk.Widget.WidgetActivateActionMethodInfo
    ResolveStackSwitcherMethod "activateDefault" o = Gtk.Widget.WidgetActivateDefaultMethodInfo
    ResolveStackSwitcherMethod "addController" o = Gtk.Widget.WidgetAddControllerMethodInfo
    ResolveStackSwitcherMethod "addCssClass" o = Gtk.Widget.WidgetAddCssClassMethodInfo
    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 "childFocus" o = Gtk.Widget.WidgetChildFocusMethodInfo
    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 "contains" o = Gtk.Widget.WidgetContainsMethodInfo
    ResolveStackSwitcherMethod "createPangoContext" o = Gtk.Widget.WidgetCreatePangoContextMethodInfo
    ResolveStackSwitcherMethod "createPangoLayout" o = Gtk.Widget.WidgetCreatePangoLayoutMethodInfo
    ResolveStackSwitcherMethod "disposeTemplate" o = Gtk.Widget.WidgetDisposeTemplateMethodInfo
    ResolveStackSwitcherMethod "dragCheckThreshold" o = Gtk.Widget.WidgetDragCheckThresholdMethodInfo
    ResolveStackSwitcherMethod "errorBell" o = Gtk.Widget.WidgetErrorBellMethodInfo
    ResolveStackSwitcherMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveStackSwitcherMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveStackSwitcherMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveStackSwitcherMethod "grabFocus" o = Gtk.Widget.WidgetGrabFocusMethodInfo
    ResolveStackSwitcherMethod "hasCssClass" o = Gtk.Widget.WidgetHasCssClassMethodInfo
    ResolveStackSwitcherMethod "hasDefault" o = Gtk.Widget.WidgetHasDefaultMethodInfo
    ResolveStackSwitcherMethod "hasFocus" o = Gtk.Widget.WidgetHasFocusMethodInfo
    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 "insertActionGroup" o = Gtk.Widget.WidgetInsertActionGroupMethodInfo
    ResolveStackSwitcherMethod "insertAfter" o = Gtk.Widget.WidgetInsertAfterMethodInfo
    ResolveStackSwitcherMethod "insertBefore" o = Gtk.Widget.WidgetInsertBeforeMethodInfo
    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 "isVisible" o = Gtk.Widget.WidgetIsVisibleMethodInfo
    ResolveStackSwitcherMethod "keynavFailed" o = Gtk.Widget.WidgetKeynavFailedMethodInfo
    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 "pick" o = Gtk.Widget.WidgetPickMethodInfo
    ResolveStackSwitcherMethod "queueAllocate" o = Gtk.Widget.WidgetQueueAllocateMethodInfo
    ResolveStackSwitcherMethod "queueDraw" o = Gtk.Widget.WidgetQueueDrawMethodInfo
    ResolveStackSwitcherMethod "queueResize" o = Gtk.Widget.WidgetQueueResizeMethodInfo
    ResolveStackSwitcherMethod "realize" o = Gtk.Widget.WidgetRealizeMethodInfo
    ResolveStackSwitcherMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveStackSwitcherMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveStackSwitcherMethod "removeController" o = Gtk.Widget.WidgetRemoveControllerMethodInfo
    ResolveStackSwitcherMethod "removeCssClass" o = Gtk.Widget.WidgetRemoveCssClassMethodInfo
    ResolveStackSwitcherMethod "removeMnemonicLabel" o = Gtk.Widget.WidgetRemoveMnemonicLabelMethodInfo
    ResolveStackSwitcherMethod "removeTickCallback" o = Gtk.Widget.WidgetRemoveTickCallbackMethodInfo
    ResolveStackSwitcherMethod "resetProperty" o = Gtk.Accessible.AccessibleResetPropertyMethodInfo
    ResolveStackSwitcherMethod "resetRelation" o = Gtk.Accessible.AccessibleResetRelationMethodInfo
    ResolveStackSwitcherMethod "resetState" o = Gtk.Accessible.AccessibleResetStateMethodInfo
    ResolveStackSwitcherMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveStackSwitcherMethod "shouldLayout" o = Gtk.Widget.WidgetShouldLayoutMethodInfo
    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 "unsetStateFlags" o = Gtk.Widget.WidgetUnsetStateFlagsMethodInfo
    ResolveStackSwitcherMethod "updateProperty" o = Gtk.Accessible.AccessibleUpdatePropertyMethodInfo
    ResolveStackSwitcherMethod "updateRelation" o = Gtk.Accessible.AccessibleUpdateRelationMethodInfo
    ResolveStackSwitcherMethod "updateState" o = Gtk.Accessible.AccessibleUpdateStateMethodInfo
    ResolveStackSwitcherMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveStackSwitcherMethod "getAccessibleRole" o = Gtk.Accessible.AccessibleGetAccessibleRoleMethodInfo
    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 "getBuildableId" o = Gtk.Buildable.BuildableGetBuildableIdMethodInfo
    ResolveStackSwitcherMethod "getCanFocus" o = Gtk.Widget.WidgetGetCanFocusMethodInfo
    ResolveStackSwitcherMethod "getCanTarget" o = Gtk.Widget.WidgetGetCanTargetMethodInfo
    ResolveStackSwitcherMethod "getChildVisible" o = Gtk.Widget.WidgetGetChildVisibleMethodInfo
    ResolveStackSwitcherMethod "getClipboard" o = Gtk.Widget.WidgetGetClipboardMethodInfo
    ResolveStackSwitcherMethod "getCssClasses" o = Gtk.Widget.WidgetGetCssClassesMethodInfo
    ResolveStackSwitcherMethod "getCssName" o = Gtk.Widget.WidgetGetCssNameMethodInfo
    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 "getFocusOnClick" o = Gtk.Widget.WidgetGetFocusOnClickMethodInfo
    ResolveStackSwitcherMethod "getFocusable" o = Gtk.Widget.WidgetGetFocusableMethodInfo
    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 "getHasTooltip" o = Gtk.Widget.WidgetGetHasTooltipMethodInfo
    ResolveStackSwitcherMethod "getHeight" o = Gtk.Widget.WidgetGetHeightMethodInfo
    ResolveStackSwitcherMethod "getHexpand" o = Gtk.Widget.WidgetGetHexpandMethodInfo
    ResolveStackSwitcherMethod "getHexpandSet" o = Gtk.Widget.WidgetGetHexpandSetMethodInfo
    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 "getName" o = Gtk.Widget.WidgetGetNameMethodInfo
    ResolveStackSwitcherMethod "getNative" o = Gtk.Widget.WidgetGetNativeMethodInfo
    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 "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 "getSize" o = Gtk.Widget.WidgetGetSizeMethodInfo
    ResolveStackSwitcherMethod "getSizeRequest" o = Gtk.Widget.WidgetGetSizeRequestMethodInfo
    ResolveStackSwitcherMethod "getStack" o = StackSwitcherGetStackMethodInfo
    ResolveStackSwitcherMethod "getStateFlags" o = Gtk.Widget.WidgetGetStateFlagsMethodInfo
    ResolveStackSwitcherMethod "getStyleContext" o = Gtk.Widget.WidgetGetStyleContextMethodInfo
    ResolveStackSwitcherMethod "getTemplateChild" o = Gtk.Widget.WidgetGetTemplateChildMethodInfo
    ResolveStackSwitcherMethod "getTooltipMarkup" o = Gtk.Widget.WidgetGetTooltipMarkupMethodInfo
    ResolveStackSwitcherMethod "getTooltipText" o = Gtk.Widget.WidgetGetTooltipTextMethodInfo
    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 "setCanFocus" o = Gtk.Widget.WidgetSetCanFocusMethodInfo
    ResolveStackSwitcherMethod "setCanTarget" o = Gtk.Widget.WidgetSetCanTargetMethodInfo
    ResolveStackSwitcherMethod "setChildVisible" o = Gtk.Widget.WidgetSetChildVisibleMethodInfo
    ResolveStackSwitcherMethod "setCssClasses" o = Gtk.Widget.WidgetSetCssClassesMethodInfo
    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 "setFocusOnClick" o = Gtk.Widget.WidgetSetFocusOnClickMethodInfo
    ResolveStackSwitcherMethod "setFocusable" o = Gtk.Widget.WidgetSetFocusableMethodInfo
    ResolveStackSwitcherMethod "setFontMap" o = Gtk.Widget.WidgetSetFontMapMethodInfo
    ResolveStackSwitcherMethod "setFontOptions" o = Gtk.Widget.WidgetSetFontOptionsMethodInfo
    ResolveStackSwitcherMethod "setHalign" o = Gtk.Widget.WidgetSetHalignMethodInfo
    ResolveStackSwitcherMethod "setHasTooltip" o = Gtk.Widget.WidgetSetHasTooltipMethodInfo
    ResolveStackSwitcherMethod "setHexpand" o = Gtk.Widget.WidgetSetHexpandMethodInfo
    ResolveStackSwitcherMethod "setHexpandSet" o = Gtk.Widget.WidgetSetHexpandSetMethodInfo
    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 "setStack" o = StackSwitcherSetStackMethodInfo
    ResolveStackSwitcherMethod "setStateFlags" o = Gtk.Widget.WidgetSetStateFlagsMethodInfo
    ResolveStackSwitcherMethod "setTooltipMarkup" o = Gtk.Widget.WidgetSetTooltipMarkupMethodInfo
    ResolveStackSwitcherMethod "setTooltipText" o = Gtk.Widget.WidgetSetTooltipTextMethodInfo
    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.OverloadedMethod 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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveStackSwitcherMethod t StackSwitcher, O.OverloadedMethod info StackSwitcher p, R.HasField t StackSwitcher p) => R.HasField t StackSwitcher p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveStackSwitcherMethod t StackSwitcher, O.OverloadedMethodInfo info StackSwitcher) => OL.IsLabel t (O.MethodProxy info StackSwitcher) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#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 :: forall (m :: * -> *) o.
(MonadIO m, IsStackSwitcher o) =>
o -> m (Maybe Stack)
getStackSwitcherStack o
obj = IO (Maybe Stack) -> m (Maybe Stack)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"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 :: forall (m :: * -> *) o a.
(MonadIO m, IsStackSwitcher o, IsStack a) =>
o -> a -> m ()
setStackSwitcherStack o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"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, MIO.MonadIO m, Gtk.Stack.IsStack a) => a -> m (GValueConstruct o)
constructStackSwitcherStack :: forall o (m :: * -> *) a.
(IsStackSwitcher o, MonadIO m, IsStack a) =>
a -> m (GValueConstruct o)
constructStackSwitcherStack a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"stack" (a -> Maybe a
forall a. a -> Maybe a
P.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 :: forall (m :: * -> *) o. (MonadIO m, IsStackSwitcher o) => o -> m ()
clearStackSwitcherStack o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Stack -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"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
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.StackSwitcher.stack"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-StackSwitcher.html#g:attr:stack"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList StackSwitcher
type instance O.AttributeList StackSwitcher = StackSwitcherAttributeList
type StackSwitcherAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("canFocus", Gtk.Widget.WidgetCanFocusPropertyInfo), '("canTarget", Gtk.Widget.WidgetCanTargetPropertyInfo), '("cssClasses", Gtk.Widget.WidgetCssClassesPropertyInfo), '("cssName", Gtk.Widget.WidgetCssNamePropertyInfo), '("cursor", Gtk.Widget.WidgetCursorPropertyInfo), '("focusOnClick", Gtk.Widget.WidgetFocusOnClickPropertyInfo), '("focusable", Gtk.Widget.WidgetFocusablePropertyInfo), '("halign", Gtk.Widget.WidgetHalignPropertyInfo), '("hasDefault", Gtk.Widget.WidgetHasDefaultPropertyInfo), '("hasFocus", Gtk.Widget.WidgetHasFocusPropertyInfo), '("hasTooltip", Gtk.Widget.WidgetHasTooltipPropertyInfo), '("heightRequest", Gtk.Widget.WidgetHeightRequestPropertyInfo), '("hexpand", Gtk.Widget.WidgetHexpandPropertyInfo), '("hexpandSet", Gtk.Widget.WidgetHexpandSetPropertyInfo), '("layoutManager", Gtk.Widget.WidgetLayoutManagerPropertyInfo), '("marginBottom", Gtk.Widget.WidgetMarginBottomPropertyInfo), '("marginEnd", Gtk.Widget.WidgetMarginEndPropertyInfo), '("marginStart", Gtk.Widget.WidgetMarginStartPropertyInfo), '("marginTop", Gtk.Widget.WidgetMarginTopPropertyInfo), '("name", Gtk.Widget.WidgetNamePropertyInfo), '("opacity", Gtk.Widget.WidgetOpacityPropertyInfo), '("orientation", Gtk.Orientable.OrientableOrientationPropertyInfo), '("overflow", Gtk.Widget.WidgetOverflowPropertyInfo), '("parent", Gtk.Widget.WidgetParentPropertyInfo), '("receivesDefault", Gtk.Widget.WidgetReceivesDefaultPropertyInfo), '("root", Gtk.Widget.WidgetRootPropertyInfo), '("scaleFactor", Gtk.Widget.WidgetScaleFactorPropertyInfo), '("sensitive", Gtk.Widget.WidgetSensitivePropertyInfo), '("stack", StackSwitcherStackPropertyInfo), '("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 = ('[ '("destroy", Gtk.Widget.WidgetDestroySignalInfo), '("directionChanged", Gtk.Widget.WidgetDirectionChangedSignalInfo), '("hide", Gtk.Widget.WidgetHideSignalInfo), '("keynavFailed", Gtk.Widget.WidgetKeynavFailedSignalInfo), '("map", Gtk.Widget.WidgetMapSignalInfo), '("mnemonicActivate", Gtk.Widget.WidgetMnemonicActivateSignalInfo), '("moveFocus", Gtk.Widget.WidgetMoveFocusSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("queryTooltip", Gtk.Widget.WidgetQueryTooltipSignalInfo), '("realize", Gtk.Widget.WidgetRealizeSignalInfo), '("show", Gtk.Widget.WidgetShowSignalInfo), '("stateFlagsChanged", Gtk.Widget.WidgetStateFlagsChangedSignalInfo), '("unmap", Gtk.Widget.WidgetUnmapSignalInfo), '("unrealize", Gtk.Widget.WidgetUnrealizeSignalInfo)] :: [(Symbol, *)])

#endif

-- method 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 @GtkStackSwitcher@.
stackSwitcherNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m StackSwitcher
    -- ^ __Returns:__ a new @GtkStackSwitcher@.
stackSwitcherNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m StackSwitcher
stackSwitcherNew  = IO StackSwitcher -> m StackSwitcher
forall a. IO a -> m a
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 Text
"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 a. a -> IO a
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.
stackSwitcherGetStack ::
    (B.CallStack.HasCallStack, MonadIO m, IsStackSwitcher a) =>
    a
    -- ^ /@switcher@/: a @GtkStackSwitcher@
    -> m (Maybe Gtk.Stack.Stack)
    -- ^ __Returns:__ the stack
stackSwitcherGetStack :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStackSwitcher a) =>
a -> m (Maybe Stack)
stackSwitcherGetStack a
switcher = IO (Maybe Stack) -> m (Maybe Stack)
forall a. IO a -> m a
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
$ \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 a. a -> IO a
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 a. a -> IO a
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.OverloadedMethod StackSwitcherGetStackMethodInfo a signature where
    overloadedMethod = stackSwitcherGetStack

instance O.OverloadedMethodInfo StackSwitcherGetStackMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.StackSwitcher.stackSwitcherGetStack",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-StackSwitcher.html#v: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 @GtkStackSwitcher@
    -> Maybe (b)
    -- ^ /@stack@/: a @GtkStack@
    -> m ()
stackSwitcherSetStack :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsStackSwitcher a, IsStack b) =>
a -> Maybe b -> m ()
stackSwitcherSetStack a
switcher Maybe b
stack = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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
        Maybe b
Nothing -> Ptr Stack -> IO (Ptr Stack)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Stack
forall a. Ptr a
nullPtr
        Just 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 a. a -> IO a
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 a. a -> IO a
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.OverloadedMethod StackSwitcherSetStackMethodInfo a signature where
    overloadedMethod = stackSwitcherSetStack

instance O.OverloadedMethodInfo StackSwitcherSetStackMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.StackSwitcher.stackSwitcherSetStack",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-StackSwitcher.html#v:stackSwitcherSetStack"
        })


#endif