{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Applications and libraries often contain binary or textual data that is
-- really part of the application, rather than user data. For instance
-- <https://docs.gtk.org/gtk4/class.Builder.html `GtkBuilder`> @.ui@ files,
-- splashscreen images, t'GI.Gio.Objects.Menu.Menu' markup XML, CSS files, icons, etc.
-- These are often shipped as files in @$datadir\/appname@, or manually
-- included as literal strings in the code.
-- 
-- The @GResource@ API and the
-- <http://developer.gnome.org/gio/stable/glib-compile-resources.html `glib-compile-resources`> program provide a
-- convenient and efficient alternative to this which has some nice properties.
-- You maintain the files as normal files, so it’s easy to edit them, but during
-- the build the files are combined into a binary bundle that is linked into the
-- executable. This means that loading the resource files are efficient (as they
-- are already in memory, shared with other instances) and simple (no need to
-- check for things like I\/O errors or locate the files in the filesystem). It
-- also makes it easier to create relocatable applications.
-- 
-- Resource files can also be marked as compressed. Such files will be included
-- in the resource bundle in a compressed form, but will be automatically
-- uncompressed when the resource is used. This is very useful e.g. for larger
-- text files that are parsed once (or rarely) and then thrown away.
-- 
-- Resource files can also be marked to be preprocessed, by setting the value of the
-- @preprocess@ attribute to a comma-separated list of preprocessing options.
-- The only options currently supported are:
-- 
--  - @xml-stripblanks@ which will use the <http://developer.gnome.org/gio/stable/man:xmllint(1 `xmllint`>) command
--    to strip ignorable whitespace from the XML file. For this to work,
--    the @XMLLINT@ environment variable must be set to the full path to
--    the xmllint executable, or xmllint must be in the @PATH@; otherwise
--    the preprocessing step is skipped.
-- 
--  - @to-pixdata@ (deprecated since gdk-pixbuf 2.32) which will use the
--    @gdk-pixbuf-pixdata@ command to convert images to the <https://docs.gtk.org/gdk-pixbuf/class.Pixdata.html `GdkPixdata`>
--    format, which allows you to create pixbufs directly using the data inside
--    the resource file, rather than an (uncompressed) copy of it. For this, the
--    @gdk-pixbuf-pixdata@ program must be in the @PATH@, or the
--    @GDK_PIXBUF_PIXDATA@ environment variable must be set to the full path to
--    the @gdk-pixbuf-pixdata@ executable; otherwise the resource compiler will
--    abort. @to-pixdata@ has been deprecated since gdk-pixbuf 2.32, as
--    @GResource@ supports embedding modern image formats just as well. Instead
--    of using it, embed a PNG or SVG file in your @GResource@.
-- 
--  - @json-stripblanks@ which will use the
--    <http://developer.gnome.org/gio/stable/man:json-glib-format(1 `json-glib-format`>) command to strip ignorable
--    whitespace from the JSON file. For this to work, the @JSON_GLIB_FORMAT@
--    environment variable must be set to the full path to the
--    @json-glib-format@ executable, or it must be in the @PATH@; otherwise the
--    preprocessing step is skipped. In addition, at least version 1.6 of
--    @json-glib-format@ is required.
-- 
-- Resource files will be exported in the @GResource@ namespace using the
-- combination of the given @prefix@ and the filename from the @file@ element.
-- The @alias@ attribute can be used to alter the filename to expose them at a
-- different location in the resource namespace. Typically, this is used to
-- include files from a different source directory without exposing the source
-- directory in the resource namespace, as in the example below.
-- 
-- Resource bundles are created by the
-- <http://developer.gnome.org/gio/stable/glib-compile-resources.html `glib-compile-resources`> program
-- which takes an XML file that describes the bundle, and a set of files that
-- the XML references. These are combined into a binary resource bundle.
-- 
-- An example resource description:
-- 
-- === /xml code/
-- ><?xml version="1.0" encoding="UTF-8"?>
-- ><gresources>
-- >  <gresource prefix="/org/gtk/Example">
-- >    <file>data/splashscreen.png</file>
-- >    <file compressed="true">dialog.ui</file>
-- >    <file preprocess="xml-stripblanks">menumarkup.xml</file>
-- >    <file alias="example.css">data/example.css</file>
-- >  </gresource>
-- ></gresources>
-- 
-- 
-- This will create a resource bundle with the following files:
-- >/org/gtk/Example/data/splashscreen.png
-- >/org/gtk/Example/dialog.ui
-- >/org/gtk/Example/menumarkup.xml
-- >/org/gtk/Example/example.css
-- 
-- 
-- Note that all resources in the process share the same namespace, so use
-- Java-style path prefixes (like in the above example) to avoid conflicts.
-- 
-- You can then use <http://developer.gnome.org/gio/stable/glib-compile-resources.html `glib-compile-resources`> to
-- compile the XML to a binary bundle that you can load with
-- [func/@gio@/.Resource.load]. However, it’s more common to use the
-- @--generate-source@ and @--generate-header@ arguments to create a source file
-- and header to link directly into your application.
-- This will generate @get_resource()@, @register_resource()@ and
-- @unregister_resource()@ functions, prefixed by the @--c-name@ argument passed
-- to <http://developer.gnome.org/gio/stable/glib-compile-resources.html `glib-compile-resources`>. @get_resource()@
-- returns the generated @GResource@ object. The register and unregister
-- functions register the resource so its files can be accessed using
-- 'GI.Gio.Functions.resourcesLookupData'.
-- 
-- Once a @GResource@ has been created and registered all the data in it can be
-- accessed globally in the process by using API calls like
-- 'GI.Gio.Functions.resourcesOpenStream' to stream the data or
-- 'GI.Gio.Functions.resourcesLookupData' to get a direct pointer to the data. You can
-- also use URIs like @resource:\/\/\/org\/gtk\/Example\/data\/splashscreen.png@ with
-- t'GI.Gio.Interfaces.File.File' to access the resource data.
-- 
-- Some higher-level APIs, such as <https://docs.gtk.org/gtk4/class.Application.html `GtkApplication`>,
-- will automatically load resources from certain well-known paths in the
-- resource namespace as a convenience. See the documentation for those APIs
-- for details.
-- 
-- There are two forms of the generated source, the default version uses the
-- compiler support for constructor and destructor functions (where available)
-- to automatically create and register the @GResource@ on startup or library
-- load time. If you pass @--manual-register@, two functions to
-- register\/unregister the resource are created instead. This requires an
-- explicit initialization call in your application\/library, but it works on all
-- platforms, even on the minor ones where constructors are not supported.
-- (Constructor support is available for at least Win32, Mac OS and Linux.)
-- 
-- Note that resource data can point directly into the data segment of e.g. a
-- library, so if you are unloading libraries during runtime you need to be very
-- careful with keeping around pointers to data from a resource, as this goes
-- away when the library is unloaded. However, in practice this is not generally
-- a problem, since most resource accesses are for your own resources, and
-- resource data is often used once, during parsing, and then released.
-- 
-- = Overlays
-- 
-- When debugging a program or testing a change to an installed version, it is
-- often useful to be able to replace resources in the program or library,
-- without recompiling, for debugging or quick hacking and testing purposes.
-- Since GLib 2.50, it is possible to use the @G_RESOURCE_OVERLAYS@ environment
-- variable to selectively overlay resources with replacements from the
-- filesystem.  It is a @G_SEARCHPATH_SEPARATOR@-separated list of substitutions
-- to perform during resource lookups. It is ignored when running in a setuid
-- process.
-- 
-- A substitution has the form
-- 
-- >/org/gtk/libgtk=/home/desrt/gtk-overlay
-- 
-- 
-- The part before the @=@ is the resource subpath for which the overlay
-- applies.  The part after is a filesystem path which contains files and
-- subdirectories as you would like to be loaded as resources with the
-- equivalent names.
-- 
-- In the example above, if an application tried to load a resource with the
-- resource path @\/org\/gtk\/libgtk\/ui\/gtkdialog.ui@ then @GResource@ would check
-- the filesystem path @\/home\/desrt\/gtk-overlay\/ui\/gtkdialog.ui@.  If a file was
-- found there, it would be used instead.  This is an overlay, not an outright
-- replacement, which means that if a file is not found at that path, the
-- built-in version will be used instead.  Whiteouts are not currently
-- supported.
-- 
-- Substitutions must start with a slash, and must not contain a trailing slash
-- before the @=@.  The path after the slash should ideally be absolute, but
-- this is not strictly required.  It is possible to overlay the location of a
-- single resource with an individual file.
-- 
-- /Since: 2.32/

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

module GI.Gio.Structs.Resource
    ( 

-- * Exported types
    Resource(..)                            ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [enumerateChildren]("GI.Gio.Structs.Resource#g:method:enumerateChildren"), [lookupData]("GI.Gio.Structs.Resource#g:method:lookupData"), [openStream]("GI.Gio.Structs.Resource#g:method:openStream"), [ref]("GI.Gio.Structs.Resource#g:method:ref"), [unref]("GI.Gio.Structs.Resource#g:method:unref").
-- 
-- ==== Getters
-- [getInfo]("GI.Gio.Structs.Resource#g:method:getInfo").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveResourceMethod                   ,
#endif

-- ** enumerateChildren #method:enumerateChildren#

#if defined(ENABLE_OVERLOADING)
    ResourceEnumerateChildrenMethodInfo     ,
#endif
    resourceEnumerateChildren               ,


-- ** getInfo #method:getInfo#

#if defined(ENABLE_OVERLOADING)
    ResourceGetInfoMethodInfo               ,
#endif
    resourceGetInfo                         ,


-- ** load #method:load#

    resourceLoad                            ,


-- ** lookupData #method:lookupData#

#if defined(ENABLE_OVERLOADING)
    ResourceLookupDataMethodInfo            ,
#endif
    resourceLookupData                      ,


-- ** newFromData #method:newFromData#

    resourceNewFromData                     ,


-- ** openStream #method:openStream#

#if defined(ENABLE_OVERLOADING)
    ResourceOpenStreamMethodInfo            ,
#endif
    resourceOpenStream                      ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    ResourceRefMethodInfo                   ,
#endif
    resourceRef                             ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    ResourceUnrefMethodInfo                 ,
#endif
    resourceUnref                           ,




    ) 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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.PollFD as GLib.PollFD
import qualified GI.GLib.Structs.Source as GLib.Source
import qualified GI.GObject.Callbacks as GObject.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.InputStream as Gio.InputStream

#else
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Objects.InputStream as Gio.InputStream

#endif

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

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

foreign import ccall "g_resource_get_type" c_g_resource_get_type :: 
    IO GType

type instance O.ParentTypes Resource = '[]
instance O.HasParentTypes Resource

instance B.Types.TypedObject Resource where
    glibType :: IO GType
glibType = IO GType
c_g_resource_get_type

instance B.Types.GBoxed Resource

-- | Convert 'Resource' 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 Resource) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_resource_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Resource -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Resource
P.Nothing = Ptr GValue -> Ptr Resource -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr Resource
forall a. Ptr a
FP.nullPtr :: FP.Ptr Resource)
    gvalueSet_ Ptr GValue
gv (P.Just Resource
obj) = Resource -> (Ptr Resource -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Resource
obj (Ptr GValue -> Ptr Resource -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Resource)
gvalueGet_ Ptr GValue
gv = do
        ptr <- Ptr GValue -> IO (Ptr Resource)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr Resource)
        if ptr /= FP.nullPtr
        then P.Just <$> B.ManagedPtr.newBoxed Resource ptr
        else return P.Nothing
        
    


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Resource
type instance O.AttributeList Resource = ResourceAttributeList
type ResourceAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif

-- method Resource::new_from_data
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "data"
--           , argType = TInterface Name { namespace = "GLib" , name = "Bytes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GBytes" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Resource" })
-- throws : True
-- Skip return : False

foreign import ccall "g_resource_new_from_data" g_resource_new_from_data :: 
    Ptr GLib.Bytes.Bytes ->                 -- data : TInterface (Name {namespace = "GLib", name = "Bytes"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Resource)

-- | Creates a GResource from a reference to the binary resource bundle.
-- This will keep a reference to /@data@/ while the resource lives, so
-- the data should not be modified or freed.
-- 
-- If you want to use this resource in the global resource namespace you need
-- to register it with 'GI.Gio.Functions.resourcesRegister'.
-- 
-- Note: /@data@/ must be backed by memory that is at least pointer aligned.
-- Otherwise this function will internally create a copy of the memory since
-- GLib 2.56, or in older versions fail and exit the process.
-- 
-- If /@data@/ is empty or corrupt, 'GI.Gio.Enums.ResourceErrorInternal' will be returned.
-- 
-- /Since: 2.32/
resourceNewFromData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.Bytes.Bytes
    -- ^ /@data@/: A t'GI.GLib.Structs.Bytes.Bytes'
    -> m Resource
    -- ^ __Returns:__ a new t'GI.Gio.Structs.Resource.Resource', or 'P.Nothing' on error /(Can throw 'Data.GI.Base.GError.GError')/
resourceNewFromData :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bytes -> m Resource
resourceNewFromData Bytes
data_ = IO Resource -> m Resource
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Resource -> m Resource) -> IO Resource -> m Resource
forall a b. (a -> b) -> a -> b
$ do
    data_' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
data_
    onException (do
        result <- propagateGError $ g_resource_new_from_data data_'
        checkUnexpectedReturnNULL "resourceNewFromData" result
        result' <- (wrapBoxed Resource) result
        touchManagedPtr data_
        return result'
     ) (do
        return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method Resource::enumerate_children
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "resource"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Resource" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GResource" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pathname inside the resource"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "lookup_flags"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "ResourceLookupFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GResourceLookupFlags"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) (-1) (TBasicType TUTF8))
-- throws : True
-- Skip return : False

foreign import ccall "g_resource_enumerate_children" g_resource_enumerate_children :: 
    Ptr Resource ->                         -- resource : TInterface (Name {namespace = "Gio", name = "Resource"})
    CString ->                              -- path : TBasicType TUTF8
    CUInt ->                                -- lookup_flags : TInterface (Name {namespace = "Gio", name = "ResourceLookupFlags"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr CString)

-- | Returns all the names of children at the specified /@path@/ in the resource.
-- The return result is a 'P.Nothing' terminated list of strings which should
-- be released with 'GI.GLib.Functions.strfreev'.
-- 
-- If /@path@/ is invalid or does not exist in the t'GI.Gio.Structs.Resource.Resource',
-- 'GI.Gio.Enums.ResourceErrorNotFound' will be returned.
-- 
-- /@lookupFlags@/ controls the behaviour of the lookup.
-- 
-- /Since: 2.32/
resourceEnumerateChildren ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Resource
    -- ^ /@resource@/: A t'GI.Gio.Structs.Resource.Resource'
    -> T.Text
    -- ^ /@path@/: A pathname inside the resource
    -> [Gio.Flags.ResourceLookupFlags]
    -- ^ /@lookupFlags@/: A t'GI.Gio.Flags.ResourceLookupFlags'
    -> m [T.Text]
    -- ^ __Returns:__ an array of constant strings /(Can throw 'Data.GI.Base.GError.GError')/
resourceEnumerateChildren :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Resource -> Text -> [ResourceLookupFlags] -> m [Text]
resourceEnumerateChildren Resource
resource Text
path [ResourceLookupFlags]
lookupFlags = IO [Text] -> m [Text]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
    resource' <- Resource -> IO (Ptr Resource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Resource
resource
    path' <- textToCString path
    let lookupFlags' = [ResourceLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ResourceLookupFlags]
lookupFlags
    onException (do
        result <- propagateGError $ g_resource_enumerate_children resource' path' lookupFlags'
        checkUnexpectedReturnNULL "resourceEnumerateChildren" result
        result' <- unpackZeroTerminatedUTF8CArray result
        mapZeroTerminatedCArray freeMem result
        freeMem result
        touchManagedPtr resource
        freeMem path'
        return result'
     ) (do
        freeMem path'
     )

#if defined(ENABLE_OVERLOADING)
data ResourceEnumerateChildrenMethodInfo
instance (signature ~ (T.Text -> [Gio.Flags.ResourceLookupFlags] -> m [T.Text]), MonadIO m) => O.OverloadedMethod ResourceEnumerateChildrenMethodInfo Resource signature where
    overloadedMethod = resourceEnumerateChildren

instance O.OverloadedMethodInfo ResourceEnumerateChildrenMethodInfo Resource where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Structs.Resource.resourceEnumerateChildren",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Structs-Resource.html#v:resourceEnumerateChildren"
        })


#endif

-- method Resource::get_info
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "resource"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Resource" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GResource" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pathname inside the resource"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "lookup_flags"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "ResourceLookupFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GResourceLookupFlags"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TSize
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a location to place the length of the contents of the file,\n   or %NULL if the length is not needed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "flags"
--           , argType = TBasicType TUInt32
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a location to place the flags about the file,\n   or %NULL if the length is not needed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_resource_get_info" g_resource_get_info :: 
    Ptr Resource ->                         -- resource : TInterface (Name {namespace = "Gio", name = "Resource"})
    CString ->                              -- path : TBasicType TUTF8
    CUInt ->                                -- lookup_flags : TInterface (Name {namespace = "Gio", name = "ResourceLookupFlags"})
    Ptr FCT.CSize ->                        -- size : TBasicType TSize
    Ptr Word32 ->                           -- flags : TBasicType TUInt32
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Looks for a file at the specified /@path@/ in the resource and
-- if found returns information about it.
-- 
-- /@lookupFlags@/ controls the behaviour of the lookup.
-- 
-- /Since: 2.32/
resourceGetInfo ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Resource
    -- ^ /@resource@/: A t'GI.Gio.Structs.Resource.Resource'
    -> T.Text
    -- ^ /@path@/: A pathname inside the resource
    -> [Gio.Flags.ResourceLookupFlags]
    -- ^ /@lookupFlags@/: A t'GI.Gio.Flags.ResourceLookupFlags'
    -> m ((FCT.CSize, Word32))
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
resourceGetInfo :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Resource -> Text -> [ResourceLookupFlags] -> m (CSize, Word32)
resourceGetInfo Resource
resource Text
path [ResourceLookupFlags]
lookupFlags = IO (CSize, Word32) -> m (CSize, Word32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (CSize, Word32) -> m (CSize, Word32))
-> IO (CSize, Word32) -> m (CSize, Word32)
forall a b. (a -> b) -> a -> b
$ do
    resource' <- Resource -> IO (Ptr Resource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Resource
resource
    path' <- textToCString path
    let lookupFlags' = [ResourceLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ResourceLookupFlags]
lookupFlags
    size <- allocMem :: IO (Ptr FCT.CSize)
    flags <- allocMem :: IO (Ptr Word32)
    onException (do
        _ <- propagateGError $ g_resource_get_info resource' path' lookupFlags' size flags
        size' <- peek size
        flags' <- peek flags
        touchManagedPtr resource
        freeMem path'
        freeMem size
        freeMem flags
        return (size', flags')
     ) (do
        freeMem path'
        freeMem size
        freeMem flags
     )

#if defined(ENABLE_OVERLOADING)
data ResourceGetInfoMethodInfo
instance (signature ~ (T.Text -> [Gio.Flags.ResourceLookupFlags] -> m ((FCT.CSize, Word32))), MonadIO m) => O.OverloadedMethod ResourceGetInfoMethodInfo Resource signature where
    overloadedMethod = resourceGetInfo

instance O.OverloadedMethodInfo ResourceGetInfoMethodInfo Resource where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Structs.Resource.resourceGetInfo",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Structs-Resource.html#v:resourceGetInfo"
        })


#endif

-- method Resource::lookup_data
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "resource"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Resource" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GResource" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pathname inside the resource"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "lookup_flags"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "ResourceLookupFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GResourceLookupFlags"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Bytes" })
-- throws : True
-- Skip return : False

foreign import ccall "g_resource_lookup_data" g_resource_lookup_data :: 
    Ptr Resource ->                         -- resource : TInterface (Name {namespace = "Gio", name = "Resource"})
    CString ->                              -- path : TBasicType TUTF8
    CUInt ->                                -- lookup_flags : TInterface (Name {namespace = "Gio", name = "ResourceLookupFlags"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr GLib.Bytes.Bytes)

-- | Looks for a file at the specified /@path@/ in the resource and
-- returns a t'GI.GLib.Structs.Bytes.Bytes' that lets you directly access the data in
-- memory.
-- 
-- The data is always followed by a zero byte, so you
-- can safely use the data as a C string. However, that byte
-- is not included in the size of the GBytes.
-- 
-- For uncompressed resource files this is a pointer directly into
-- the resource bundle, which is typically in some readonly data section
-- in the program binary. For compressed files we allocate memory on
-- the heap and automatically uncompress the data.
-- 
-- /@lookupFlags@/ controls the behaviour of the lookup.
-- 
-- /Since: 2.32/
resourceLookupData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Resource
    -- ^ /@resource@/: A t'GI.Gio.Structs.Resource.Resource'
    -> T.Text
    -- ^ /@path@/: A pathname inside the resource
    -> [Gio.Flags.ResourceLookupFlags]
    -- ^ /@lookupFlags@/: A t'GI.Gio.Flags.ResourceLookupFlags'
    -> m GLib.Bytes.Bytes
    -- ^ __Returns:__ t'GI.GLib.Structs.Bytes.Bytes' or 'P.Nothing' on error.
    --     Free the returned object with 'GI.GLib.Structs.Bytes.bytesUnref' /(Can throw 'Data.GI.Base.GError.GError')/
resourceLookupData :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Resource -> Text -> [ResourceLookupFlags] -> m Bytes
resourceLookupData Resource
resource Text
path [ResourceLookupFlags]
lookupFlags = 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
    resource' <- Resource -> IO (Ptr Resource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Resource
resource
    path' <- textToCString path
    let lookupFlags' = [ResourceLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ResourceLookupFlags]
lookupFlags
    onException (do
        result <- propagateGError $ g_resource_lookup_data resource' path' lookupFlags'
        checkUnexpectedReturnNULL "resourceLookupData" result
        result' <- (wrapBoxed GLib.Bytes.Bytes) result
        touchManagedPtr resource
        freeMem path'
        return result'
     ) (do
        freeMem path'
     )

#if defined(ENABLE_OVERLOADING)
data ResourceLookupDataMethodInfo
instance (signature ~ (T.Text -> [Gio.Flags.ResourceLookupFlags] -> m GLib.Bytes.Bytes), MonadIO m) => O.OverloadedMethod ResourceLookupDataMethodInfo Resource signature where
    overloadedMethod = resourceLookupData

instance O.OverloadedMethodInfo ResourceLookupDataMethodInfo Resource where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Structs.Resource.resourceLookupData",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Structs-Resource.html#v:resourceLookupData"
        })


#endif

-- method Resource::open_stream
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "resource"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Resource" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GResource" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A pathname inside the resource"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "lookup_flags"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "ResourceLookupFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GResourceLookupFlags"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "InputStream" })
-- throws : True
-- Skip return : False

foreign import ccall "g_resource_open_stream" g_resource_open_stream :: 
    Ptr Resource ->                         -- resource : TInterface (Name {namespace = "Gio", name = "Resource"})
    CString ->                              -- path : TBasicType TUTF8
    CUInt ->                                -- lookup_flags : TInterface (Name {namespace = "Gio", name = "ResourceLookupFlags"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Gio.InputStream.InputStream)

-- | Looks for a file at the specified /@path@/ in the resource and
-- returns a t'GI.Gio.Objects.InputStream.InputStream' that lets you read the data.
-- 
-- /@lookupFlags@/ controls the behaviour of the lookup.
-- 
-- /Since: 2.32/
resourceOpenStream ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Resource
    -- ^ /@resource@/: A t'GI.Gio.Structs.Resource.Resource'
    -> T.Text
    -- ^ /@path@/: A pathname inside the resource
    -> [Gio.Flags.ResourceLookupFlags]
    -- ^ /@lookupFlags@/: A t'GI.Gio.Flags.ResourceLookupFlags'
    -> m Gio.InputStream.InputStream
    -- ^ __Returns:__ t'GI.Gio.Objects.InputStream.InputStream' or 'P.Nothing' on error.
    --     Free the returned object with 'GI.GObject.Objects.Object.objectUnref' /(Can throw 'Data.GI.Base.GError.GError')/
resourceOpenStream :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Resource -> Text -> [ResourceLookupFlags] -> m InputStream
resourceOpenStream Resource
resource Text
path [ResourceLookupFlags]
lookupFlags = IO InputStream -> m InputStream
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputStream -> m InputStream)
-> IO InputStream -> m InputStream
forall a b. (a -> b) -> a -> b
$ do
    resource' <- Resource -> IO (Ptr Resource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Resource
resource
    path' <- textToCString path
    let lookupFlags' = [ResourceLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ResourceLookupFlags]
lookupFlags
    onException (do
        result <- propagateGError $ g_resource_open_stream resource' path' lookupFlags'
        checkUnexpectedReturnNULL "resourceOpenStream" result
        result' <- (wrapObject Gio.InputStream.InputStream) result
        touchManagedPtr resource
        freeMem path'
        return result'
     ) (do
        freeMem path'
     )

#if defined(ENABLE_OVERLOADING)
data ResourceOpenStreamMethodInfo
instance (signature ~ (T.Text -> [Gio.Flags.ResourceLookupFlags] -> m Gio.InputStream.InputStream), MonadIO m) => O.OverloadedMethod ResourceOpenStreamMethodInfo Resource signature where
    overloadedMethod = resourceOpenStream

instance O.OverloadedMethodInfo ResourceOpenStreamMethodInfo Resource where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Structs.Resource.resourceOpenStream",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Structs-Resource.html#v:resourceOpenStream"
        })


#endif

-- method Resource::ref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "resource"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Resource" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GResource" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Resource" })
-- throws : False
-- Skip return : False

foreign import ccall "g_resource_ref" g_resource_ref :: 
    Ptr Resource ->                         -- resource : TInterface (Name {namespace = "Gio", name = "Resource"})
    IO (Ptr Resource)

-- | Atomically increments the reference count of /@resource@/ by one. This
-- function is MT-safe and may be called from any thread.
-- 
-- /Since: 2.32/
resourceRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Resource
    -- ^ /@resource@/: A t'GI.Gio.Structs.Resource.Resource'
    -> m Resource
    -- ^ __Returns:__ The passed in t'GI.Gio.Structs.Resource.Resource'
resourceRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Resource -> m Resource
resourceRef Resource
resource = IO Resource -> m Resource
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Resource -> m Resource) -> IO Resource -> m Resource
forall a b. (a -> b) -> a -> b
$ do
    resource' <- Resource -> IO (Ptr Resource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Resource
resource
    result <- g_resource_ref resource'
    checkUnexpectedReturnNULL "resourceRef" result
    result' <- (wrapBoxed Resource) result
    touchManagedPtr resource
    return result'

#if defined(ENABLE_OVERLOADING)
data ResourceRefMethodInfo
instance (signature ~ (m Resource), MonadIO m) => O.OverloadedMethod ResourceRefMethodInfo Resource signature where
    overloadedMethod = resourceRef

instance O.OverloadedMethodInfo ResourceRefMethodInfo Resource where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Structs.Resource.resourceRef",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Structs-Resource.html#v:resourceRef"
        })


#endif

-- method Resource::unref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "resource"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Resource" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GResource" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_resource_unref" g_resource_unref :: 
    Ptr Resource ->                         -- resource : TInterface (Name {namespace = "Gio", name = "Resource"})
    IO ()

-- | Atomically decrements the reference count of /@resource@/ by one. If the
-- reference count drops to 0, all memory allocated by the resource is
-- released. This function is MT-safe and may be called from any
-- thread.
-- 
-- /Since: 2.32/
resourceUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Resource
    -- ^ /@resource@/: A t'GI.Gio.Structs.Resource.Resource'
    -> m ()
resourceUnref :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Resource -> m ()
resourceUnref Resource
resource = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    resource' <- Resource -> IO (Ptr Resource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Resource
resource
    g_resource_unref resource'
    touchManagedPtr resource
    return ()

#if defined(ENABLE_OVERLOADING)
data ResourceUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod ResourceUnrefMethodInfo Resource signature where
    overloadedMethod = resourceUnref

instance O.OverloadedMethodInfo ResourceUnrefMethodInfo Resource where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Structs.Resource.resourceUnref",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Structs-Resource.html#v:resourceUnref"
        })


#endif

-- method Resource::load
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "filename"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the path of a filename to load, in the GLib filename encoding"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Resource" })
-- throws : True
-- Skip return : False

foreign import ccall "g_resource_load" g_resource_load :: 
    CString ->                              -- filename : TBasicType TFileName
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Resource)

-- | Loads a binary resource bundle and creates a t'GI.Gio.Structs.Resource.Resource' representation of it, allowing
-- you to query it for data.
-- 
-- If you want to use this resource in the global resource namespace you need
-- to register it with 'GI.Gio.Functions.resourcesRegister'.
-- 
-- If /@filename@/ is empty or the data in it is corrupt,
-- 'GI.Gio.Enums.ResourceErrorInternal' will be returned. If /@filename@/ doesn’t exist, or
-- there is an error in reading it, an error from 'GI.GLib.Structs.MappedFile.mappedFileNew' will be
-- returned.
-- 
-- /Since: 2.32/
resourceLoad ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Char]
    -- ^ /@filename@/: the path of a filename to load, in the GLib filename encoding
    -> m Resource
    -- ^ __Returns:__ a new t'GI.Gio.Structs.Resource.Resource', or 'P.Nothing' on error /(Can throw 'Data.GI.Base.GError.GError')/
resourceLoad :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> m Resource
resourceLoad String
filename = IO Resource -> m Resource
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Resource -> m Resource) -> IO Resource -> m Resource
forall a b. (a -> b) -> a -> b
$ do
    filename' <- String -> IO CString
stringToCString String
filename
    onException (do
        result <- propagateGError $ g_resource_load filename'
        checkUnexpectedReturnNULL "resourceLoad" result
        result' <- (wrapBoxed Resource) result
        freeMem filename'
        return result'
     ) (do
        freeMem filename'
     )

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveResourceMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveResourceMethod "enumerateChildren" o = ResourceEnumerateChildrenMethodInfo
    ResolveResourceMethod "lookupData" o = ResourceLookupDataMethodInfo
    ResolveResourceMethod "openStream" o = ResourceOpenStreamMethodInfo
    ResolveResourceMethod "ref" o = ResourceRefMethodInfo
    ResolveResourceMethod "unref" o = ResourceUnrefMethodInfo
    ResolveResourceMethod "getInfo" o = ResourceGetInfoMethodInfo
    ResolveResourceMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif