{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Structs.StaticResource.StaticResource' is an opaque data structure and can only be accessed
-- using the following functions.

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

module GI.Gio.Structs.StaticResource
    ( 

-- * Exported types
    StaticResource(..)                      ,
    newZeroStaticResource                   ,
    noStaticResource                        ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveStaticResourceMethod             ,
#endif


-- ** fini #method:fini#

#if defined(ENABLE_OVERLOADING)
    StaticResourceFiniMethodInfo            ,
#endif
    staticResourceFini                      ,


-- ** getResource #method:getResource#

#if defined(ENABLE_OVERLOADING)
    StaticResourceGetResourceMethodInfo     ,
#endif
    staticResourceGetResource               ,


-- ** init #method:init#

#if defined(ENABLE_OVERLOADING)
    StaticResourceInitMethodInfo            ,
#endif
    staticResourceInit                      ,




    ) 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 {-# SOURCE #-} qualified GI.Gio.Structs.Resource as Gio.Resource

-- | Memory-managed wrapper type.
newtype StaticResource = StaticResource (ManagedPtr StaticResource)
    deriving (StaticResource -> StaticResource -> Bool
(StaticResource -> StaticResource -> Bool)
-> (StaticResource -> StaticResource -> Bool) -> Eq StaticResource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StaticResource -> StaticResource -> Bool
$c/= :: StaticResource -> StaticResource -> Bool
== :: StaticResource -> StaticResource -> Bool
$c== :: StaticResource -> StaticResource -> Bool
Eq)
instance WrappedPtr StaticResource where
    wrappedPtrCalloc :: IO (Ptr StaticResource)
wrappedPtrCalloc = Int -> IO (Ptr StaticResource)
forall a. Int -> IO (Ptr a)
callocBytes 40
    wrappedPtrCopy :: StaticResource -> IO StaticResource
wrappedPtrCopy = \p :: StaticResource
p -> StaticResource
-> (Ptr StaticResource -> IO StaticResource) -> IO StaticResource
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr StaticResource
p (Int -> Ptr StaticResource -> IO (Ptr StaticResource)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 40 (Ptr StaticResource -> IO (Ptr StaticResource))
-> (Ptr StaticResource -> IO StaticResource)
-> Ptr StaticResource
-> IO StaticResource
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr StaticResource -> StaticResource)
-> Ptr StaticResource -> IO StaticResource
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr StaticResource -> StaticResource
StaticResource)
    wrappedPtrFree :: Maybe (GDestroyNotify StaticResource)
wrappedPtrFree = GDestroyNotify StaticResource
-> Maybe (GDestroyNotify StaticResource)
forall a. a -> Maybe a
Just GDestroyNotify StaticResource
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free

-- | Construct a `StaticResource` struct initialized to zero.
newZeroStaticResource :: MonadIO m => m StaticResource
newZeroStaticResource :: m StaticResource
newZeroStaticResource = IO StaticResource -> m StaticResource
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO StaticResource -> m StaticResource)
-> IO StaticResource -> m StaticResource
forall a b. (a -> b) -> a -> b
$ IO (Ptr StaticResource)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr StaticResource)
-> (Ptr StaticResource -> IO StaticResource) -> IO StaticResource
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr StaticResource -> StaticResource)
-> Ptr StaticResource -> IO StaticResource
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr StaticResource -> StaticResource
StaticResource

instance tag ~ 'AttrSet => Constructible StaticResource tag where
    new :: (ManagedPtr StaticResource -> StaticResource)
-> [AttrOp StaticResource tag] -> m StaticResource
new _ attrs :: [AttrOp StaticResource tag]
attrs = do
        StaticResource
o <- m StaticResource
forall (m :: * -> *). MonadIO m => m StaticResource
newZeroStaticResource
        StaticResource -> [AttrOp StaticResource 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set StaticResource
o [AttrOp StaticResource tag]
[AttrOp StaticResource 'AttrSet]
attrs
        StaticResource -> m StaticResource
forall (m :: * -> *) a. Monad m => a -> m a
return StaticResource
o


-- | A convenience alias for `Nothing` :: `Maybe` `StaticResource`.
noStaticResource :: Maybe StaticResource
noStaticResource :: Maybe StaticResource
noStaticResource = Maybe StaticResource
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList StaticResource
type instance O.AttributeList StaticResource = StaticResourceAttributeList
type StaticResourceAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method StaticResource::fini
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "static_resource"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "StaticResource" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "pointer to a static #GStaticResource"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_static_resource_fini" g_static_resource_fini :: 
    Ptr StaticResource ->                   -- static_resource : TInterface (Name {namespace = "Gio", name = "StaticResource"})
    IO ()

-- | Finalized a GResource initialized by 'GI.Gio.Structs.StaticResource.staticResourceInit'.
-- 
-- This is normally used by code generated by
-- [glib-compile-resources][glib-compile-resources]
-- and is not typically used by other code.
-- 
-- /Since: 2.32/
staticResourceFini ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    StaticResource
    -- ^ /@staticResource@/: pointer to a static t'GI.Gio.Structs.StaticResource.StaticResource'
    -> m ()
staticResourceFini :: StaticResource -> m ()
staticResourceFini staticResource :: StaticResource
staticResource = 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 StaticResource
staticResource' <- StaticResource -> IO (Ptr StaticResource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr StaticResource
staticResource
    Ptr StaticResource -> IO ()
g_static_resource_fini Ptr StaticResource
staticResource'
    StaticResource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr StaticResource
staticResource
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StaticResourceFiniMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo StaticResourceFiniMethodInfo StaticResource signature where
    overloadedMethod = staticResourceFini

#endif

-- method StaticResource::get_resource
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "static_resource"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "StaticResource" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "pointer to a static #GStaticResource"
--                 , 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_static_resource_get_resource" g_static_resource_get_resource :: 
    Ptr StaticResource ->                   -- static_resource : TInterface (Name {namespace = "Gio", name = "StaticResource"})
    IO (Ptr Gio.Resource.Resource)

-- | Gets the GResource that was registered by a call to 'GI.Gio.Structs.StaticResource.staticResourceInit'.
-- 
-- This is normally used by code generated by
-- [glib-compile-resources][glib-compile-resources]
-- and is not typically used by other code.
-- 
-- /Since: 2.32/
staticResourceGetResource ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    StaticResource
    -- ^ /@staticResource@/: pointer to a static t'GI.Gio.Structs.StaticResource.StaticResource'
    -> m Gio.Resource.Resource
    -- ^ __Returns:__ a t'GI.Gio.Structs.Resource.Resource'
staticResourceGetResource :: StaticResource -> m Resource
staticResourceGetResource staticResource :: StaticResource
staticResource = 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 StaticResource
staticResource' <- StaticResource -> IO (Ptr StaticResource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr StaticResource
staticResource
    Ptr Resource
result <- Ptr StaticResource -> IO (Ptr Resource)
g_static_resource_get_resource Ptr StaticResource
staticResource'
    Text -> Ptr Resource -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "staticResourceGetResource" Ptr Resource
result
    Resource
result' <- ((ManagedPtr Resource -> Resource) -> Ptr Resource -> IO Resource
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Resource -> Resource
Gio.Resource.Resource) Ptr Resource
result
    StaticResource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr StaticResource
staticResource
    Resource -> IO Resource
forall (m :: * -> *) a. Monad m => a -> m a
return Resource
result'

#if defined(ENABLE_OVERLOADING)
data StaticResourceGetResourceMethodInfo
instance (signature ~ (m Gio.Resource.Resource), MonadIO m) => O.MethodInfo StaticResourceGetResourceMethodInfo StaticResource signature where
    overloadedMethod = staticResourceGetResource

#endif

-- method StaticResource::init
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "static_resource"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "StaticResource" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "pointer to a static #GStaticResource"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_static_resource_init" g_static_resource_init :: 
    Ptr StaticResource ->                   -- static_resource : TInterface (Name {namespace = "Gio", name = "StaticResource"})
    IO ()

-- | Initializes a GResource from static data using a
-- GStaticResource.
-- 
-- This is normally used by code generated by
-- [glib-compile-resources][glib-compile-resources]
-- and is not typically used by other code.
-- 
-- /Since: 2.32/
staticResourceInit ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    StaticResource
    -- ^ /@staticResource@/: pointer to a static t'GI.Gio.Structs.StaticResource.StaticResource'
    -> m ()
staticResourceInit :: StaticResource -> m ()
staticResourceInit staticResource :: StaticResource
staticResource = 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 StaticResource
staticResource' <- StaticResource -> IO (Ptr StaticResource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr StaticResource
staticResource
    Ptr StaticResource -> IO ()
g_static_resource_init Ptr StaticResource
staticResource'
    StaticResource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr StaticResource
staticResource
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data StaticResourceInitMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo StaticResourceInitMethodInfo StaticResource signature where
    overloadedMethod = staticResourceInit

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveStaticResourceMethod (t :: Symbol) (o :: *) :: * where
    ResolveStaticResourceMethod "fini" o = StaticResourceFiniMethodInfo
    ResolveStaticResourceMethod "init" o = StaticResourceInitMethodInfo
    ResolveStaticResourceMethod "getResource" o = StaticResourceGetResourceMethodInfo
    ResolveStaticResourceMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveStaticResourceMethod t StaticResource, O.MethodInfo info StaticResource p) => OL.IsLabel t (StaticResource -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif