{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Atk.Objects.Relation
(
Relation(..) ,
IsRelation ,
toRelation ,
#if defined(ENABLE_OVERLOADING)
ResolveRelationMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
RelationAddTargetMethodInfo ,
#endif
relationAddTarget ,
#if defined(ENABLE_OVERLOADING)
RelationGetRelationTypeMethodInfo ,
#endif
relationGetRelationType ,
#if defined(ENABLE_OVERLOADING)
RelationGetTargetMethodInfo ,
#endif
relationGetTarget ,
relationNew ,
#if defined(ENABLE_OVERLOADING)
RelationRemoveTargetMethodInfo ,
#endif
relationRemoveTarget ,
#if defined(ENABLE_OVERLOADING)
RelationRelationTypePropertyInfo ,
#endif
constructRelationRelationType ,
getRelationRelationType ,
#if defined(ENABLE_OVERLOADING)
relationRelationType ,
#endif
setRelationRelationType ,
#if defined(ENABLE_OVERLOADING)
RelationTargetPropertyInfo ,
#endif
clearRelationTarget ,
constructRelationTarget ,
getRelationTarget ,
#if defined(ENABLE_OVERLOADING)
relationTarget ,
#endif
setRelationTarget ,
) 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.Enums as Atk.Enums
import {-# SOURCE #-} qualified GI.Atk.Objects.Object as Atk.Object
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.GObject.Structs.ValueArray as GObject.ValueArray
newtype Relation = Relation (SP.ManagedPtr Relation)
deriving (Relation -> Relation -> Bool
(Relation -> Relation -> Bool)
-> (Relation -> Relation -> Bool) -> Eq Relation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Relation -> Relation -> Bool
$c/= :: Relation -> Relation -> Bool
== :: Relation -> Relation -> Bool
$c== :: Relation -> Relation -> Bool
Eq)
instance SP.ManagedPtrNewtype Relation where
toManagedPtr :: Relation -> ManagedPtr Relation
toManagedPtr (Relation ManagedPtr Relation
p) = ManagedPtr Relation
p
foreign import ccall "atk_relation_get_type"
c_atk_relation_get_type :: IO B.Types.GType
instance B.Types.TypedObject Relation where
glibType :: IO GType
glibType = IO GType
c_atk_relation_get_type
instance B.Types.GObject Relation
instance B.GValue.IsGValue Relation where
toGValue :: Relation -> IO GValue
toGValue Relation
o = do
GType
gtype <- IO GType
c_atk_relation_get_type
Relation -> (Ptr Relation -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Relation
o (GType
-> (GValue -> Ptr Relation -> IO ()) -> Ptr Relation -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Relation -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO Relation
fromGValue GValue
gv = do
Ptr Relation
ptr <- GValue -> IO (Ptr Relation)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Relation)
(ManagedPtr Relation -> Relation) -> Ptr Relation -> IO Relation
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Relation -> Relation
Relation Ptr Relation
ptr
class (SP.GObject o, O.IsDescendantOf Relation o) => IsRelation o
instance (SP.GObject o, O.IsDescendantOf Relation o) => IsRelation o
instance O.HasParentTypes Relation
type instance O.ParentTypes Relation = '[GObject.Object.Object]
toRelation :: (MonadIO m, IsRelation o) => o -> m Relation
toRelation :: o -> m Relation
toRelation = IO Relation -> m Relation
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Relation -> m Relation)
-> (o -> IO Relation) -> o -> m Relation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Relation -> Relation) -> o -> IO Relation
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Relation -> Relation
Relation
#if defined(ENABLE_OVERLOADING)
type family ResolveRelationMethod (t :: Symbol) (o :: *) :: * where
ResolveRelationMethod "addTarget" o = RelationAddTargetMethodInfo
ResolveRelationMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveRelationMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveRelationMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveRelationMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveRelationMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveRelationMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveRelationMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveRelationMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveRelationMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveRelationMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveRelationMethod "removeTarget" o = RelationRemoveTargetMethodInfo
ResolveRelationMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveRelationMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveRelationMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveRelationMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveRelationMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveRelationMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveRelationMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveRelationMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveRelationMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveRelationMethod "getRelationType" o = RelationGetRelationTypeMethodInfo
ResolveRelationMethod "getTarget" o = RelationGetTargetMethodInfo
ResolveRelationMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveRelationMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveRelationMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveRelationMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveRelationMethod t Relation, O.MethodInfo info Relation p) => OL.IsLabel t (Relation -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
getRelationRelationType :: (MonadIO m, IsRelation o) => o -> m Atk.Enums.RelationType
getRelationRelationType :: o -> m RelationType
getRelationRelationType o
obj = IO RelationType -> m RelationType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RelationType -> m RelationType)
-> IO RelationType -> m RelationType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO RelationType
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"relation-type"
setRelationRelationType :: (MonadIO m, IsRelation o) => o -> Atk.Enums.RelationType -> m ()
setRelationRelationType :: o -> RelationType -> m ()
setRelationRelationType o
obj RelationType
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> RelationType -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"relation-type" RelationType
val
constructRelationRelationType :: (IsRelation o, MIO.MonadIO m) => Atk.Enums.RelationType -> m (GValueConstruct o)
constructRelationRelationType :: RelationType -> m (GValueConstruct o)
constructRelationRelationType RelationType
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> RelationType -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"relation-type" RelationType
val
#if defined(ENABLE_OVERLOADING)
data RelationRelationTypePropertyInfo
instance AttrInfo RelationRelationTypePropertyInfo where
type AttrAllowedOps RelationRelationTypePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint RelationRelationTypePropertyInfo = IsRelation
type AttrSetTypeConstraint RelationRelationTypePropertyInfo = (~) Atk.Enums.RelationType
type AttrTransferTypeConstraint RelationRelationTypePropertyInfo = (~) Atk.Enums.RelationType
type AttrTransferType RelationRelationTypePropertyInfo = Atk.Enums.RelationType
type AttrGetType RelationRelationTypePropertyInfo = Atk.Enums.RelationType
type AttrLabel RelationRelationTypePropertyInfo = "relation-type"
type AttrOrigin RelationRelationTypePropertyInfo = Relation
attrGet = getRelationRelationType
attrSet = setRelationRelationType
attrTransfer _ v = do
return v
attrConstruct = constructRelationRelationType
attrClear = undefined
#endif
getRelationTarget :: (MonadIO m, IsRelation o) => o -> m (Maybe GObject.ValueArray.ValueArray)
getRelationTarget :: o -> m (Maybe ValueArray)
getRelationTarget o
obj = IO (Maybe ValueArray) -> m (Maybe ValueArray)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ValueArray) -> m (Maybe ValueArray))
-> IO (Maybe ValueArray) -> m (Maybe ValueArray)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr ValueArray -> ValueArray)
-> IO (Maybe ValueArray)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"target" ManagedPtr ValueArray -> ValueArray
GObject.ValueArray.ValueArray
setRelationTarget :: (MonadIO m, IsRelation o) => o -> GObject.ValueArray.ValueArray -> m ()
setRelationTarget :: o -> ValueArray -> m ()
setRelationTarget o
obj ValueArray
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe ValueArray -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"target" (ValueArray -> Maybe ValueArray
forall a. a -> Maybe a
Just ValueArray
val)
constructRelationTarget :: (IsRelation o, MIO.MonadIO m) => GObject.ValueArray.ValueArray -> m (GValueConstruct o)
constructRelationTarget :: ValueArray -> m (GValueConstruct o)
constructRelationTarget ValueArray
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe ValueArray -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"target" (ValueArray -> Maybe ValueArray
forall a. a -> Maybe a
P.Just ValueArray
val)
clearRelationTarget :: (MonadIO m, IsRelation o) => o -> m ()
clearRelationTarget :: o -> m ()
clearRelationTarget o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe ValueArray -> IO ()
forall a b.
(GObject a, GBoxed b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyBoxed o
obj String
"target" (Maybe ValueArray
forall a. Maybe a
Nothing :: Maybe GObject.ValueArray.ValueArray)
#if defined(ENABLE_OVERLOADING)
data RelationTargetPropertyInfo
instance AttrInfo RelationTargetPropertyInfo where
type AttrAllowedOps RelationTargetPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint RelationTargetPropertyInfo = IsRelation
type AttrSetTypeConstraint RelationTargetPropertyInfo = (~) GObject.ValueArray.ValueArray
type AttrTransferTypeConstraint RelationTargetPropertyInfo = (~) GObject.ValueArray.ValueArray
type AttrTransferType RelationTargetPropertyInfo = GObject.ValueArray.ValueArray
type AttrGetType RelationTargetPropertyInfo = (Maybe GObject.ValueArray.ValueArray)
type AttrLabel RelationTargetPropertyInfo = "target"
type AttrOrigin RelationTargetPropertyInfo = Relation
attrGet = getRelationTarget
attrSet = setRelationTarget
attrTransfer _ v = do
return v
attrConstruct = constructRelationTarget
attrClear = clearRelationTarget
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Relation
type instance O.AttributeList Relation = RelationAttributeList
type RelationAttributeList = ('[ '("relationType", RelationRelationTypePropertyInfo), '("target", RelationTargetPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
relationRelationType :: AttrLabelProxy "relationType"
relationRelationType = AttrLabelProxy
relationTarget :: AttrLabelProxy "target"
relationTarget = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Relation = RelationSignalList
type RelationSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "atk_relation_new" atk_relation_new ::
Ptr (Ptr Atk.Object.Object) ->
Int32 ->
CUInt ->
IO (Ptr Relation)
relationNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
[Atk.Object.Object]
-> Atk.Enums.RelationType
-> m Relation
relationNew :: [Object] -> RelationType -> m Relation
relationNew [Object]
targets RelationType
relationship = IO Relation -> m Relation
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Relation -> m Relation) -> IO Relation -> m Relation
forall a b. (a -> b) -> a -> b
$ do
let nTargets :: Int32
nTargets = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [Object] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Object]
targets
[Ptr Object]
targets' <- (Object -> IO (Ptr Object)) -> [Object] -> IO [Ptr Object]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Object -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr [Object]
targets
Ptr (Ptr Object)
targets'' <- [Ptr Object] -> IO (Ptr (Ptr Object))
forall a. [Ptr a] -> IO (Ptr (Ptr a))
packPtrArray [Ptr Object]
targets'
let relationship' :: CUInt
relationship' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (RelationType -> Int) -> RelationType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RelationType -> Int
forall a. Enum a => a -> Int
fromEnum) RelationType
relationship
Ptr Relation
result <- Ptr (Ptr Object) -> Int32 -> CUInt -> IO (Ptr Relation)
atk_relation_new Ptr (Ptr Object)
targets'' Int32
nTargets CUInt
relationship'
Text -> Ptr Relation -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"relationNew" Ptr Relation
result
Relation
result' <- ((ManagedPtr Relation -> Relation) -> Ptr Relation -> IO Relation
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Relation -> Relation
Relation) Ptr Relation
result
(Object -> IO ()) -> [Object] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Object -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [Object]
targets
Ptr (Ptr Object) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Object)
targets''
Relation -> IO Relation
forall (m :: * -> *) a. Monad m => a -> m a
return Relation
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "atk_relation_add_target" atk_relation_add_target ::
Ptr Relation ->
Ptr Atk.Object.Object ->
IO ()
relationAddTarget ::
(B.CallStack.HasCallStack, MonadIO m, IsRelation a, Atk.Object.IsObject b) =>
a
-> b
-> m ()
relationAddTarget :: a -> b -> m ()
relationAddTarget a
relation b
target = 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 Relation
relation' <- a -> IO (Ptr Relation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
relation
Ptr Object
target' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
target
Ptr Relation -> Ptr Object -> IO ()
atk_relation_add_target Ptr Relation
relation' Ptr Object
target'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
relation
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
target
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data RelationAddTargetMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsRelation a, Atk.Object.IsObject b) => O.MethodInfo RelationAddTargetMethodInfo a signature where
overloadedMethod = relationAddTarget
#endif
foreign import ccall "atk_relation_get_relation_type" atk_relation_get_relation_type ::
Ptr Relation ->
IO CUInt
relationGetRelationType ::
(B.CallStack.HasCallStack, MonadIO m, IsRelation a) =>
a
-> m Atk.Enums.RelationType
relationGetRelationType :: a -> m RelationType
relationGetRelationType a
relation = IO RelationType -> m RelationType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RelationType -> m RelationType)
-> IO RelationType -> m RelationType
forall a b. (a -> b) -> a -> b
$ do
Ptr Relation
relation' <- a -> IO (Ptr Relation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
relation
CUInt
result <- Ptr Relation -> IO CUInt
atk_relation_get_relation_type Ptr Relation
relation'
let result' :: RelationType
result' = (Int -> RelationType
forall a. Enum a => Int -> a
toEnum (Int -> RelationType) -> (CUInt -> Int) -> CUInt -> RelationType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
relation
RelationType -> IO RelationType
forall (m :: * -> *) a. Monad m => a -> m a
return RelationType
result'
#if defined(ENABLE_OVERLOADING)
data RelationGetRelationTypeMethodInfo
instance (signature ~ (m Atk.Enums.RelationType), MonadIO m, IsRelation a) => O.MethodInfo RelationGetRelationTypeMethodInfo a signature where
overloadedMethod = relationGetRelationType
#endif
foreign import ccall "atk_relation_get_target" atk_relation_get_target ::
Ptr Relation ->
IO (Ptr (GPtrArray (Ptr Atk.Object.Object)))
relationGetTarget ::
(B.CallStack.HasCallStack, MonadIO m, IsRelation a) =>
a
-> m [Atk.Object.Object]
relationGetTarget :: a -> m [Object]
relationGetTarget a
relation = 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 Relation
relation' <- a -> IO (Ptr Relation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
relation
Ptr (GPtrArray (Ptr Object))
result <- Ptr Relation -> IO (Ptr (GPtrArray (Ptr Object)))
atk_relation_get_target Ptr Relation
relation'
Text -> Ptr (GPtrArray (Ptr Object)) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"relationGetTarget" Ptr (GPtrArray (Ptr Object))
result
[Ptr Object]
result' <- Ptr (GPtrArray (Ptr Object)) -> IO [Ptr Object]
forall a. Ptr (GPtrArray (Ptr a)) -> IO [Ptr a]
unpackGPtrArray Ptr (GPtrArray (Ptr Object))
result
[Object]
result'' <- (Ptr Object -> IO Object) -> [Ptr Object] -> IO [Object]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((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
Atk.Object.Object) [Ptr Object]
result'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
relation
[Object] -> IO [Object]
forall (m :: * -> *) a. Monad m => a -> m a
return [Object]
result''
#if defined(ENABLE_OVERLOADING)
data RelationGetTargetMethodInfo
instance (signature ~ (m [Atk.Object.Object]), MonadIO m, IsRelation a) => O.MethodInfo RelationGetTargetMethodInfo a signature where
overloadedMethod = relationGetTarget
#endif
foreign import ccall "atk_relation_remove_target" atk_relation_remove_target ::
Ptr Relation ->
Ptr Atk.Object.Object ->
IO CInt
relationRemoveTarget ::
(B.CallStack.HasCallStack, MonadIO m, IsRelation a, Atk.Object.IsObject b) =>
a
-> b
-> m Bool
relationRemoveTarget :: a -> b -> m Bool
relationRemoveTarget a
relation b
target = 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 Relation
relation' <- a -> IO (Ptr Relation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
relation
Ptr Object
target' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
target
CInt
result <- Ptr Relation -> Ptr Object -> IO CInt
atk_relation_remove_target Ptr Relation
relation' Ptr Object
target'
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
relation
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
target
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data RelationRemoveTargetMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsRelation a, Atk.Object.IsObject b) => O.MethodInfo RelationRemoveTargetMethodInfo a signature where
overloadedMethod = relationRemoveTarget
#endif