{-# 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.GObject.Objects.TypeModule.TypeModule' provides a simple implementation of the t'GI.GObject.Interfaces.TypePlugin.TypePlugin'
-- interface. The model of t'GI.GObject.Objects.TypeModule.TypeModule' is a dynamically loaded module
-- which implements some number of types and interface implementations.
-- When the module is loaded, it registers its types and interfaces
-- using 'GI.GObject.Objects.TypeModule.typeModuleRegisterType' and 'GI.GObject.Objects.TypeModule.typeModuleAddInterface'.
-- As long as any instances of these types and interface implementations
-- are in use, the module is kept loaded. When the types and interfaces
-- are gone, the module may be unloaded. If the types and interfaces
-- become used again, the module will be reloaded. Note that the last
-- unref cannot happen in module code, since that would lead to the
-- caller\'s code being unloaded before 'GI.GObject.Objects.Object.objectUnref' returns to it.
-- 
-- Keeping track of whether the module should be loaded or not is done by
-- using a use count - it starts at zero, and whenever it is greater than
-- zero, the module is loaded. The use count is maintained internally by
-- the type system, but also can be explicitly controlled by
-- 'GI.GObject.Objects.TypeModule.typeModuleUse' and 'GI.GObject.Objects.TypeModule.typeModuleUnuse'. Typically, when loading
-- a module for the first type, 'GI.GObject.Objects.TypeModule.typeModuleUse' will be used to load
-- it so that it can initialize its types. At some later point, when the
-- module no longer needs to be loaded except for the type
-- implementations it contains, 'GI.GObject.Objects.TypeModule.typeModuleUnuse' is called.
-- 
-- t'GI.GObject.Objects.TypeModule.TypeModule' does not actually provide any implementation of module
-- loading and unloading. To create a particular module type you must
-- derive from t'GI.GObject.Objects.TypeModule.TypeModule' and implement the load and unload functions
-- in t'GI.GObject.Structs.TypeModuleClass.TypeModuleClass'.

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

module GI.GObject.Objects.TypeModule
    ( 

-- * Exported types
    TypeModule(..)                          ,
    IsTypeModule                            ,
    toTypeModule                            ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveTypeModuleMethod                 ,
#endif


-- ** addInterface #method:addInterface#

#if defined(ENABLE_OVERLOADING)
    TypeModuleAddInterfaceMethodInfo        ,
#endif
    typeModuleAddInterface                  ,


-- ** registerEnum #method:registerEnum#

#if defined(ENABLE_OVERLOADING)
    TypeModuleRegisterEnumMethodInfo        ,
#endif
    typeModuleRegisterEnum                  ,


-- ** registerFlags #method:registerFlags#

#if defined(ENABLE_OVERLOADING)
    TypeModuleRegisterFlagsMethodInfo       ,
#endif
    typeModuleRegisterFlags                 ,


-- ** registerType #method:registerType#

#if defined(ENABLE_OVERLOADING)
    TypeModuleRegisterTypeMethodInfo        ,
#endif
    typeModuleRegisterType                  ,


-- ** setName #method:setName#

#if defined(ENABLE_OVERLOADING)
    TypeModuleSetNameMethodInfo             ,
#endif
    typeModuleSetName                       ,


-- ** unuse #method:unuse#

#if defined(ENABLE_OVERLOADING)
    TypeModuleUnuseMethodInfo               ,
#endif
    typeModuleUnuse                         ,


-- ** use #method:use#

#if defined(ENABLE_OVERLOADING)
    TypeModuleUseMethodInfo                 ,
#endif
    typeModuleUse                           ,




    ) 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.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.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.GObject.Flags as GObject.Flags
import {-# SOURCE #-} qualified GI.GObject.Interfaces.TypePlugin as GObject.TypePlugin
import {-# SOURCE #-} qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.GObject.Structs.EnumValue as GObject.EnumValue
import {-# SOURCE #-} qualified GI.GObject.Structs.FlagsValue as GObject.FlagsValue
import {-# SOURCE #-} qualified GI.GObject.Structs.InterfaceInfo as GObject.InterfaceInfo
import {-# SOURCE #-} qualified GI.GObject.Structs.TypeInfo as GObject.TypeInfo

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

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

foreign import ccall "g_type_module_get_type"
    c_g_type_module_get_type :: IO B.Types.GType

instance B.Types.TypedObject TypeModule where
    glibType :: IO GType
glibType = IO GType
c_g_type_module_get_type

instance B.Types.GObject TypeModule

-- | Convert 'TypeModule' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue TypeModule where
    toGValue :: TypeModule -> IO GValue
toGValue TypeModule
o = do
        GType
gtype <- IO GType
c_g_type_module_get_type
        TypeModule -> (Ptr TypeModule -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TypeModule
o (GType
-> (GValue -> Ptr TypeModule -> IO ())
-> Ptr TypeModule
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr TypeModule -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO TypeModule
fromGValue GValue
gv = do
        Ptr TypeModule
ptr <- GValue -> IO (Ptr TypeModule)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr TypeModule)
        (ManagedPtr TypeModule -> TypeModule)
-> Ptr TypeModule -> IO TypeModule
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr TypeModule -> TypeModule
TypeModule Ptr TypeModule
ptr
        
    

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

instance O.HasParentTypes TypeModule
type instance O.ParentTypes TypeModule = '[GObject.Object.Object, GObject.TypePlugin.TypePlugin]

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

#if defined(ENABLE_OVERLOADING)
type family ResolveTypeModuleMethod (t :: Symbol) (o :: *) :: * where
    ResolveTypeModuleMethod "addInterface" o = TypeModuleAddInterfaceMethodInfo
    ResolveTypeModuleMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveTypeModuleMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveTypeModuleMethod "completeInterfaceInfo" o = GObject.TypePlugin.TypePluginCompleteInterfaceInfoMethodInfo
    ResolveTypeModuleMethod "completeTypeInfo" o = GObject.TypePlugin.TypePluginCompleteTypeInfoMethodInfo
    ResolveTypeModuleMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveTypeModuleMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveTypeModuleMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveTypeModuleMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveTypeModuleMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveTypeModuleMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveTypeModuleMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveTypeModuleMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveTypeModuleMethod "registerEnum" o = TypeModuleRegisterEnumMethodInfo
    ResolveTypeModuleMethod "registerFlags" o = TypeModuleRegisterFlagsMethodInfo
    ResolveTypeModuleMethod "registerType" o = TypeModuleRegisterTypeMethodInfo
    ResolveTypeModuleMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveTypeModuleMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveTypeModuleMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveTypeModuleMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveTypeModuleMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveTypeModuleMethod "unuse" o = TypeModuleUnuseMethodInfo
    ResolveTypeModuleMethod "use" o = TypeModuleUseMethodInfo
    ResolveTypeModuleMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveTypeModuleMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveTypeModuleMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveTypeModuleMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveTypeModuleMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveTypeModuleMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveTypeModuleMethod "setName" o = TypeModuleSetNameMethodInfo
    ResolveTypeModuleMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveTypeModuleMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList TypeModule = TypeModuleSignalList
type TypeModuleSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method TypeModule::add_interface
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "module"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "TypeModule" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTypeModule" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "instance_type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "type to which to add the interface."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interface_type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "interface type to add"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "interface_info"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "InterfaceInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "type information structure"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_type_module_add_interface" g_type_module_add_interface :: 
    Ptr TypeModule ->                       -- module : TInterface (Name {namespace = "GObject", name = "TypeModule"})
    CGType ->                               -- instance_type : TBasicType TGType
    CGType ->                               -- interface_type : TBasicType TGType
    Ptr GObject.InterfaceInfo.InterfaceInfo -> -- interface_info : TInterface (Name {namespace = "GObject", name = "InterfaceInfo"})
    IO ()

-- | Registers an additional interface for a type, whose interface lives
-- in the given type plugin. If the interface was already registered
-- for the type in this plugin, nothing will be done.
-- 
-- As long as any instances of the type exist, the type plugin will
-- not be unloaded.
-- 
-- Since 2.56 if /@module@/ is 'P.Nothing' this will call 'GI.GObject.Functions.typeAddInterfaceStatic'
-- instead. This can be used when making a static build of the module.
typeModuleAddInterface ::
    (B.CallStack.HasCallStack, MonadIO m, IsTypeModule a) =>
    a
    -- ^ /@module@/: a t'GI.GObject.Objects.TypeModule.TypeModule'
    -> GType
    -- ^ /@instanceType@/: type to which to add the interface.
    -> GType
    -- ^ /@interfaceType@/: interface type to add
    -> GObject.InterfaceInfo.InterfaceInfo
    -- ^ /@interfaceInfo@/: type information structure
    -> m ()
typeModuleAddInterface :: a -> GType -> GType -> InterfaceInfo -> m ()
typeModuleAddInterface a
module_ GType
instanceType GType
interfaceType InterfaceInfo
interfaceInfo = 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 TypeModule
module_' <- a -> IO (Ptr TypeModule)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
module_
    let instanceType' :: CGType
instanceType' = GType -> CGType
gtypeToCGType GType
instanceType
    let interfaceType' :: CGType
interfaceType' = GType -> CGType
gtypeToCGType GType
interfaceType
    Ptr InterfaceInfo
interfaceInfo' <- InterfaceInfo -> IO (Ptr InterfaceInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr InterfaceInfo
interfaceInfo
    Ptr TypeModule -> CGType -> CGType -> Ptr InterfaceInfo -> IO ()
g_type_module_add_interface Ptr TypeModule
module_' CGType
instanceType' CGType
interfaceType' Ptr InterfaceInfo
interfaceInfo'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
module_
    InterfaceInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr InterfaceInfo
interfaceInfo
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TypeModuleAddInterfaceMethodInfo
instance (signature ~ (GType -> GType -> GObject.InterfaceInfo.InterfaceInfo -> m ()), MonadIO m, IsTypeModule a) => O.MethodInfo TypeModuleAddInterfaceMethodInfo a signature where
    overloadedMethod = typeModuleAddInterface

#endif

-- method TypeModule::register_enum
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "module"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "TypeModule" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTypeModule" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name for the type" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "const_static_values"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "EnumValue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "an array of #GEnumValue structs for the\n                      possible enumeration values. The array is\n                      terminated by a struct with all members being\n                      0."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TGType)
-- throws : False
-- Skip return : False

foreign import ccall "g_type_module_register_enum" g_type_module_register_enum :: 
    Ptr TypeModule ->                       -- module : TInterface (Name {namespace = "GObject", name = "TypeModule"})
    CString ->                              -- name : TBasicType TUTF8
    Ptr GObject.EnumValue.EnumValue ->      -- const_static_values : TInterface (Name {namespace = "GObject", name = "EnumValue"})
    IO CGType

-- | Looks up or registers an enumeration that is implemented with a particular
-- type plugin. If a type with name /@typeName@/ was previously registered,
-- the t'GType' identifier for the type is returned, otherwise the type
-- is newly registered, and the resulting t'GType' identifier returned.
-- 
-- As long as any instances of the type exist, the type plugin will
-- not be unloaded.
-- 
-- Since 2.56 if /@module@/ is 'P.Nothing' this will call 'GI.GObject.Functions.typeRegisterStatic'
-- instead. This can be used when making a static build of the module.
-- 
-- /Since: 2.6/
typeModuleRegisterEnum ::
    (B.CallStack.HasCallStack, MonadIO m, IsTypeModule a) =>
    a
    -- ^ /@module@/: a t'GI.GObject.Objects.TypeModule.TypeModule'
    -> T.Text
    -- ^ /@name@/: name for the type
    -> GObject.EnumValue.EnumValue
    -- ^ /@constStaticValues@/: an array of t'GI.GObject.Structs.EnumValue.EnumValue' structs for the
    --                       possible enumeration values. The array is
    --                       terminated by a struct with all members being
    --                       0.
    -> m GType
    -- ^ __Returns:__ the new or existing type ID
typeModuleRegisterEnum :: a -> Text -> EnumValue -> m GType
typeModuleRegisterEnum a
module_ Text
name EnumValue
constStaticValues = IO GType -> m GType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GType -> m GType) -> IO GType -> m GType
forall a b. (a -> b) -> a -> b
$ do
    Ptr TypeModule
module_' <- a -> IO (Ptr TypeModule)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
module_
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr EnumValue
constStaticValues' <- EnumValue -> IO (Ptr EnumValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr EnumValue
constStaticValues
    CGType
result <- Ptr TypeModule -> CString -> Ptr EnumValue -> IO CGType
g_type_module_register_enum Ptr TypeModule
module_' CString
name' Ptr EnumValue
constStaticValues'
    let result' :: GType
result' = CGType -> GType
GType CGType
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
module_
    EnumValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr EnumValue
constStaticValues
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    GType -> IO GType
forall (m :: * -> *) a. Monad m => a -> m a
return GType
result'

#if defined(ENABLE_OVERLOADING)
data TypeModuleRegisterEnumMethodInfo
instance (signature ~ (T.Text -> GObject.EnumValue.EnumValue -> m GType), MonadIO m, IsTypeModule a) => O.MethodInfo TypeModuleRegisterEnumMethodInfo a signature where
    overloadedMethod = typeModuleRegisterEnum

#endif

-- method TypeModule::register_flags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "module"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "TypeModule" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTypeModule" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name for the type" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "const_static_values"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "FlagsValue" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "an array of #GFlagsValue structs for the\n                      possible flags values. The array is\n                      terminated by a struct with all members being\n                      0."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TGType)
-- throws : False
-- Skip return : False

foreign import ccall "g_type_module_register_flags" g_type_module_register_flags :: 
    Ptr TypeModule ->                       -- module : TInterface (Name {namespace = "GObject", name = "TypeModule"})
    CString ->                              -- name : TBasicType TUTF8
    Ptr GObject.FlagsValue.FlagsValue ->    -- const_static_values : TInterface (Name {namespace = "GObject", name = "FlagsValue"})
    IO CGType

-- | Looks up or registers a flags type that is implemented with a particular
-- type plugin. If a type with name /@typeName@/ was previously registered,
-- the t'GType' identifier for the type is returned, otherwise the type
-- is newly registered, and the resulting t'GType' identifier returned.
-- 
-- As long as any instances of the type exist, the type plugin will
-- not be unloaded.
-- 
-- Since 2.56 if /@module@/ is 'P.Nothing' this will call 'GI.GObject.Functions.typeRegisterStatic'
-- instead. This can be used when making a static build of the module.
-- 
-- /Since: 2.6/
typeModuleRegisterFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsTypeModule a) =>
    a
    -- ^ /@module@/: a t'GI.GObject.Objects.TypeModule.TypeModule'
    -> T.Text
    -- ^ /@name@/: name for the type
    -> GObject.FlagsValue.FlagsValue
    -- ^ /@constStaticValues@/: an array of t'GI.GObject.Structs.FlagsValue.FlagsValue' structs for the
    --                       possible flags values. The array is
    --                       terminated by a struct with all members being
    --                       0.
    -> m GType
    -- ^ __Returns:__ the new or existing type ID
typeModuleRegisterFlags :: a -> Text -> FlagsValue -> m GType
typeModuleRegisterFlags a
module_ Text
name FlagsValue
constStaticValues = IO GType -> m GType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GType -> m GType) -> IO GType -> m GType
forall a b. (a -> b) -> a -> b
$ do
    Ptr TypeModule
module_' <- a -> IO (Ptr TypeModule)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
module_
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr FlagsValue
constStaticValues' <- FlagsValue -> IO (Ptr FlagsValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FlagsValue
constStaticValues
    CGType
result <- Ptr TypeModule -> CString -> Ptr FlagsValue -> IO CGType
g_type_module_register_flags Ptr TypeModule
module_' CString
name' Ptr FlagsValue
constStaticValues'
    let result' :: GType
result' = CGType -> GType
GType CGType
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
module_
    FlagsValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FlagsValue
constStaticValues
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    GType -> IO GType
forall (m :: * -> *) a. Monad m => a -> m a
return GType
result'

#if defined(ENABLE_OVERLOADING)
data TypeModuleRegisterFlagsMethodInfo
instance (signature ~ (T.Text -> GObject.FlagsValue.FlagsValue -> m GType), MonadIO m, IsTypeModule a) => O.MethodInfo TypeModuleRegisterFlagsMethodInfo a signature where
    overloadedMethod = typeModuleRegisterFlags

#endif

-- method TypeModule::register_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "module"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "TypeModule" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTypeModule" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parent_type"
--           , argType = TBasicType TGType
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the type for the parent class"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "name for the type" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "type_info"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "TypeInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "type information structure"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "TypeFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags field providing details about the type"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TGType)
-- throws : False
-- Skip return : False

foreign import ccall "g_type_module_register_type" g_type_module_register_type :: 
    Ptr TypeModule ->                       -- module : TInterface (Name {namespace = "GObject", name = "TypeModule"})
    CGType ->                               -- parent_type : TBasicType TGType
    CString ->                              -- type_name : TBasicType TUTF8
    Ptr GObject.TypeInfo.TypeInfo ->        -- type_info : TInterface (Name {namespace = "GObject", name = "TypeInfo"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "GObject", name = "TypeFlags"})
    IO CGType

-- | Looks up or registers a type that is implemented with a particular
-- type plugin. If a type with name /@typeName@/ was previously registered,
-- the t'GType' identifier for the type is returned, otherwise the type
-- is newly registered, and the resulting t'GType' identifier returned.
-- 
-- When reregistering a type (typically because a module is unloaded
-- then reloaded, and reinitialized), /@module@/ and /@parentType@/ must
-- be the same as they were previously.
-- 
-- As long as any instances of the type exist, the type plugin will
-- not be unloaded.
-- 
-- Since 2.56 if /@module@/ is 'P.Nothing' this will call 'GI.GObject.Functions.typeRegisterStatic'
-- instead. This can be used when making a static build of the module.
typeModuleRegisterType ::
    (B.CallStack.HasCallStack, MonadIO m, IsTypeModule a) =>
    a
    -- ^ /@module@/: a t'GI.GObject.Objects.TypeModule.TypeModule'
    -> GType
    -- ^ /@parentType@/: the type for the parent class
    -> T.Text
    -- ^ /@typeName@/: name for the type
    -> GObject.TypeInfo.TypeInfo
    -- ^ /@typeInfo@/: type information structure
    -> [GObject.Flags.TypeFlags]
    -- ^ /@flags@/: flags field providing details about the type
    -> m GType
    -- ^ __Returns:__ the new or existing type ID
typeModuleRegisterType :: a -> GType -> Text -> TypeInfo -> [TypeFlags] -> m GType
typeModuleRegisterType a
module_ GType
parentType Text
typeName TypeInfo
typeInfo [TypeFlags]
flags = IO GType -> m GType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GType -> m GType) -> IO GType -> m GType
forall a b. (a -> b) -> a -> b
$ do
    Ptr TypeModule
module_' <- a -> IO (Ptr TypeModule)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
module_
    let parentType' :: CGType
parentType' = GType -> CGType
gtypeToCGType GType
parentType
    CString
typeName' <- Text -> IO CString
textToCString Text
typeName
    Ptr TypeInfo
typeInfo' <- TypeInfo -> IO (Ptr TypeInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TypeInfo
typeInfo
    let flags' :: CUInt
flags' = [TypeFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [TypeFlags]
flags
    CGType
result <- Ptr TypeModule
-> CGType -> CString -> Ptr TypeInfo -> CUInt -> IO CGType
g_type_module_register_type Ptr TypeModule
module_' CGType
parentType' CString
typeName' Ptr TypeInfo
typeInfo' CUInt
flags'
    let result' :: GType
result' = CGType -> GType
GType CGType
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
module_
    TypeInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TypeInfo
typeInfo
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
typeName'
    GType -> IO GType
forall (m :: * -> *) a. Monad m => a -> m a
return GType
result'

#if defined(ENABLE_OVERLOADING)
data TypeModuleRegisterTypeMethodInfo
instance (signature ~ (GType -> T.Text -> GObject.TypeInfo.TypeInfo -> [GObject.Flags.TypeFlags] -> m GType), MonadIO m, IsTypeModule a) => O.MethodInfo TypeModuleRegisterTypeMethodInfo a signature where
    overloadedMethod = typeModuleRegisterType

#endif

-- method TypeModule::set_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "module"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "TypeModule" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTypeModule." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a human-readable name to use in error messages."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_type_module_set_name" g_type_module_set_name :: 
    Ptr TypeModule ->                       -- module : TInterface (Name {namespace = "GObject", name = "TypeModule"})
    CString ->                              -- name : TBasicType TUTF8
    IO ()

-- | Sets the name for a t'GI.GObject.Objects.TypeModule.TypeModule'
typeModuleSetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsTypeModule a) =>
    a
    -- ^ /@module@/: a t'GI.GObject.Objects.TypeModule.TypeModule'.
    -> T.Text
    -- ^ /@name@/: a human-readable name to use in error messages.
    -> m ()
typeModuleSetName :: a -> Text -> m ()
typeModuleSetName a
module_ Text
name = 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 TypeModule
module_' <- a -> IO (Ptr TypeModule)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
module_
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr TypeModule -> CString -> IO ()
g_type_module_set_name Ptr TypeModule
module_' CString
name'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
module_
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TypeModuleSetNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsTypeModule a) => O.MethodInfo TypeModuleSetNameMethodInfo a signature where
    overloadedMethod = typeModuleSetName

#endif

-- method TypeModule::unuse
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "module"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "TypeModule" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTypeModule" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_type_module_unuse" g_type_module_unuse :: 
    Ptr TypeModule ->                       -- module : TInterface (Name {namespace = "GObject", name = "TypeModule"})
    IO ()

-- | Decreases the use count of a t'GI.GObject.Objects.TypeModule.TypeModule' by one. If the
-- result is zero, the module will be unloaded. (However, the
-- t'GI.GObject.Objects.TypeModule.TypeModule' will not be freed, and types associated with the
-- t'GI.GObject.Objects.TypeModule.TypeModule' are not unregistered. Once a t'GI.GObject.Objects.TypeModule.TypeModule' is
-- initialized, it must exist forever.)
typeModuleUnuse ::
    (B.CallStack.HasCallStack, MonadIO m, IsTypeModule a) =>
    a
    -- ^ /@module@/: a t'GI.GObject.Objects.TypeModule.TypeModule'
    -> m ()
typeModuleUnuse :: a -> m ()
typeModuleUnuse a
module_ = 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 TypeModule
module_' <- a -> IO (Ptr TypeModule)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
module_
    Ptr TypeModule -> IO ()
g_type_module_unuse Ptr TypeModule
module_'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
module_
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data TypeModuleUnuseMethodInfo
instance (signature ~ (m ()), MonadIO m, IsTypeModule a) => O.MethodInfo TypeModuleUnuseMethodInfo a signature where
    overloadedMethod = typeModuleUnuse

#endif

-- method TypeModule::use
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "module"
--           , argType =
--               TInterface Name { namespace = "GObject" , name = "TypeModule" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GTypeModule" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_type_module_use" g_type_module_use :: 
    Ptr TypeModule ->                       -- module : TInterface (Name {namespace = "GObject", name = "TypeModule"})
    IO CInt

-- | Increases the use count of a t'GI.GObject.Objects.TypeModule.TypeModule' by one. If the
-- use count was zero before, the plugin will be loaded.
-- If loading the plugin fails, the use count is reset to
-- its prior value.
typeModuleUse ::
    (B.CallStack.HasCallStack, MonadIO m, IsTypeModule a) =>
    a
    -- ^ /@module@/: a t'GI.GObject.Objects.TypeModule.TypeModule'
    -> m Bool
    -- ^ __Returns:__ 'P.False' if the plugin needed to be loaded and
    --  loading the plugin failed.
typeModuleUse :: a -> m Bool
typeModuleUse a
module_ = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr TypeModule
module_' <- a -> IO (Ptr TypeModule)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
module_
    CInt
result <- Ptr TypeModule -> IO CInt
g_type_module_use Ptr TypeModule
module_'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
module_
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data TypeModuleUseMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsTypeModule a) => O.MethodInfo TypeModuleUseMethodInfo a signature where
    overloadedMethod = typeModuleUse

#endif