{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Atk.Objects.RelationSet
(
RelationSet(..) ,
IsRelationSet ,
toRelationSet ,
#if defined(ENABLE_OVERLOADING)
ResolveRelationSetMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
RelationSetAddMethodInfo ,
#endif
relationSetAdd ,
#if defined(ENABLE_OVERLOADING)
RelationSetAddRelationByTypeMethodInfo ,
#endif
relationSetAddRelationByType ,
#if defined(ENABLE_OVERLOADING)
RelationSetContainsMethodInfo ,
#endif
relationSetContains ,
#if defined(ENABLE_OVERLOADING)
RelationSetContainsTargetMethodInfo ,
#endif
relationSetContainsTarget ,
#if defined(ENABLE_OVERLOADING)
RelationSetGetNRelationsMethodInfo ,
#endif
relationSetGetNRelations ,
#if defined(ENABLE_OVERLOADING)
RelationSetGetRelationMethodInfo ,
#endif
relationSetGetRelation ,
#if defined(ENABLE_OVERLOADING)
RelationSetGetRelationByTypeMethodInfo ,
#endif
relationSetGetRelationByType ,
relationSetNew ,
#if defined(ENABLE_OVERLOADING)
RelationSetRemoveMethodInfo ,
#endif
relationSetRemove ,
) 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 {-# SOURCE #-} qualified GI.Atk.Objects.Relation as Atk.Relation
import qualified GI.GObject.Objects.Object as GObject.Object
newtype RelationSet = RelationSet (SP.ManagedPtr RelationSet)
deriving (RelationSet -> RelationSet -> Bool
(RelationSet -> RelationSet -> Bool)
-> (RelationSet -> RelationSet -> Bool) -> Eq RelationSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelationSet -> RelationSet -> Bool
$c/= :: RelationSet -> RelationSet -> Bool
== :: RelationSet -> RelationSet -> Bool
$c== :: RelationSet -> RelationSet -> Bool
Eq)
instance SP.ManagedPtrNewtype RelationSet where
toManagedPtr :: RelationSet -> ManagedPtr RelationSet
toManagedPtr (RelationSet ManagedPtr RelationSet
p) = ManagedPtr RelationSet
p
foreign import ccall "atk_relation_set_get_type"
c_atk_relation_set_get_type :: IO B.Types.GType
instance B.Types.TypedObject RelationSet where
glibType :: IO GType
glibType = IO GType
c_atk_relation_set_get_type
instance B.Types.GObject RelationSet
instance B.GValue.IsGValue RelationSet where
toGValue :: RelationSet -> IO GValue
toGValue RelationSet
o = do
GType
gtype <- IO GType
c_atk_relation_set_get_type
RelationSet -> (Ptr RelationSet -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr RelationSet
o (GType
-> (GValue -> Ptr RelationSet -> IO ())
-> Ptr RelationSet
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr RelationSet -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO RelationSet
fromGValue GValue
gv = do
Ptr RelationSet
ptr <- GValue -> IO (Ptr RelationSet)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr RelationSet)
(ManagedPtr RelationSet -> RelationSet)
-> Ptr RelationSet -> IO RelationSet
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr RelationSet -> RelationSet
RelationSet Ptr RelationSet
ptr
class (SP.GObject o, O.IsDescendantOf RelationSet o) => IsRelationSet o
instance (SP.GObject o, O.IsDescendantOf RelationSet o) => IsRelationSet o
instance O.HasParentTypes RelationSet
type instance O.ParentTypes RelationSet = '[GObject.Object.Object]
toRelationSet :: (MonadIO m, IsRelationSet o) => o -> m RelationSet
toRelationSet :: o -> m RelationSet
toRelationSet = IO RelationSet -> m RelationSet
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RelationSet -> m RelationSet)
-> (o -> IO RelationSet) -> o -> m RelationSet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr RelationSet -> RelationSet) -> o -> IO RelationSet
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr RelationSet -> RelationSet
RelationSet
#if defined(ENABLE_OVERLOADING)
type family ResolveRelationSetMethod (t :: Symbol) (o :: *) :: * where
ResolveRelationSetMethod "add" o = RelationSetAddMethodInfo
ResolveRelationSetMethod "addRelationByType" o = RelationSetAddRelationByTypeMethodInfo
ResolveRelationSetMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveRelationSetMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveRelationSetMethod "contains" o = RelationSetContainsMethodInfo
ResolveRelationSetMethod "containsTarget" o = RelationSetContainsTargetMethodInfo
ResolveRelationSetMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveRelationSetMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveRelationSetMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveRelationSetMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveRelationSetMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveRelationSetMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveRelationSetMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveRelationSetMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveRelationSetMethod "remove" o = RelationSetRemoveMethodInfo
ResolveRelationSetMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveRelationSetMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveRelationSetMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveRelationSetMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveRelationSetMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveRelationSetMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveRelationSetMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveRelationSetMethod "getNRelations" o = RelationSetGetNRelationsMethodInfo
ResolveRelationSetMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveRelationSetMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveRelationSetMethod "getRelation" o = RelationSetGetRelationMethodInfo
ResolveRelationSetMethod "getRelationByType" o = RelationSetGetRelationByTypeMethodInfo
ResolveRelationSetMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveRelationSetMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveRelationSetMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveRelationSetMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveRelationSetMethod t RelationSet, O.MethodInfo info RelationSet p) => OL.IsLabel t (RelationSet -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList RelationSet
type instance O.AttributeList RelationSet = RelationSetAttributeList
type RelationSetAttributeList = ('[ ] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList RelationSet = RelationSetSignalList
type RelationSetSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "atk_relation_set_new" atk_relation_set_new ::
IO (Ptr RelationSet)
relationSetNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m RelationSet
relationSetNew :: m RelationSet
relationSetNew = IO RelationSet -> m RelationSet
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RelationSet -> m RelationSet)
-> IO RelationSet -> m RelationSet
forall a b. (a -> b) -> a -> b
$ do
Ptr RelationSet
result <- IO (Ptr RelationSet)
atk_relation_set_new
Text -> Ptr RelationSet -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"relationSetNew" Ptr RelationSet
result
RelationSet
result' <- ((ManagedPtr RelationSet -> RelationSet)
-> Ptr RelationSet -> IO RelationSet
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr RelationSet -> RelationSet
RelationSet) Ptr RelationSet
result
RelationSet -> IO RelationSet
forall (m :: * -> *) a. Monad m => a -> m a
return RelationSet
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "atk_relation_set_add" atk_relation_set_add ::
Ptr RelationSet ->
Ptr Atk.Relation.Relation ->
IO ()
relationSetAdd ::
(B.CallStack.HasCallStack, MonadIO m, IsRelationSet a, Atk.Relation.IsRelation b) =>
a
-> b
-> m ()
relationSetAdd :: a -> b -> m ()
relationSetAdd a
set b
relation = 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 RelationSet
set' <- a -> IO (Ptr RelationSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
set
Ptr Relation
relation' <- b -> IO (Ptr Relation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
relation
Ptr RelationSet -> Ptr Relation -> IO ()
atk_relation_set_add Ptr RelationSet
set' Ptr Relation
relation'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
set
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
relation
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data RelationSetAddMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsRelationSet a, Atk.Relation.IsRelation b) => O.MethodInfo RelationSetAddMethodInfo a signature where
overloadedMethod = relationSetAdd
#endif
foreign import ccall "atk_relation_set_add_relation_by_type" atk_relation_set_add_relation_by_type ::
Ptr RelationSet ->
CUInt ->
Ptr Atk.Object.Object ->
IO ()
relationSetAddRelationByType ::
(B.CallStack.HasCallStack, MonadIO m, IsRelationSet a, Atk.Object.IsObject b) =>
a
-> Atk.Enums.RelationType
-> b
-> m ()
relationSetAddRelationByType :: a -> RelationType -> b -> m ()
relationSetAddRelationByType a
set RelationType
relationship 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 RelationSet
set' <- a -> IO (Ptr RelationSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
set
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 Object
target' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
target
Ptr RelationSet -> CUInt -> Ptr Object -> IO ()
atk_relation_set_add_relation_by_type Ptr RelationSet
set' CUInt
relationship' Ptr Object
target'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
set
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 RelationSetAddRelationByTypeMethodInfo
instance (signature ~ (Atk.Enums.RelationType -> b -> m ()), MonadIO m, IsRelationSet a, Atk.Object.IsObject b) => O.MethodInfo RelationSetAddRelationByTypeMethodInfo a signature where
overloadedMethod = relationSetAddRelationByType
#endif
foreign import ccall "atk_relation_set_contains" atk_relation_set_contains ::
Ptr RelationSet ->
CUInt ->
IO CInt
relationSetContains ::
(B.CallStack.HasCallStack, MonadIO m, IsRelationSet a) =>
a
-> Atk.Enums.RelationType
-> m Bool
relationSetContains :: a -> RelationType -> m Bool
relationSetContains a
set RelationType
relationship = 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 RelationSet
set' <- a -> IO (Ptr RelationSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
set
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
CInt
result <- Ptr RelationSet -> CUInt -> IO CInt
atk_relation_set_contains Ptr RelationSet
set' CUInt
relationship'
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
set
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data RelationSetContainsMethodInfo
instance (signature ~ (Atk.Enums.RelationType -> m Bool), MonadIO m, IsRelationSet a) => O.MethodInfo RelationSetContainsMethodInfo a signature where
overloadedMethod = relationSetContains
#endif
foreign import ccall "atk_relation_set_contains_target" atk_relation_set_contains_target ::
Ptr RelationSet ->
CUInt ->
Ptr Atk.Object.Object ->
IO CInt
relationSetContainsTarget ::
(B.CallStack.HasCallStack, MonadIO m, IsRelationSet a, Atk.Object.IsObject b) =>
a
-> Atk.Enums.RelationType
-> b
-> m Bool
relationSetContainsTarget :: a -> RelationType -> b -> m Bool
relationSetContainsTarget a
set RelationType
relationship 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 RelationSet
set' <- a -> IO (Ptr RelationSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
set
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 Object
target' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
target
CInt
result <- Ptr RelationSet -> CUInt -> Ptr Object -> IO CInt
atk_relation_set_contains_target Ptr RelationSet
set' CUInt
relationship' 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
set
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 RelationSetContainsTargetMethodInfo
instance (signature ~ (Atk.Enums.RelationType -> b -> m Bool), MonadIO m, IsRelationSet a, Atk.Object.IsObject b) => O.MethodInfo RelationSetContainsTargetMethodInfo a signature where
overloadedMethod = relationSetContainsTarget
#endif
foreign import ccall "atk_relation_set_get_n_relations" atk_relation_set_get_n_relations ::
Ptr RelationSet ->
IO Int32
relationSetGetNRelations ::
(B.CallStack.HasCallStack, MonadIO m, IsRelationSet a) =>
a
-> m Int32
relationSetGetNRelations :: a -> m Int32
relationSetGetNRelations a
set = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr RelationSet
set' <- a -> IO (Ptr RelationSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
set
Int32
result <- Ptr RelationSet -> IO Int32
atk_relation_set_get_n_relations Ptr RelationSet
set'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
set
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data RelationSetGetNRelationsMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsRelationSet a) => O.MethodInfo RelationSetGetNRelationsMethodInfo a signature where
overloadedMethod = relationSetGetNRelations
#endif
foreign import ccall "atk_relation_set_get_relation" atk_relation_set_get_relation ::
Ptr RelationSet ->
Int32 ->
IO (Ptr Atk.Relation.Relation)
relationSetGetRelation ::
(B.CallStack.HasCallStack, MonadIO m, IsRelationSet a) =>
a
-> Int32
-> m Atk.Relation.Relation
relationSetGetRelation :: a -> Int32 -> m Relation
relationSetGetRelation a
set Int32
i = 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
Ptr RelationSet
set' <- a -> IO (Ptr RelationSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
set
Ptr Relation
result <- Ptr RelationSet -> Int32 -> IO (Ptr Relation)
atk_relation_set_get_relation Ptr RelationSet
set' Int32
i
Text -> Ptr Relation -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"relationSetGetRelation" 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
newObject ManagedPtr Relation -> Relation
Atk.Relation.Relation) Ptr Relation
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
set
Relation -> IO Relation
forall (m :: * -> *) a. Monad m => a -> m a
return Relation
result'
#if defined(ENABLE_OVERLOADING)
data RelationSetGetRelationMethodInfo
instance (signature ~ (Int32 -> m Atk.Relation.Relation), MonadIO m, IsRelationSet a) => O.MethodInfo RelationSetGetRelationMethodInfo a signature where
overloadedMethod = relationSetGetRelation
#endif
foreign import ccall "atk_relation_set_get_relation_by_type" atk_relation_set_get_relation_by_type ::
Ptr RelationSet ->
CUInt ->
IO (Ptr Atk.Relation.Relation)
relationSetGetRelationByType ::
(B.CallStack.HasCallStack, MonadIO m, IsRelationSet a) =>
a
-> Atk.Enums.RelationType
-> m Atk.Relation.Relation
relationSetGetRelationByType :: a -> RelationType -> m Relation
relationSetGetRelationByType a
set 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
Ptr RelationSet
set' <- a -> IO (Ptr RelationSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
set
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 RelationSet -> CUInt -> IO (Ptr Relation)
atk_relation_set_get_relation_by_type Ptr RelationSet
set' CUInt
relationship'
Text -> Ptr Relation -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"relationSetGetRelationByType" 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
newObject ManagedPtr Relation -> Relation
Atk.Relation.Relation) Ptr Relation
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
set
Relation -> IO Relation
forall (m :: * -> *) a. Monad m => a -> m a
return Relation
result'
#if defined(ENABLE_OVERLOADING)
data RelationSetGetRelationByTypeMethodInfo
instance (signature ~ (Atk.Enums.RelationType -> m Atk.Relation.Relation), MonadIO m, IsRelationSet a) => O.MethodInfo RelationSetGetRelationByTypeMethodInfo a signature where
overloadedMethod = relationSetGetRelationByType
#endif
foreign import ccall "atk_relation_set_remove" atk_relation_set_remove ::
Ptr RelationSet ->
Ptr Atk.Relation.Relation ->
IO ()
relationSetRemove ::
(B.CallStack.HasCallStack, MonadIO m, IsRelationSet a, Atk.Relation.IsRelation b) =>
a
-> b
-> m ()
relationSetRemove :: a -> b -> m ()
relationSetRemove a
set b
relation = 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 RelationSet
set' <- a -> IO (Ptr RelationSet)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
set
Ptr Relation
relation' <- b -> IO (Ptr Relation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
relation
Ptr RelationSet -> Ptr Relation -> IO ()
atk_relation_set_remove Ptr RelationSet
set' Ptr Relation
relation'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
set
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
relation
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data RelationSetRemoveMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsRelationSet a, Atk.Relation.IsRelation b) => O.MethodInfo RelationSetRemoveMethodInfo a signature where
overloadedMethod = relationSetRemove
#endif