{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GObject.Interfaces.TypePlugin
(
TypePlugin(..) ,
IsTypePlugin ,
#if defined(ENABLE_OVERLOADING)
ResolveTypePluginMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
TypePluginCompleteInterfaceInfoMethodInfo,
#endif
typePluginCompleteInterfaceInfo ,
#if defined(ENABLE_OVERLOADING)
TypePluginCompleteTypeInfoMethodInfo ,
#endif
typePluginCompleteTypeInfo ,
#if defined(ENABLE_OVERLOADING)
TypePluginUnuseMethodInfo ,
#endif
typePluginUnuse ,
#if defined(ENABLE_OVERLOADING)
TypePluginUseMethodInfo ,
#endif
typePluginUse ,
) 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.Structs.InterfaceInfo as GObject.InterfaceInfo
import {-# SOURCE #-} qualified GI.GObject.Structs.TypeInfo as GObject.TypeInfo
import {-# SOURCE #-} qualified GI.GObject.Structs.TypeValueTable as GObject.TypeValueTable
newtype TypePlugin = TypePlugin (SP.ManagedPtr TypePlugin)
deriving (TypePlugin -> TypePlugin -> Bool
(TypePlugin -> TypePlugin -> Bool)
-> (TypePlugin -> TypePlugin -> Bool) -> Eq TypePlugin
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypePlugin -> TypePlugin -> Bool
$c/= :: TypePlugin -> TypePlugin -> Bool
== :: TypePlugin -> TypePlugin -> Bool
$c== :: TypePlugin -> TypePlugin -> Bool
Eq)
instance SP.ManagedPtrNewtype TypePlugin where
toManagedPtr :: TypePlugin -> ManagedPtr TypePlugin
toManagedPtr (TypePlugin ManagedPtr TypePlugin
p) = ManagedPtr TypePlugin
p
class (ManagedPtrNewtype o, O.IsDescendantOf TypePlugin o) => IsTypePlugin o
instance (ManagedPtrNewtype o, O.IsDescendantOf TypePlugin o) => IsTypePlugin o
instance BoxedPtr TypePlugin where
boxedPtrCopy :: TypePlugin -> IO TypePlugin
boxedPtrCopy = TypePlugin -> IO TypePlugin
forall (m :: * -> *) a. Monad m => a -> m a
return
boxedPtrFree :: TypePlugin -> IO ()
boxedPtrFree = \TypePlugin
_x -> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
type family ResolveTypePluginMethod (t :: Symbol) (o :: *) :: * where
ResolveTypePluginMethod "completeInterfaceInfo" o = TypePluginCompleteInterfaceInfoMethodInfo
ResolveTypePluginMethod "completeTypeInfo" o = TypePluginCompleteTypeInfoMethodInfo
ResolveTypePluginMethod "unuse" o = TypePluginUnuseMethodInfo
ResolveTypePluginMethod "use" o = TypePluginUseMethodInfo
ResolveTypePluginMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTypePluginMethod t TypePlugin, O.OverloadedMethod info TypePlugin p) => OL.IsLabel t (TypePlugin -> 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 ~ ResolveTypePluginMethod t TypePlugin, O.OverloadedMethod info TypePlugin p, R.HasField t TypePlugin p) => R.HasField t TypePlugin p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveTypePluginMethod t TypePlugin, O.OverloadedMethodInfo info TypePlugin) => OL.IsLabel t (O.MethodProxy info TypePlugin) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
foreign import ccall "g_type_plugin_complete_interface_info" g_type_plugin_complete_interface_info ::
Ptr TypePlugin ->
CGType ->
CGType ->
Ptr GObject.InterfaceInfo.InterfaceInfo ->
IO ()
typePluginCompleteInterfaceInfo ::
(B.CallStack.HasCallStack, MonadIO m, IsTypePlugin a) =>
a
-> GType
-> GType
-> GObject.InterfaceInfo.InterfaceInfo
-> m ()
typePluginCompleteInterfaceInfo :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTypePlugin a) =>
a -> GType -> GType -> InterfaceInfo -> m ()
typePluginCompleteInterfaceInfo a
plugin GType
instanceType GType
interfaceType InterfaceInfo
info = 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 TypePlugin
plugin' <- a -> IO (Ptr TypePlugin)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
plugin
let instanceType' :: CGType
instanceType' = GType -> CGType
gtypeToCGType GType
instanceType
let interfaceType' :: CGType
interfaceType' = GType -> CGType
gtypeToCGType GType
interfaceType
Ptr InterfaceInfo
info' <- InterfaceInfo -> IO (Ptr InterfaceInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr InterfaceInfo
info
Ptr TypePlugin -> CGType -> CGType -> Ptr InterfaceInfo -> IO ()
g_type_plugin_complete_interface_info Ptr TypePlugin
plugin' CGType
instanceType' CGType
interfaceType' Ptr InterfaceInfo
info'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
plugin
InterfaceInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr InterfaceInfo
info
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TypePluginCompleteInterfaceInfoMethodInfo
instance (signature ~ (GType -> GType -> GObject.InterfaceInfo.InterfaceInfo -> m ()), MonadIO m, IsTypePlugin a) => O.OverloadedMethod TypePluginCompleteInterfaceInfoMethodInfo a signature where
overloadedMethod = typePluginCompleteInterfaceInfo
instance O.OverloadedMethodInfo TypePluginCompleteInterfaceInfoMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Interfaces.TypePlugin.typePluginCompleteInterfaceInfo",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Interfaces-TypePlugin.html#v:typePluginCompleteInterfaceInfo"
})
#endif
foreign import ccall "g_type_plugin_complete_type_info" g_type_plugin_complete_type_info ::
Ptr TypePlugin ->
CGType ->
Ptr GObject.TypeInfo.TypeInfo ->
Ptr GObject.TypeValueTable.TypeValueTable ->
IO ()
typePluginCompleteTypeInfo ::
(B.CallStack.HasCallStack, MonadIO m, IsTypePlugin a) =>
a
-> GType
-> GObject.TypeInfo.TypeInfo
-> GObject.TypeValueTable.TypeValueTable
-> m ()
typePluginCompleteTypeInfo :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTypePlugin a) =>
a -> GType -> TypeInfo -> TypeValueTable -> m ()
typePluginCompleteTypeInfo a
plugin GType
gType TypeInfo
info TypeValueTable
valueTable = 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 TypePlugin
plugin' <- a -> IO (Ptr TypePlugin)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
plugin
let gType' :: CGType
gType' = GType -> CGType
gtypeToCGType GType
gType
Ptr TypeInfo
info' <- TypeInfo -> IO (Ptr TypeInfo)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TypeInfo
info
Ptr TypeValueTable
valueTable' <- TypeValueTable -> IO (Ptr TypeValueTable)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TypeValueTable
valueTable
Ptr TypePlugin
-> CGType -> Ptr TypeInfo -> Ptr TypeValueTable -> IO ()
g_type_plugin_complete_type_info Ptr TypePlugin
plugin' CGType
gType' Ptr TypeInfo
info' Ptr TypeValueTable
valueTable'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
plugin
TypeInfo -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TypeInfo
info
TypeValueTable -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TypeValueTable
valueTable
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TypePluginCompleteTypeInfoMethodInfo
instance (signature ~ (GType -> GObject.TypeInfo.TypeInfo -> GObject.TypeValueTable.TypeValueTable -> m ()), MonadIO m, IsTypePlugin a) => O.OverloadedMethod TypePluginCompleteTypeInfoMethodInfo a signature where
overloadedMethod = typePluginCompleteTypeInfo
instance O.OverloadedMethodInfo TypePluginCompleteTypeInfoMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Interfaces.TypePlugin.typePluginCompleteTypeInfo",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Interfaces-TypePlugin.html#v:typePluginCompleteTypeInfo"
})
#endif
foreign import ccall "g_type_plugin_unuse" g_type_plugin_unuse ::
Ptr TypePlugin ->
IO ()
typePluginUnuse ::
(B.CallStack.HasCallStack, MonadIO m, IsTypePlugin a) =>
a
-> m ()
typePluginUnuse :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTypePlugin a) =>
a -> m ()
typePluginUnuse a
plugin = 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 TypePlugin
plugin' <- a -> IO (Ptr TypePlugin)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
plugin
Ptr TypePlugin -> IO ()
g_type_plugin_unuse Ptr TypePlugin
plugin'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
plugin
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TypePluginUnuseMethodInfo
instance (signature ~ (m ()), MonadIO m, IsTypePlugin a) => O.OverloadedMethod TypePluginUnuseMethodInfo a signature where
overloadedMethod = typePluginUnuse
instance O.OverloadedMethodInfo TypePluginUnuseMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Interfaces.TypePlugin.typePluginUnuse",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Interfaces-TypePlugin.html#v:typePluginUnuse"
})
#endif
foreign import ccall "g_type_plugin_use" g_type_plugin_use ::
Ptr TypePlugin ->
IO ()
typePluginUse ::
(B.CallStack.HasCallStack, MonadIO m, IsTypePlugin a) =>
a
-> m ()
typePluginUse :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsTypePlugin a) =>
a -> m ()
typePluginUse a
plugin = 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 TypePlugin
plugin' <- a -> IO (Ptr TypePlugin)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
plugin
Ptr TypePlugin -> IO ()
g_type_plugin_use Ptr TypePlugin
plugin'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
plugin
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data TypePluginUseMethodInfo
instance (signature ~ (m ()), MonadIO m, IsTypePlugin a) => O.OverloadedMethod TypePluginUseMethodInfo a signature where
overloadedMethod = typePluginUse
instance O.OverloadedMethodInfo TypePluginUseMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Interfaces.TypePlugin.typePluginUse",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Interfaces-TypePlugin.html#v:typePluginUse"
})
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList TypePlugin = TypePluginSignalList
type TypePluginSignalList = ('[ ] :: [(Symbol, *)])
#endif