{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.AssistantPage
    ( 
    AssistantPage(..)                       ,
    IsAssistantPage                         ,
    toAssistantPage                         ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveAssistantPageMethod              ,
#endif
#if defined(ENABLE_OVERLOADING)
    AssistantPageGetChildMethodInfo         ,
#endif
    assistantPageGetChild                   ,
 
#if defined(ENABLE_OVERLOADING)
    AssistantPageChildPropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    assistantPageChild                      ,
#endif
    constructAssistantPageChild             ,
    getAssistantPageChild                   ,
#if defined(ENABLE_OVERLOADING)
    AssistantPageCompletePropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    assistantPageComplete                   ,
#endif
    constructAssistantPageComplete          ,
    getAssistantPageComplete                ,
    setAssistantPageComplete                ,
#if defined(ENABLE_OVERLOADING)
    AssistantPagePageTypePropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    assistantPagePageType                   ,
#endif
    constructAssistantPagePageType          ,
    getAssistantPagePageType                ,
    setAssistantPagePageType                ,
#if defined(ENABLE_OVERLOADING)
    AssistantPageTitlePropertyInfo          ,
#endif
#if defined(ENABLE_OVERLOADING)
    assistantPageTitle                      ,
#endif
    clearAssistantPageTitle                 ,
    constructAssistantPageTitle             ,
    getAssistantPageTitle                   ,
    setAssistantPageTitle                   ,
    ) 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.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
newtype AssistantPage = AssistantPage (SP.ManagedPtr AssistantPage)
    deriving (AssistantPage -> AssistantPage -> Bool
(AssistantPage -> AssistantPage -> Bool)
-> (AssistantPage -> AssistantPage -> Bool) -> Eq AssistantPage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AssistantPage -> AssistantPage -> Bool
== :: AssistantPage -> AssistantPage -> Bool
$c/= :: AssistantPage -> AssistantPage -> Bool
/= :: AssistantPage -> AssistantPage -> Bool
Eq)
instance SP.ManagedPtrNewtype AssistantPage where
    toManagedPtr :: AssistantPage -> ManagedPtr AssistantPage
toManagedPtr (AssistantPage ManagedPtr AssistantPage
p) = ManagedPtr AssistantPage
p
foreign import ccall "gtk_assistant_page_get_type"
    c_gtk_assistant_page_get_type :: IO B.Types.GType
instance B.Types.TypedObject AssistantPage where
    glibType :: IO GType
glibType = IO GType
c_gtk_assistant_page_get_type
instance B.Types.GObject AssistantPage
class (SP.GObject o, O.IsDescendantOf AssistantPage o) => IsAssistantPage o
instance (SP.GObject o, O.IsDescendantOf AssistantPage o) => IsAssistantPage o
instance O.HasParentTypes AssistantPage
type instance O.ParentTypes AssistantPage = '[GObject.Object.Object]
toAssistantPage :: (MIO.MonadIO m, IsAssistantPage o) => o -> m AssistantPage
toAssistantPage :: forall (m :: * -> *) o.
(MonadIO m, IsAssistantPage o) =>
o -> m AssistantPage
toAssistantPage = IO AssistantPage -> m AssistantPage
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO AssistantPage -> m AssistantPage)
-> (o -> IO AssistantPage) -> o -> m AssistantPage
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr AssistantPage -> AssistantPage)
-> o -> IO AssistantPage
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr AssistantPage -> AssistantPage
AssistantPage
instance B.GValue.IsGValue (Maybe AssistantPage) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_assistant_page_get_type
    gvalueSet_ :: Ptr GValue -> Maybe AssistantPage -> IO ()
gvalueSet_ Ptr GValue
gv Maybe AssistantPage
P.Nothing = Ptr GValue -> Ptr AssistantPage -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr AssistantPage
forall a. Ptr a
FP.nullPtr :: FP.Ptr AssistantPage)
    gvalueSet_ Ptr GValue
gv (P.Just AssistantPage
obj) = AssistantPage -> (Ptr AssistantPage -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AssistantPage
obj (Ptr GValue -> Ptr AssistantPage -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe AssistantPage)
gvalueGet_ Ptr GValue
gv = do
        Ptr AssistantPage
ptr <- Ptr GValue -> IO (Ptr AssistantPage)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr AssistantPage)
        if Ptr AssistantPage
ptr Ptr AssistantPage -> Ptr AssistantPage -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr AssistantPage
forall a. Ptr a
FP.nullPtr
        then AssistantPage -> Maybe AssistantPage
forall a. a -> Maybe a
P.Just (AssistantPage -> Maybe AssistantPage)
-> IO AssistantPage -> IO (Maybe AssistantPage)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr AssistantPage -> AssistantPage)
-> Ptr AssistantPage -> IO AssistantPage
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr AssistantPage -> AssistantPage
AssistantPage Ptr AssistantPage
ptr
        else Maybe AssistantPage -> IO (Maybe AssistantPage)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AssistantPage
forall a. Maybe a
P.Nothing
        
    
#if defined(ENABLE_OVERLOADING)
type family ResolveAssistantPageMethod (t :: Symbol) (o :: *) :: * where
    ResolveAssistantPageMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveAssistantPageMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveAssistantPageMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveAssistantPageMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveAssistantPageMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveAssistantPageMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveAssistantPageMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveAssistantPageMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveAssistantPageMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveAssistantPageMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveAssistantPageMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveAssistantPageMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveAssistantPageMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveAssistantPageMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveAssistantPageMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveAssistantPageMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveAssistantPageMethod "getChild" o = AssistantPageGetChildMethodInfo
    ResolveAssistantPageMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveAssistantPageMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveAssistantPageMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveAssistantPageMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveAssistantPageMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveAssistantPageMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveAssistantPageMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveAssistantPageMethod t AssistantPage, O.OverloadedMethod info AssistantPage p) => OL.IsLabel t (AssistantPage -> 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 ~ ResolveAssistantPageMethod t AssistantPage, O.OverloadedMethod info AssistantPage p, R.HasField t AssistantPage p) => R.HasField t AssistantPage p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveAssistantPageMethod t AssistantPage, O.OverloadedMethodInfo info AssistantPage) => OL.IsLabel t (O.MethodProxy info AssistantPage) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif
   
   
   
getAssistantPageChild :: (MonadIO m, IsAssistantPage o) => o -> m Gtk.Widget.Widget
getAssistantPageChild :: forall (m :: * -> *) o.
(MonadIO m, IsAssistantPage o) =>
o -> m Widget
getAssistantPageChild o
obj = IO Widget -> m Widget
forall a. IO a -> m a
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
"getAssistantPageChild" (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
constructAssistantPageChild :: (IsAssistantPage o, MIO.MonadIO m, Gtk.Widget.IsWidget a) => a -> m (GValueConstruct o)
constructAssistantPageChild :: forall o (m :: * -> *) a.
(IsAssistantPage o, MonadIO m, IsWidget a) =>
a -> m (GValueConstruct o)
constructAssistantPageChild 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
"child" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data AssistantPageChildPropertyInfo
instance AttrInfo AssistantPageChildPropertyInfo where
    type AttrAllowedOps AssistantPageChildPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint AssistantPageChildPropertyInfo = IsAssistantPage
    type AttrSetTypeConstraint AssistantPageChildPropertyInfo = Gtk.Widget.IsWidget
    type AttrTransferTypeConstraint AssistantPageChildPropertyInfo = Gtk.Widget.IsWidget
    type AttrTransferType AssistantPageChildPropertyInfo = Gtk.Widget.Widget
    type AttrGetType AssistantPageChildPropertyInfo = Gtk.Widget.Widget
    type AttrLabel AssistantPageChildPropertyInfo = "child"
    type AttrOrigin AssistantPageChildPropertyInfo = AssistantPage
    attrGet = getAssistantPageChild
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gtk.Widget.Widget v
    attrConstruct = constructAssistantPageChild
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.AssistantPage.child"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-AssistantPage.html#g:attr:child"
        })
#endif
   
   
   
getAssistantPageComplete :: (MonadIO m, IsAssistantPage o) => o -> m Bool
getAssistantPageComplete :: forall (m :: * -> *) o.
(MonadIO m, IsAssistantPage o) =>
o -> m Bool
getAssistantPageComplete o
obj = IO Bool -> m Bool
forall a. IO a -> m a
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
"complete"
setAssistantPageComplete :: (MonadIO m, IsAssistantPage o) => o -> Bool -> m ()
setAssistantPageComplete :: forall (m :: * -> *) o.
(MonadIO m, IsAssistantPage o) =>
o -> Bool -> m ()
setAssistantPageComplete o
obj Bool
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 -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"complete" Bool
val
constructAssistantPageComplete :: (IsAssistantPage o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructAssistantPageComplete :: forall o (m :: * -> *).
(IsAssistantPage o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructAssistantPageComplete Bool
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 -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"complete" Bool
val
#if defined(ENABLE_OVERLOADING)
data AssistantPageCompletePropertyInfo
instance AttrInfo AssistantPageCompletePropertyInfo where
    type AttrAllowedOps AssistantPageCompletePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint AssistantPageCompletePropertyInfo = IsAssistantPage
    type AttrSetTypeConstraint AssistantPageCompletePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint AssistantPageCompletePropertyInfo = (~) Bool
    type AttrTransferType AssistantPageCompletePropertyInfo = Bool
    type AttrGetType AssistantPageCompletePropertyInfo = Bool
    type AttrLabel AssistantPageCompletePropertyInfo = "complete"
    type AttrOrigin AssistantPageCompletePropertyInfo = AssistantPage
    attrGet = getAssistantPageComplete
    attrSet = setAssistantPageComplete
    attrTransfer _ v = do
        return v
    attrConstruct = constructAssistantPageComplete
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.AssistantPage.complete"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-AssistantPage.html#g:attr:complete"
        })
#endif
   
   
   
getAssistantPagePageType :: (MonadIO m, IsAssistantPage o) => o -> m Gtk.Enums.AssistantPageType
getAssistantPagePageType :: forall (m :: * -> *) o.
(MonadIO m, IsAssistantPage o) =>
o -> m AssistantPageType
getAssistantPagePageType o
obj = IO AssistantPageType -> m AssistantPageType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO AssistantPageType -> m AssistantPageType)
-> IO AssistantPageType -> m AssistantPageType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO AssistantPageType
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"page-type"
setAssistantPagePageType :: (MonadIO m, IsAssistantPage o) => o -> Gtk.Enums.AssistantPageType -> m ()
setAssistantPagePageType :: forall (m :: * -> *) o.
(MonadIO m, IsAssistantPage o) =>
o -> AssistantPageType -> m ()
setAssistantPagePageType o
obj AssistantPageType
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 -> AssistantPageType -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"page-type" AssistantPageType
val
constructAssistantPagePageType :: (IsAssistantPage o, MIO.MonadIO m) => Gtk.Enums.AssistantPageType -> m (GValueConstruct o)
constructAssistantPagePageType :: forall o (m :: * -> *).
(IsAssistantPage o, MonadIO m) =>
AssistantPageType -> m (GValueConstruct o)
constructAssistantPagePageType AssistantPageType
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 -> AssistantPageType -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"page-type" AssistantPageType
val
#if defined(ENABLE_OVERLOADING)
data AssistantPagePageTypePropertyInfo
instance AttrInfo AssistantPagePageTypePropertyInfo where
    type AttrAllowedOps AssistantPagePageTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint AssistantPagePageTypePropertyInfo = IsAssistantPage
    type AttrSetTypeConstraint AssistantPagePageTypePropertyInfo = (~) Gtk.Enums.AssistantPageType
    type AttrTransferTypeConstraint AssistantPagePageTypePropertyInfo = (~) Gtk.Enums.AssistantPageType
    type AttrTransferType AssistantPagePageTypePropertyInfo = Gtk.Enums.AssistantPageType
    type AttrGetType AssistantPagePageTypePropertyInfo = Gtk.Enums.AssistantPageType
    type AttrLabel AssistantPagePageTypePropertyInfo = "page-type"
    type AttrOrigin AssistantPagePageTypePropertyInfo = AssistantPage
    attrGet = getAssistantPagePageType
    attrSet = setAssistantPagePageType
    attrTransfer _ v = do
        return v
    attrConstruct = constructAssistantPagePageType
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.AssistantPage.pageType"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-AssistantPage.html#g:attr:pageType"
        })
#endif
   
   
   
getAssistantPageTitle :: (MonadIO m, IsAssistantPage o) => o -> m (Maybe T.Text)
getAssistantPageTitle :: forall (m :: * -> *) o.
(MonadIO m, IsAssistantPage o) =>
o -> m (Maybe Text)
getAssistantPageTitle o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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"
setAssistantPageTitle :: (MonadIO m, IsAssistantPage o) => o -> T.Text -> m ()
setAssistantPageTitle :: forall (m :: * -> *) o.
(MonadIO m, IsAssistantPage o) =>
o -> Text -> m ()
setAssistantPageTitle o
obj Text
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 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)
constructAssistantPageTitle :: (IsAssistantPage o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructAssistantPageTitle :: forall o (m :: * -> *).
(IsAssistantPage o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructAssistantPageTitle Text
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 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)
clearAssistantPageTitle :: (MonadIO m, IsAssistantPage o) => o -> m ()
clearAssistantPageTitle :: forall (m :: * -> *) o. (MonadIO m, IsAssistantPage o) => o -> m ()
clearAssistantPageTitle 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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"title" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data AssistantPageTitlePropertyInfo
instance AttrInfo AssistantPageTitlePropertyInfo where
    type AttrAllowedOps AssistantPageTitlePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint AssistantPageTitlePropertyInfo = IsAssistantPage
    type AttrSetTypeConstraint AssistantPageTitlePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint AssistantPageTitlePropertyInfo = (~) T.Text
    type AttrTransferType AssistantPageTitlePropertyInfo = T.Text
    type AttrGetType AssistantPageTitlePropertyInfo = (Maybe T.Text)
    type AttrLabel AssistantPageTitlePropertyInfo = "title"
    type AttrOrigin AssistantPageTitlePropertyInfo = AssistantPage
    attrGet = getAssistantPageTitle
    attrSet = setAssistantPageTitle
    attrTransfer _ v = do
        return v
    attrConstruct = constructAssistantPageTitle
    attrClear = clearAssistantPageTitle
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.AssistantPage.title"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-AssistantPage.html#g:attr:title"
        })
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AssistantPage
type instance O.AttributeList AssistantPage = AssistantPageAttributeList
type AssistantPageAttributeList = ('[ '("child", AssistantPageChildPropertyInfo), '("complete", AssistantPageCompletePropertyInfo), '("pageType", AssistantPagePageTypePropertyInfo), '("title", AssistantPageTitlePropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
assistantPageChild :: AttrLabelProxy "child"
assistantPageChild = AttrLabelProxy
assistantPageComplete :: AttrLabelProxy "complete"
assistantPageComplete = AttrLabelProxy
assistantPagePageType :: AttrLabelProxy "pageType"
assistantPagePageType = AttrLabelProxy
assistantPageTitle :: AttrLabelProxy "title"
assistantPageTitle = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList AssistantPage = AssistantPageSignalList
type AssistantPageSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_assistant_page_get_child" gtk_assistant_page_get_child :: 
    Ptr AssistantPage ->                    
    IO (Ptr Gtk.Widget.Widget)
assistantPageGetChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsAssistantPage a) =>
    a
    
    -> m Gtk.Widget.Widget
    
assistantPageGetChild :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAssistantPage a) =>
a -> m Widget
assistantPageGetChild a
page = IO Widget -> m Widget
forall a. IO a -> m a
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 AssistantPage
page' <- a -> IO (Ptr AssistantPage)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
page
    Ptr Widget
result <- Ptr AssistantPage -> IO (Ptr Widget)
gtk_assistant_page_get_child Ptr AssistantPage
page'
    Text -> Ptr Widget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"assistantPageGetChild" 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
page
    Widget -> IO Widget
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result'
#if defined(ENABLE_OVERLOADING)
data AssistantPageGetChildMethodInfo
instance (signature ~ (m Gtk.Widget.Widget), MonadIO m, IsAssistantPage a) => O.OverloadedMethod AssistantPageGetChildMethodInfo a signature where
    overloadedMethod = assistantPageGetChild
instance O.OverloadedMethodInfo AssistantPageGetChildMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.AssistantPage.assistantPageGetChild",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.6/docs/GI-Gtk-Objects-AssistantPage.html#v:assistantPageGetChild"
        })
#endif