{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GObject.Objects.ParamSpec
(
ParamSpec(..) ,
IsParamSpec ,
toParamSpec ,
#if defined(ENABLE_OVERLOADING)
ResolveParamSpecMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ParamSpecGetBlurbMethodInfo ,
#endif
paramSpecGetBlurb ,
#if defined(ENABLE_OVERLOADING)
ParamSpecGetDefaultValueMethodInfo ,
#endif
paramSpecGetDefaultValue ,
#if defined(ENABLE_OVERLOADING)
ParamSpecGetNameMethodInfo ,
#endif
paramSpecGetName ,
#if defined(ENABLE_OVERLOADING)
ParamSpecGetNameQuarkMethodInfo ,
#endif
paramSpecGetNameQuark ,
#if defined(ENABLE_OVERLOADING)
ParamSpecGetNickMethodInfo ,
#endif
paramSpecGetNick ,
#if defined(ENABLE_OVERLOADING)
ParamSpecGetQdataMethodInfo ,
#endif
paramSpecGetQdata ,
#if defined(ENABLE_OVERLOADING)
ParamSpecGetRedirectTargetMethodInfo ,
#endif
paramSpecGetRedirectTarget ,
#if defined(ENABLE_OVERLOADING)
ParamSpecSetQdataMethodInfo ,
#endif
paramSpecSetQdata ,
#if defined(ENABLE_OVERLOADING)
ParamSpecSinkMethodInfo ,
#endif
paramSpecSink ,
#if defined(ENABLE_OVERLOADING)
ParamSpecStealQdataMethodInfo ,
#endif
paramSpecStealQdata ,
) 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
newtype ParamSpec = ParamSpec (SP.ManagedPtr ParamSpec)
deriving (ParamSpec -> ParamSpec -> Bool
(ParamSpec -> ParamSpec -> Bool)
-> (ParamSpec -> ParamSpec -> Bool) -> Eq ParamSpec
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParamSpec -> ParamSpec -> Bool
$c/= :: ParamSpec -> ParamSpec -> Bool
== :: ParamSpec -> ParamSpec -> Bool
$c== :: ParamSpec -> ParamSpec -> Bool
Eq)
instance SP.ManagedPtrNewtype ParamSpec where
toManagedPtr :: ParamSpec -> ManagedPtr ParamSpec
toManagedPtr (ParamSpec ManagedPtr ParamSpec
p) = ManagedPtr ParamSpec
p
foreign import ccall "haskell_gi_pspec_type_init_ParamSpec"
c_haskell_gi_pspec_type_init_ParamSpec :: IO B.Types.GType
instance B.Types.TypedObject ParamSpec where
glibType :: IO GType
glibType = IO GType
c_haskell_gi_pspec_type_init_ParamSpec
class (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf ParamSpec o) => IsParamSpec o
instance (SP.BoxedPtr o, SP.TypedObject o, O.IsDescendantOf ParamSpec o) => IsParamSpec o
instance O.HasParentTypes ParamSpec
type instance O.ParentTypes ParamSpec = '[]
toParamSpec :: (MonadIO m, IsParamSpec o) => o -> m ParamSpec
toParamSpec :: o -> m ParamSpec
toParamSpec = IO ParamSpec -> m ParamSpec
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ParamSpec -> m ParamSpec)
-> (o -> IO ParamSpec) -> o -> m ParamSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr ParamSpec -> ParamSpec) -> o -> IO ParamSpec
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr ParamSpec -> ParamSpec
ParamSpec
#if defined(ENABLE_OVERLOADING)
type family ResolveParamSpecMethod (t :: Symbol) (o :: *) :: * where
ResolveParamSpecMethod "sink" o = ParamSpecSinkMethodInfo
ResolveParamSpecMethod "stealQdata" o = ParamSpecStealQdataMethodInfo
ResolveParamSpecMethod "getBlurb" o = ParamSpecGetBlurbMethodInfo
ResolveParamSpecMethod "getDefaultValue" o = ParamSpecGetDefaultValueMethodInfo
ResolveParamSpecMethod "getName" o = ParamSpecGetNameMethodInfo
ResolveParamSpecMethod "getNameQuark" o = ParamSpecGetNameQuarkMethodInfo
ResolveParamSpecMethod "getNick" o = ParamSpecGetNickMethodInfo
ResolveParamSpecMethod "getQdata" o = ParamSpecGetQdataMethodInfo
ResolveParamSpecMethod "getRedirectTarget" o = ParamSpecGetRedirectTargetMethodInfo
ResolveParamSpecMethod "setQdata" o = ParamSpecSetQdataMethodInfo
ResolveParamSpecMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveParamSpecMethod t ParamSpec, O.MethodInfo info ParamSpec p) => OL.IsLabel t (ParamSpec -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
foreign import ccall "g_param_spec_ref_sink" _ParamSpec_copy_g_param_spec_ref_sink :: Ptr a -> IO (Ptr a)
foreign import ccall "g_param_spec_unref" _ParamSpec_free_g_param_spec_unref :: Ptr a -> IO ()
instance BoxedPtr ParamSpec where
boxedPtrCopy :: ParamSpec -> IO ParamSpec
boxedPtrCopy = \ParamSpec
p -> ParamSpec -> (Ptr ParamSpec -> IO ParamSpec) -> IO ParamSpec
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ParamSpec
p (Ptr ParamSpec -> IO (Ptr ParamSpec)
forall a. Ptr a -> IO (Ptr a)
_ParamSpec_copy_g_param_spec_ref_sink (Ptr ParamSpec -> IO (Ptr ParamSpec))
-> (Ptr ParamSpec -> IO ParamSpec) -> Ptr ParamSpec -> IO ParamSpec
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr ParamSpec -> ParamSpec)
-> Ptr ParamSpec -> IO ParamSpec
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr ParamSpec -> ParamSpec
ParamSpec)
boxedPtrFree :: ParamSpec -> IO ()
boxedPtrFree = \ParamSpec
p -> ParamSpec -> (Ptr ParamSpec -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ParamSpec
p Ptr ParamSpec -> IO ()
forall a. Ptr a -> IO ()
_ParamSpec_free_g_param_spec_unref
foreign import ccall "g_param_spec_get_blurb" g_param_spec_get_blurb ::
Ptr GParamSpec ->
IO CString
paramSpecGetBlurb ::
(B.CallStack.HasCallStack, MonadIO m) =>
GParamSpec
-> m T.Text
paramSpecGetBlurb :: GParamSpec -> m Text
paramSpecGetBlurb GParamSpec
pspec = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
CString
result <- Ptr GParamSpec -> IO CString
g_param_spec_get_blurb Ptr GParamSpec
pspec'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"paramSpecGetBlurb" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data ParamSpecGetBlurbMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo ParamSpecGetBlurbMethodInfo GParamSpec signature where
overloadedMethod = paramSpecGetBlurb
#endif
foreign import ccall "g_param_spec_get_default_value" g_param_spec_get_default_value ::
Ptr GParamSpec ->
IO (Ptr GValue)
paramSpecGetDefaultValue ::
(B.CallStack.HasCallStack, MonadIO m) =>
GParamSpec
-> m GValue
paramSpecGetDefaultValue :: GParamSpec -> m GValue
paramSpecGetDefaultValue GParamSpec
pspec = IO GValue -> m GValue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GValue -> m GValue) -> IO GValue -> m GValue
forall a b. (a -> b) -> a -> b
$ do
Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
Ptr GValue
result <- Ptr GParamSpec -> IO (Ptr GValue)
g_param_spec_get_default_value Ptr GParamSpec
pspec'
Text -> Ptr GValue -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"paramSpecGetDefaultValue" Ptr GValue
result
GValue
result' <- Ptr GValue -> IO GValue
B.GValue.newGValueFromPtr Ptr GValue
result
GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
GValue -> IO GValue
forall (m :: * -> *) a. Monad m => a -> m a
return GValue
result'
#if defined(ENABLE_OVERLOADING)
data ParamSpecGetDefaultValueMethodInfo
instance (signature ~ (m GValue), MonadIO m) => O.MethodInfo ParamSpecGetDefaultValueMethodInfo GParamSpec signature where
overloadedMethod = paramSpecGetDefaultValue
#endif
foreign import ccall "g_param_spec_get_name" g_param_spec_get_name ::
Ptr GParamSpec ->
IO CString
paramSpecGetName ::
(B.CallStack.HasCallStack, MonadIO m) =>
GParamSpec
-> m T.Text
paramSpecGetName :: GParamSpec -> m Text
paramSpecGetName GParamSpec
pspec = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
CString
result <- Ptr GParamSpec -> IO CString
g_param_spec_get_name Ptr GParamSpec
pspec'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"paramSpecGetName" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data ParamSpecGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo ParamSpecGetNameMethodInfo GParamSpec signature where
overloadedMethod = paramSpecGetName
#endif
foreign import ccall "g_param_spec_get_name_quark" g_param_spec_get_name_quark ::
Ptr GParamSpec ->
IO Word32
paramSpecGetNameQuark ::
(B.CallStack.HasCallStack, MonadIO m) =>
GParamSpec
-> m Word32
paramSpecGetNameQuark :: GParamSpec -> m Word32
paramSpecGetNameQuark GParamSpec
pspec = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
Word32
result <- Ptr GParamSpec -> IO Word32
g_param_spec_get_name_quark Ptr GParamSpec
pspec'
GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data ParamSpecGetNameQuarkMethodInfo
instance (signature ~ (m Word32), MonadIO m) => O.MethodInfo ParamSpecGetNameQuarkMethodInfo GParamSpec signature where
overloadedMethod = paramSpecGetNameQuark
#endif
foreign import ccall "g_param_spec_get_nick" g_param_spec_get_nick ::
Ptr GParamSpec ->
IO CString
paramSpecGetNick ::
(B.CallStack.HasCallStack, MonadIO m) =>
GParamSpec
-> m T.Text
paramSpecGetNick :: GParamSpec -> m Text
paramSpecGetNick GParamSpec
pspec = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
CString
result <- Ptr GParamSpec -> IO CString
g_param_spec_get_nick Ptr GParamSpec
pspec'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"paramSpecGetNick" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data ParamSpecGetNickMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo ParamSpecGetNickMethodInfo GParamSpec signature where
overloadedMethod = paramSpecGetNick
#endif
foreign import ccall "g_param_spec_get_qdata" g_param_spec_get_qdata ::
Ptr GParamSpec ->
Word32 ->
IO (Ptr ())
paramSpecGetQdata ::
(B.CallStack.HasCallStack, MonadIO m) =>
GParamSpec
-> Word32
-> m (Ptr ())
paramSpecGetQdata :: GParamSpec -> Word32 -> m (Ptr ())
paramSpecGetQdata GParamSpec
pspec Word32
quark = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
Ptr ()
result <- Ptr GParamSpec -> Word32 -> IO (Ptr ())
g_param_spec_get_qdata Ptr GParamSpec
pspec' Word32
quark
GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result
#if defined(ENABLE_OVERLOADING)
data ParamSpecGetQdataMethodInfo
instance (signature ~ (Word32 -> m (Ptr ())), MonadIO m) => O.MethodInfo ParamSpecGetQdataMethodInfo GParamSpec signature where
overloadedMethod = paramSpecGetQdata
#endif
foreign import ccall "g_param_spec_get_redirect_target" g_param_spec_get_redirect_target ::
Ptr GParamSpec ->
IO (Ptr GParamSpec)
paramSpecGetRedirectTarget ::
(B.CallStack.HasCallStack, MonadIO m) =>
GParamSpec
-> m GParamSpec
paramSpecGetRedirectTarget :: GParamSpec -> m GParamSpec
paramSpecGetRedirectTarget GParamSpec
pspec = IO GParamSpec -> m GParamSpec
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GParamSpec -> m GParamSpec) -> IO GParamSpec -> m GParamSpec
forall a b. (a -> b) -> a -> b
$ do
Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
Ptr GParamSpec
result <- Ptr GParamSpec -> IO (Ptr GParamSpec)
g_param_spec_get_redirect_target Ptr GParamSpec
pspec'
Text -> Ptr GParamSpec -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"paramSpecGetRedirectTarget" Ptr GParamSpec
result
GParamSpec
result' <- Ptr GParamSpec -> IO GParamSpec
B.GParamSpec.newGParamSpecFromPtr Ptr GParamSpec
result
GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
GParamSpec -> IO GParamSpec
forall (m :: * -> *) a. Monad m => a -> m a
return GParamSpec
result'
#if defined(ENABLE_OVERLOADING)
data ParamSpecGetRedirectTargetMethodInfo
instance (signature ~ (m GParamSpec), MonadIO m) => O.MethodInfo ParamSpecGetRedirectTargetMethodInfo GParamSpec signature where
overloadedMethod = paramSpecGetRedirectTarget
#endif
foreign import ccall "g_param_spec_set_qdata" g_param_spec_set_qdata ::
Ptr GParamSpec ->
Word32 ->
Ptr () ->
IO ()
paramSpecSetQdata ::
(B.CallStack.HasCallStack, MonadIO m) =>
GParamSpec
-> Word32
-> Ptr ()
-> m ()
paramSpecSetQdata :: GParamSpec -> Word32 -> Ptr () -> m ()
paramSpecSetQdata GParamSpec
pspec Word32
quark Ptr ()
data_ = 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 GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
Ptr GParamSpec -> Word32 -> Ptr () -> IO ()
g_param_spec_set_qdata Ptr GParamSpec
pspec' Word32
quark Ptr ()
data_
GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ParamSpecSetQdataMethodInfo
instance (signature ~ (Word32 -> Ptr () -> m ()), MonadIO m) => O.MethodInfo ParamSpecSetQdataMethodInfo GParamSpec signature where
overloadedMethod = paramSpecSetQdata
#endif
foreign import ccall "g_param_spec_sink" g_param_spec_sink ::
Ptr GParamSpec ->
IO ()
paramSpecSink ::
(B.CallStack.HasCallStack, MonadIO m) =>
GParamSpec
-> m ()
paramSpecSink :: GParamSpec -> m ()
paramSpecSink GParamSpec
pspec = 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 GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
Ptr GParamSpec -> IO ()
g_param_spec_sink Ptr GParamSpec
pspec'
GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ParamSpecSinkMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo ParamSpecSinkMethodInfo GParamSpec signature where
overloadedMethod = paramSpecSink
#endif
foreign import ccall "g_param_spec_steal_qdata" g_param_spec_steal_qdata ::
Ptr GParamSpec ->
Word32 ->
IO (Ptr ())
paramSpecStealQdata ::
(B.CallStack.HasCallStack, MonadIO m) =>
GParamSpec
-> Word32
-> m (Ptr ())
paramSpecStealQdata :: GParamSpec -> Word32 -> m (Ptr ())
paramSpecStealQdata GParamSpec
pspec Word32
quark = IO (Ptr ()) -> m (Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr ()) -> m (Ptr ())) -> IO (Ptr ()) -> m (Ptr ())
forall a b. (a -> b) -> a -> b
$ do
Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
Ptr ()
result <- Ptr GParamSpec -> Word32 -> IO (Ptr ())
g_param_spec_steal_qdata Ptr GParamSpec
pspec' Word32
quark
GParamSpec -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result
#if defined(ENABLE_OVERLOADING)
data ParamSpecStealQdataMethodInfo
instance (signature ~ (Word32 -> m (Ptr ())), MonadIO m) => O.MethodInfo ParamSpecStealQdataMethodInfo GParamSpec signature where
overloadedMethod = paramSpecStealQdata
#endif