{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- 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
-- @/GtkBuilder/@ .ui files, splashscreen images, GMenu 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 t'GI.Gio.Structs.Resource.Resource' API and the [glib-compile-resources][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 its 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 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@ which will use the gdk-pixbuf-pixdata command to convert
-- images to the GdkPixdata format, which allows you to create pixbufs directly using the data inside
-- the resource file, rather than an (uncompressed) copy if 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.
-- 
-- 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 [glib-compile-resources][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 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 [glib-compile-resources][glib-compile-resources] to compile the XML to a
-- binary bundle that you can load with 'GI.Gio.Functions.resourceLoad'. However, its 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 [glib-compile-resources][glib-compile-resources]. @get_resource()@ returns
-- the generated t'GI.Gio.Structs.Resource.Resource' object. The register and unregister functions
-- register the resource so its files can be accessed using
-- 'GI.Gio.Functions.resourcesLookupData'.
-- 
-- Once a t'GI.Gio.Structs.Resource.Resource' 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 @/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 t'GI.Gio.Structs.Resource.Resource' 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.
-- 
-- 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 'GI.GLib.Constants.SEARCHPATH_SEPARATOR'-separated list of substitutions to perform
-- during resource lookups.
-- 
-- 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(..)                            ,
    noResource                              ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified 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

-- | Memory-managed wrapper type.
newtype Resource = Resource (ManagedPtr Resource)
    deriving (Resource -> Resource -> Bool
(Resource -> Resource -> Bool)
-> (Resource -> Resource -> Bool) -> Eq Resource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Resource -> Resource -> Bool
$c/= :: Resource -> Resource -> Bool
== :: Resource -> Resource -> Bool
$c== :: Resource -> Resource -> Bool
Eq)
foreign import ccall "g_resource_get_type" c_g_resource_get_type :: 
    IO GType

instance BoxedObject Resource where
    boxedType :: Resource -> IO GType
boxedType _ = IO GType
c_g_resource_get_type

-- | Convert 'Resource' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue Resource where
    toGValue :: Resource -> IO GValue
toGValue o :: Resource
o = do
        GType
gtype <- IO GType
c_g_resource_get_type
        Resource -> (Ptr Resource -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Resource
o (GType
-> (GValue -> Ptr Resource -> IO ()) -> Ptr Resource -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Resource -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO Resource
fromGValue gv :: GValue
gv = do
        Ptr Resource
ptr <- GValue -> IO (Ptr Resource)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr Resource)
        (ManagedPtr Resource -> Resource) -> Ptr Resource -> IO Resource
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Resource -> Resource
Resource Ptr Resource
ptr
        
    

-- | A convenience alias for `Nothing` :: `Maybe` `Resource`.
noResource :: Maybe Resource
noResource :: Maybe Resource
noResource = Maybe Resource
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Resource
type instance O.AttributeList Resource = ResourceAttributeList
type ResourceAttributeList = ('[ ] :: [(Symbol, *)])
#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
--           , 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 :: Bytes -> m Resource
resourceNewFromData data_ :: Bytes
data_ = IO Resource -> m Resource
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
    Ptr Bytes
data_' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
data_
    IO Resource -> IO () -> IO Resource
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Resource
result <- (Ptr (Ptr GError) -> IO (Ptr Resource)) -> IO (Ptr Resource)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Resource)) -> IO (Ptr Resource))
-> (Ptr (Ptr GError) -> IO (Ptr Resource)) -> IO (Ptr Resource)
forall a b. (a -> b) -> a -> b
$ Ptr Bytes -> Ptr (Ptr GError) -> IO (Ptr Resource)
g_resource_new_from_data Ptr Bytes
data_'
        Text -> Ptr Resource -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "resourceNewFromData" Ptr Resource
result
        Resource
result' <- ((ManagedPtr Resource -> Resource) -> Ptr Resource -> IO Resource
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Resource -> Resource
Resource) Ptr Resource
result
        Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
data_
        Resource -> IO Resource
forall (m :: * -> *) a. Monad m => a -> m a
return Resource
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
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
--           , 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
--           , 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
--           , 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 :: Resource -> Text -> [ResourceLookupFlags] -> m [Text]
resourceEnumerateChildren resource :: Resource
resource path :: Text
path lookupFlags :: [ResourceLookupFlags]
lookupFlags = IO [Text] -> m [Text]
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
    Ptr Resource
resource' <- Resource -> IO (Ptr Resource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Resource
resource
    CString
path' <- Text -> IO CString
textToCString Text
path
    let lookupFlags' :: CUInt
lookupFlags' = [ResourceLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ResourceLookupFlags]
lookupFlags
    IO [Text] -> IO () -> IO [Text]
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr CString
result <- (Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString))
-> (Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString)
forall a b. (a -> b) -> a -> b
$ Ptr Resource
-> CString -> CUInt -> Ptr (Ptr GError) -> IO (Ptr CString)
g_resource_enumerate_children Ptr Resource
resource' CString
path' CUInt
lookupFlags'
        Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "resourceEnumerateChildren" Ptr CString
result
        [Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
        (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
        Resource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Resource
resource
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
        [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
     )

#if defined(ENABLE_OVERLOADING)
data ResourceEnumerateChildrenMethodInfo
instance (signature ~ (T.Text -> [Gio.Flags.ResourceLookupFlags] -> m [T.Text]), MonadIO m) => O.MethodInfo ResourceEnumerateChildrenMethodInfo Resource signature where
    overloadedMethod = 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
--           , 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
--           , 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
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType = TBasicType TUInt64
--           , 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
--           , 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
--           , 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 Word64 ->                           -- size : TBasicType TUInt64
    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 ((Word64, Word32))
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
resourceGetInfo :: Resource -> Text -> [ResourceLookupFlags] -> m (Word64, Word32)
resourceGetInfo resource :: Resource
resource path :: Text
path lookupFlags :: [ResourceLookupFlags]
lookupFlags = IO (Word64, Word32) -> m (Word64, Word32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Word64, Word32) -> m (Word64, Word32))
-> IO (Word64, Word32) -> m (Word64, Word32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Resource
resource' <- Resource -> IO (Ptr Resource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Resource
resource
    CString
path' <- Text -> IO CString
textToCString Text
path
    let lookupFlags' :: CUInt
lookupFlags' = [ResourceLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ResourceLookupFlags]
lookupFlags
    Ptr Word64
size <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    Ptr Word32
flags <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    IO (Word64, Word32) -> IO () -> IO (Word64, Word32)
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Resource
-> CString
-> CUInt
-> Ptr Word64
-> Ptr Word32
-> Ptr (Ptr GError)
-> IO CInt
g_resource_get_info Ptr Resource
resource' CString
path' CUInt
lookupFlags' Ptr Word64
size Ptr Word32
flags
        Word64
size' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
size
        Word32
flags' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
flags
        Resource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Resource
resource
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
size
        Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
flags
        (Word64, Word32) -> IO (Word64, Word32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Word64
size', Word32
flags')
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
size
        Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
flags
     )

#if defined(ENABLE_OVERLOADING)
data ResourceGetInfoMethodInfo
instance (signature ~ (T.Text -> [Gio.Flags.ResourceLookupFlags] -> m ((Word64, Word32))), MonadIO m) => O.MethodInfo ResourceGetInfoMethodInfo Resource signature where
    overloadedMethod = 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
--           , 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
--           , 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
--           , 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 :: Resource -> Text -> [ResourceLookupFlags] -> m Bytes
resourceLookupData resource :: Resource
resource path :: Text
path lookupFlags :: [ResourceLookupFlags]
lookupFlags = IO Bytes -> m Bytes
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 Resource
resource' <- Resource -> IO (Ptr Resource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Resource
resource
    CString
path' <- Text -> IO CString
textToCString Text
path
    let lookupFlags' :: CUInt
lookupFlags' = [ResourceLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ResourceLookupFlags]
lookupFlags
    IO Bytes -> IO () -> IO Bytes
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Bytes
result <- (Ptr (Ptr GError) -> IO (Ptr Bytes)) -> IO (Ptr Bytes)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Bytes)) -> IO (Ptr Bytes))
-> (Ptr (Ptr GError) -> IO (Ptr Bytes)) -> IO (Ptr Bytes)
forall a b. (a -> b) -> a -> b
$ Ptr Resource
-> CString -> CUInt -> Ptr (Ptr GError) -> IO (Ptr Bytes)
g_resource_lookup_data Ptr Resource
resource' CString
path' CUInt
lookupFlags'
        Text -> Ptr Bytes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "resourceLookupData" Ptr Bytes
result
        Bytes
result' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes) Ptr Bytes
result
        Resource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Resource
resource
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
        Bytes -> IO Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
     )

#if defined(ENABLE_OVERLOADING)
data ResourceLookupDataMethodInfo
instance (signature ~ (T.Text -> [Gio.Flags.ResourceLookupFlags] -> m GLib.Bytes.Bytes), MonadIO m) => O.MethodInfo ResourceLookupDataMethodInfo Resource signature where
    overloadedMethod = 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
--           , 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
--           , 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
--           , 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 :: Resource -> Text -> [ResourceLookupFlags] -> m InputStream
resourceOpenStream resource :: Resource
resource path :: Text
path lookupFlags :: [ResourceLookupFlags]
lookupFlags = IO InputStream -> m InputStream
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
    Ptr Resource
resource' <- Resource -> IO (Ptr Resource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Resource
resource
    CString
path' <- Text -> IO CString
textToCString Text
path
    let lookupFlags' :: CUInt
lookupFlags' = [ResourceLookupFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ResourceLookupFlags]
lookupFlags
    IO InputStream -> IO () -> IO InputStream
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr InputStream
result <- (Ptr (Ptr GError) -> IO (Ptr InputStream)) -> IO (Ptr InputStream)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr InputStream))
 -> IO (Ptr InputStream))
-> (Ptr (Ptr GError) -> IO (Ptr InputStream))
-> IO (Ptr InputStream)
forall a b. (a -> b) -> a -> b
$ Ptr Resource
-> CString -> CUInt -> Ptr (Ptr GError) -> IO (Ptr InputStream)
g_resource_open_stream Ptr Resource
resource' CString
path' CUInt
lookupFlags'
        Text -> Ptr InputStream -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "resourceOpenStream" Ptr InputStream
result
        InputStream
result' <- ((ManagedPtr InputStream -> InputStream)
-> Ptr InputStream -> IO InputStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr InputStream -> InputStream
Gio.InputStream.InputStream) Ptr InputStream
result
        Resource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Resource
resource
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
        InputStream -> IO InputStream
forall (m :: * -> *) a. Monad m => a -> m a
return InputStream
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
     )

#if defined(ENABLE_OVERLOADING)
data ResourceOpenStreamMethodInfo
instance (signature ~ (T.Text -> [Gio.Flags.ResourceLookupFlags] -> m Gio.InputStream.InputStream), MonadIO m) => O.MethodInfo ResourceOpenStreamMethodInfo Resource signature where
    overloadedMethod = 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
--           , 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 :: Resource -> m Resource
resourceRef resource :: Resource
resource = IO Resource -> m Resource
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
    Ptr Resource
resource' <- Resource -> IO (Ptr Resource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Resource
resource
    Ptr Resource
result <- Ptr Resource -> IO (Ptr Resource)
g_resource_ref Ptr Resource
resource'
    Text -> Ptr Resource -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "resourceRef" Ptr Resource
result
    Resource
result' <- ((ManagedPtr Resource -> Resource) -> Ptr Resource -> IO Resource
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Resource -> Resource
Resource) Ptr Resource
result
    Resource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Resource
resource
    Resource -> IO Resource
forall (m :: * -> *) a. Monad m => a -> m a
return Resource
result'

#if defined(ENABLE_OVERLOADING)
data ResourceRefMethodInfo
instance (signature ~ (m Resource), MonadIO m) => O.MethodInfo ResourceRefMethodInfo Resource signature where
    overloadedMethod = 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
--           , 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 :: Resource -> m ()
resourceUnref resource :: Resource
resource = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Resource
resource' <- Resource -> IO (Ptr Resource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Resource
resource
    Ptr Resource -> IO ()
g_resource_unref Ptr Resource
resource'
    Resource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Resource
resource
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ResourceUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo ResourceUnrefMethodInfo Resource signature where
    overloadedMethod = 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
--           , 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 :: [Char] -> m Resource
resourceLoad filename :: [Char]
filename = IO Resource -> m Resource
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
    CString
filename' <- [Char] -> IO CString
stringToCString [Char]
filename
    IO Resource -> IO () -> IO Resource
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Resource
result <- (Ptr (Ptr GError) -> IO (Ptr Resource)) -> IO (Ptr Resource)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Resource)) -> IO (Ptr Resource))
-> (Ptr (Ptr GError) -> IO (Ptr Resource)) -> IO (Ptr Resource)
forall a b. (a -> b) -> a -> b
$ CString -> Ptr (Ptr GError) -> IO (Ptr Resource)
g_resource_load CString
filename'
        Text -> Ptr Resource -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "resourceLoad" Ptr Resource
result
        Resource
result' <- ((ManagedPtr Resource -> Resource) -> Ptr Resource -> IO Resource
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Resource -> Resource
Resource) Ptr Resource
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
        Resource -> IO Resource
forall (m :: * -> *) a. Monad m => a -> m a
return Resource
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
     )

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveResourceMethod (t :: Symbol) (o :: *) :: * 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.MethodInfo 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

#endif