{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- /No description available in the introspection data./

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

module GI.Gtk.Objects.StackPage
    ( 

-- * Exported types
    StackPage(..)                           ,
    IsStackPage                             ,
    toStackPage                             ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [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"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [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"), [getChild]("GI.Gtk.Objects.StackPage#g:method:getChild"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getIconName]("GI.Gtk.Objects.StackPage#g:method:getIconName"), [getName]("GI.Gtk.Objects.StackPage#g:method:getName"), [getNeedsAttention]("GI.Gtk.Objects.StackPage#g:method:getNeedsAttention"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getTitle]("GI.Gtk.Objects.StackPage#g:method:getTitle"), [getUseUnderline]("GI.Gtk.Objects.StackPage#g:method:getUseUnderline"), [getVisible]("GI.Gtk.Objects.StackPage#g:method:getVisible").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setIconName]("GI.Gtk.Objects.StackPage#g:method:setIconName"), [setName]("GI.Gtk.Objects.StackPage#g:method:setName"), [setNeedsAttention]("GI.Gtk.Objects.StackPage#g:method:setNeedsAttention"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setTitle]("GI.Gtk.Objects.StackPage#g:method:setTitle"), [setUseUnderline]("GI.Gtk.Objects.StackPage#g:method:setUseUnderline"), [setVisible]("GI.Gtk.Objects.StackPage#g:method:setVisible").

#if defined(ENABLE_OVERLOADING)
    ResolveStackPageMethod                  ,
#endif

-- ** getChild #method:getChild#

#if defined(ENABLE_OVERLOADING)
    StackPageGetChildMethodInfo             ,
#endif
    stackPageGetChild                       ,


-- ** getIconName #method:getIconName#

#if defined(ENABLE_OVERLOADING)
    StackPageGetIconNameMethodInfo          ,
#endif
    stackPageGetIconName                    ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    StackPageGetNameMethodInfo              ,
#endif
    stackPageGetName                        ,


-- ** getNeedsAttention #method:getNeedsAttention#

#if defined(ENABLE_OVERLOADING)
    StackPageGetNeedsAttentionMethodInfo    ,
#endif
    stackPageGetNeedsAttention              ,


-- ** getTitle #method:getTitle#

#if defined(ENABLE_OVERLOADING)
    StackPageGetTitleMethodInfo             ,
#endif
    stackPageGetTitle                       ,


-- ** getUseUnderline #method:getUseUnderline#

#if defined(ENABLE_OVERLOADING)
    StackPageGetUseUnderlineMethodInfo      ,
#endif
    stackPageGetUseUnderline                ,


-- ** getVisible #method:getVisible#

#if defined(ENABLE_OVERLOADING)
    StackPageGetVisibleMethodInfo           ,
#endif
    stackPageGetVisible                     ,


-- ** setIconName #method:setIconName#

#if defined(ENABLE_OVERLOADING)
    StackPageSetIconNameMethodInfo          ,
#endif
    stackPageSetIconName                    ,


-- ** setName #method:setName#

#if defined(ENABLE_OVERLOADING)
    StackPageSetNameMethodInfo              ,
#endif
    stackPageSetName                        ,


-- ** setNeedsAttention #method:setNeedsAttention#

#if defined(ENABLE_OVERLOADING)
    StackPageSetNeedsAttentionMethodInfo    ,
#endif
    stackPageSetNeedsAttention              ,


-- ** setTitle #method:setTitle#

#if defined(ENABLE_OVERLOADING)
    StackPageSetTitleMethodInfo             ,
#endif
    stackPageSetTitle                       ,


-- ** setUseUnderline #method:setUseUnderline#

#if defined(ENABLE_OVERLOADING)
    StackPageSetUseUnderlineMethodInfo      ,
#endif
    stackPageSetUseUnderline                ,


-- ** setVisible #method:setVisible#

#if defined(ENABLE_OVERLOADING)
    StackPageSetVisibleMethodInfo           ,
#endif
    stackPageSetVisible                     ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    StackPageChildPropertyInfo              ,
#endif
    constructStackPageChild                 ,
    getStackPageChild                       ,
#if defined(ENABLE_OVERLOADING)
    stackPageChild                          ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    StackPageIconNamePropertyInfo           ,
#endif
    constructStackPageIconName              ,
    getStackPageIconName                    ,
    setStackPageIconName                    ,
#if defined(ENABLE_OVERLOADING)
    stackPageIconName                       ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    StackPageNamePropertyInfo               ,
#endif
    constructStackPageName                  ,
    getStackPageName                        ,
#if defined(ENABLE_OVERLOADING)
    stackPageName                           ,
#endif


-- ** needsAttention #attr:needsAttention#
-- | Sets a flag specifying whether the page requires the user attention.
-- This is used by the t'GI.Gtk.Objects.StackSwitcher.StackSwitcher' to change the appearance of the
-- corresponding button when a page needs attention and it is not the
-- current one.

#if defined(ENABLE_OVERLOADING)
    StackPageNeedsAttentionPropertyInfo     ,
#endif
    constructStackPageNeedsAttention        ,
    getStackPageNeedsAttention              ,
    setStackPageNeedsAttention              ,
#if defined(ENABLE_OVERLOADING)
    stackPageNeedsAttention                 ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    StackPageTitlePropertyInfo              ,
#endif
    constructStackPageTitle                 ,
    getStackPageTitle                       ,
    setStackPageTitle                       ,
#if defined(ENABLE_OVERLOADING)
    stackPageTitle                          ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    StackPageUseUnderlinePropertyInfo       ,
#endif
    constructStackPageUseUnderline          ,
    getStackPageUseUnderline                ,
    setStackPageUseUnderline                ,
#if defined(ENABLE_OVERLOADING)
    stackPageUseUnderline                   ,
#endif


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

#if defined(ENABLE_OVERLOADING)
    StackPageVisiblePropertyInfo            ,
#endif
    constructStackPageVisible               ,
    getStackPageVisible                     ,
    setStackPageVisible                     ,
#if defined(ENABLE_OVERLOADING)
    stackPageVisible                        ,
#endif




    ) where

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

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

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

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

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

foreign import ccall "gtk_stack_page_get_type"
    c_gtk_stack_page_get_type :: IO B.Types.GType

instance B.Types.TypedObject StackPage where
    glibType :: IO GType
glibType = IO GType
c_gtk_stack_page_get_type

instance B.Types.GObject StackPage

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

instance O.HasParentTypes StackPage
type instance O.ParentTypes StackPage = '[GObject.Object.Object, Gtk.Accessible.Accessible]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveStackPageMethod (t :: Symbol) (o :: *) :: * where
    ResolveStackPageMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveStackPageMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveStackPageMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveStackPageMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveStackPageMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveStackPageMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveStackPageMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveStackPageMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveStackPageMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveStackPageMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveStackPageMethod "resetProperty" o = Gtk.Accessible.AccessibleResetPropertyMethodInfo
    ResolveStackPageMethod "resetRelation" o = Gtk.Accessible.AccessibleResetRelationMethodInfo
    ResolveStackPageMethod "resetState" o = Gtk.Accessible.AccessibleResetStateMethodInfo
    ResolveStackPageMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveStackPageMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveStackPageMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveStackPageMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveStackPageMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveStackPageMethod "updateProperty" o = Gtk.Accessible.AccessibleUpdatePropertyMethodInfo
    ResolveStackPageMethod "updateRelation" o = Gtk.Accessible.AccessibleUpdateRelationMethodInfo
    ResolveStackPageMethod "updateState" o = Gtk.Accessible.AccessibleUpdateStateMethodInfo
    ResolveStackPageMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveStackPageMethod "getAccessibleRole" o = Gtk.Accessible.AccessibleGetAccessibleRoleMethodInfo
    ResolveStackPageMethod "getChild" o = StackPageGetChildMethodInfo
    ResolveStackPageMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveStackPageMethod "getIconName" o = StackPageGetIconNameMethodInfo
    ResolveStackPageMethod "getName" o = StackPageGetNameMethodInfo
    ResolveStackPageMethod "getNeedsAttention" o = StackPageGetNeedsAttentionMethodInfo
    ResolveStackPageMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveStackPageMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveStackPageMethod "getTitle" o = StackPageGetTitleMethodInfo
    ResolveStackPageMethod "getUseUnderline" o = StackPageGetUseUnderlineMethodInfo
    ResolveStackPageMethod "getVisible" o = StackPageGetVisibleMethodInfo
    ResolveStackPageMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveStackPageMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveStackPageMethod "setIconName" o = StackPageSetIconNameMethodInfo
    ResolveStackPageMethod "setName" o = StackPageSetNameMethodInfo
    ResolveStackPageMethod "setNeedsAttention" o = StackPageSetNeedsAttentionMethodInfo
    ResolveStackPageMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveStackPageMethod "setTitle" o = StackPageSetTitleMethodInfo
    ResolveStackPageMethod "setUseUnderline" o = StackPageSetUseUnderlineMethodInfo
    ResolveStackPageMethod "setVisible" o = StackPageSetVisibleMethodInfo
    ResolveStackPageMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "child"
   -- Type: TInterface (Name {namespace = "Gtk", name = "Widget"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

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

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

#if defined(ENABLE_OVERLOADING)
data StackPageChildPropertyInfo
instance AttrInfo StackPageChildPropertyInfo where
    type AttrAllowedOps StackPageChildPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint StackPageChildPropertyInfo = IsStackPage
    type AttrSetTypeConstraint StackPageChildPropertyInfo = Gtk.Widget.IsWidget
    type AttrTransferTypeConstraint StackPageChildPropertyInfo = Gtk.Widget.IsWidget
    type AttrTransferType StackPageChildPropertyInfo = Gtk.Widget.Widget
    type AttrGetType StackPageChildPropertyInfo = Gtk.Widget.Widget
    type AttrLabel StackPageChildPropertyInfo = "child"
    type AttrOrigin StackPageChildPropertyInfo = StackPage
    attrGet = getStackPageChild
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gtk.Widget.Widget v
    attrConstruct = constructStackPageChild
    attrClear = undefined
#endif

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data StackPageIconNamePropertyInfo
instance AttrInfo StackPageIconNamePropertyInfo where
    type AttrAllowedOps StackPageIconNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint StackPageIconNamePropertyInfo = IsStackPage
    type AttrSetTypeConstraint StackPageIconNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint StackPageIconNamePropertyInfo = (~) T.Text
    type AttrTransferType StackPageIconNamePropertyInfo = T.Text
    type AttrGetType StackPageIconNamePropertyInfo = (Maybe T.Text)
    type AttrLabel StackPageIconNamePropertyInfo = "icon-name"
    type AttrOrigin StackPageIconNamePropertyInfo = StackPage
    attrGet = getStackPageIconName
    attrSet = setStackPageIconName
    attrTransfer _ v = do
        return v
    attrConstruct = constructStackPageIconName
    attrClear = undefined
#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data StackPageNamePropertyInfo
instance AttrInfo StackPageNamePropertyInfo where
    type AttrAllowedOps StackPageNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint StackPageNamePropertyInfo = IsStackPage
    type AttrSetTypeConstraint StackPageNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint StackPageNamePropertyInfo = (~) T.Text
    type AttrTransferType StackPageNamePropertyInfo = T.Text
    type AttrGetType StackPageNamePropertyInfo = (Maybe T.Text)
    type AttrLabel StackPageNamePropertyInfo = "name"
    type AttrOrigin StackPageNamePropertyInfo = StackPage
    attrGet = getStackPageName
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructStackPageName
    attrClear = undefined
#endif

-- VVV Prop "needs-attention"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

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

-- | Set the value of the “@needs-attention@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' stackPage [ #needsAttention 'Data.GI.Base.Attributes.:=' value ]
-- @
setStackPageNeedsAttention :: (MonadIO m, IsStackPage o) => o -> Bool -> m ()
setStackPageNeedsAttention :: forall (m :: * -> *) o.
(MonadIO m, IsStackPage o) =>
o -> Bool -> m ()
setStackPageNeedsAttention o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"needs-attention" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@needs-attention@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructStackPageNeedsAttention :: (IsStackPage o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructStackPageNeedsAttention :: forall o (m :: * -> *).
(IsStackPage o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructStackPageNeedsAttention Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"needs-attention" Bool
val

#if defined(ENABLE_OVERLOADING)
data StackPageNeedsAttentionPropertyInfo
instance AttrInfo StackPageNeedsAttentionPropertyInfo where
    type AttrAllowedOps StackPageNeedsAttentionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint StackPageNeedsAttentionPropertyInfo = IsStackPage
    type AttrSetTypeConstraint StackPageNeedsAttentionPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint StackPageNeedsAttentionPropertyInfo = (~) Bool
    type AttrTransferType StackPageNeedsAttentionPropertyInfo = Bool
    type AttrGetType StackPageNeedsAttentionPropertyInfo = Bool
    type AttrLabel StackPageNeedsAttentionPropertyInfo = "needs-attention"
    type AttrOrigin StackPageNeedsAttentionPropertyInfo = StackPage
    attrGet = getStackPageNeedsAttention
    attrSet = setStackPageNeedsAttention
    attrTransfer _ v = do
        return v
    attrConstruct = constructStackPageNeedsAttention
    attrClear = undefined
#endif

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

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

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

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

#if defined(ENABLE_OVERLOADING)
data StackPageTitlePropertyInfo
instance AttrInfo StackPageTitlePropertyInfo where
    type AttrAllowedOps StackPageTitlePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint StackPageTitlePropertyInfo = IsStackPage
    type AttrSetTypeConstraint StackPageTitlePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint StackPageTitlePropertyInfo = (~) T.Text
    type AttrTransferType StackPageTitlePropertyInfo = T.Text
    type AttrGetType StackPageTitlePropertyInfo = (Maybe T.Text)
    type AttrLabel StackPageTitlePropertyInfo = "title"
    type AttrOrigin StackPageTitlePropertyInfo = StackPage
    attrGet = getStackPageTitle
    attrSet = setStackPageTitle
    attrTransfer _ v = do
        return v
    attrConstruct = constructStackPageTitle
    attrClear = undefined
#endif

-- VVV Prop "use-underline"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

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

-- | Set the value of the “@use-underline@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' stackPage [ #useUnderline 'Data.GI.Base.Attributes.:=' value ]
-- @
setStackPageUseUnderline :: (MonadIO m, IsStackPage o) => o -> Bool -> m ()
setStackPageUseUnderline :: forall (m :: * -> *) o.
(MonadIO m, IsStackPage o) =>
o -> Bool -> m ()
setStackPageUseUnderline o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"use-underline" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@use-underline@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructStackPageUseUnderline :: (IsStackPage o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructStackPageUseUnderline :: forall o (m :: * -> *).
(IsStackPage o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructStackPageUseUnderline Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"use-underline" Bool
val

#if defined(ENABLE_OVERLOADING)
data StackPageUseUnderlinePropertyInfo
instance AttrInfo StackPageUseUnderlinePropertyInfo where
    type AttrAllowedOps StackPageUseUnderlinePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint StackPageUseUnderlinePropertyInfo = IsStackPage
    type AttrSetTypeConstraint StackPageUseUnderlinePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint StackPageUseUnderlinePropertyInfo = (~) Bool
    type AttrTransferType StackPageUseUnderlinePropertyInfo = Bool
    type AttrGetType StackPageUseUnderlinePropertyInfo = Bool
    type AttrLabel StackPageUseUnderlinePropertyInfo = "use-underline"
    type AttrOrigin StackPageUseUnderlinePropertyInfo = StackPage
    attrGet = getStackPageUseUnderline
    attrSet = setStackPageUseUnderline
    attrTransfer _ v = do
        return v
    attrConstruct = constructStackPageUseUnderline
    attrClear = undefined
#endif

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

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

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

-- | Construct a `GValueConstruct` with valid value for the “@visible@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructStackPageVisible :: (IsStackPage o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructStackPageVisible :: forall o (m :: * -> *).
(IsStackPage o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructStackPageVisible Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"visible" Bool
val

#if defined(ENABLE_OVERLOADING)
data StackPageVisiblePropertyInfo
instance AttrInfo StackPageVisiblePropertyInfo where
    type AttrAllowedOps StackPageVisiblePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint StackPageVisiblePropertyInfo = IsStackPage
    type AttrSetTypeConstraint StackPageVisiblePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint StackPageVisiblePropertyInfo = (~) Bool
    type AttrTransferType StackPageVisiblePropertyInfo = Bool
    type AttrGetType StackPageVisiblePropertyInfo = Bool
    type AttrLabel StackPageVisiblePropertyInfo = "visible"
    type AttrOrigin StackPageVisiblePropertyInfo = StackPage
    attrGet = getStackPageVisible
    attrSet = setStackPageVisible
    attrTransfer _ v = do
        return v
    attrConstruct = constructStackPageVisible
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList StackPage
type instance O.AttributeList StackPage = StackPageAttributeList
type StackPageAttributeList = ('[ '("accessibleRole", Gtk.Accessible.AccessibleAccessibleRolePropertyInfo), '("child", StackPageChildPropertyInfo), '("iconName", StackPageIconNamePropertyInfo), '("name", StackPageNamePropertyInfo), '("needsAttention", StackPageNeedsAttentionPropertyInfo), '("title", StackPageTitlePropertyInfo), '("useUnderline", StackPageUseUnderlinePropertyInfo), '("visible", StackPageVisiblePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
stackPageChild :: AttrLabelProxy "child"
stackPageChild = AttrLabelProxy

stackPageIconName :: AttrLabelProxy "iconName"
stackPageIconName = AttrLabelProxy

stackPageName :: AttrLabelProxy "name"
stackPageName = AttrLabelProxy

stackPageNeedsAttention :: AttrLabelProxy "needsAttention"
stackPageNeedsAttention = AttrLabelProxy

stackPageTitle :: AttrLabelProxy "title"
stackPageTitle = AttrLabelProxy

stackPageUseUnderline :: AttrLabelProxy "useUnderline"
stackPageUseUnderline = AttrLabelProxy

stackPageVisible :: AttrLabelProxy "visible"
stackPageVisible = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList StackPage = StackPageSignalList
type StackPageSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "gtk_stack_page_get_child" gtk_stack_page_get_child :: 
    Ptr StackPage ->                        -- self : TInterface (Name {namespace = "Gtk", name = "StackPage"})
    IO (Ptr Gtk.Widget.Widget)

-- | Returns the stack child to which /@self@/ belongs.
stackPageGetChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsStackPage a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.StackPage.StackPage'
    -> m Gtk.Widget.Widget
    -- ^ __Returns:__ the child to which /@self@/ belongs
stackPageGetChild :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStackPage a) =>
a -> m Widget
stackPageGetChild a
self = IO Widget -> m Widget
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Widget -> m Widget) -> IO Widget -> m Widget
forall a b. (a -> b) -> a -> b
$ do
    Ptr StackPage
self' <- a -> IO (Ptr StackPage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Widget
result <- Ptr StackPage -> IO (Ptr Widget)
gtk_stack_page_get_child Ptr StackPage
self'
    Text -> Ptr Widget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"stackPageGetChild" Ptr Widget
result
    Widget
result' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result'

#if defined(ENABLE_OVERLOADING)
data StackPageGetChildMethodInfo
instance (signature ~ (m Gtk.Widget.Widget), MonadIO m, IsStackPage a) => O.OverloadedMethod StackPageGetChildMethodInfo a signature where
    overloadedMethod = stackPageGetChild

instance O.OverloadedMethodInfo StackPageGetChildMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.StackPage.stackPageGetChild",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-StackPage.html#v:stackPageGetChild"
        }


#endif

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

foreign import ccall "gtk_stack_page_get_icon_name" gtk_stack_page_get_icon_name :: 
    Ptr StackPage ->                        -- self : TInterface (Name {namespace = "Gtk", name = "StackPage"})
    IO CString

-- | Returns the current value of the t'GI.Gtk.Objects.StackPage.StackPage':@/icon-name/@ property.
stackPageGetIconName ::
    (B.CallStack.HasCallStack, MonadIO m, IsStackPage a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.StackPage.StackPage'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The value of the t'GI.Gtk.Objects.StackPage.StackPage':@/icon-name/@ property.
    --   See 'GI.Gtk.Objects.StackPage.stackPageSetIconName' for details on how to set a new value.
stackPageGetIconName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStackPage a) =>
a -> m (Maybe Text)
stackPageGetIconName a
self = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr StackPage
self' <- a -> IO (Ptr StackPage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr StackPage -> IO CString
gtk_stack_page_get_icon_name Ptr StackPage
self'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

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

instance O.OverloadedMethodInfo StackPageGetIconNameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.StackPage.stackPageGetIconName",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-StackPage.html#v:stackPageGetIconName"
        }


#endif

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

foreign import ccall "gtk_stack_page_get_name" gtk_stack_page_get_name :: 
    Ptr StackPage ->                        -- self : TInterface (Name {namespace = "Gtk", name = "StackPage"})
    IO CString

-- | Returns the current value of the t'GI.Gtk.Objects.StackPage.StackPage':@/name/@ property.
stackPageGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsStackPage a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.StackPage.StackPage'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The value of the t'GI.Gtk.Objects.StackPage.StackPage':@/name/@ property.
    --   See 'GI.Gtk.Objects.StackPage.stackPageSetName' for details on how to set a new value.
stackPageGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStackPage a) =>
a -> m (Maybe Text)
stackPageGetName a
self = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr StackPage
self' <- a -> IO (Ptr StackPage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr StackPage -> IO CString
gtk_stack_page_get_name Ptr StackPage
self'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

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

instance O.OverloadedMethodInfo StackPageGetNameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.StackPage.stackPageGetName",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-StackPage.html#v:stackPageGetName"
        }


#endif

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

foreign import ccall "gtk_stack_page_get_needs_attention" gtk_stack_page_get_needs_attention :: 
    Ptr StackPage ->                        -- self : TInterface (Name {namespace = "Gtk", name = "StackPage"})
    IO CInt

-- | Returns the current value of the t'GI.Gtk.Objects.StackPage.StackPage':@/needs-attention/@ property.
stackPageGetNeedsAttention ::
    (B.CallStack.HasCallStack, MonadIO m, IsStackPage a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.StackPage.StackPage'
    -> m Bool
    -- ^ __Returns:__ The value of the t'GI.Gtk.Objects.StackPage.StackPage':@/needs-attention/@ property.
    --   See 'GI.Gtk.Objects.StackPage.stackPageSetNeedsAttention' for details on how to set a new value.
stackPageGetNeedsAttention :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStackPage a) =>
a -> m Bool
stackPageGetNeedsAttention a
self = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr StackPage
self' <- a -> IO (Ptr StackPage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr StackPage -> IO CInt
gtk_stack_page_get_needs_attention Ptr StackPage
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data StackPageGetNeedsAttentionMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsStackPage a) => O.OverloadedMethod StackPageGetNeedsAttentionMethodInfo a signature where
    overloadedMethod = stackPageGetNeedsAttention

instance O.OverloadedMethodInfo StackPageGetNeedsAttentionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.StackPage.stackPageGetNeedsAttention",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-StackPage.html#v:stackPageGetNeedsAttention"
        }


#endif

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

foreign import ccall "gtk_stack_page_get_title" gtk_stack_page_get_title :: 
    Ptr StackPage ->                        -- self : TInterface (Name {namespace = "Gtk", name = "StackPage"})
    IO CString

-- | Returns the current value of the t'GI.Gtk.Objects.StackPage.StackPage':@/title/@ property.
stackPageGetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsStackPage a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.StackPage.StackPage'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The value of the t'GI.Gtk.Objects.StackPage.StackPage':@/title/@ property.
    --   See 'GI.Gtk.Objects.StackPage.stackPageSetTitle' for details on how to set a new value.
stackPageGetTitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStackPage a) =>
a -> m (Maybe Text)
stackPageGetTitle a
self = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr StackPage
self' <- a -> IO (Ptr StackPage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr StackPage -> IO CString
gtk_stack_page_get_title Ptr StackPage
self'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

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

instance O.OverloadedMethodInfo StackPageGetTitleMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.StackPage.stackPageGetTitle",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-StackPage.html#v:stackPageGetTitle"
        }


#endif

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

foreign import ccall "gtk_stack_page_get_use_underline" gtk_stack_page_get_use_underline :: 
    Ptr StackPage ->                        -- self : TInterface (Name {namespace = "Gtk", name = "StackPage"})
    IO CInt

-- | Returns the current value of the t'GI.Gtk.Objects.StackPage.StackPage':@/use-underline/@ property.
stackPageGetUseUnderline ::
    (B.CallStack.HasCallStack, MonadIO m, IsStackPage a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.StackPage.StackPage'
    -> m Bool
    -- ^ __Returns:__ The value of the t'GI.Gtk.Objects.StackPage.StackPage':@/use-underline/@ property.
    --   See 'GI.Gtk.Objects.StackPage.stackPageSetUseUnderline' for details on how to set a new value.
stackPageGetUseUnderline :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStackPage a) =>
a -> m Bool
stackPageGetUseUnderline a
self = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr StackPage
self' <- a -> IO (Ptr StackPage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr StackPage -> IO CInt
gtk_stack_page_get_use_underline Ptr StackPage
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data StackPageGetUseUnderlineMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsStackPage a) => O.OverloadedMethod StackPageGetUseUnderlineMethodInfo a signature where
    overloadedMethod = stackPageGetUseUnderline

instance O.OverloadedMethodInfo StackPageGetUseUnderlineMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.StackPage.stackPageGetUseUnderline",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-StackPage.html#v:stackPageGetUseUnderline"
        }


#endif

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

foreign import ccall "gtk_stack_page_get_visible" gtk_stack_page_get_visible :: 
    Ptr StackPage ->                        -- self : TInterface (Name {namespace = "Gtk", name = "StackPage"})
    IO CInt

-- | Returns whether /@page@/ is visible in its t'GI.Gtk.Objects.Stack.Stack'.
-- This is independent from the t'GI.Gtk.Objects.Widget.Widget':@/visible/@ value of its
-- t'GI.Gtk.Objects.Widget.Widget'.
stackPageGetVisible ::
    (B.CallStack.HasCallStack, MonadIO m, IsStackPage a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.StackPage.StackPage'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@page@/ is visible
stackPageGetVisible :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStackPage a) =>
a -> m Bool
stackPageGetVisible a
self = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr StackPage
self' <- a -> IO (Ptr StackPage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr StackPage -> IO CInt
gtk_stack_page_get_visible Ptr StackPage
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data StackPageGetVisibleMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsStackPage a) => O.OverloadedMethod StackPageGetVisibleMethodInfo a signature where
    overloadedMethod = stackPageGetVisible

instance O.OverloadedMethodInfo StackPageGetVisibleMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.StackPage.stackPageGetVisible",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-StackPage.html#v:stackPageGetVisible"
        }


#endif

-- method StackPage::set_icon_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StackPage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStackPage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "setting"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new value to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_stack_page_set_icon_name" gtk_stack_page_set_icon_name :: 
    Ptr StackPage ->                        -- self : TInterface (Name {namespace = "Gtk", name = "StackPage"})
    CString ->                              -- setting : TBasicType TUTF8
    IO ()

-- | Sets the new value of the t'GI.Gtk.Objects.StackPage.StackPage':@/icon-name/@ property.
-- See also 'GI.Gtk.Objects.StackPage.stackPageGetIconName'
stackPageSetIconName ::
    (B.CallStack.HasCallStack, MonadIO m, IsStackPage a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.StackPage.StackPage'
    -> T.Text
    -- ^ /@setting@/: the new value to set
    -> m ()
stackPageSetIconName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStackPage a) =>
a -> Text -> m ()
stackPageSetIconName a
self Text
setting = 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 StackPage
self' <- a -> IO (Ptr StackPage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
setting' <- Text -> IO CString
textToCString Text
setting
    Ptr StackPage -> CString -> IO ()
gtk_stack_page_set_icon_name Ptr StackPage
self' CString
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
setting'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo StackPageSetIconNameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.StackPage.stackPageSetIconName",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-StackPage.html#v:stackPageSetIconName"
        }


#endif

-- method StackPage::set_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StackPage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStackPage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "setting"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new value to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_stack_page_set_name" gtk_stack_page_set_name :: 
    Ptr StackPage ->                        -- self : TInterface (Name {namespace = "Gtk", name = "StackPage"})
    CString ->                              -- setting : TBasicType TUTF8
    IO ()

-- | Sets the new value of the t'GI.Gtk.Objects.StackPage.StackPage':@/name/@ property.
-- See also 'GI.Gtk.Objects.StackPage.stackPageGetName'
stackPageSetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsStackPage a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.StackPage.StackPage'
    -> T.Text
    -- ^ /@setting@/: the new value to set
    -> m ()
stackPageSetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStackPage a) =>
a -> Text -> m ()
stackPageSetName a
self Text
setting = 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 StackPage
self' <- a -> IO (Ptr StackPage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
setting' <- Text -> IO CString
textToCString Text
setting
    Ptr StackPage -> CString -> IO ()
gtk_stack_page_set_name Ptr StackPage
self' CString
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
setting'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo StackPageSetNameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.StackPage.stackPageSetName",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-StackPage.html#v:stackPageSetName"
        }


#endif

-- method StackPage::set_needs_attention
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StackPage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStackPage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "setting"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new value to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_stack_page_set_needs_attention" gtk_stack_page_set_needs_attention :: 
    Ptr StackPage ->                        -- self : TInterface (Name {namespace = "Gtk", name = "StackPage"})
    CInt ->                                 -- setting : TBasicType TBoolean
    IO ()

-- | Sets the new value of the t'GI.Gtk.Objects.StackPage.StackPage':@/needs-attention/@ property.
-- See also 'GI.Gtk.Objects.StackPage.stackPageGetNeedsAttention'
stackPageSetNeedsAttention ::
    (B.CallStack.HasCallStack, MonadIO m, IsStackPage a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.StackPage.StackPage'
    -> Bool
    -- ^ /@setting@/: the new value to set
    -> m ()
stackPageSetNeedsAttention :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStackPage a) =>
a -> Bool -> m ()
stackPageSetNeedsAttention a
self Bool
setting = 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 StackPage
self' <- a -> IO (Ptr StackPage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let setting' :: CInt
setting' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
setting
    Ptr StackPage -> CInt -> IO ()
gtk_stack_page_set_needs_attention Ptr StackPage
self' CInt
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StackPageSetNeedsAttentionMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsStackPage a) => O.OverloadedMethod StackPageSetNeedsAttentionMethodInfo a signature where
    overloadedMethod = stackPageSetNeedsAttention

instance O.OverloadedMethodInfo StackPageSetNeedsAttentionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.StackPage.stackPageSetNeedsAttention",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-StackPage.html#v:stackPageSetNeedsAttention"
        }


#endif

-- method StackPage::set_title
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StackPage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStackPage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "setting"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new value to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_stack_page_set_title" gtk_stack_page_set_title :: 
    Ptr StackPage ->                        -- self : TInterface (Name {namespace = "Gtk", name = "StackPage"})
    CString ->                              -- setting : TBasicType TUTF8
    IO ()

-- | Sets the new value of the t'GI.Gtk.Objects.StackPage.StackPage':@/title/@ property.
-- See also 'GI.Gtk.Objects.StackPage.stackPageGetTitle'
stackPageSetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsStackPage a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.StackPage.StackPage'
    -> T.Text
    -- ^ /@setting@/: the new value to set
    -> m ()
stackPageSetTitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStackPage a) =>
a -> Text -> m ()
stackPageSetTitle a
self Text
setting = 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 StackPage
self' <- a -> IO (Ptr StackPage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
setting' <- Text -> IO CString
textToCString Text
setting
    Ptr StackPage -> CString -> IO ()
gtk_stack_page_set_title Ptr StackPage
self' CString
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
setting'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

instance O.OverloadedMethodInfo StackPageSetTitleMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.StackPage.stackPageSetTitle",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-StackPage.html#v:stackPageSetTitle"
        }


#endif

-- method StackPage::set_use_underline
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StackPage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStackPage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "setting"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new value to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_stack_page_set_use_underline" gtk_stack_page_set_use_underline :: 
    Ptr StackPage ->                        -- self : TInterface (Name {namespace = "Gtk", name = "StackPage"})
    CInt ->                                 -- setting : TBasicType TBoolean
    IO ()

-- | Sets the new value of the t'GI.Gtk.Objects.StackPage.StackPage':@/use-underline/@ property.
-- See also 'GI.Gtk.Objects.StackPage.stackPageGetUseUnderline'
stackPageSetUseUnderline ::
    (B.CallStack.HasCallStack, MonadIO m, IsStackPage a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.StackPage.StackPage'
    -> Bool
    -- ^ /@setting@/: the new value to set
    -> m ()
stackPageSetUseUnderline :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStackPage a) =>
a -> Bool -> m ()
stackPageSetUseUnderline a
self Bool
setting = 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 StackPage
self' <- a -> IO (Ptr StackPage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let setting' :: CInt
setting' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
setting
    Ptr StackPage -> CInt -> IO ()
gtk_stack_page_set_use_underline Ptr StackPage
self' CInt
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StackPageSetUseUnderlineMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsStackPage a) => O.OverloadedMethod StackPageSetUseUnderlineMethodInfo a signature where
    overloadedMethod = stackPageSetUseUnderline

instance O.OverloadedMethodInfo StackPageSetUseUnderlineMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.StackPage.stackPageSetUseUnderline",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-StackPage.html#v:stackPageSetUseUnderline"
        }


#endif

-- method StackPage::set_visible
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "StackPage" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkStackPage" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "visible"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The new property value"
--                 , 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_page_set_visible" gtk_stack_page_set_visible :: 
    Ptr StackPage ->                        -- self : TInterface (Name {namespace = "Gtk", name = "StackPage"})
    CInt ->                                 -- visible : TBasicType TBoolean
    IO ()

-- | Sets the new value of the t'GI.Gtk.Objects.StackPage.StackPage':@/visible/@ property
-- to /@visible@/.
stackPageSetVisible ::
    (B.CallStack.HasCallStack, MonadIO m, IsStackPage a) =>
    a
    -- ^ /@self@/: a t'GI.Gtk.Objects.StackPage.StackPage'
    -> Bool
    -- ^ /@visible@/: The new property value
    -> m ()
stackPageSetVisible :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsStackPage a) =>
a -> Bool -> m ()
stackPageSetVisible a
self Bool
visible = 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 StackPage
self' <- a -> IO (Ptr StackPage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let visible' :: CInt
visible' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
visible
    Ptr StackPage -> CInt -> IO ()
gtk_stack_page_set_visible Ptr StackPage
self' CInt
visible'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StackPageSetVisibleMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsStackPage a) => O.OverloadedMethod StackPageSetVisibleMethodInfo a signature where
    overloadedMethod = stackPageSetVisible

instance O.OverloadedMethodInfo StackPageSetVisibleMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.StackPage.stackPageSetVisible",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-StackPage.html#v:stackPageSetVisible"
        }


#endif