{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkBuilderListItemFactory@ is a @GtkListItemFactory@ that creates
-- widgets by instantiating @GtkBuilder@ UI templates.
-- 
-- The templates must be extending @GtkListItem@, and typically use
-- @GtkExpression@s to obtain data from the items in the model.
-- 
-- Example:
-- 
-- === /xml code/
-- >  <interface>
-- >    <template class="GtkListItem">
-- >      <property name="child">
-- >        <object class="GtkLabel">
-- >          <property name="xalign">0</property>
-- >          <binding name="label">
-- >            <lookup name="name" type="SettingsKey">
-- >              <lookup name="item">GtkListItem</lookup>
-- >            </lookup>
-- >          </binding>
-- >        </object>
-- >      </property>
-- >    </template>
-- >  </interface>
-- 

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

module GI.Gtk.Objects.BuilderListItemFactory
    ( 

-- * Exported types
    BuilderListItemFactory(..)              ,
    IsBuilderListItemFactory                ,
    toBuilderListItemFactory                ,


 -- * 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"), [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"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getBytes]("GI.Gtk.Objects.BuilderListItemFactory#g:method:getBytes"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getResource]("GI.Gtk.Objects.BuilderListItemFactory#g:method:getResource"), [getScope]("GI.Gtk.Objects.BuilderListItemFactory#g:method:getScope").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveBuilderListItemFactoryMethod     ,
#endif

-- ** getBytes #method:getBytes#

#if defined(ENABLE_OVERLOADING)
    BuilderListItemFactoryGetBytesMethodInfo,
#endif
    builderListItemFactoryGetBytes          ,


-- ** getResource #method:getResource#

#if defined(ENABLE_OVERLOADING)
    BuilderListItemFactoryGetResourceMethodInfo,
#endif
    builderListItemFactoryGetResource       ,


-- ** getScope #method:getScope#

#if defined(ENABLE_OVERLOADING)
    BuilderListItemFactoryGetScopeMethodInfo,
#endif
    builderListItemFactoryGetScope          ,


-- ** newFromBytes #method:newFromBytes#

    builderListItemFactoryNewFromBytes      ,


-- ** newFromResource #method:newFromResource#

    builderListItemFactoryNewFromResource   ,




 -- * Properties


-- ** bytes #attr:bytes#
-- | @GBytes@ containing the UI definition.

#if defined(ENABLE_OVERLOADING)
    BuilderListItemFactoryBytesPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
    builderListItemFactoryBytes             ,
#endif
    constructBuilderListItemFactoryBytes    ,
    getBuilderListItemFactoryBytes          ,


-- ** resource #attr:resource#
-- | Path of the resource containing the UI definition.

#if defined(ENABLE_OVERLOADING)
    BuilderListItemFactoryResourcePropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    builderListItemFactoryResource          ,
#endif
    constructBuilderListItemFactoryResource ,
    getBuilderListItemFactoryResource       ,


-- ** scope #attr:scope#
-- | @GtkBuilderScope@ to use when instantiating listitems

#if defined(ENABLE_OVERLOADING)
    BuilderListItemFactoryScopePropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
    builderListItemFactoryScope             ,
#endif
    constructBuilderListItemFactoryScope    ,
    getBuilderListItemFactoryScope          ,




    ) 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.Kind as DK
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.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.BuilderScope as Gtk.BuilderScope
import {-# SOURCE #-} qualified GI.Gtk.Objects.ListItemFactory as Gtk.ListItemFactory

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

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

foreign import ccall "gtk_builder_list_item_factory_get_type"
    c_gtk_builder_list_item_factory_get_type :: IO B.Types.GType

instance B.Types.TypedObject BuilderListItemFactory where
    glibType :: IO GType
glibType = IO GType
c_gtk_builder_list_item_factory_get_type

instance B.Types.GObject BuilderListItemFactory

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

instance O.HasParentTypes BuilderListItemFactory
type instance O.ParentTypes BuilderListItemFactory = '[Gtk.ListItemFactory.ListItemFactory, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveBuilderListItemFactoryMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveBuilderListItemFactoryMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveBuilderListItemFactoryMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveBuilderListItemFactoryMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveBuilderListItemFactoryMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveBuilderListItemFactoryMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveBuilderListItemFactoryMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveBuilderListItemFactoryMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveBuilderListItemFactoryMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveBuilderListItemFactoryMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveBuilderListItemFactoryMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveBuilderListItemFactoryMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveBuilderListItemFactoryMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveBuilderListItemFactoryMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveBuilderListItemFactoryMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveBuilderListItemFactoryMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveBuilderListItemFactoryMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveBuilderListItemFactoryMethod "getBytes" o = BuilderListItemFactoryGetBytesMethodInfo
    ResolveBuilderListItemFactoryMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveBuilderListItemFactoryMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveBuilderListItemFactoryMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveBuilderListItemFactoryMethod "getResource" o = BuilderListItemFactoryGetResourceMethodInfo
    ResolveBuilderListItemFactoryMethod "getScope" o = BuilderListItemFactoryGetScopeMethodInfo
    ResolveBuilderListItemFactoryMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveBuilderListItemFactoryMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveBuilderListItemFactoryMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveBuilderListItemFactoryMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

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

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

-- | Construct a `GValueConstruct` with valid value for the “@bytes@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructBuilderListItemFactoryBytes :: (IsBuilderListItemFactory o, MIO.MonadIO m) => GLib.Bytes.Bytes -> m (GValueConstruct o)
constructBuilderListItemFactoryBytes :: forall o (m :: * -> *).
(IsBuilderListItemFactory o, MonadIO m) =>
Bytes -> m (GValueConstruct o)
constructBuilderListItemFactoryBytes Bytes
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 Bytes -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"bytes" (Bytes -> Maybe Bytes
forall a. a -> Maybe a
P.Just Bytes
val)

#if defined(ENABLE_OVERLOADING)
data BuilderListItemFactoryBytesPropertyInfo
instance AttrInfo BuilderListItemFactoryBytesPropertyInfo where
    type AttrAllowedOps BuilderListItemFactoryBytesPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint BuilderListItemFactoryBytesPropertyInfo = IsBuilderListItemFactory
    type AttrSetTypeConstraint BuilderListItemFactoryBytesPropertyInfo = (~) GLib.Bytes.Bytes
    type AttrTransferTypeConstraint BuilderListItemFactoryBytesPropertyInfo = (~) GLib.Bytes.Bytes
    type AttrTransferType BuilderListItemFactoryBytesPropertyInfo = GLib.Bytes.Bytes
    type AttrGetType BuilderListItemFactoryBytesPropertyInfo = GLib.Bytes.Bytes
    type AttrLabel BuilderListItemFactoryBytesPropertyInfo = "bytes"
    type AttrOrigin BuilderListItemFactoryBytesPropertyInfo = BuilderListItemFactory
    attrGet = getBuilderListItemFactoryBytes
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructBuilderListItemFactoryBytes
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.BuilderListItemFactory.bytes"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-BuilderListItemFactory.html#g:attr:bytes"
        })
#endif

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

-- | Get the value of the “@resource@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' builderListItemFactory #resource
-- @
getBuilderListItemFactoryResource :: (MonadIO m, IsBuilderListItemFactory o) => o -> m (Maybe T.Text)
getBuilderListItemFactoryResource :: forall (m :: * -> *) o.
(MonadIO m, IsBuilderListItemFactory o) =>
o -> m (Maybe Text)
getBuilderListItemFactoryResource 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
"resource"

-- | Construct a `GValueConstruct` with valid value for the “@resource@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructBuilderListItemFactoryResource :: (IsBuilderListItemFactory o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructBuilderListItemFactoryResource :: forall o (m :: * -> *).
(IsBuilderListItemFactory o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructBuilderListItemFactoryResource 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
"resource" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data BuilderListItemFactoryResourcePropertyInfo
instance AttrInfo BuilderListItemFactoryResourcePropertyInfo where
    type AttrAllowedOps BuilderListItemFactoryResourcePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint BuilderListItemFactoryResourcePropertyInfo = IsBuilderListItemFactory
    type AttrSetTypeConstraint BuilderListItemFactoryResourcePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint BuilderListItemFactoryResourcePropertyInfo = (~) T.Text
    type AttrTransferType BuilderListItemFactoryResourcePropertyInfo = T.Text
    type AttrGetType BuilderListItemFactoryResourcePropertyInfo = (Maybe T.Text)
    type AttrLabel BuilderListItemFactoryResourcePropertyInfo = "resource"
    type AttrOrigin BuilderListItemFactoryResourcePropertyInfo = BuilderListItemFactory
    attrGet = getBuilderListItemFactoryResource
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructBuilderListItemFactoryResource
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.BuilderListItemFactory.resource"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-BuilderListItemFactory.html#g:attr:resource"
        })
#endif

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

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

-- | Construct a `GValueConstruct` with valid value for the “@scope@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructBuilderListItemFactoryScope :: (IsBuilderListItemFactory o, MIO.MonadIO m, Gtk.BuilderScope.IsBuilderScope a) => a -> m (GValueConstruct o)
constructBuilderListItemFactoryScope :: forall o (m :: * -> *) a.
(IsBuilderListItemFactory o, MonadIO m, IsBuilderScope a) =>
a -> m (GValueConstruct o)
constructBuilderListItemFactoryScope 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
"scope" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data BuilderListItemFactoryScopePropertyInfo
instance AttrInfo BuilderListItemFactoryScopePropertyInfo where
    type AttrAllowedOps BuilderListItemFactoryScopePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint BuilderListItemFactoryScopePropertyInfo = IsBuilderListItemFactory
    type AttrSetTypeConstraint BuilderListItemFactoryScopePropertyInfo = Gtk.BuilderScope.IsBuilderScope
    type AttrTransferTypeConstraint BuilderListItemFactoryScopePropertyInfo = Gtk.BuilderScope.IsBuilderScope
    type AttrTransferType BuilderListItemFactoryScopePropertyInfo = Gtk.BuilderScope.BuilderScope
    type AttrGetType BuilderListItemFactoryScopePropertyInfo = (Maybe Gtk.BuilderScope.BuilderScope)
    type AttrLabel BuilderListItemFactoryScopePropertyInfo = "scope"
    type AttrOrigin BuilderListItemFactoryScopePropertyInfo = BuilderListItemFactory
    attrGet = getBuilderListItemFactoryScope
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gtk.BuilderScope.BuilderScope v
    attrConstruct = constructBuilderListItemFactoryScope
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.BuilderListItemFactory.scope"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.8/docs/GI-Gtk-Objects-BuilderListItemFactory.html#g:attr:scope"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList BuilderListItemFactory
type instance O.AttributeList BuilderListItemFactory = BuilderListItemFactoryAttributeList
type BuilderListItemFactoryAttributeList = ('[ '("bytes", BuilderListItemFactoryBytesPropertyInfo), '("resource", BuilderListItemFactoryResourcePropertyInfo), '("scope", BuilderListItemFactoryScopePropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
builderListItemFactoryBytes :: AttrLabelProxy "bytes"
builderListItemFactoryBytes = AttrLabelProxy

builderListItemFactoryResource :: AttrLabelProxy "resource"
builderListItemFactoryResource = AttrLabelProxy

builderListItemFactoryScope :: AttrLabelProxy "scope"
builderListItemFactoryScope = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList BuilderListItemFactory = BuilderListItemFactorySignalList
type BuilderListItemFactorySignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method BuilderListItemFactory::new_from_bytes
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "scope"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "BuilderScope" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A scope to use when instantiating"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "bytes"
--           , argType = TInterface Name { namespace = "GLib" , name = "Bytes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the `GBytes` containing the ui file to instantiate"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gtk" , name = "BuilderListItemFactory" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_builder_list_item_factory_new_from_bytes" gtk_builder_list_item_factory_new_from_bytes :: 
    Ptr Gtk.BuilderScope.BuilderScope ->    -- scope : TInterface (Name {namespace = "Gtk", name = "BuilderScope"})
    Ptr GLib.Bytes.Bytes ->                 -- bytes : TInterface (Name {namespace = "GLib", name = "Bytes"})
    IO (Ptr BuilderListItemFactory)

-- | Creates a new @GtkBuilderListItemFactory@ that instantiates widgets
-- using /@bytes@/ as the data to pass to @GtkBuilder@.
builderListItemFactoryNewFromBytes ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.BuilderScope.IsBuilderScope a) =>
    Maybe (a)
    -- ^ /@scope@/: A scope to use when instantiating
    -> GLib.Bytes.Bytes
    -- ^ /@bytes@/: the @GBytes@ containing the ui file to instantiate
    -> m BuilderListItemFactory
    -- ^ __Returns:__ a new @GtkBuilderListItemFactory@
builderListItemFactoryNewFromBytes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBuilderScope a) =>
Maybe a -> Bytes -> m BuilderListItemFactory
builderListItemFactoryNewFromBytes Maybe a
scope Bytes
bytes = IO BuilderListItemFactory -> m BuilderListItemFactory
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BuilderListItemFactory -> m BuilderListItemFactory)
-> IO BuilderListItemFactory -> m BuilderListItemFactory
forall a b. (a -> b) -> a -> b
$ do
    Ptr BuilderScope
maybeScope <- case Maybe a
scope of
        Maybe a
Nothing -> Ptr BuilderScope -> IO (Ptr BuilderScope)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr BuilderScope
forall a. Ptr a
nullPtr
        Just a
jScope -> do
            Ptr BuilderScope
jScope' <- a -> IO (Ptr BuilderScope)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jScope
            Ptr BuilderScope -> IO (Ptr BuilderScope)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr BuilderScope
jScope'
    Ptr Bytes
bytes' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
bytes
    Ptr BuilderListItemFactory
result <- Ptr BuilderScope -> Ptr Bytes -> IO (Ptr BuilderListItemFactory)
gtk_builder_list_item_factory_new_from_bytes Ptr BuilderScope
maybeScope Ptr Bytes
bytes'
    Text -> Ptr BuilderListItemFactory -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"builderListItemFactoryNewFromBytes" Ptr BuilderListItemFactory
result
    BuilderListItemFactory
result' <- ((ManagedPtr BuilderListItemFactory -> BuilderListItemFactory)
-> Ptr BuilderListItemFactory -> IO BuilderListItemFactory
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr BuilderListItemFactory -> BuilderListItemFactory
BuilderListItemFactory) Ptr BuilderListItemFactory
result
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
scope a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
bytes
    BuilderListItemFactory -> IO BuilderListItemFactory
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BuilderListItemFactory
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method BuilderListItemFactory::new_from_resource
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "scope"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "BuilderScope" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A scope to use when instantiating"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "resource_path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "valid path to a resource that contains the data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gtk" , name = "BuilderListItemFactory" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_builder_list_item_factory_new_from_resource" gtk_builder_list_item_factory_new_from_resource :: 
    Ptr Gtk.BuilderScope.BuilderScope ->    -- scope : TInterface (Name {namespace = "Gtk", name = "BuilderScope"})
    CString ->                              -- resource_path : TBasicType TUTF8
    IO (Ptr BuilderListItemFactory)

-- | Creates a new @GtkBuilderListItemFactory@ that instantiates widgets
-- using data read from the given /@resourcePath@/ to pass to @GtkBuilder@.
builderListItemFactoryNewFromResource ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.BuilderScope.IsBuilderScope a) =>
    Maybe (a)
    -- ^ /@scope@/: A scope to use when instantiating
    -> T.Text
    -- ^ /@resourcePath@/: valid path to a resource that contains the data
    -> m BuilderListItemFactory
    -- ^ __Returns:__ a new @GtkBuilderListItemFactory@
builderListItemFactoryNewFromResource :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBuilderScope a) =>
Maybe a -> Text -> m BuilderListItemFactory
builderListItemFactoryNewFromResource Maybe a
scope Text
resourcePath = IO BuilderListItemFactory -> m BuilderListItemFactory
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BuilderListItemFactory -> m BuilderListItemFactory)
-> IO BuilderListItemFactory -> m BuilderListItemFactory
forall a b. (a -> b) -> a -> b
$ do
    Ptr BuilderScope
maybeScope <- case Maybe a
scope of
        Maybe a
Nothing -> Ptr BuilderScope -> IO (Ptr BuilderScope)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr BuilderScope
forall a. Ptr a
nullPtr
        Just a
jScope -> do
            Ptr BuilderScope
jScope' <- a -> IO (Ptr BuilderScope)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
jScope
            Ptr BuilderScope -> IO (Ptr BuilderScope)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr BuilderScope
jScope'
    CString
resourcePath' <- Text -> IO CString
textToCString Text
resourcePath
    Ptr BuilderListItemFactory
result <- Ptr BuilderScope -> CString -> IO (Ptr BuilderListItemFactory)
gtk_builder_list_item_factory_new_from_resource Ptr BuilderScope
maybeScope CString
resourcePath'
    Text -> Ptr BuilderListItemFactory -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"builderListItemFactoryNewFromResource" Ptr BuilderListItemFactory
result
    BuilderListItemFactory
result' <- ((ManagedPtr BuilderListItemFactory -> BuilderListItemFactory)
-> Ptr BuilderListItemFactory -> IO BuilderListItemFactory
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr BuilderListItemFactory -> BuilderListItemFactory
BuilderListItemFactory) Ptr BuilderListItemFactory
result
    Maybe a -> (a -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe a
scope a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
resourcePath'
    BuilderListItemFactory -> IO BuilderListItemFactory
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BuilderListItemFactory
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "gtk_builder_list_item_factory_get_bytes" gtk_builder_list_item_factory_get_bytes :: 
    Ptr BuilderListItemFactory ->           -- self : TInterface (Name {namespace = "Gtk", name = "BuilderListItemFactory"})
    IO (Ptr GLib.Bytes.Bytes)

-- | Gets the data used as the @GtkBuilder@ UI template for constructing
-- listitems.
builderListItemFactoryGetBytes ::
    (B.CallStack.HasCallStack, MonadIO m, IsBuilderListItemFactory a) =>
    a
    -- ^ /@self@/: a @GtkBuilderListItemFactory@
    -> m GLib.Bytes.Bytes
    -- ^ __Returns:__ The @GtkBuilder@ data
builderListItemFactoryGetBytes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBuilderListItemFactory a) =>
a -> m Bytes
builderListItemFactoryGetBytes a
self = IO Bytes -> m Bytes
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bytes -> m Bytes) -> IO Bytes -> m Bytes
forall a b. (a -> b) -> a -> b
$ do
    Ptr BuilderListItemFactory
self' <- a -> IO (Ptr BuilderListItemFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Bytes
result <- Ptr BuilderListItemFactory -> IO (Ptr Bytes)
gtk_builder_list_item_factory_get_bytes Ptr BuilderListItemFactory
self'
    Text -> Ptr Bytes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"builderListItemFactoryGetBytes" Ptr Bytes
result
    Bytes
result' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes) Ptr Bytes
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bytes -> IO Bytes
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
result'

#if defined(ENABLE_OVERLOADING)
data BuilderListItemFactoryGetBytesMethodInfo
instance (signature ~ (m GLib.Bytes.Bytes), MonadIO m, IsBuilderListItemFactory a) => O.OverloadedMethod BuilderListItemFactoryGetBytesMethodInfo a signature where
    overloadedMethod = builderListItemFactoryGetBytes

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


#endif

-- method BuilderListItemFactory::get_resource
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "BuilderListItemFactory" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkBuilderListItemFactory`"
--                 , 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_builder_list_item_factory_get_resource" gtk_builder_list_item_factory_get_resource :: 
    Ptr BuilderListItemFactory ->           -- self : TInterface (Name {namespace = "Gtk", name = "BuilderListItemFactory"})
    IO CString

-- | If the data references a resource, gets the path of that resource.
builderListItemFactoryGetResource ::
    (B.CallStack.HasCallStack, MonadIO m, IsBuilderListItemFactory a) =>
    a
    -- ^ /@self@/: a @GtkBuilderListItemFactory@
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The path to the resource
builderListItemFactoryGetResource :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBuilderListItemFactory a) =>
a -> m (Maybe Text)
builderListItemFactoryGetResource a
self = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
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 BuilderListItemFactory
self' <- a -> IO (Ptr BuilderListItemFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr BuilderListItemFactory -> IO CString
gtk_builder_list_item_factory_get_resource Ptr BuilderListItemFactory
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 a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

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

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


#endif

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

foreign import ccall "gtk_builder_list_item_factory_get_scope" gtk_builder_list_item_factory_get_scope :: 
    Ptr BuilderListItemFactory ->           -- self : TInterface (Name {namespace = "Gtk", name = "BuilderListItemFactory"})
    IO (Ptr Gtk.BuilderScope.BuilderScope)

-- | Gets the scope used when constructing listitems.
builderListItemFactoryGetScope ::
    (B.CallStack.HasCallStack, MonadIO m, IsBuilderListItemFactory a) =>
    a
    -- ^ /@self@/: a @GtkBuilderListItemFactory@
    -> m (Maybe Gtk.BuilderScope.BuilderScope)
    -- ^ __Returns:__ The scope used when constructing listitems
builderListItemFactoryGetScope :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsBuilderListItemFactory a) =>
a -> m (Maybe BuilderScope)
builderListItemFactoryGetScope a
self = IO (Maybe BuilderScope) -> m (Maybe BuilderScope)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe BuilderScope) -> m (Maybe BuilderScope))
-> IO (Maybe BuilderScope) -> m (Maybe BuilderScope)
forall a b. (a -> b) -> a -> b
$ do
    Ptr BuilderListItemFactory
self' <- a -> IO (Ptr BuilderListItemFactory)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr BuilderScope
result <- Ptr BuilderListItemFactory -> IO (Ptr BuilderScope)
gtk_builder_list_item_factory_get_scope Ptr BuilderListItemFactory
self'
    Maybe BuilderScope
maybeResult <- Ptr BuilderScope
-> (Ptr BuilderScope -> IO BuilderScope) -> IO (Maybe BuilderScope)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr BuilderScope
result ((Ptr BuilderScope -> IO BuilderScope) -> IO (Maybe BuilderScope))
-> (Ptr BuilderScope -> IO BuilderScope) -> IO (Maybe BuilderScope)
forall a b. (a -> b) -> a -> b
$ \Ptr BuilderScope
result' -> do
        BuilderScope
result'' <- ((ManagedPtr BuilderScope -> BuilderScope)
-> Ptr BuilderScope -> IO BuilderScope
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr BuilderScope -> BuilderScope
Gtk.BuilderScope.BuilderScope) Ptr BuilderScope
result'
        BuilderScope -> IO BuilderScope
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return BuilderScope
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe BuilderScope -> IO (Maybe BuilderScope)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe BuilderScope
maybeResult

#if defined(ENABLE_OVERLOADING)
data BuilderListItemFactoryGetScopeMethodInfo
instance (signature ~ (m (Maybe Gtk.BuilderScope.BuilderScope)), MonadIO m, IsBuilderListItemFactory a) => O.OverloadedMethod BuilderListItemFactoryGetScopeMethodInfo a signature where
    overloadedMethod = builderListItemFactoryGetScope

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


#endif