{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Atk.Objects.Registry
(
Registry(..) ,
IsRegistry ,
toRegistry ,
#if defined(ENABLE_OVERLOADING)
ResolveRegistryMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
RegistryGetFactoryMethodInfo ,
#endif
registryGetFactory ,
#if defined(ENABLE_OVERLOADING)
RegistryGetFactoryTypeMethodInfo ,
#endif
registryGetFactoryType ,
#if defined(ENABLE_OVERLOADING)
RegistrySetFactoryTypeMethodInfo ,
#endif
registrySetFactoryType ,
) 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.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.Atk.Objects.ObjectFactory as Atk.ObjectFactory
import qualified GI.GObject.Objects.Object as GObject.Object
newtype Registry = Registry (SP.ManagedPtr Registry)
deriving (Registry -> Registry -> Bool
(Registry -> Registry -> Bool)
-> (Registry -> Registry -> Bool) -> Eq Registry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Registry -> Registry -> Bool
$c/= :: Registry -> Registry -> Bool
== :: Registry -> Registry -> Bool
$c== :: Registry -> Registry -> Bool
Eq)
instance SP.ManagedPtrNewtype Registry where
toManagedPtr :: Registry -> ManagedPtr Registry
toManagedPtr (Registry ManagedPtr Registry
p) = ManagedPtr Registry
p
foreign import ccall "atk_registry_get_type"
c_atk_registry_get_type :: IO B.Types.GType
instance B.Types.TypedObject Registry where
glibType :: IO GType
glibType = IO GType
c_atk_registry_get_type
instance B.Types.GObject Registry
instance B.GValue.IsGValue Registry where
toGValue :: Registry -> IO GValue
toGValue Registry
o = do
GType
gtype <- IO GType
c_atk_registry_get_type
Registry -> (Ptr Registry -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Registry
o (GType
-> (GValue -> Ptr Registry -> IO ()) -> Ptr Registry -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Registry -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO Registry
fromGValue GValue
gv = do
Ptr Registry
ptr <- GValue -> IO (Ptr Registry)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Registry)
(ManagedPtr Registry -> Registry) -> Ptr Registry -> IO Registry
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Registry -> Registry
Registry Ptr Registry
ptr
class (SP.GObject o, O.IsDescendantOf Registry o) => IsRegistry o
instance (SP.GObject o, O.IsDescendantOf Registry o) => IsRegistry o
instance O.HasParentTypes Registry
type instance O.ParentTypes Registry = '[GObject.Object.Object]
toRegistry :: (MonadIO m, IsRegistry o) => o -> m Registry
toRegistry :: o -> m Registry
toRegistry = IO Registry -> m Registry
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Registry -> m Registry)
-> (o -> IO Registry) -> o -> m Registry
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Registry -> Registry) -> o -> IO Registry
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Registry -> Registry
Registry
#if defined(ENABLE_OVERLOADING)
type family ResolveRegistryMethod (t :: Symbol) (o :: *) :: * where
ResolveRegistryMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveRegistryMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveRegistryMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveRegistryMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveRegistryMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveRegistryMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveRegistryMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveRegistryMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveRegistryMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveRegistryMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveRegistryMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveRegistryMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveRegistryMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveRegistryMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveRegistryMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveRegistryMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveRegistryMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveRegistryMethod "getFactory" o = RegistryGetFactoryMethodInfo
ResolveRegistryMethod "getFactoryType" o = RegistryGetFactoryTypeMethodInfo
ResolveRegistryMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveRegistryMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveRegistryMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveRegistryMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveRegistryMethod "setFactoryType" o = RegistrySetFactoryTypeMethodInfo
ResolveRegistryMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveRegistryMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveRegistryMethod t Registry, O.MethodInfo info Registry p) => OL.IsLabel t (Registry -> 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 Registry
type instance O.AttributeList Registry = RegistryAttributeList
type RegistryAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Registry = RegistrySignalList
type RegistrySignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "atk_registry_get_factory" atk_registry_get_factory ::
Ptr Registry ->
CGType ->
IO (Ptr Atk.ObjectFactory.ObjectFactory)
registryGetFactory ::
(B.CallStack.HasCallStack, MonadIO m, IsRegistry a) =>
a
-> GType
-> m Atk.ObjectFactory.ObjectFactory
registryGetFactory :: a -> GType -> m ObjectFactory
registryGetFactory a
registry GType
type_ = IO ObjectFactory -> m ObjectFactory
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ObjectFactory -> m ObjectFactory)
-> IO ObjectFactory -> m ObjectFactory
forall a b. (a -> b) -> a -> b
$ do
Ptr Registry
registry' <- a -> IO (Ptr Registry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
registry
let type_' :: CGType
type_' = GType -> CGType
gtypeToCGType GType
type_
Ptr ObjectFactory
result <- Ptr Registry -> CGType -> IO (Ptr ObjectFactory)
atk_registry_get_factory Ptr Registry
registry' CGType
type_'
Text -> Ptr ObjectFactory -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"registryGetFactory" Ptr ObjectFactory
result
ObjectFactory
result' <- ((ManagedPtr ObjectFactory -> ObjectFactory)
-> Ptr ObjectFactory -> IO ObjectFactory
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr ObjectFactory -> ObjectFactory
Atk.ObjectFactory.ObjectFactory) Ptr ObjectFactory
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
registry
ObjectFactory -> IO ObjectFactory
forall (m :: * -> *) a. Monad m => a -> m a
return ObjectFactory
result'
#if defined(ENABLE_OVERLOADING)
data RegistryGetFactoryMethodInfo
instance (signature ~ (GType -> m Atk.ObjectFactory.ObjectFactory), MonadIO m, IsRegistry a) => O.MethodInfo RegistryGetFactoryMethodInfo a signature where
overloadedMethod = registryGetFactory
#endif
foreign import ccall "atk_registry_get_factory_type" atk_registry_get_factory_type ::
Ptr Registry ->
CGType ->
IO CGType
registryGetFactoryType ::
(B.CallStack.HasCallStack, MonadIO m, IsRegistry a) =>
a
-> GType
-> m GType
registryGetFactoryType :: a -> GType -> m GType
registryGetFactoryType a
registry GType
type_ = 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 Registry
registry' <- a -> IO (Ptr Registry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
registry
let type_' :: CGType
type_' = GType -> CGType
gtypeToCGType GType
type_
CGType
result <- Ptr Registry -> CGType -> IO CGType
atk_registry_get_factory_type Ptr Registry
registry' CGType
type_'
let result' :: GType
result' = CGType -> GType
GType CGType
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
registry
GType -> IO GType
forall (m :: * -> *) a. Monad m => a -> m a
return GType
result'
#if defined(ENABLE_OVERLOADING)
data RegistryGetFactoryTypeMethodInfo
instance (signature ~ (GType -> m GType), MonadIO m, IsRegistry a) => O.MethodInfo RegistryGetFactoryTypeMethodInfo a signature where
overloadedMethod = registryGetFactoryType
#endif
foreign import ccall "atk_registry_set_factory_type" atk_registry_set_factory_type ::
Ptr Registry ->
CGType ->
CGType ->
IO ()
registrySetFactoryType ::
(B.CallStack.HasCallStack, MonadIO m, IsRegistry a) =>
a
-> GType
-> GType
-> m ()
registrySetFactoryType :: a -> GType -> GType -> m ()
registrySetFactoryType a
registry GType
type_ GType
factoryType = 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 Registry
registry' <- a -> IO (Ptr Registry)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
registry
let type_' :: CGType
type_' = GType -> CGType
gtypeToCGType GType
type_
let factoryType' :: CGType
factoryType' = GType -> CGType
gtypeToCGType GType
factoryType
Ptr Registry -> CGType -> CGType -> IO ()
atk_registry_set_factory_type Ptr Registry
registry' CGType
type_' CGType
factoryType'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
registry
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data RegistrySetFactoryTypeMethodInfo
instance (signature ~ (GType -> GType -> m ()), MonadIO m, IsRegistry a) => O.MethodInfo RegistrySetFactoryTypeMethodInfo a signature where
overloadedMethod = registrySetFactoryType
#endif