{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The AtkRelationSet held by an object establishes its relationships
-- with objects beyond the normal \"parent\/child\" hierarchical
-- relationships that all user interface objects have.
-- AtkRelationSets establish whether objects are labelled or
-- controlled by other components, share group membership with other
-- components (for instance within a radio-button group), or share
-- content which \"flows\" between them, among other types of possible
-- relationships.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Atk.Objects.RelationSet
    ( 

-- * Exported types
    RelationSet(..)                         ,
    IsRelationSet                           ,
    toRelationSet                           ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [add]("GI.Atk.Objects.RelationSet#g:method:add"), [addRelationByType]("GI.Atk.Objects.RelationSet#g:method:addRelationByType"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [contains]("GI.Atk.Objects.RelationSet#g:method:contains"), [containsTarget]("GI.Atk.Objects.RelationSet#g:method:containsTarget"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [remove]("GI.Atk.Objects.RelationSet#g:method:remove"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getNRelations]("GI.Atk.Objects.RelationSet#g:method:getNRelations"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRelation]("GI.Atk.Objects.RelationSet#g:method:getRelation"), [getRelationByType]("GI.Atk.Objects.RelationSet#g:method:getRelationByType").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveRelationSetMethod                ,
#endif

-- ** add #method:add#

#if defined(ENABLE_OVERLOADING)
    RelationSetAddMethodInfo                ,
#endif
    relationSetAdd                          ,


-- ** addRelationByType #method:addRelationByType#

#if defined(ENABLE_OVERLOADING)
    RelationSetAddRelationByTypeMethodInfo  ,
#endif
    relationSetAddRelationByType            ,


-- ** contains #method:contains#

#if defined(ENABLE_OVERLOADING)
    RelationSetContainsMethodInfo           ,
#endif
    relationSetContains                     ,


-- ** containsTarget #method:containsTarget#

#if defined(ENABLE_OVERLOADING)
    RelationSetContainsTargetMethodInfo     ,
#endif
    relationSetContainsTarget               ,


-- ** getNRelations #method:getNRelations#

#if defined(ENABLE_OVERLOADING)
    RelationSetGetNRelationsMethodInfo      ,
#endif
    relationSetGetNRelations                ,


-- ** getRelation #method:getRelation#

#if defined(ENABLE_OVERLOADING)
    RelationSetGetRelationMethodInfo        ,
#endif
    relationSetGetRelation                  ,


-- ** getRelationByType #method:getRelationByType#

#if defined(ENABLE_OVERLOADING)
    RelationSetGetRelationByTypeMethodInfo  ,
#endif
    relationSetGetRelationByType            ,


-- ** new #method:new#

    relationSetNew                          ,


-- ** remove #method:remove#

#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.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 {-# 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

-- | Memory-managed wrapper type.
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

-- | Type class for types which can be safely cast to `RelationSet`, for instance with `toRelationSet`.
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]

-- | Cast to `RelationSet`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toRelationSet :: (MIO.MonadIO m, IsRelationSet o) => o -> m RelationSet
toRelationSet :: forall (m :: * -> *) o.
(MonadIO m, IsRelationSet o) =>
o -> m RelationSet
toRelationSet = IO RelationSet -> m RelationSet
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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'
B.ManagedPtr.unsafeCastTo ManagedPtr RelationSet -> RelationSet
RelationSet

-- | Convert 'RelationSet' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe RelationSet) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_atk_relation_set_get_type
    gvalueSet_ :: Ptr GValue -> Maybe RelationSet -> IO ()
gvalueSet_ Ptr GValue
gv Maybe RelationSet
P.Nothing = Ptr GValue -> Ptr RelationSet -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr RelationSet
forall a. Ptr a
FP.nullPtr :: FP.Ptr RelationSet)
    gvalueSet_ Ptr GValue
gv (P.Just RelationSet
obj) = RelationSet -> (Ptr RelationSet -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr RelationSet
obj (Ptr GValue -> Ptr RelationSet -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe RelationSet)
gvalueGet_ Ptr GValue
gv = do
        Ptr RelationSet
ptr <- Ptr GValue -> IO (Ptr RelationSet)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr RelationSet)
        if Ptr RelationSet
ptr Ptr RelationSet -> Ptr RelationSet -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr RelationSet
forall a. Ptr a
FP.nullPtr
        then RelationSet -> Maybe RelationSet
forall a. a -> Maybe a
P.Just (RelationSet -> Maybe RelationSet)
-> IO RelationSet -> IO (Maybe RelationSet)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
        else Maybe RelationSet -> IO (Maybe RelationSet)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe RelationSet
forall a. Maybe a
P.Nothing
        
    

#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.OverloadedMethod 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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveRelationSetMethod t RelationSet, O.OverloadedMethod info RelationSet p, R.HasField t RelationSet p) => R.HasField t RelationSet p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveRelationSetMethod t RelationSet, O.OverloadedMethodInfo info RelationSet) => OL.IsLabel t (O.MethodProxy info RelationSet) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#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

-- method RelationSet::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Atk" , name = "RelationSet" })
-- throws : False
-- Skip return : False

foreign import ccall "atk_relation_set_new" atk_relation_set_new :: 
    IO (Ptr RelationSet)

-- | Creates a new empty relation set.
relationSetNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m RelationSet
    -- ^ __Returns:__ a new t'GI.Atk.Objects.RelationSet.RelationSet'
relationSetNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => 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

-- method RelationSet::add
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "set"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "RelationSet" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkRelationSet" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "relation"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Relation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkRelation" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_relation_set_add" atk_relation_set_add :: 
    Ptr RelationSet ->                      -- set : TInterface (Name {namespace = "Atk", name = "RelationSet"})
    Ptr Atk.Relation.Relation ->            -- relation : TInterface (Name {namespace = "Atk", name = "Relation"})
    IO ()

-- | Add a new relation to the current relation set if it is not already
-- present.
-- This function ref\'s the AtkRelation so the caller of this function
-- should unref it to ensure that it will be destroyed when the AtkRelationSet
-- is destroyed.
relationSetAdd ::
    (B.CallStack.HasCallStack, MonadIO m, IsRelationSet a, Atk.Relation.IsRelation b) =>
    a
    -- ^ /@set@/: an t'GI.Atk.Objects.RelationSet.RelationSet'
    -> b
    -- ^ /@relation@/: an t'GI.Atk.Objects.Relation.Relation'
    -> m ()
relationSetAdd :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRelationSet a, IsRelation b) =>
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.OverloadedMethod RelationSetAddMethodInfo a signature where
    overloadedMethod = relationSetAdd

instance O.OverloadedMethodInfo RelationSetAddMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Objects.RelationSet.relationSetAdd",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Objects-RelationSet.html#v:relationSetAdd"
        })


#endif

-- method RelationSet::add_relation_by_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "set"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "RelationSet" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkRelationSet" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "relationship"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "RelationType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkRelationType"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target"
--           , argType = TInterface Name { namespace = "Atk" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkObject" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_relation_set_add_relation_by_type" atk_relation_set_add_relation_by_type :: 
    Ptr RelationSet ->                      -- set : TInterface (Name {namespace = "Atk", name = "RelationSet"})
    CUInt ->                                -- relationship : TInterface (Name {namespace = "Atk", name = "RelationType"})
    Ptr Atk.Object.Object ->                -- target : TInterface (Name {namespace = "Atk", name = "Object"})
    IO ()

-- | Add a new relation of the specified type with the specified target to
-- the current relation set if the relation set does not contain a relation
-- of that type. If it is does contain a relation of that typea the target
-- is added to the relation.
-- 
-- /Since: 1.9/
relationSetAddRelationByType ::
    (B.CallStack.HasCallStack, MonadIO m, IsRelationSet a, Atk.Object.IsObject b) =>
    a
    -- ^ /@set@/: an t'GI.Atk.Objects.RelationSet.RelationSet'
    -> Atk.Enums.RelationType
    -- ^ /@relationship@/: an t'GI.Atk.Enums.RelationType'
    -> b
    -- ^ /@target@/: an t'GI.Atk.Objects.Object.Object'
    -> m ()
relationSetAddRelationByType :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRelationSet a, IsObject b) =>
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.OverloadedMethod RelationSetAddRelationByTypeMethodInfo a signature where
    overloadedMethod = relationSetAddRelationByType

instance O.OverloadedMethodInfo RelationSetAddRelationByTypeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Objects.RelationSet.relationSetAddRelationByType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Objects-RelationSet.html#v:relationSetAddRelationByType"
        })


#endif

-- method RelationSet::contains
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "set"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "RelationSet" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkRelationSet" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "relationship"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "RelationType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkRelationType"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "atk_relation_set_contains" atk_relation_set_contains :: 
    Ptr RelationSet ->                      -- set : TInterface (Name {namespace = "Atk", name = "RelationSet"})
    CUInt ->                                -- relationship : TInterface (Name {namespace = "Atk", name = "RelationType"})
    IO CInt

-- | Determines whether the relation set contains a relation that matches the
-- specified type.
relationSetContains ::
    (B.CallStack.HasCallStack, MonadIO m, IsRelationSet a) =>
    a
    -- ^ /@set@/: an t'GI.Atk.Objects.RelationSet.RelationSet'
    -> Atk.Enums.RelationType
    -- ^ /@relationship@/: an t'GI.Atk.Enums.RelationType'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@relationship@/ is the relationship type of a relation
    -- in /@set@/, 'P.False' otherwise
relationSetContains :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRelationSet a) =>
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.OverloadedMethod RelationSetContainsMethodInfo a signature where
    overloadedMethod = relationSetContains

instance O.OverloadedMethodInfo RelationSetContainsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Objects.RelationSet.relationSetContains",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Objects-RelationSet.html#v:relationSetContains"
        })


#endif

-- method RelationSet::contains_target
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "set"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "RelationSet" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkRelationSet" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "relationship"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "RelationType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkRelationType"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target"
--           , argType = TInterface Name { namespace = "Atk" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkObject" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "atk_relation_set_contains_target" atk_relation_set_contains_target :: 
    Ptr RelationSet ->                      -- set : TInterface (Name {namespace = "Atk", name = "RelationSet"})
    CUInt ->                                -- relationship : TInterface (Name {namespace = "Atk", name = "RelationType"})
    Ptr Atk.Object.Object ->                -- target : TInterface (Name {namespace = "Atk", name = "Object"})
    IO CInt

-- | Determines whether the relation set contains a relation that
-- matches the specified pair formed by type /@relationship@/ and object
-- /@target@/.
relationSetContainsTarget ::
    (B.CallStack.HasCallStack, MonadIO m, IsRelationSet a, Atk.Object.IsObject b) =>
    a
    -- ^ /@set@/: an t'GI.Atk.Objects.RelationSet.RelationSet'
    -> Atk.Enums.RelationType
    -- ^ /@relationship@/: an t'GI.Atk.Enums.RelationType'
    -> b
    -- ^ /@target@/: an t'GI.Atk.Objects.Object.Object'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@set@/ contains a relation with the relationship
    -- type /@relationship@/ with an object /@target@/, 'P.False' otherwise
relationSetContainsTarget :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRelationSet a, IsObject b) =>
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.OverloadedMethod RelationSetContainsTargetMethodInfo a signature where
    overloadedMethod = relationSetContainsTarget

instance O.OverloadedMethodInfo RelationSetContainsTargetMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Objects.RelationSet.relationSetContainsTarget",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Objects-RelationSet.html#v:relationSetContainsTarget"
        })


#endif

-- method RelationSet::get_n_relations
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "set"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "RelationSet" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkRelationSet" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "atk_relation_set_get_n_relations" atk_relation_set_get_n_relations :: 
    Ptr RelationSet ->                      -- set : TInterface (Name {namespace = "Atk", name = "RelationSet"})
    IO Int32

-- | Determines the number of relations in a relation set.
relationSetGetNRelations ::
    (B.CallStack.HasCallStack, MonadIO m, IsRelationSet a) =>
    a
    -- ^ /@set@/: an t'GI.Atk.Objects.RelationSet.RelationSet'
    -> m Int32
    -- ^ __Returns:__ an integer representing the number of relations in the set.
relationSetGetNRelations :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRelationSet a) =>
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.OverloadedMethod RelationSetGetNRelationsMethodInfo a signature where
    overloadedMethod = relationSetGetNRelations

instance O.OverloadedMethodInfo RelationSetGetNRelationsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Objects.RelationSet.relationSetGetNRelations",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Objects-RelationSet.html#v:relationSetGetNRelations"
        })


#endif

-- method RelationSet::get_relation
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "set"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "RelationSet" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkRelationSet" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "i"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a gint representing a position in the set, starting from 0."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Atk" , name = "Relation" })
-- throws : False
-- Skip return : False

foreign import ccall "atk_relation_set_get_relation" atk_relation_set_get_relation :: 
    Ptr RelationSet ->                      -- set : TInterface (Name {namespace = "Atk", name = "RelationSet"})
    Int32 ->                                -- i : TBasicType TInt
    IO (Ptr Atk.Relation.Relation)

-- | Determines the relation at the specified position in the relation set.
relationSetGetRelation ::
    (B.CallStack.HasCallStack, MonadIO m, IsRelationSet a) =>
    a
    -- ^ /@set@/: an t'GI.Atk.Objects.RelationSet.RelationSet'
    -> Int32
    -- ^ /@i@/: a gint representing a position in the set, starting from 0.
    -> m Atk.Relation.Relation
    -- ^ __Returns:__ a t'GI.Atk.Objects.Relation.Relation', which is the relation at
    -- position i in the set.
relationSetGetRelation :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRelationSet a) =>
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.OverloadedMethod RelationSetGetRelationMethodInfo a signature where
    overloadedMethod = relationSetGetRelation

instance O.OverloadedMethodInfo RelationSetGetRelationMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Objects.RelationSet.relationSetGetRelation",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Objects-RelationSet.html#v:relationSetGetRelation"
        })


#endif

-- method RelationSet::get_relation_by_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "set"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "RelationSet" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkRelationSet" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "relationship"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "RelationType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkRelationType"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Atk" , name = "Relation" })
-- throws : False
-- Skip return : False

foreign import ccall "atk_relation_set_get_relation_by_type" atk_relation_set_get_relation_by_type :: 
    Ptr RelationSet ->                      -- set : TInterface (Name {namespace = "Atk", name = "RelationSet"})
    CUInt ->                                -- relationship : TInterface (Name {namespace = "Atk", name = "RelationType"})
    IO (Ptr Atk.Relation.Relation)

-- | Finds a relation that matches the specified type.
relationSetGetRelationByType ::
    (B.CallStack.HasCallStack, MonadIO m, IsRelationSet a) =>
    a
    -- ^ /@set@/: an t'GI.Atk.Objects.RelationSet.RelationSet'
    -> Atk.Enums.RelationType
    -- ^ /@relationship@/: an t'GI.Atk.Enums.RelationType'
    -> m Atk.Relation.Relation
    -- ^ __Returns:__ an t'GI.Atk.Objects.Relation.Relation', which is a relation matching the
    -- specified type.
relationSetGetRelationByType :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRelationSet a) =>
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.OverloadedMethod RelationSetGetRelationByTypeMethodInfo a signature where
    overloadedMethod = relationSetGetRelationByType

instance O.OverloadedMethodInfo RelationSetGetRelationByTypeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Objects.RelationSet.relationSetGetRelationByType",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Objects-RelationSet.html#v:relationSetGetRelationByType"
        })


#endif

-- method RelationSet::remove
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "set"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "RelationSet" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkRelationSet" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "relation"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "Relation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkRelation" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_relation_set_remove" atk_relation_set_remove :: 
    Ptr RelationSet ->                      -- set : TInterface (Name {namespace = "Atk", name = "RelationSet"})
    Ptr Atk.Relation.Relation ->            -- relation : TInterface (Name {namespace = "Atk", name = "Relation"})
    IO ()

-- | Removes a relation from the relation set.
-- This function unref\'s the t'GI.Atk.Objects.Relation.Relation' so it will be deleted unless there
-- is another reference to it.
relationSetRemove ::
    (B.CallStack.HasCallStack, MonadIO m, IsRelationSet a, Atk.Relation.IsRelation b) =>
    a
    -- ^ /@set@/: an t'GI.Atk.Objects.RelationSet.RelationSet'
    -> b
    -- ^ /@relation@/: an t'GI.Atk.Objects.Relation.Relation'
    -> m ()
relationSetRemove :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRelationSet a, IsRelation b) =>
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.OverloadedMethod RelationSetRemoveMethodInfo a signature where
    overloadedMethod = relationSetRemove

instance O.OverloadedMethodInfo RelationSetRemoveMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Atk.Objects.RelationSet.relationSetRemove",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-atk-2.0.24/docs/GI-Atk-Objects-RelationSet.html#v:relationSetRemove"
        })


#endif