{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GObject.Structs.TypeInterface
(
TypeInterface(..) ,
newZeroTypeInterface ,
#if defined(ENABLE_OVERLOADING)
ResolveTypeInterfaceMethod ,
#endif
typeInterfaceAddPrerequisite ,
typeInterfaceGetPlugin ,
typeInterfaceInstantiatablePrerequisite ,
typeInterfacePeek ,
#if defined(ENABLE_OVERLOADING)
TypeInterfacePeekParentMethodInfo ,
#endif
typeInterfacePeekParent ,
typeInterfacePrerequisites ,
) 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.Interfaces.TypePlugin as GObject.TypePlugin
import {-# SOURCE #-} qualified GI.GObject.Structs.TypeClass as GObject.TypeClass
newtype TypeInterface = TypeInterface (SP.ManagedPtr TypeInterface)
deriving (TypeInterface -> TypeInterface -> Bool
(TypeInterface -> TypeInterface -> Bool)
-> (TypeInterface -> TypeInterface -> Bool) -> Eq TypeInterface
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeInterface -> TypeInterface -> Bool
$c/= :: TypeInterface -> TypeInterface -> Bool
== :: TypeInterface -> TypeInterface -> Bool
$c== :: TypeInterface -> TypeInterface -> Bool
Eq)
instance SP.ManagedPtrNewtype TypeInterface where
toManagedPtr :: TypeInterface -> ManagedPtr TypeInterface
toManagedPtr (TypeInterface ManagedPtr TypeInterface
p) = ManagedPtr TypeInterface
p
instance BoxedPtr TypeInterface where
boxedPtrCopy :: TypeInterface -> IO TypeInterface
boxedPtrCopy = \TypeInterface
p -> TypeInterface
-> (Ptr TypeInterface -> IO TypeInterface) -> IO TypeInterface
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr TypeInterface
p (Int -> Ptr TypeInterface -> IO (Ptr TypeInterface)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
16 (Ptr TypeInterface -> IO (Ptr TypeInterface))
-> (Ptr TypeInterface -> IO TypeInterface)
-> Ptr TypeInterface
-> IO TypeInterface
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr TypeInterface -> TypeInterface)
-> Ptr TypeInterface -> IO TypeInterface
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr TypeInterface -> TypeInterface
TypeInterface)
boxedPtrFree :: TypeInterface -> IO ()
boxedPtrFree = \TypeInterface
x -> TypeInterface -> (Ptr TypeInterface -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr TypeInterface
x Ptr TypeInterface -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr TypeInterface where
boxedPtrCalloc :: IO (Ptr TypeInterface)
boxedPtrCalloc = Int -> IO (Ptr TypeInterface)
forall a. Int -> IO (Ptr a)
callocBytes Int
16
newZeroTypeInterface :: MonadIO m => m TypeInterface
newZeroTypeInterface :: forall (m :: * -> *). MonadIO m => m TypeInterface
newZeroTypeInterface = IO TypeInterface -> m TypeInterface
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TypeInterface -> m TypeInterface)
-> IO TypeInterface -> m TypeInterface
forall a b. (a -> b) -> a -> b
$ IO (Ptr TypeInterface)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr TypeInterface)
-> (Ptr TypeInterface -> IO TypeInterface) -> IO TypeInterface
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr TypeInterface -> TypeInterface)
-> Ptr TypeInterface -> IO TypeInterface
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr TypeInterface -> TypeInterface
TypeInterface
instance tag ~ 'AttrSet => Constructible TypeInterface tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr TypeInterface -> TypeInterface)
-> [AttrOp TypeInterface tag] -> m TypeInterface
new ManagedPtr TypeInterface -> TypeInterface
_ [AttrOp TypeInterface tag]
attrs = do
TypeInterface
o <- m TypeInterface
forall (m :: * -> *). MonadIO m => m TypeInterface
newZeroTypeInterface
TypeInterface -> [AttrOp TypeInterface 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set TypeInterface
o [AttrOp TypeInterface tag]
[AttrOp TypeInterface 'AttrSet]
attrs
TypeInterface -> m TypeInterface
forall (m :: * -> *) a. Monad m => a -> m a
return TypeInterface
o
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList TypeInterface
type instance O.AttributeList TypeInterface = TypeInterfaceAttributeList
type TypeInterfaceAttributeList = ('[ ] :: [(Symbol, *)])
#endif
foreign import ccall "g_type_interface_peek_parent" g_type_interface_peek_parent ::
Ptr TypeInterface ->
IO (Ptr TypeInterface)
typeInterfacePeekParent ::
(B.CallStack.HasCallStack, MonadIO m) =>
TypeInterface
-> m TypeInterface
typeInterfacePeekParent :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
TypeInterface -> m TypeInterface
typeInterfacePeekParent TypeInterface
gIface = IO TypeInterface -> m TypeInterface
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TypeInterface -> m TypeInterface)
-> IO TypeInterface -> m TypeInterface
forall a b. (a -> b) -> a -> b
$ do
Ptr TypeInterface
gIface' <- TypeInterface -> IO (Ptr TypeInterface)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TypeInterface
gIface
Ptr TypeInterface
result <- Ptr TypeInterface -> IO (Ptr TypeInterface)
g_type_interface_peek_parent Ptr TypeInterface
gIface'
Text -> Ptr TypeInterface -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"typeInterfacePeekParent" Ptr TypeInterface
result
TypeInterface
result' <- ((ManagedPtr TypeInterface -> TypeInterface)
-> Ptr TypeInterface -> IO TypeInterface
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr TypeInterface -> TypeInterface
TypeInterface) Ptr TypeInterface
result
TypeInterface -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TypeInterface
gIface
TypeInterface -> IO TypeInterface
forall (m :: * -> *) a. Monad m => a -> m a
return TypeInterface
result'
#if defined(ENABLE_OVERLOADING)
data TypeInterfacePeekParentMethodInfo
instance (signature ~ (m TypeInterface), MonadIO m) => O.OverloadedMethod TypeInterfacePeekParentMethodInfo TypeInterface signature where
overloadedMethod = typeInterfacePeekParent
instance O.OverloadedMethodInfo TypeInterfacePeekParentMethodInfo TypeInterface where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Structs.TypeInterface.typeInterfacePeekParent",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Structs-TypeInterface.html#v:typeInterfacePeekParent"
})
#endif
foreign import ccall "g_type_interface_add_prerequisite" g_type_interface_add_prerequisite ::
CGType ->
CGType ->
IO ()
typeInterfaceAddPrerequisite ::
(B.CallStack.HasCallStack, MonadIO m) =>
GType
-> GType
-> m ()
typeInterfaceAddPrerequisite :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
GType -> GType -> m ()
typeInterfaceAddPrerequisite GType
interfaceType GType
prerequisiteType = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
let interfaceType' :: CGType
interfaceType' = GType -> CGType
gtypeToCGType GType
interfaceType
let prerequisiteType' :: CGType
prerequisiteType' = GType -> CGType
gtypeToCGType GType
prerequisiteType
CGType -> CGType -> IO ()
g_type_interface_add_prerequisite CGType
interfaceType' CGType
prerequisiteType'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_type_interface_get_plugin" g_type_interface_get_plugin ::
CGType ->
CGType ->
IO (Ptr GObject.TypePlugin.TypePlugin)
typeInterfaceGetPlugin ::
(B.CallStack.HasCallStack, MonadIO m) =>
GType
-> GType
-> m GObject.TypePlugin.TypePlugin
typeInterfaceGetPlugin :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
GType -> GType -> m TypePlugin
typeInterfaceGetPlugin GType
instanceType GType
interfaceType = IO TypePlugin -> m TypePlugin
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TypePlugin -> m TypePlugin) -> IO TypePlugin -> m TypePlugin
forall a b. (a -> b) -> a -> b
$ do
let instanceType' :: CGType
instanceType' = GType -> CGType
gtypeToCGType GType
instanceType
let interfaceType' :: CGType
interfaceType' = GType -> CGType
gtypeToCGType GType
interfaceType
Ptr TypePlugin
result <- CGType -> CGType -> IO (Ptr TypePlugin)
g_type_interface_get_plugin CGType
instanceType' CGType
interfaceType'
Text -> Ptr TypePlugin -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"typeInterfaceGetPlugin" Ptr TypePlugin
result
TypePlugin
result' <- ((ManagedPtr TypePlugin -> TypePlugin)
-> Ptr TypePlugin -> IO TypePlugin
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr TypePlugin -> TypePlugin
GObject.TypePlugin.TypePlugin) Ptr TypePlugin
result
TypePlugin -> IO TypePlugin
forall (m :: * -> *) a. Monad m => a -> m a
return TypePlugin
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_type_interface_instantiatable_prerequisite" g_type_interface_instantiatable_prerequisite ::
CGType ->
IO CGType
typeInterfaceInstantiatablePrerequisite ::
(B.CallStack.HasCallStack, MonadIO m) =>
GType
-> m GType
typeInterfaceInstantiatablePrerequisite :: forall (m :: * -> *). (HasCallStack, MonadIO m) => GType -> m GType
typeInterfaceInstantiatablePrerequisite GType
interfaceType = 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
let interfaceType' :: CGType
interfaceType' = GType -> CGType
gtypeToCGType GType
interfaceType
CGType
result <- CGType -> IO CGType
g_type_interface_instantiatable_prerequisite CGType
interfaceType'
let result' :: GType
result' = CGType -> GType
GType CGType
result
GType -> IO GType
forall (m :: * -> *) a. Monad m => a -> m a
return GType
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_type_interface_peek" g_type_interface_peek ::
Ptr GObject.TypeClass.TypeClass ->
CGType ->
IO (Ptr TypeInterface)
typeInterfacePeek ::
(B.CallStack.HasCallStack, MonadIO m) =>
GObject.TypeClass.TypeClass
-> GType
-> m TypeInterface
typeInterfacePeek :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
TypeClass -> GType -> m TypeInterface
typeInterfacePeek TypeClass
instanceClass GType
ifaceType = IO TypeInterface -> m TypeInterface
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO TypeInterface -> m TypeInterface)
-> IO TypeInterface -> m TypeInterface
forall a b. (a -> b) -> a -> b
$ do
Ptr TypeClass
instanceClass' <- TypeClass -> IO (Ptr TypeClass)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TypeClass
instanceClass
let ifaceType' :: CGType
ifaceType' = GType -> CGType
gtypeToCGType GType
ifaceType
Ptr TypeInterface
result <- Ptr TypeClass -> CGType -> IO (Ptr TypeInterface)
g_type_interface_peek Ptr TypeClass
instanceClass' CGType
ifaceType'
Text -> Ptr TypeInterface -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"typeInterfacePeek" Ptr TypeInterface
result
TypeInterface
result' <- ((ManagedPtr TypeInterface -> TypeInterface)
-> Ptr TypeInterface -> IO TypeInterface
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr TypeInterface -> TypeInterface
TypeInterface) Ptr TypeInterface
result
TypeClass -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TypeClass
instanceClass
TypeInterface -> IO TypeInterface
forall (m :: * -> *) a. Monad m => a -> m a
return TypeInterface
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_type_interface_prerequisites" g_type_interface_prerequisites ::
CGType ->
Ptr Word32 ->
IO (Ptr CGType)
typeInterfacePrerequisites ::
(B.CallStack.HasCallStack, MonadIO m) =>
GType
-> m [GType]
typeInterfacePrerequisites :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
GType -> m [GType]
typeInterfacePrerequisites GType
interfaceType = 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
let interfaceType' :: CGType
interfaceType' = GType -> CGType
gtypeToCGType GType
interfaceType
Ptr Word32
nPrerequisites <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
Ptr CGType
result <- CGType -> Ptr Word32 -> IO (Ptr CGType)
g_type_interface_prerequisites CGType
interfaceType' Ptr Word32
nPrerequisites
Word32
nPrerequisites' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
nPrerequisites
Text -> Ptr CGType -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"typeInterfacePrerequisites" Ptr CGType
result
[GType]
result' <- ((CGType -> GType) -> Word32 -> Ptr CGType -> IO [GType]
forall a b c.
(Integral a, Storable b) =>
(b -> c) -> a -> Ptr b -> IO [c]
unpackMapStorableArrayWithLength CGType -> GType
GType Word32
nPrerequisites') Ptr CGType
result
Ptr CGType -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CGType
result
Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
nPrerequisites
[GType] -> IO [GType]
forall (m :: * -> *) a. Monad m => a -> m a
return [GType]
result'
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveTypeInterfaceMethod (t :: Symbol) (o :: *) :: * where
ResolveTypeInterfaceMethod "peekParent" o = TypeInterfacePeekParentMethodInfo
ResolveTypeInterfaceMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveTypeInterfaceMethod t TypeInterface, O.OverloadedMethod info TypeInterface p) => OL.IsLabel t (TypeInterface -> 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 ~ ResolveTypeInterfaceMethod t TypeInterface, O.OverloadedMethod info TypeInterface p, R.HasField t TypeInterface p) => R.HasField t TypeInterface p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveTypeInterfaceMethod t TypeInterface, O.OverloadedMethodInfo info TypeInterface) => OL.IsLabel t (O.MethodProxy info TypeInterface) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif