{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GObject.Objects.Object
(
#if defined(ENABLE_OVERLOADING)
ObjectInterfaceListPropertiesMethodInfo ,
#endif
Object(..) ,
IsObject ,
toObject ,
#if defined(ENABLE_OVERLOADING)
ResolveObjectMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
ObjectBindPropertyMethodInfo ,
#endif
objectBindProperty ,
#if defined(ENABLE_OVERLOADING)
ObjectBindPropertyFullMethodInfo ,
#endif
objectBindPropertyFull ,
objectCompatControl ,
#if defined(ENABLE_OVERLOADING)
ObjectForceFloatingMethodInfo ,
#endif
objectForceFloating ,
#if defined(ENABLE_OVERLOADING)
ObjectFreezeNotifyMethodInfo ,
#endif
objectFreezeNotify ,
#if defined(ENABLE_OVERLOADING)
ObjectGetDataMethodInfo ,
#endif
objectGetData ,
#if defined(ENABLE_OVERLOADING)
ObjectGetPropertyMethodInfo ,
#endif
objectGetProperty ,
#if defined(ENABLE_OVERLOADING)
ObjectGetQdataMethodInfo ,
#endif
objectGetQdata ,
#if defined(ENABLE_OVERLOADING)
ObjectGetvMethodInfo ,
#endif
objectGetv ,
objectInterfaceFindProperty ,
objectInterfaceInstallProperty ,
#if defined(ENABLE_OVERLOADING)
ObjectIsFloatingMethodInfo ,
#endif
objectIsFloating ,
objectNewv ,
#if defined(ENABLE_OVERLOADING)
ObjectNotifyMethodInfo ,
#endif
objectNotify ,
#if defined(ENABLE_OVERLOADING)
ObjectNotifyByPspecMethodInfo ,
#endif
objectNotifyByPspec ,
#if defined(ENABLE_OVERLOADING)
ObjectRefMethodInfo ,
#endif
objectRef ,
#if defined(ENABLE_OVERLOADING)
ObjectRefSinkMethodInfo ,
#endif
objectRefSink ,
#if defined(ENABLE_OVERLOADING)
ObjectRunDisposeMethodInfo ,
#endif
objectRunDispose ,
#if defined(ENABLE_OVERLOADING)
ObjectSetDataMethodInfo ,
#endif
objectSetData ,
#if defined(ENABLE_OVERLOADING)
ObjectSetDataFullMethodInfo ,
#endif
objectSetDataFull ,
#if defined(ENABLE_OVERLOADING)
ObjectSetPropertyMethodInfo ,
#endif
objectSetProperty ,
#if defined(ENABLE_OVERLOADING)
ObjectStealDataMethodInfo ,
#endif
objectStealData ,
#if defined(ENABLE_OVERLOADING)
ObjectStealQdataMethodInfo ,
#endif
objectStealQdata ,
#if defined(ENABLE_OVERLOADING)
ObjectThawNotifyMethodInfo ,
#endif
objectThawNotify ,
#if defined(ENABLE_OVERLOADING)
ObjectUnrefMethodInfo ,
#endif
objectUnref ,
#if defined(ENABLE_OVERLOADING)
ObjectWatchClosureMethodInfo ,
#endif
objectWatchClosure ,
ObjectNotifyCallback ,
#if defined(ENABLE_OVERLOADING)
ObjectNotifySignalInfo ,
#endif
afterObjectNotify ,
onObjectNotify ,
) 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 qualified GI.GLib.Callbacks as GLib.Callbacks
import {-# SOURCE #-} qualified GI.GObject.Flags as GObject.Flags
import {-# SOURCE #-} qualified GI.GObject.Objects.Binding as GObject.Binding
import {-# SOURCE #-} qualified GI.GObject.Structs.Parameter as GObject.Parameter
import {-# SOURCE #-} qualified GI.GObject.Structs.TypeInterface as GObject.TypeInterface
newtype Object = Object (SP.ManagedPtr Object)
deriving (Object -> Object -> Bool
(Object -> Object -> Bool)
-> (Object -> Object -> Bool) -> Eq Object
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Object -> Object -> Bool
$c/= :: Object -> Object -> Bool
== :: Object -> Object -> Bool
$c== :: Object -> Object -> Bool
Eq)
instance SP.ManagedPtrNewtype Object where
toManagedPtr :: Object -> ManagedPtr Object
toManagedPtr (Object ManagedPtr Object
p) = ManagedPtr Object
p
foreign import ccall "g_object_get_type"
c_g_object_get_type :: IO B.Types.GType
instance B.Types.TypedObject Object where
glibType :: IO GType
glibType = IO GType
c_g_object_get_type
instance B.Types.GObject Object
class (SP.GObject o, O.IsDescendantOf Object o) => IsObject o
instance (SP.GObject o, O.IsDescendantOf Object o) => IsObject o
instance O.HasParentTypes Object
type instance O.ParentTypes Object = '[]
toObject :: (MIO.MonadIO m, IsObject o) => o -> m Object
toObject :: forall (m :: * -> *) o. (MonadIO m, IsObject o) => o -> m Object
toObject = IO Object -> m Object
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Object -> m Object) -> (o -> IO Object) -> o -> m Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Object -> Object) -> o -> IO Object
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Object -> Object
Object
instance B.GValue.IsGValue (Maybe Object) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_object_get_type
gvalueSet_ :: Ptr GValue -> Maybe Object -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Object
P.Nothing = Ptr GValue -> Ptr Object -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Object
forall a. Ptr a
FP.nullPtr :: FP.Ptr Object)
gvalueSet_ Ptr GValue
gv (P.Just Object
obj) = Object -> (Ptr Object -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Object
obj (Ptr GValue -> Ptr Object -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Object)
gvalueGet_ Ptr GValue
gv = do
Ptr Object
ptr <- Ptr GValue -> IO (Ptr Object)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Object)
if Ptr Object
ptr Ptr Object -> Ptr Object -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Object
forall a. Ptr a
FP.nullPtr
then Object -> Maybe Object
forall a. a -> Maybe a
P.Just (Object -> Maybe Object) -> IO Object -> IO (Maybe Object)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Object -> Object
Object Ptr Object
ptr
else Maybe Object -> IO (Maybe Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Object
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveObjectMethod (t :: Symbol) (o :: *) :: * where
ResolveObjectMethod "bindProperty" o = ObjectBindPropertyMethodInfo
ResolveObjectMethod "bindPropertyFull" o = ObjectBindPropertyFullMethodInfo
ResolveObjectMethod "forceFloating" o = ObjectForceFloatingMethodInfo
ResolveObjectMethod "freezeNotify" o = ObjectFreezeNotifyMethodInfo
ResolveObjectMethod "getv" o = ObjectGetvMethodInfo
ResolveObjectMethod "isFloating" o = ObjectIsFloatingMethodInfo
ResolveObjectMethod "notify" o = ObjectNotifyMethodInfo
ResolveObjectMethod "notifyByPspec" o = ObjectNotifyByPspecMethodInfo
ResolveObjectMethod "ref" o = ObjectRefMethodInfo
ResolveObjectMethod "refSink" o = ObjectRefSinkMethodInfo
ResolveObjectMethod "runDispose" o = ObjectRunDisposeMethodInfo
ResolveObjectMethod "stealData" o = ObjectStealDataMethodInfo
ResolveObjectMethod "stealQdata" o = ObjectStealQdataMethodInfo
ResolveObjectMethod "thawNotify" o = ObjectThawNotifyMethodInfo
ResolveObjectMethod "unref" o = ObjectUnrefMethodInfo
ResolveObjectMethod "watchClosure" o = ObjectWatchClosureMethodInfo
ResolveObjectMethod "getData" o = ObjectGetDataMethodInfo
ResolveObjectMethod "getProperty" o = ObjectGetPropertyMethodInfo
ResolveObjectMethod "getQdata" o = ObjectGetQdataMethodInfo
ResolveObjectMethod "setData" o = ObjectSetDataMethodInfo
ResolveObjectMethod "setDataFull" o = ObjectSetDataFullMethodInfo
ResolveObjectMethod "setProperty" o = ObjectSetPropertyMethodInfo
ResolveObjectMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveObjectMethod t Object, O.OverloadedMethod info Object p) => OL.IsLabel t (Object -> 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 ~ ResolveObjectMethod t Object, O.OverloadedMethod info Object p, R.HasField t Object p) => R.HasField t Object p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveObjectMethod t Object, O.OverloadedMethodInfo info Object) => OL.IsLabel t (O.MethodProxy info Object) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
type ObjectNotifyCallback =
GParamSpec
-> IO ()
type C_ObjectNotifyCallback =
Ptr Object ->
Ptr GParamSpec ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_ObjectNotifyCallback :: C_ObjectNotifyCallback -> IO (FunPtr C_ObjectNotifyCallback)
wrap_ObjectNotifyCallback ::
GObject a => (a -> ObjectNotifyCallback) ->
C_ObjectNotifyCallback
wrap_ObjectNotifyCallback :: forall a.
GObject a =>
(a -> ObjectNotifyCallback) -> C_ObjectNotifyCallback
wrap_ObjectNotifyCallback a -> ObjectNotifyCallback
gi'cb Ptr Object
gi'selfPtr Ptr GParamSpec
pspec Ptr ()
_ = do
GParamSpec
pspec' <- Ptr GParamSpec -> IO GParamSpec
B.GParamSpec.newGParamSpecFromPtr Ptr GParamSpec
pspec
Ptr Object -> (Object -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr Object
gi'selfPtr ((Object -> IO ()) -> IO ()) -> (Object -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Object
gi'self -> a -> ObjectNotifyCallback
gi'cb (Object -> a
Coerce.coerce Object
gi'self) GParamSpec
pspec'
onObjectNotify :: (IsObject a, MonadIO m) => a -> P.Maybe T.Text -> ((?self :: a) => ObjectNotifyCallback) -> m SignalHandlerId
onObjectNotify :: forall a (m :: * -> *).
(IsObject a, MonadIO m) =>
a
-> Maybe Text
-> ((?self::a) => ObjectNotifyCallback)
-> m SignalHandlerId
onObjectNotify a
obj Maybe Text
detail (?self::a) => ObjectNotifyCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> ObjectNotifyCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => ObjectNotifyCallback
ObjectNotifyCallback
cb
let wrapped' :: C_ObjectNotifyCallback
wrapped' = (a -> ObjectNotifyCallback) -> C_ObjectNotifyCallback
forall a.
GObject a =>
(a -> ObjectNotifyCallback) -> C_ObjectNotifyCallback
wrap_ObjectNotifyCallback a -> ObjectNotifyCallback
wrapped
FunPtr C_ObjectNotifyCallback
wrapped'' <- C_ObjectNotifyCallback -> IO (FunPtr C_ObjectNotifyCallback)
mk_ObjectNotifyCallback C_ObjectNotifyCallback
wrapped'
a
-> Text
-> FunPtr C_ObjectNotifyCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"notify" FunPtr C_ObjectNotifyCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
detail
afterObjectNotify :: (IsObject a, MonadIO m) => a -> P.Maybe T.Text -> ((?self :: a) => ObjectNotifyCallback) -> m SignalHandlerId
afterObjectNotify :: forall a (m :: * -> *).
(IsObject a, MonadIO m) =>
a
-> Maybe Text
-> ((?self::a) => ObjectNotifyCallback)
-> m SignalHandlerId
afterObjectNotify a
obj Maybe Text
detail (?self::a) => ObjectNotifyCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> ObjectNotifyCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => ObjectNotifyCallback
ObjectNotifyCallback
cb
let wrapped' :: C_ObjectNotifyCallback
wrapped' = (a -> ObjectNotifyCallback) -> C_ObjectNotifyCallback
forall a.
GObject a =>
(a -> ObjectNotifyCallback) -> C_ObjectNotifyCallback
wrap_ObjectNotifyCallback a -> ObjectNotifyCallback
wrapped
FunPtr C_ObjectNotifyCallback
wrapped'' <- C_ObjectNotifyCallback -> IO (FunPtr C_ObjectNotifyCallback)
mk_ObjectNotifyCallback C_ObjectNotifyCallback
wrapped'
a
-> Text
-> FunPtr C_ObjectNotifyCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"notify" FunPtr C_ObjectNotifyCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
detail
#if defined(ENABLE_OVERLOADING)
data ObjectNotifySignalInfo
instance SignalInfo ObjectNotifySignalInfo where
type HaskellCallbackType ObjectNotifySignalInfo = ObjectNotifyCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_ObjectNotifyCallback cb
cb'' <- mk_ObjectNotifyCallback cb'
connectSignalFunPtr obj "notify" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object::notify"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#g:signal:notify"})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Object
type instance O.AttributeList Object = ObjectAttributeList
type ObjectAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Object = ObjectSignalList
type ObjectSignalList = ('[ '("notify", ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "g_object_newv" g_object_newv ::
CGType ->
Word32 ->
Ptr GObject.Parameter.Parameter ->
IO (Ptr Object)
{-# DEPRECATED objectNewv ["(Since version 2.54)","Use @/g_object_new_with_properties()/@ instead.","deprecated. See t'GI.GObject.Structs.Parameter.Parameter' for more information."] #-}
objectNewv ::
(B.CallStack.HasCallStack, MonadIO m) =>
GType
-> [GObject.Parameter.Parameter]
-> m Object
objectNewv :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
GType -> [Parameter] -> m Object
objectNewv GType
objectType [Parameter]
parameters = IO Object -> m Object
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Object -> m Object) -> IO Object -> m Object
forall a b. (a -> b) -> a -> b
$ do
let nParameters :: Word32
nParameters = Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [Parameter] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Parameter]
parameters
let objectType' :: CGType
objectType' = GType -> CGType
gtypeToCGType GType
objectType
[Ptr Parameter]
parameters' <- (Parameter -> IO (Ptr Parameter))
-> [Parameter] -> IO [Ptr Parameter]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Parameter -> IO (Ptr Parameter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [Parameter]
parameters
Ptr Parameter
parameters'' <- Int -> [Ptr Parameter] -> IO (Ptr Parameter)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray Int
32 [Ptr Parameter]
parameters'
Ptr Object
result <- CGType -> Word32 -> Ptr Parameter -> IO (Ptr Object)
g_object_newv CGType
objectType' Word32
nParameters Ptr Parameter
parameters''
Text -> Ptr Object -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"objectNewv" Ptr Object
result
Object
result' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Object -> Object
Object) Ptr Object
result
(Parameter -> IO ()) -> [Parameter] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Parameter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [Parameter]
parameters
Ptr Parameter -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Parameter
parameters''
Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_object_bind_property" g_object_bind_property ::
Ptr Object ->
CString ->
Ptr Object ->
CString ->
CUInt ->
IO (Ptr GObject.Binding.Binding)
objectBindProperty ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a, IsObject b) =>
a
-> T.Text
-> b
-> T.Text
-> [GObject.Flags.BindingFlags]
-> m GObject.Binding.Binding
objectBindProperty :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsObject a, IsObject b) =>
a -> Text -> b -> Text -> [BindingFlags] -> m Binding
objectBindProperty a
source Text
sourceProperty b
target Text
targetProperty [BindingFlags]
flags = IO Binding -> m Binding
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Binding -> m Binding) -> IO Binding -> m Binding
forall a b. (a -> b) -> a -> b
$ do
Ptr Object
source' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
source
CString
sourceProperty' <- Text -> IO CString
textToCString Text
sourceProperty
Ptr Object
target' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
target
CString
targetProperty' <- Text -> IO CString
textToCString Text
targetProperty
let flags' :: CUInt
flags' = [BindingFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [BindingFlags]
flags
Ptr Binding
result <- Ptr Object
-> CString -> Ptr Object -> CString -> CUInt -> IO (Ptr Binding)
g_object_bind_property Ptr Object
source' CString
sourceProperty' Ptr Object
target' CString
targetProperty' CUInt
flags'
Text -> Ptr Binding -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"objectBindProperty" Ptr Binding
result
Binding
result' <- ((ManagedPtr Binding -> Binding) -> Ptr Binding -> IO Binding
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Binding -> Binding
GObject.Binding.Binding) Ptr Binding
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
source
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
target
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
sourceProperty'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
targetProperty'
Binding -> IO Binding
forall (m :: * -> *) a. Monad m => a -> m a
return Binding
result'
#if defined(ENABLE_OVERLOADING)
data ObjectBindPropertyMethodInfo
instance (signature ~ (T.Text -> b -> T.Text -> [GObject.Flags.BindingFlags] -> m GObject.Binding.Binding), MonadIO m, IsObject a, IsObject b) => O.OverloadedMethod ObjectBindPropertyMethodInfo a signature where
overloadedMethod = objectBindProperty
instance O.OverloadedMethodInfo ObjectBindPropertyMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectBindProperty",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectBindProperty"
})
#endif
foreign import ccall "g_object_bind_property_with_closures" g_object_bind_property_with_closures ::
Ptr Object ->
CString ->
Ptr Object ->
CString ->
CUInt ->
Ptr (GClosure ()) ->
Ptr (GClosure ()) ->
IO (Ptr GObject.Binding.Binding)
objectBindPropertyFull ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a, IsObject b) =>
a
-> T.Text
-> b
-> T.Text
-> [GObject.Flags.BindingFlags]
-> GClosure c
-> GClosure d
-> m GObject.Binding.Binding
objectBindPropertyFull :: forall (m :: * -> *) a b c d.
(HasCallStack, MonadIO m, IsObject a, IsObject b) =>
a
-> Text
-> b
-> Text
-> [BindingFlags]
-> GClosure c
-> GClosure d
-> m Binding
objectBindPropertyFull a
source Text
sourceProperty b
target Text
targetProperty [BindingFlags]
flags GClosure c
transformTo GClosure d
transformFrom = IO Binding -> m Binding
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Binding -> m Binding) -> IO Binding -> m Binding
forall a b. (a -> b) -> a -> b
$ do
Ptr Object
source' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
source
CString
sourceProperty' <- Text -> IO CString
textToCString Text
sourceProperty
Ptr Object
target' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
target
CString
targetProperty' <- Text -> IO CString
textToCString Text
targetProperty
let flags' :: CUInt
flags' = [BindingFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [BindingFlags]
flags
Ptr (GClosure ())
transformTo' <- GClosure c -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure c
transformTo
Ptr (GClosure ())
transformFrom' <- GClosure d -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure d
transformFrom
Ptr Binding
result <- Ptr Object
-> CString
-> Ptr Object
-> CString
-> CUInt
-> Ptr (GClosure ())
-> Ptr (GClosure ())
-> IO (Ptr Binding)
g_object_bind_property_with_closures Ptr Object
source' CString
sourceProperty' Ptr Object
target' CString
targetProperty' CUInt
flags' Ptr (GClosure ())
transformTo' Ptr (GClosure ())
transformFrom'
Text -> Ptr Binding -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"objectBindPropertyFull" Ptr Binding
result
Binding
result' <- ((ManagedPtr Binding -> Binding) -> Ptr Binding -> IO Binding
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Binding -> Binding
GObject.Binding.Binding) Ptr Binding
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
source
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
target
GClosure c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure c
transformTo
GClosure d -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure d
transformFrom
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
sourceProperty'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
targetProperty'
Binding -> IO Binding
forall (m :: * -> *) a. Monad m => a -> m a
return Binding
result'
#if defined(ENABLE_OVERLOADING)
data ObjectBindPropertyFullMethodInfo
instance (signature ~ (T.Text -> b -> T.Text -> [GObject.Flags.BindingFlags] -> GClosure c -> GClosure d -> m GObject.Binding.Binding), MonadIO m, IsObject a, IsObject b) => O.OverloadedMethod ObjectBindPropertyFullMethodInfo a signature where
overloadedMethod = objectBindPropertyFull
instance O.OverloadedMethodInfo ObjectBindPropertyFullMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectBindPropertyFull",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectBindPropertyFull"
})
#endif
foreign import ccall "g_object_force_floating" g_object_force_floating ::
Ptr Object ->
IO ()
objectForceFloating ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> m ()
objectForceFloating :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> m ()
objectForceFloating a
object = 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
Ptr Object -> IO ()
g_object_force_floating Ptr Object
object'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ObjectForceFloatingMethodInfo
instance (signature ~ (m ()), MonadIO m, IsObject a) => O.OverloadedMethod ObjectForceFloatingMethodInfo a signature where
overloadedMethod = objectForceFloating
instance O.OverloadedMethodInfo ObjectForceFloatingMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectForceFloating",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectForceFloating"
})
#endif
foreign import ccall "g_object_freeze_notify" g_object_freeze_notify ::
Ptr Object ->
IO ()
objectFreezeNotify ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> m ()
objectFreezeNotify :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> m ()
objectFreezeNotify a
object = 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
Ptr Object -> IO ()
g_object_freeze_notify Ptr Object
object'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ObjectFreezeNotifyMethodInfo
instance (signature ~ (m ()), MonadIO m, IsObject a) => O.OverloadedMethod ObjectFreezeNotifyMethodInfo a signature where
overloadedMethod = objectFreezeNotify
instance O.OverloadedMethodInfo ObjectFreezeNotifyMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectFreezeNotify",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectFreezeNotify"
})
#endif
foreign import ccall "g_object_get_data" g_object_get_data ::
Ptr Object ->
CString ->
IO (Ptr ())
objectGetData ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> T.Text
-> m (Ptr ())
objectGetData :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> Text -> m (Ptr ())
objectGetData a
object Text
key = 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
CString
key' <- Text -> IO CString
textToCString Text
key
Ptr ()
result <- Ptr Object -> CString -> IO (Ptr ())
g_object_get_data Ptr Object
object' CString
key'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result
#if defined(ENABLE_OVERLOADING)
data ObjectGetDataMethodInfo
instance (signature ~ (T.Text -> m (Ptr ())), MonadIO m, IsObject a) => O.OverloadedMethod ObjectGetDataMethodInfo a signature where
overloadedMethod = objectGetData
instance O.OverloadedMethodInfo ObjectGetDataMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectGetData",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectGetData"
})
#endif
foreign import ccall "g_object_get_property" g_object_get_property ::
Ptr Object ->
CString ->
Ptr GValue ->
IO ()
objectGetProperty ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> T.Text
-> GValue
-> m ()
objectGetProperty :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> Text -> GValue -> m ()
objectGetProperty a
object Text
propertyName GValue
value = 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
Ptr GValue
value' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
value
Ptr Object -> CString -> Ptr GValue -> IO ()
g_object_get_property Ptr Object
object' CString
propertyName' Ptr GValue
value'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
value
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ObjectGetPropertyMethodInfo
instance (signature ~ (T.Text -> GValue -> m ()), MonadIO m, IsObject a) => O.OverloadedMethod ObjectGetPropertyMethodInfo a signature where
overloadedMethod = objectGetProperty
instance O.OverloadedMethodInfo ObjectGetPropertyMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectGetProperty",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectGetProperty"
})
#endif
foreign import ccall "g_object_get_qdata" g_object_get_qdata ::
Ptr Object ->
Word32 ->
IO (Ptr ())
objectGetQdata ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> Word32
-> m (Ptr ())
objectGetQdata :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> Word32 -> m (Ptr ())
objectGetQdata a
object 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
Ptr ()
result <- Ptr Object -> Word32 -> IO (Ptr ())
g_object_get_qdata Ptr Object
object' Word32
quark
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result
#if defined(ENABLE_OVERLOADING)
data ObjectGetQdataMethodInfo
instance (signature ~ (Word32 -> m (Ptr ())), MonadIO m, IsObject a) => O.OverloadedMethod ObjectGetQdataMethodInfo a signature where
overloadedMethod = objectGetQdata
instance O.OverloadedMethodInfo ObjectGetQdataMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectGetQdata",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectGetQdata"
})
#endif
foreign import ccall "g_object_getv" g_object_getv ::
Ptr Object ->
Word32 ->
Ptr CString ->
Ptr B.GValue.GValue ->
IO ()
objectGetv ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> [T.Text]
-> [GValue]
-> m ()
objectGetv :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> [Text] -> [GValue] -> m ()
objectGetv a
object [Text]
names [GValue]
values = 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 nProperties :: Word32
nProperties = Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [GValue] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [GValue]
values
let names_expected_length_ :: Word32
names_expected_length_ = Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ [Text] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Text]
names
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Word32
names_expected_length_ Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
/= Word32
nProperties) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
[Char] -> IO ()
forall a. HasCallStack => [Char] -> a
error [Char]
"GObject.objectGetv : length of 'names' does not agree with that of 'values'."
Ptr Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
Ptr CString
names' <- [Text] -> IO (Ptr CString)
packUTF8CArray [Text]
names
Ptr GValue
values' <- [GValue] -> IO (Ptr GValue)
B.GValue.packGValueArray [GValue]
values
Ptr Object -> Word32 -> Ptr CString -> Ptr GValue -> IO ()
g_object_getv Ptr Object
object' Word32
nProperties Ptr CString
names' Ptr GValue
values'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
(GValue -> IO ()) -> [GValue] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [GValue]
values
(Word32 -> (CString -> IO ()) -> Ptr CString -> IO ()
forall a b c.
(Storable a, Integral b) =>
b -> (a -> IO c) -> Ptr a -> IO ()
mapCArrayWithLength Word32
nProperties) CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
names'
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
names'
Ptr GValue -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr GValue
values'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ObjectGetvMethodInfo
instance (signature ~ ([T.Text] -> [GValue] -> m ()), MonadIO m, IsObject a) => O.OverloadedMethod ObjectGetvMethodInfo a signature where
overloadedMethod = objectGetv
instance O.OverloadedMethodInfo ObjectGetvMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectGetv",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectGetv"
})
#endif
foreign import ccall "g_object_is_floating" g_object_is_floating ::
Ptr Object ->
IO CInt
objectIsFloating ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> m Bool
objectIsFloating :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> m Bool
objectIsFloating a
object = 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
CInt
result <- Ptr Object -> IO CInt
g_object_is_floating Ptr Object
object'
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
object
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data ObjectIsFloatingMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsObject a) => O.OverloadedMethod ObjectIsFloatingMethodInfo a signature where
overloadedMethod = objectIsFloating
instance O.OverloadedMethodInfo ObjectIsFloatingMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectIsFloating",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectIsFloating"
})
#endif
foreign import ccall "g_object_notify" g_object_notify ::
Ptr Object ->
CString ->
IO ()
objectNotify ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> T.Text
-> m ()
objectNotify :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> Text -> m ()
objectNotify a
object Text
propertyName = 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
Ptr Object -> CString -> IO ()
g_object_notify Ptr Object
object' CString
propertyName'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ObjectNotifyMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsObject a) => O.OverloadedMethod ObjectNotifyMethodInfo a signature where
overloadedMethod = objectNotify
instance O.OverloadedMethodInfo ObjectNotifyMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectNotify",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectNotify"
})
#endif
foreign import ccall "g_object_notify_by_pspec" g_object_notify_by_pspec ::
Ptr Object ->
Ptr GParamSpec ->
IO ()
objectNotifyByPspec ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> GParamSpec
-> m ()
objectNotifyByPspec :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> GParamSpec -> m ()
objectNotifyByPspec a
object 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
Ptr Object -> Ptr GParamSpec -> IO ()
g_object_notify_by_pspec Ptr Object
object' Ptr GParamSpec
pspec'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
ObjectNotifyCallback
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ObjectNotifyByPspecMethodInfo
instance (signature ~ (GParamSpec -> m ()), MonadIO m, IsObject a) => O.OverloadedMethod ObjectNotifyByPspecMethodInfo a signature where
overloadedMethod = objectNotifyByPspec
instance O.OverloadedMethodInfo ObjectNotifyByPspecMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectNotifyByPspec",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectNotifyByPspec"
})
#endif
foreign import ccall "g_object_ref" g_object_ref ::
Ptr Object ->
IO (Ptr Object)
objectRef ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> m Object
objectRef :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> m Object
objectRef a
object = IO Object -> m Object
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Object -> m Object) -> IO Object -> m Object
forall a b. (a -> b) -> a -> b
$ do
Ptr Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
Ptr Object
result <- Ptr Object -> IO (Ptr Object)
g_object_ref Ptr Object
object'
Text -> Ptr Object -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"objectRef" Ptr Object
result
Object
result' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
Object) Ptr Object
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result'
#if defined(ENABLE_OVERLOADING)
data ObjectRefMethodInfo
instance (signature ~ (m Object), MonadIO m, IsObject a) => O.OverloadedMethod ObjectRefMethodInfo a signature where
overloadedMethod = objectRef
instance O.OverloadedMethodInfo ObjectRefMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectRef",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectRef"
})
#endif
foreign import ccall "g_object_ref_sink" g_object_ref_sink ::
Ptr Object ->
IO (Ptr Object)
objectRefSink ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> m Object
objectRefSink :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> m Object
objectRefSink a
object = IO Object -> m Object
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Object -> m Object) -> IO Object -> m Object
forall a b. (a -> b) -> a -> b
$ do
Ptr Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
Ptr Object
result <- Ptr Object -> IO (Ptr Object)
g_object_ref_sink Ptr Object
object'
Text -> Ptr Object -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"objectRefSink" Ptr Object
result
Object
result' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
Object) Ptr Object
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result'
#if defined(ENABLE_OVERLOADING)
data ObjectRefSinkMethodInfo
instance (signature ~ (m Object), MonadIO m, IsObject a) => O.OverloadedMethod ObjectRefSinkMethodInfo a signature where
overloadedMethod = objectRefSink
instance O.OverloadedMethodInfo ObjectRefSinkMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectRefSink",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectRefSink"
})
#endif
foreign import ccall "g_object_run_dispose" g_object_run_dispose ::
Ptr Object ->
IO ()
objectRunDispose ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> m ()
objectRunDispose :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> m ()
objectRunDispose a
object = 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
Ptr Object -> IO ()
g_object_run_dispose Ptr Object
object'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ObjectRunDisposeMethodInfo
instance (signature ~ (m ()), MonadIO m, IsObject a) => O.OverloadedMethod ObjectRunDisposeMethodInfo a signature where
overloadedMethod = objectRunDispose
instance O.OverloadedMethodInfo ObjectRunDisposeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectRunDispose",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectRunDispose"
})
#endif
foreign import ccall "g_object_set_data" g_object_set_data ::
Ptr Object ->
CString ->
Ptr () ->
IO ()
objectSetData ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> T.Text
-> Ptr ()
-> m ()
objectSetData :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> Text -> Ptr () -> m ()
objectSetData a
object Text
key 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
CString
key' <- Text -> IO CString
textToCString Text
key
Ptr Object -> CString -> Ptr () -> IO ()
g_object_set_data Ptr Object
object' CString
key' Ptr ()
data_
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ObjectSetDataMethodInfo
instance (signature ~ (T.Text -> Ptr () -> m ()), MonadIO m, IsObject a) => O.OverloadedMethod ObjectSetDataMethodInfo a signature where
overloadedMethod = objectSetData
instance O.OverloadedMethodInfo ObjectSetDataMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectSetData",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectSetData"
})
#endif
foreign import ccall "g_object_set_data_full" g_object_set_data_full ::
Ptr Object ->
CString ->
Ptr () ->
FunPtr GLib.Callbacks.C_DestroyNotify ->
IO ()
objectSetDataFull ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> T.Text
-> Ptr ()
-> Maybe (GLib.Callbacks.DestroyNotify)
-> m ()
objectSetDataFull :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> Text -> Ptr () -> Maybe (Ptr () -> IO ()) -> m ()
objectSetDataFull a
object Text
key Ptr ()
data_ Maybe (Ptr () -> IO ())
destroy = 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
CString
key' <- Text -> IO CString
textToCString Text
key
FunPtr (Ptr () -> IO ())
maybeDestroy <- case Maybe (Ptr () -> IO ())
destroy of
Maybe (Ptr () -> IO ())
Nothing -> FunPtr (Ptr () -> IO ()) -> IO (FunPtr (Ptr () -> IO ()))
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr (Ptr () -> IO ())
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
Just Ptr () -> IO ()
jDestroy -> do
Ptr (FunPtr (Ptr () -> IO ()))
ptrdestroy <- IO (Ptr (FunPtr (Ptr () -> IO ())))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr GLib.Callbacks.C_DestroyNotify))
FunPtr (Ptr () -> IO ())
jDestroy' <- (Ptr () -> IO ()) -> IO (FunPtr (Ptr () -> IO ()))
GLib.Callbacks.mk_DestroyNotify (Maybe (Ptr (FunPtr (Ptr () -> IO ())))
-> (Ptr () -> IO ()) -> Ptr () -> IO ()
GLib.Callbacks.wrap_DestroyNotify (Ptr (FunPtr (Ptr () -> IO ()))
-> Maybe (Ptr (FunPtr (Ptr () -> IO ())))
forall a. a -> Maybe a
Just Ptr (FunPtr (Ptr () -> IO ()))
ptrdestroy) Ptr () -> IO ()
jDestroy)
Ptr (FunPtr (Ptr () -> IO ())) -> FunPtr (Ptr () -> IO ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr (Ptr () -> IO ()))
ptrdestroy FunPtr (Ptr () -> IO ())
jDestroy'
FunPtr (Ptr () -> IO ()) -> IO (FunPtr (Ptr () -> IO ()))
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr (Ptr () -> IO ())
jDestroy'
Ptr Object
-> CString -> Ptr () -> FunPtr (Ptr () -> IO ()) -> IO ()
g_object_set_data_full Ptr Object
object' CString
key' Ptr ()
data_ FunPtr (Ptr () -> IO ())
maybeDestroy
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ObjectSetDataFullMethodInfo
instance (signature ~ (T.Text -> Ptr () -> Maybe (GLib.Callbacks.DestroyNotify) -> m ()), MonadIO m, IsObject a) => O.OverloadedMethod ObjectSetDataFullMethodInfo a signature where
overloadedMethod = objectSetDataFull
instance O.OverloadedMethodInfo ObjectSetDataFullMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectSetDataFull",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectSetDataFull"
})
#endif
foreign import ccall "g_object_set_property" g_object_set_property ::
Ptr Object ->
CString ->
Ptr GValue ->
IO ()
objectSetProperty ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> T.Text
-> GValue
-> m ()
objectSetProperty :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> Text -> GValue -> m ()
objectSetProperty a
object Text
propertyName GValue
value = 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
Ptr GValue
value' <- GValue -> IO (Ptr GValue)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GValue
value
Ptr Object -> CString -> Ptr GValue -> IO ()
g_object_set_property Ptr Object
object' CString
propertyName' Ptr GValue
value'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
GValue -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GValue
value
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ObjectSetPropertyMethodInfo
instance (signature ~ (T.Text -> GValue -> m ()), MonadIO m, IsObject a) => O.OverloadedMethod ObjectSetPropertyMethodInfo a signature where
overloadedMethod = objectSetProperty
instance O.OverloadedMethodInfo ObjectSetPropertyMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectSetProperty",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectSetProperty"
})
#endif
foreign import ccall "g_object_steal_data" g_object_steal_data ::
Ptr Object ->
CString ->
IO (Ptr ())
objectStealData ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> T.Text
-> m (Ptr ())
objectStealData :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> Text -> m (Ptr ())
objectStealData a
object Text
key = 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
CString
key' <- Text -> IO CString
textToCString Text
key
Ptr ()
result <- Ptr Object -> CString -> IO (Ptr ())
g_object_steal_data Ptr Object
object' CString
key'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result
#if defined(ENABLE_OVERLOADING)
data ObjectStealDataMethodInfo
instance (signature ~ (T.Text -> m (Ptr ())), MonadIO m, IsObject a) => O.OverloadedMethod ObjectStealDataMethodInfo a signature where
overloadedMethod = objectStealData
instance O.OverloadedMethodInfo ObjectStealDataMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectStealData",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectStealData"
})
#endif
foreign import ccall "g_object_steal_qdata" g_object_steal_qdata ::
Ptr Object ->
Word32 ->
IO (Ptr ())
objectStealQdata ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> Word32
-> m (Ptr ())
objectStealQdata :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> Word32 -> m (Ptr ())
objectStealQdata a
object 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
Ptr ()
result <- Ptr Object -> Word32 -> IO (Ptr ())
g_object_steal_qdata Ptr Object
object' Word32
quark
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
Ptr () -> IO (Ptr ())
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr ()
result
#if defined(ENABLE_OVERLOADING)
data ObjectStealQdataMethodInfo
instance (signature ~ (Word32 -> m (Ptr ())), MonadIO m, IsObject a) => O.OverloadedMethod ObjectStealQdataMethodInfo a signature where
overloadedMethod = objectStealQdata
instance O.OverloadedMethodInfo ObjectStealQdataMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectStealQdata",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectStealQdata"
})
#endif
foreign import ccall "g_object_thaw_notify" g_object_thaw_notify ::
Ptr Object ->
IO ()
objectThawNotify ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> m ()
objectThawNotify :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> m ()
objectThawNotify a
object = 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
Ptr Object -> IO ()
g_object_thaw_notify Ptr Object
object'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ObjectThawNotifyMethodInfo
instance (signature ~ (m ()), MonadIO m, IsObject a) => O.OverloadedMethod ObjectThawNotifyMethodInfo a signature where
overloadedMethod = objectThawNotify
instance O.OverloadedMethodInfo ObjectThawNotifyMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectThawNotify",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectThawNotify"
})
#endif
foreign import ccall "g_object_unref" g_object_unref ::
Ptr Object ->
IO ()
objectUnref ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> m ()
objectUnref :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsObject a) =>
a -> m ()
objectUnref a
object = 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
Ptr Object -> IO ()
g_object_unref Ptr Object
object'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ObjectUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m, IsObject a) => O.OverloadedMethod ObjectUnrefMethodInfo a signature where
overloadedMethod = objectUnref
instance O.OverloadedMethodInfo ObjectUnrefMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectUnref",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectUnref"
})
#endif
foreign import ccall "g_object_watch_closure" g_object_watch_closure ::
Ptr Object ->
Ptr (GClosure ()) ->
IO ()
objectWatchClosure ::
(B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
a
-> GClosure b
-> m ()
objectWatchClosure :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsObject a) =>
a -> GClosure b -> m ()
objectWatchClosure a
object GClosure b
closure = 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
Ptr (GClosure ())
closure' <- GClosure b -> IO (Ptr (GClosure ()))
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr GClosure b
closure
Ptr Object -> Ptr (GClosure ()) -> IO ()
g_object_watch_closure Ptr Object
object' Ptr (GClosure ())
closure'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
GClosure b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GClosure b
closure
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data ObjectWatchClosureMethodInfo
instance (signature ~ (GClosure b -> m ()), MonadIO m, IsObject a) => O.OverloadedMethod ObjectWatchClosureMethodInfo a signature where
overloadedMethod = objectWatchClosure
instance O.OverloadedMethodInfo ObjectWatchClosureMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.GObject.Objects.Object.objectWatchClosure",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gobject-2.0.27/docs/GI-GObject-Objects-Object.html#v:objectWatchClosure"
})
#endif
foreign import ccall "g_object_compat_control" g_object_compat_control ::
Word64 ->
Ptr () ->
IO Word64
objectCompatControl ::
(B.CallStack.HasCallStack, MonadIO m) =>
Word64
-> Ptr ()
-> m Word64
objectCompatControl :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
CGType -> Ptr () -> m CGType
objectCompatControl CGType
what Ptr ()
data_ = IO CGType -> m CGType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CGType -> m CGType) -> IO CGType -> m CGType
forall a b. (a -> b) -> a -> b
$ do
CGType
result <- CGType -> Ptr () -> IO CGType
g_object_compat_control CGType
what Ptr ()
data_
CGType -> IO CGType
forall (m :: * -> *) a. Monad m => a -> m a
return CGType
result
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_object_interface_find_property" g_object_interface_find_property ::
Ptr GObject.TypeInterface.TypeInterface ->
CString ->
IO (Ptr GParamSpec)
objectInterfaceFindProperty ::
(B.CallStack.HasCallStack, MonadIO m) =>
GObject.TypeInterface.TypeInterface
-> T.Text
-> m GParamSpec
objectInterfaceFindProperty :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
TypeInterface -> Text -> m GParamSpec
objectInterfaceFindProperty TypeInterface
gIface Text
propertyName = 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 TypeInterface
gIface' <- TypeInterface -> IO (Ptr TypeInterface)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TypeInterface
gIface
CString
propertyName' <- Text -> IO CString
textToCString Text
propertyName
Ptr GParamSpec
result <- Ptr TypeInterface -> CString -> IO (Ptr GParamSpec)
g_object_interface_find_property Ptr TypeInterface
gIface' CString
propertyName'
Text -> Ptr GParamSpec -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"objectInterfaceFindProperty" Ptr GParamSpec
result
GParamSpec
result' <- Ptr GParamSpec -> IO GParamSpec
B.GParamSpec.newGParamSpecFromPtr Ptr GParamSpec
result
TypeInterface -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TypeInterface
gIface
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
propertyName'
GParamSpec -> IO GParamSpec
forall (m :: * -> *) a. Monad m => a -> m a
return GParamSpec
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_object_interface_install_property" g_object_interface_install_property ::
Ptr GObject.TypeInterface.TypeInterface ->
Ptr GParamSpec ->
IO ()
objectInterfaceInstallProperty ::
(B.CallStack.HasCallStack, MonadIO m) =>
GObject.TypeInterface.TypeInterface
-> GParamSpec
-> m ()
objectInterfaceInstallProperty :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
TypeInterface -> GParamSpec -> m ()
objectInterfaceInstallProperty TypeInterface
gIface 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 TypeInterface
gIface' <- TypeInterface -> IO (Ptr TypeInterface)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TypeInterface
gIface
Ptr GParamSpec
pspec' <- GParamSpec -> IO (Ptr GParamSpec)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GParamSpec
pspec
Ptr TypeInterface -> Ptr GParamSpec -> IO ()
g_object_interface_install_property Ptr TypeInterface
gIface' Ptr GParamSpec
pspec'
TypeInterface -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr TypeInterface
gIface
ObjectNotifyCallback
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GParamSpec
pspec
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
data ObjectInterfaceListPropertiesMethodInfo
instance (p ~ (), o ~ O.UnsupportedMethodError "interfaceListProperties" Object) => O.OverloadedMethod ObjectInterfaceListPropertiesMethodInfo o p where
overloadedMethod = undefined
instance (o ~ O.UnsupportedMethodError "interfaceListProperties" Object) => O.OverloadedMethodInfo ObjectInterfaceListPropertiesMethodInfo o where
overloadedMethodInfo = undefined
#endif