{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GObject.Objects.TypeModule
(
TypeModule(..) ,
IsTypeModule ,
toTypeModule ,
#if defined(ENABLE_OVERLOADING)
ResolveTypeModuleMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
TypeModuleAddInterfaceMethodInfo ,
#endif
typeModuleAddInterface ,
#if defined(ENABLE_OVERLOADING)
TypeModuleRegisterEnumMethodInfo ,
#endif
typeModuleRegisterEnum ,
#if defined(ENABLE_OVERLOADING)
TypeModuleRegisterFlagsMethodInfo ,
#endif
typeModuleRegisterFlags ,
#if defined(ENABLE_OVERLOADING)
TypeModuleRegisterTypeMethodInfo ,
#endif
typeModuleRegisterType ,
#if defined(ENABLE_OVERLOADING)
TypeModuleSetNameMethodInfo ,
#endif
typeModuleSetName ,
#if defined(ENABLE_OVERLOADING)
TypeModuleUnuseMethodInfo ,
#endif
typeModuleUnuse ,
#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.Coerce as Coerce
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 GHC.Records as R
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
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
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]
toTypeModule :: (MIO.MonadIO m, IsTypeModule o) => o -> m TypeModule
toTypeModule :: forall (m :: * -> *) o.
(MonadIO m, IsTypeModule o) =>
o -> m TypeModule
toTypeModule = IO TypeModule -> m TypeModule
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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'
B.ManagedPtr.unsafeCastTo ManagedPtr TypeModule -> TypeModule
TypeModule
instance B.GValue.IsGValue (Maybe TypeModule) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_type_module_get_type
gvalueSet_ :: Ptr GValue -> Maybe TypeModule -> IO ()
gvalueSet_ Ptr GValue
gv Maybe TypeModule
P.Nothing = Ptr GValue -> Ptr TypeModule -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr TypeModule
forall a. Ptr a
FP.nullPtr :: FP.Ptr TypeModule)
gvalueSet_ Ptr GValue
gv (P.Just TypeModule
obj) = TypeModule -> (Ptr TypeModule -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TypeModule
obj (Ptr GValue -> Ptr TypeModule -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe TypeModule)
gvalueGet_ Ptr GValue
gv = do
Ptr TypeModule
ptr <- Ptr GValue -> IO (Ptr TypeModule)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr TypeModule)
if Ptr TypeModule
ptr Ptr TypeModule -> Ptr TypeModule -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr TypeModule
forall a. Ptr a
FP.nullPtr
then TypeModule -> Maybe TypeModule
forall a. a -> Maybe a
P.Just (TypeModule -> Maybe TypeModule)
-> IO TypeModule -> IO (Maybe TypeModule)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
else Maybe TypeModule -> IO (Maybe TypeModule)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TypeModule
forall a. Maybe a
P.Nothing
#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.OverloadedMethod 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
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveTypeModuleMethod t TypeModule, O.OverloadedMethod info TypeModule p, R.HasField t TypeModule p) => R.HasField t TypeModule p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveTypeModuleMethod t TypeModule, O.OverloadedMethodInfo info TypeModule) => OL.IsLabel t (O.MethodProxy info TypeModule) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#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
foreign import ccall "g_type_module_add_interface" g_type_module_add_interface ::
Ptr TypeModule ->
CGType ->
CGType ->
Ptr GObject.InterfaceInfo.InterfaceInfo ->
IO ()
typeModuleAddInterface ::
(B.CallStack.HasCallStack, MonadIO m, IsTypeModule a) =>
a
-> GType
-> GType
-> GObject.InterfaceInfo.InterfaceInfo
-> m ()
typeModuleAddInterface :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTypeModule a) =>
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.OverloadedMethod TypeModuleAddInterfaceMethodInfo a signature where
overloadedMethod = typeModuleAddInterface
instance O.OverloadedMethodInfo TypeModuleAddInterfaceMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.TypeModule.typeModuleAddInterface",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-TypeModule.html#v:typeModuleAddInterface"
})
#endif
foreign import ccall "g_type_module_register_enum" g_type_module_register_enum ::
Ptr TypeModule ->
CString ->
Ptr GObject.EnumValue.EnumValue ->
IO CGType
typeModuleRegisterEnum ::
(B.CallStack.HasCallStack, MonadIO m, IsTypeModule a) =>
a
-> T.Text
-> GObject.EnumValue.EnumValue
-> m GType
typeModuleRegisterEnum :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTypeModule a) =>
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.OverloadedMethod TypeModuleRegisterEnumMethodInfo a signature where
overloadedMethod = typeModuleRegisterEnum
instance O.OverloadedMethodInfo TypeModuleRegisterEnumMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.TypeModule.typeModuleRegisterEnum",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-TypeModule.html#v:typeModuleRegisterEnum"
})
#endif
foreign import ccall "g_type_module_register_flags" g_type_module_register_flags ::
Ptr TypeModule ->
CString ->
Ptr GObject.FlagsValue.FlagsValue ->
IO CGType
typeModuleRegisterFlags ::
(B.CallStack.HasCallStack, MonadIO m, IsTypeModule a) =>
a
-> T.Text
-> GObject.FlagsValue.FlagsValue
-> m GType
typeModuleRegisterFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTypeModule a) =>
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.OverloadedMethod TypeModuleRegisterFlagsMethodInfo a signature where
overloadedMethod = typeModuleRegisterFlags
instance O.OverloadedMethodInfo TypeModuleRegisterFlagsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.TypeModule.typeModuleRegisterFlags",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-TypeModule.html#v:typeModuleRegisterFlags"
})
#endif
foreign import ccall "g_type_module_register_type" g_type_module_register_type ::
Ptr TypeModule ->
CGType ->
CString ->
Ptr GObject.TypeInfo.TypeInfo ->
CUInt ->
IO CGType
typeModuleRegisterType ::
(B.CallStack.HasCallStack, MonadIO m, IsTypeModule a) =>
a
-> GType
-> T.Text
-> GObject.TypeInfo.TypeInfo
-> [GObject.Flags.TypeFlags]
-> m GType
typeModuleRegisterType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTypeModule a) =>
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.OverloadedMethod TypeModuleRegisterTypeMethodInfo a signature where
overloadedMethod = typeModuleRegisterType
instance O.OverloadedMethodInfo TypeModuleRegisterTypeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.TypeModule.typeModuleRegisterType",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-TypeModule.html#v:typeModuleRegisterType"
})
#endif
foreign import ccall "g_type_module_set_name" g_type_module_set_name ::
Ptr TypeModule ->
CString ->
IO ()
typeModuleSetName ::
(B.CallStack.HasCallStack, MonadIO m, IsTypeModule a) =>
a
-> T.Text
-> m ()
typeModuleSetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTypeModule a) =>
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.OverloadedMethod TypeModuleSetNameMethodInfo a signature where
overloadedMethod = typeModuleSetName
instance O.OverloadedMethodInfo TypeModuleSetNameMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.TypeModule.typeModuleSetName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-TypeModule.html#v:typeModuleSetName"
})
#endif
foreign import ccall "g_type_module_unuse" g_type_module_unuse ::
Ptr TypeModule ->
IO ()
typeModuleUnuse ::
(B.CallStack.HasCallStack, MonadIO m, IsTypeModule a) =>
a
-> m ()
typeModuleUnuse :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTypeModule a) =>
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.OverloadedMethod TypeModuleUnuseMethodInfo a signature where
overloadedMethod = typeModuleUnuse
instance O.OverloadedMethodInfo TypeModuleUnuseMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.TypeModule.typeModuleUnuse",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-TypeModule.html#v:typeModuleUnuse"
})
#endif
foreign import ccall "g_type_module_use" g_type_module_use ::
Ptr TypeModule ->
IO CInt
typeModuleUse ::
(B.CallStack.HasCallStack, MonadIO m, IsTypeModule a) =>
a
-> m Bool
typeModuleUse :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTypeModule a) =>
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.OverloadedMethod TypeModuleUseMethodInfo a signature where
overloadedMethod = typeModuleUse
instance O.OverloadedMethodInfo TypeModuleUseMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.TypeModule.typeModuleUse",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-TypeModule.html#v:typeModuleUse"
})
#endif