{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- This class is the primary class for accessibility support via the
-- Accessibility ToolKit (ATK).  Objects which are instances of
-- t'GI.Atk.Objects.Object.Object' (or instances of AtkObject-derived types) are queried
-- for properties which relate basic (and generic) properties of a UI
-- component such as name and description.  Instances of t'GI.Atk.Objects.Object.Object'
-- may also be queried as to whether they implement other ATK
-- interfaces (e.g. t'GI.Atk.Interfaces.Action.Action', t'GI.Atk.Interfaces.Component.Component', etc.), as appropriate
-- to the role which a given UI component plays in a user interface.
-- 
-- All UI components in an application which provide useful
-- information or services to the user must provide corresponding
-- t'GI.Atk.Objects.Object.Object' instances on request (in GTK+, for instance, usually on
-- a call to @/gtk_widget_get_accessible/@ ()), either via ATK support
-- built into the toolkit for the widget class or ancestor class, or
-- in the case of custom widgets, if the inherited t'GI.Atk.Objects.Object.Object'
-- implementation is insufficient, via instances of a new t'GI.Atk.Objects.Object.Object'
-- subclass.
-- 
-- See also: t'GI.Atk.Objects.ObjectFactory.ObjectFactory', t'GI.Atk.Objects.Registry.Registry'.  (GTK+ users see also
-- @/GtkAccessible/@).

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

module GI.Atk.Objects.Object
    ( 

-- * Exported types
    Object(..)                              ,
    IsObject                                ,
    toObject                                ,
    noObject                                ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveObjectMethod                     ,
#endif


-- ** addRelationship #method:addRelationship#

#if defined(ENABLE_OVERLOADING)
    ObjectAddRelationshipMethodInfo         ,
#endif
    objectAddRelationship                   ,


-- ** getAttributes #method:getAttributes#

#if defined(ENABLE_OVERLOADING)
    ObjectGetAttributesMethodInfo           ,
#endif
    objectGetAttributes                     ,


-- ** getDescription #method:getDescription#

#if defined(ENABLE_OVERLOADING)
    ObjectGetDescriptionMethodInfo          ,
#endif
    objectGetDescription                    ,


-- ** getIndexInParent #method:getIndexInParent#

#if defined(ENABLE_OVERLOADING)
    ObjectGetIndexInParentMethodInfo        ,
#endif
    objectGetIndexInParent                  ,


-- ** getLayer #method:getLayer#

#if defined(ENABLE_OVERLOADING)
    ObjectGetLayerMethodInfo                ,
#endif
    objectGetLayer                          ,


-- ** getMdiZorder #method:getMdiZorder#

#if defined(ENABLE_OVERLOADING)
    ObjectGetMdiZorderMethodInfo            ,
#endif
    objectGetMdiZorder                      ,


-- ** getNAccessibleChildren #method:getNAccessibleChildren#

#if defined(ENABLE_OVERLOADING)
    ObjectGetNAccessibleChildrenMethodInfo  ,
#endif
    objectGetNAccessibleChildren            ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    ObjectGetNameMethodInfo                 ,
#endif
    objectGetName                           ,


-- ** getObjectLocale #method:getObjectLocale#

#if defined(ENABLE_OVERLOADING)
    ObjectGetObjectLocaleMethodInfo         ,
#endif
    objectGetObjectLocale                   ,


-- ** getParent #method:getParent#

#if defined(ENABLE_OVERLOADING)
    ObjectGetParentMethodInfo               ,
#endif
    objectGetParent                         ,


-- ** getRole #method:getRole#

#if defined(ENABLE_OVERLOADING)
    ObjectGetRoleMethodInfo                 ,
#endif
    objectGetRole                           ,


-- ** initialize #method:initialize#

#if defined(ENABLE_OVERLOADING)
    ObjectInitializeMethodInfo              ,
#endif
    objectInitialize                        ,


-- ** notifyStateChange #method:notifyStateChange#

#if defined(ENABLE_OVERLOADING)
    ObjectNotifyStateChangeMethodInfo       ,
#endif
    objectNotifyStateChange                 ,


-- ** peekParent #method:peekParent#

#if defined(ENABLE_OVERLOADING)
    ObjectPeekParentMethodInfo              ,
#endif
    objectPeekParent                        ,


-- ** refAccessibleChild #method:refAccessibleChild#

#if defined(ENABLE_OVERLOADING)
    ObjectRefAccessibleChildMethodInfo      ,
#endif
    objectRefAccessibleChild                ,


-- ** refRelationSet #method:refRelationSet#

#if defined(ENABLE_OVERLOADING)
    ObjectRefRelationSetMethodInfo          ,
#endif
    objectRefRelationSet                    ,


-- ** refStateSet #method:refStateSet#

#if defined(ENABLE_OVERLOADING)
    ObjectRefStateSetMethodInfo             ,
#endif
    objectRefStateSet                       ,


-- ** removePropertyChangeHandler #method:removePropertyChangeHandler#

#if defined(ENABLE_OVERLOADING)
    ObjectRemovePropertyChangeHandlerMethodInfo,
#endif
    objectRemovePropertyChangeHandler       ,


-- ** removeRelationship #method:removeRelationship#

#if defined(ENABLE_OVERLOADING)
    ObjectRemoveRelationshipMethodInfo      ,
#endif
    objectRemoveRelationship                ,


-- ** setDescription #method:setDescription#

#if defined(ENABLE_OVERLOADING)
    ObjectSetDescriptionMethodInfo          ,
#endif
    objectSetDescription                    ,


-- ** setName #method:setName#

#if defined(ENABLE_OVERLOADING)
    ObjectSetNameMethodInfo                 ,
#endif
    objectSetName                           ,


-- ** setParent #method:setParent#

#if defined(ENABLE_OVERLOADING)
    ObjectSetParentMethodInfo               ,
#endif
    objectSetParent                         ,


-- ** setRole #method:setRole#

#if defined(ENABLE_OVERLOADING)
    ObjectSetRoleMethodInfo                 ,
#endif
    objectSetRole                           ,




 -- * Properties
-- ** accessibleComponentLayer #attr:accessibleComponentLayer#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    ObjectAccessibleComponentLayerPropertyInfo,
#endif
    getObjectAccessibleComponentLayer       ,
#if defined(ENABLE_OVERLOADING)
    objectAccessibleComponentLayer          ,
#endif


-- ** accessibleComponentMdiZorder #attr:accessibleComponentMdiZorder#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    ObjectAccessibleComponentMdiZorderPropertyInfo,
#endif
    getObjectAccessibleComponentMdiZorder   ,
#if defined(ENABLE_OVERLOADING)
    objectAccessibleComponentMdiZorder      ,
#endif


-- ** accessibleDescription #attr:accessibleDescription#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    ObjectAccessibleDescriptionPropertyInfo ,
#endif
    clearObjectAccessibleDescription        ,
    constructObjectAccessibleDescription    ,
    getObjectAccessibleDescription          ,
#if defined(ENABLE_OVERLOADING)
    objectAccessibleDescription             ,
#endif
    setObjectAccessibleDescription          ,


-- ** accessibleHypertextNlinks #attr:accessibleHypertextNlinks#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    ObjectAccessibleHypertextNlinksPropertyInfo,
#endif
    getObjectAccessibleHypertextNlinks      ,
#if defined(ENABLE_OVERLOADING)
    objectAccessibleHypertextNlinks         ,
#endif


-- ** accessibleName #attr:accessibleName#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    ObjectAccessibleNamePropertyInfo        ,
#endif
    clearObjectAccessibleName               ,
    constructObjectAccessibleName           ,
    getObjectAccessibleName                 ,
#if defined(ENABLE_OVERLOADING)
    objectAccessibleName                    ,
#endif
    setObjectAccessibleName                 ,


-- ** accessibleParent #attr:accessibleParent#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    ObjectAccessibleParentPropertyInfo      ,
#endif
    clearObjectAccessibleParent             ,
    constructObjectAccessibleParent         ,
    getObjectAccessibleParent               ,
#if defined(ENABLE_OVERLOADING)
    objectAccessibleParent                  ,
#endif
    setObjectAccessibleParent               ,


-- ** accessibleRole #attr:accessibleRole#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    ObjectAccessibleRolePropertyInfo        ,
#endif
    constructObjectAccessibleRole           ,
    getObjectAccessibleRole                 ,
#if defined(ENABLE_OVERLOADING)
    objectAccessibleRole                    ,
#endif
    setObjectAccessibleRole                 ,


-- ** accessibleTableCaption #attr:accessibleTableCaption#
-- | Table caption.

#if defined(ENABLE_OVERLOADING)
    ObjectAccessibleTableCaptionPropertyInfo,
#endif
    clearObjectAccessibleTableCaption       ,
    constructObjectAccessibleTableCaption   ,
    getObjectAccessibleTableCaption         ,
#if defined(ENABLE_OVERLOADING)
    objectAccessibleTableCaption            ,
#endif
    setObjectAccessibleTableCaption         ,


-- ** accessibleTableCaptionObject #attr:accessibleTableCaptionObject#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    ObjectAccessibleTableCaptionObjectPropertyInfo,
#endif
    clearObjectAccessibleTableCaptionObject ,
    constructObjectAccessibleTableCaptionObject,
    getObjectAccessibleTableCaptionObject   ,
#if defined(ENABLE_OVERLOADING)
    objectAccessibleTableCaptionObject      ,
#endif
    setObjectAccessibleTableCaptionObject   ,


-- ** accessibleTableColumnDescription #attr:accessibleTableColumnDescription#
-- | Accessible table column description.

#if defined(ENABLE_OVERLOADING)
    ObjectAccessibleTableColumnDescriptionPropertyInfo,
#endif
    clearObjectAccessibleTableColumnDescription,
    constructObjectAccessibleTableColumnDescription,
    getObjectAccessibleTableColumnDescription,
#if defined(ENABLE_OVERLOADING)
    objectAccessibleTableColumnDescription  ,
#endif
    setObjectAccessibleTableColumnDescription,


-- ** accessibleTableColumnHeader #attr:accessibleTableColumnHeader#
-- | Accessible table column header.

#if defined(ENABLE_OVERLOADING)
    ObjectAccessibleTableColumnHeaderPropertyInfo,
#endif
    clearObjectAccessibleTableColumnHeader  ,
    constructObjectAccessibleTableColumnHeader,
    getObjectAccessibleTableColumnHeader    ,
#if defined(ENABLE_OVERLOADING)
    objectAccessibleTableColumnHeader       ,
#endif
    setObjectAccessibleTableColumnHeader    ,


-- ** accessibleTableRowDescription #attr:accessibleTableRowDescription#
-- | Accessible table row description.

#if defined(ENABLE_OVERLOADING)
    ObjectAccessibleTableRowDescriptionPropertyInfo,
#endif
    clearObjectAccessibleTableRowDescription,
    constructObjectAccessibleTableRowDescription,
    getObjectAccessibleTableRowDescription  ,
#if defined(ENABLE_OVERLOADING)
    objectAccessibleTableRowDescription     ,
#endif
    setObjectAccessibleTableRowDescription  ,


-- ** accessibleTableRowHeader #attr:accessibleTableRowHeader#
-- | Accessible table row header.

#if defined(ENABLE_OVERLOADING)
    ObjectAccessibleTableRowHeaderPropertyInfo,
#endif
    clearObjectAccessibleTableRowHeader     ,
    constructObjectAccessibleTableRowHeader ,
    getObjectAccessibleTableRowHeader       ,
#if defined(ENABLE_OVERLOADING)
    objectAccessibleTableRowHeader          ,
#endif
    setObjectAccessibleTableRowHeader       ,


-- ** accessibleTableSummary #attr:accessibleTableSummary#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    ObjectAccessibleTableSummaryPropertyInfo,
#endif
    clearObjectAccessibleTableSummary       ,
    constructObjectAccessibleTableSummary   ,
    getObjectAccessibleTableSummary         ,
#if defined(ENABLE_OVERLOADING)
    objectAccessibleTableSummary            ,
#endif
    setObjectAccessibleTableSummary         ,


-- ** accessibleValue #attr:accessibleValue#
-- | Numeric value of this object, in case being and AtkValue.

#if defined(ENABLE_OVERLOADING)
    ObjectAccessibleValuePropertyInfo       ,
#endif
    constructObjectAccessibleValue          ,
    getObjectAccessibleValue                ,
#if defined(ENABLE_OVERLOADING)
    objectAccessibleValue                   ,
#endif
    setObjectAccessibleValue                ,




 -- * Signals
-- ** activeDescendantChanged #signal:activeDescendantChanged#

    C_ObjectActiveDescendantChangedCallback ,
    ObjectActiveDescendantChangedCallback   ,
#if defined(ENABLE_OVERLOADING)
    ObjectActiveDescendantChangedSignalInfo ,
#endif
    afterObjectActiveDescendantChanged      ,
    genClosure_ObjectActiveDescendantChanged,
    mk_ObjectActiveDescendantChangedCallback,
    noObjectActiveDescendantChangedCallback ,
    onObjectActiveDescendantChanged         ,
    wrap_ObjectActiveDescendantChangedCallback,


-- ** childrenChanged #signal:childrenChanged#

    C_ObjectChildrenChangedCallback         ,
    ObjectChildrenChangedCallback           ,
#if defined(ENABLE_OVERLOADING)
    ObjectChildrenChangedSignalInfo         ,
#endif
    afterObjectChildrenChanged              ,
    genClosure_ObjectChildrenChanged        ,
    mk_ObjectChildrenChangedCallback        ,
    noObjectChildrenChangedCallback         ,
    onObjectChildrenChanged                 ,
    wrap_ObjectChildrenChangedCallback      ,


-- ** focusEvent #signal:focusEvent#

    C_ObjectFocusEventCallback              ,
    ObjectFocusEventCallback                ,
#if defined(ENABLE_OVERLOADING)
    ObjectFocusEventSignalInfo              ,
#endif
    afterObjectFocusEvent                   ,
    genClosure_ObjectFocusEvent             ,
    mk_ObjectFocusEventCallback             ,
    noObjectFocusEventCallback              ,
    onObjectFocusEvent                      ,
    wrap_ObjectFocusEventCallback           ,


-- ** propertyChange #signal:propertyChange#

    C_ObjectPropertyChangeCallback          ,
    ObjectPropertyChangeCallback            ,
#if defined(ENABLE_OVERLOADING)
    ObjectPropertyChangeSignalInfo          ,
#endif
    afterObjectPropertyChange               ,
    genClosure_ObjectPropertyChange         ,
    mk_ObjectPropertyChangeCallback         ,
    noObjectPropertyChangeCallback          ,
    onObjectPropertyChange                  ,
    wrap_ObjectPropertyChangeCallback       ,


-- ** stateChange #signal:stateChange#

    C_ObjectStateChangeCallback             ,
    ObjectStateChangeCallback               ,
#if defined(ENABLE_OVERLOADING)
    ObjectStateChangeSignalInfo             ,
#endif
    afterObjectStateChange                  ,
    genClosure_ObjectStateChange            ,
    mk_ObjectStateChangeCallback            ,
    noObjectStateChangeCallback             ,
    onObjectStateChange                     ,
    wrap_ObjectStateChangeCallback          ,


-- ** visibleDataChanged #signal:visibleDataChanged#

    C_ObjectVisibleDataChangedCallback      ,
    ObjectVisibleDataChangedCallback        ,
#if defined(ENABLE_OVERLOADING)
    ObjectVisibleDataChangedSignalInfo      ,
#endif
    afterObjectVisibleDataChanged           ,
    genClosure_ObjectVisibleDataChanged     ,
    mk_ObjectVisibleDataChangedCallback     ,
    noObjectVisibleDataChangedCallback      ,
    onObjectVisibleDataChanged              ,
    wrap_ObjectVisibleDataChangedCallback   ,




    ) 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.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 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.RelationSet as Atk.RelationSet
import {-# SOURCE #-} qualified GI.Atk.Objects.StateSet as Atk.StateSet
import {-# SOURCE #-} qualified GI.Atk.Structs.PropertyValues as Atk.PropertyValues
import qualified GI.GObject.Objects.Object as GObject.Object

-- | Memory-managed wrapper type.
newtype Object = Object (ManagedPtr Object)
    deriving (Object -> Object -> Bool
(Object -> Object -> Bool)
-> (Object -> Object -> Bool) -> Eq Object
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Object -> Object -> Bool
$c/= :: Object -> Object -> Bool
== :: Object -> Object -> Bool
$c== :: Object -> Object -> Bool
Eq)
foreign import ccall "atk_object_get_type"
    c_atk_object_get_type :: IO GType

instance GObject Object where
    gobjectType :: IO GType
gobjectType = IO GType
c_atk_object_get_type
    

-- | Convert 'Object' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue Object where
    toGValue :: Object -> IO GValue
toGValue o :: Object
o = do
        GType
gtype <- IO GType
c_atk_object_get_type
        Object -> (Ptr Object -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Object
o (GType -> (GValue -> Ptr Object -> IO ()) -> Ptr Object -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Object -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO Object
fromGValue gv :: GValue
gv = do
        Ptr Object
ptr <- GValue -> IO (Ptr Object)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Object)
        (ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Object -> Object
Object Ptr Object
ptr
        
    

-- | Type class for types which can be safely cast to `Object`, for instance with `toObject`.
class (GObject o, O.IsDescendantOf Object o) => IsObject o
instance (GObject o, O.IsDescendantOf Object o) => IsObject o

instance O.HasParentTypes Object
type instance O.ParentTypes Object = '[GObject.Object.Object]

-- | Cast to `Object`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toObject :: (MonadIO m, IsObject o) => o -> m Object
toObject :: o -> m Object
toObject = IO Object -> m Object
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Object -> m Object) -> (o -> IO Object) -> o -> m Object
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Object -> Object) -> o -> IO Object
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Object -> Object
Object

-- | A convenience alias for `Nothing` :: `Maybe` `Object`.
noObject :: Maybe Object
noObject :: Maybe Object
noObject = Maybe Object
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveObjectMethod (t :: Symbol) (o :: *) :: * where
    ResolveObjectMethod "addRelationship" o = ObjectAddRelationshipMethodInfo
    ResolveObjectMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveObjectMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveObjectMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveObjectMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveObjectMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveObjectMethod "initialize" o = ObjectInitializeMethodInfo
    ResolveObjectMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveObjectMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveObjectMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveObjectMethod "notifyStateChange" o = ObjectNotifyStateChangeMethodInfo
    ResolveObjectMethod "peekParent" o = ObjectPeekParentMethodInfo
    ResolveObjectMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveObjectMethod "refAccessibleChild" o = ObjectRefAccessibleChildMethodInfo
    ResolveObjectMethod "refRelationSet" o = ObjectRefRelationSetMethodInfo
    ResolveObjectMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveObjectMethod "refStateSet" o = ObjectRefStateSetMethodInfo
    ResolveObjectMethod "removePropertyChangeHandler" o = ObjectRemovePropertyChangeHandlerMethodInfo
    ResolveObjectMethod "removeRelationship" o = ObjectRemoveRelationshipMethodInfo
    ResolveObjectMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveObjectMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveObjectMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveObjectMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveObjectMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveObjectMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveObjectMethod "getAttributes" o = ObjectGetAttributesMethodInfo
    ResolveObjectMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveObjectMethod "getDescription" o = ObjectGetDescriptionMethodInfo
    ResolveObjectMethod "getIndexInParent" o = ObjectGetIndexInParentMethodInfo
    ResolveObjectMethod "getLayer" o = ObjectGetLayerMethodInfo
    ResolveObjectMethod "getMdiZorder" o = ObjectGetMdiZorderMethodInfo
    ResolveObjectMethod "getNAccessibleChildren" o = ObjectGetNAccessibleChildrenMethodInfo
    ResolveObjectMethod "getName" o = ObjectGetNameMethodInfo
    ResolveObjectMethod "getObjectLocale" o = ObjectGetObjectLocaleMethodInfo
    ResolveObjectMethod "getParent" o = ObjectGetParentMethodInfo
    ResolveObjectMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveObjectMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveObjectMethod "getRole" o = ObjectGetRoleMethodInfo
    ResolveObjectMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveObjectMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveObjectMethod "setDescription" o = ObjectSetDescriptionMethodInfo
    ResolveObjectMethod "setName" o = ObjectSetNameMethodInfo
    ResolveObjectMethod "setParent" o = ObjectSetParentMethodInfo
    ResolveObjectMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveObjectMethod "setRole" o = ObjectSetRoleMethodInfo
    ResolveObjectMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveObjectMethod t Object, O.MethodInfo info Object p) => OL.IsLabel t (Object -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- signal Object::active-descendant-changed
-- | The \"active-descendant-changed\" signal is emitted by an object
-- which has the state ATK_STATE_MANAGES_DESCENDANTS when the focus
-- object in the object changes. For instance, a table will emit the
-- signal when the cell in the table which has focus changes.
type ObjectActiveDescendantChangedCallback =
    Maybe Object
    -- ^ /@arg1@/: the newly focused object.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `ObjectActiveDescendantChangedCallback`@.
noObjectActiveDescendantChangedCallback :: Maybe ObjectActiveDescendantChangedCallback
noObjectActiveDescendantChangedCallback :: Maybe ObjectActiveDescendantChangedCallback
noObjectActiveDescendantChangedCallback = Maybe ObjectActiveDescendantChangedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_ObjectActiveDescendantChangedCallback =
    Ptr () ->                               -- object
    Ptr Object ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_ObjectActiveDescendantChangedCallback`.
foreign import ccall "wrapper"
    mk_ObjectActiveDescendantChangedCallback :: C_ObjectActiveDescendantChangedCallback -> IO (FunPtr C_ObjectActiveDescendantChangedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_ObjectActiveDescendantChanged :: MonadIO m => ObjectActiveDescendantChangedCallback -> m (GClosure C_ObjectActiveDescendantChangedCallback)
genClosure_ObjectActiveDescendantChanged :: ObjectActiveDescendantChangedCallback
-> m (GClosure C_ObjectActiveDescendantChangedCallback)
genClosure_ObjectActiveDescendantChanged cb :: ObjectActiveDescendantChangedCallback
cb = IO (GClosure C_ObjectActiveDescendantChangedCallback)
-> m (GClosure C_ObjectActiveDescendantChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ObjectActiveDescendantChangedCallback)
 -> m (GClosure C_ObjectActiveDescendantChangedCallback))
-> IO (GClosure C_ObjectActiveDescendantChangedCallback)
-> m (GClosure C_ObjectActiveDescendantChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ObjectActiveDescendantChangedCallback
cb' = ObjectActiveDescendantChangedCallback
-> C_ObjectActiveDescendantChangedCallback
wrap_ObjectActiveDescendantChangedCallback ObjectActiveDescendantChangedCallback
cb
    C_ObjectActiveDescendantChangedCallback
-> IO (FunPtr C_ObjectActiveDescendantChangedCallback)
mk_ObjectActiveDescendantChangedCallback C_ObjectActiveDescendantChangedCallback
cb' IO (FunPtr C_ObjectActiveDescendantChangedCallback)
-> (FunPtr C_ObjectActiveDescendantChangedCallback
    -> IO (GClosure C_ObjectActiveDescendantChangedCallback))
-> IO (GClosure C_ObjectActiveDescendantChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ObjectActiveDescendantChangedCallback
-> IO (GClosure C_ObjectActiveDescendantChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `ObjectActiveDescendantChangedCallback` into a `C_ObjectActiveDescendantChangedCallback`.
wrap_ObjectActiveDescendantChangedCallback ::
    ObjectActiveDescendantChangedCallback ->
    C_ObjectActiveDescendantChangedCallback
wrap_ObjectActiveDescendantChangedCallback :: ObjectActiveDescendantChangedCallback
-> C_ObjectActiveDescendantChangedCallback
wrap_ObjectActiveDescendantChangedCallback _cb :: ObjectActiveDescendantChangedCallback
_cb _ arg1 :: Ptr Object
arg1 _ = do
    Maybe Object
maybeArg1 <-
        if Ptr Object
arg1 Ptr Object -> Ptr Object -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Object
forall a. Ptr a
nullPtr
        then Maybe Object -> IO (Maybe Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Object
forall a. Maybe a
Nothing
        else do
            Object
arg1' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
Object) Ptr Object
arg1
            Maybe Object -> IO (Maybe Object)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Object -> IO (Maybe Object))
-> Maybe Object -> IO (Maybe Object)
forall a b. (a -> b) -> a -> b
$ Object -> Maybe Object
forall a. a -> Maybe a
Just Object
arg1'
    ObjectActiveDescendantChangedCallback
_cb  Maybe Object
maybeArg1


-- | Connect a signal handler for the [activeDescendantChanged](#signal:activeDescendantChanged) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' object #activeDescendantChanged callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@active-descendant-changed::detail@” instead.
-- 
onObjectActiveDescendantChanged :: (IsObject a, MonadIO m) => a -> P.Maybe T.Text -> ObjectActiveDescendantChangedCallback -> m SignalHandlerId
onObjectActiveDescendantChanged :: a
-> Maybe Text
-> ObjectActiveDescendantChangedCallback
-> m SignalHandlerId
onObjectActiveDescendantChanged obj :: a
obj detail :: Maybe Text
detail cb :: ObjectActiveDescendantChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ObjectActiveDescendantChangedCallback
cb' = ObjectActiveDescendantChangedCallback
-> C_ObjectActiveDescendantChangedCallback
wrap_ObjectActiveDescendantChangedCallback ObjectActiveDescendantChangedCallback
cb
    FunPtr C_ObjectActiveDescendantChangedCallback
cb'' <- C_ObjectActiveDescendantChangedCallback
-> IO (FunPtr C_ObjectActiveDescendantChangedCallback)
mk_ObjectActiveDescendantChangedCallback C_ObjectActiveDescendantChangedCallback
cb'
    a
-> Text
-> FunPtr C_ObjectActiveDescendantChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "active-descendant-changed" FunPtr C_ObjectActiveDescendantChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
detail

-- | Connect a signal handler for the [activeDescendantChanged](#signal:activeDescendantChanged) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' object #activeDescendantChanged callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@active-descendant-changed::detail@” instead.
-- 
afterObjectActiveDescendantChanged :: (IsObject a, MonadIO m) => a -> P.Maybe T.Text -> ObjectActiveDescendantChangedCallback -> m SignalHandlerId
afterObjectActiveDescendantChanged :: a
-> Maybe Text
-> ObjectActiveDescendantChangedCallback
-> m SignalHandlerId
afterObjectActiveDescendantChanged obj :: a
obj detail :: Maybe Text
detail cb :: ObjectActiveDescendantChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ObjectActiveDescendantChangedCallback
cb' = ObjectActiveDescendantChangedCallback
-> C_ObjectActiveDescendantChangedCallback
wrap_ObjectActiveDescendantChangedCallback ObjectActiveDescendantChangedCallback
cb
    FunPtr C_ObjectActiveDescendantChangedCallback
cb'' <- C_ObjectActiveDescendantChangedCallback
-> IO (FunPtr C_ObjectActiveDescendantChangedCallback)
mk_ObjectActiveDescendantChangedCallback C_ObjectActiveDescendantChangedCallback
cb'
    a
-> Text
-> FunPtr C_ObjectActiveDescendantChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "active-descendant-changed" FunPtr C_ObjectActiveDescendantChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
detail


#if defined(ENABLE_OVERLOADING)
data ObjectActiveDescendantChangedSignalInfo
instance SignalInfo ObjectActiveDescendantChangedSignalInfo where
    type HaskellCallbackType ObjectActiveDescendantChangedSignalInfo = ObjectActiveDescendantChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ObjectActiveDescendantChangedCallback cb
        cb'' <- mk_ObjectActiveDescendantChangedCallback cb'
        connectSignalFunPtr obj "active-descendant-changed" cb'' connectMode detail

#endif

-- signal Object::children-changed
-- | The signal \"children-changed\" is emitted when a child is added or
-- removed form an object. It supports two details: \"add\" and
-- \"remove\"
type ObjectChildrenChangedCallback =
    Word32
    -- ^ /@arg1@/: The index of the added or removed child. The value can be
    -- -1. This is used if the value is not known by the implementor
    -- when the child is added\/removed or irrelevant.
    -> Maybe Object
    -- ^ /@arg2@/: A gpointer to the child AtkObject which was added or
    -- removed. If the child was removed, it is possible that it is not
    -- available for the implementor. In that case this pointer can be
    -- NULL.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `ObjectChildrenChangedCallback`@.
noObjectChildrenChangedCallback :: Maybe ObjectChildrenChangedCallback
noObjectChildrenChangedCallback :: Maybe ObjectChildrenChangedCallback
noObjectChildrenChangedCallback = Maybe ObjectChildrenChangedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_ObjectChildrenChangedCallback =
    Ptr () ->                               -- object
    Word32 ->
    Ptr Object ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_ObjectChildrenChangedCallback`.
foreign import ccall "wrapper"
    mk_ObjectChildrenChangedCallback :: C_ObjectChildrenChangedCallback -> IO (FunPtr C_ObjectChildrenChangedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_ObjectChildrenChanged :: MonadIO m => ObjectChildrenChangedCallback -> m (GClosure C_ObjectChildrenChangedCallback)
genClosure_ObjectChildrenChanged :: ObjectChildrenChangedCallback
-> m (GClosure C_ObjectChildrenChangedCallback)
genClosure_ObjectChildrenChanged cb :: ObjectChildrenChangedCallback
cb = IO (GClosure C_ObjectChildrenChangedCallback)
-> m (GClosure C_ObjectChildrenChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ObjectChildrenChangedCallback)
 -> m (GClosure C_ObjectChildrenChangedCallback))
-> IO (GClosure C_ObjectChildrenChangedCallback)
-> m (GClosure C_ObjectChildrenChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ObjectChildrenChangedCallback
cb' = ObjectChildrenChangedCallback -> C_ObjectChildrenChangedCallback
wrap_ObjectChildrenChangedCallback ObjectChildrenChangedCallback
cb
    C_ObjectChildrenChangedCallback
-> IO (FunPtr C_ObjectChildrenChangedCallback)
mk_ObjectChildrenChangedCallback C_ObjectChildrenChangedCallback
cb' IO (FunPtr C_ObjectChildrenChangedCallback)
-> (FunPtr C_ObjectChildrenChangedCallback
    -> IO (GClosure C_ObjectChildrenChangedCallback))
-> IO (GClosure C_ObjectChildrenChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ObjectChildrenChangedCallback
-> IO (GClosure C_ObjectChildrenChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `ObjectChildrenChangedCallback` into a `C_ObjectChildrenChangedCallback`.
wrap_ObjectChildrenChangedCallback ::
    ObjectChildrenChangedCallback ->
    C_ObjectChildrenChangedCallback
wrap_ObjectChildrenChangedCallback :: ObjectChildrenChangedCallback -> C_ObjectChildrenChangedCallback
wrap_ObjectChildrenChangedCallback _cb :: ObjectChildrenChangedCallback
_cb _ arg1 :: Word32
arg1 arg2 :: Ptr Object
arg2 _ = do
    Maybe Object
maybeArg2 <-
        if Ptr Object
arg2 Ptr Object -> Ptr Object -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Object
forall a. Ptr a
nullPtr
        then Maybe Object -> IO (Maybe Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Object
forall a. Maybe a
Nothing
        else do
            Object
arg2' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
Object) Ptr Object
arg2
            Maybe Object -> IO (Maybe Object)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Object -> IO (Maybe Object))
-> Maybe Object -> IO (Maybe Object)
forall a b. (a -> b) -> a -> b
$ Object -> Maybe Object
forall a. a -> Maybe a
Just Object
arg2'
    ObjectChildrenChangedCallback
_cb  Word32
arg1 Maybe Object
maybeArg2


-- | Connect a signal handler for the [childrenChanged](#signal:childrenChanged) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' object #childrenChanged callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@children-changed::detail@” instead.
-- 
onObjectChildrenChanged :: (IsObject a, MonadIO m) => a -> P.Maybe T.Text -> ObjectChildrenChangedCallback -> m SignalHandlerId
onObjectChildrenChanged :: a
-> Maybe Text -> ObjectChildrenChangedCallback -> m SignalHandlerId
onObjectChildrenChanged obj :: a
obj detail :: Maybe Text
detail cb :: ObjectChildrenChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ObjectChildrenChangedCallback
cb' = ObjectChildrenChangedCallback -> C_ObjectChildrenChangedCallback
wrap_ObjectChildrenChangedCallback ObjectChildrenChangedCallback
cb
    FunPtr C_ObjectChildrenChangedCallback
cb'' <- C_ObjectChildrenChangedCallback
-> IO (FunPtr C_ObjectChildrenChangedCallback)
mk_ObjectChildrenChangedCallback C_ObjectChildrenChangedCallback
cb'
    a
-> Text
-> FunPtr C_ObjectChildrenChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "children-changed" FunPtr C_ObjectChildrenChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
detail

-- | Connect a signal handler for the [childrenChanged](#signal:childrenChanged) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' object #childrenChanged callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@children-changed::detail@” instead.
-- 
afterObjectChildrenChanged :: (IsObject a, MonadIO m) => a -> P.Maybe T.Text -> ObjectChildrenChangedCallback -> m SignalHandlerId
afterObjectChildrenChanged :: a
-> Maybe Text -> ObjectChildrenChangedCallback -> m SignalHandlerId
afterObjectChildrenChanged obj :: a
obj detail :: Maybe Text
detail cb :: ObjectChildrenChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ObjectChildrenChangedCallback
cb' = ObjectChildrenChangedCallback -> C_ObjectChildrenChangedCallback
wrap_ObjectChildrenChangedCallback ObjectChildrenChangedCallback
cb
    FunPtr C_ObjectChildrenChangedCallback
cb'' <- C_ObjectChildrenChangedCallback
-> IO (FunPtr C_ObjectChildrenChangedCallback)
mk_ObjectChildrenChangedCallback C_ObjectChildrenChangedCallback
cb'
    a
-> Text
-> FunPtr C_ObjectChildrenChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "children-changed" FunPtr C_ObjectChildrenChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
detail


#if defined(ENABLE_OVERLOADING)
data ObjectChildrenChangedSignalInfo
instance SignalInfo ObjectChildrenChangedSignalInfo where
    type HaskellCallbackType ObjectChildrenChangedSignalInfo = ObjectChildrenChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ObjectChildrenChangedCallback cb
        cb'' <- mk_ObjectChildrenChangedCallback cb'
        connectSignalFunPtr obj "children-changed" cb'' connectMode detail

#endif

-- signal Object::focus-event
{-# DEPRECATED ObjectFocusEventCallback ["(Since version 2.9.4)","Use the [stateChange](\"GI.Atk.Objects.Object#signal:stateChange\") signal instead."] #-}
-- | The signal \"focus-event\" is emitted when an object gained or lost
-- focus.
type ObjectFocusEventCallback =
    Bool
    -- ^ /@arg1@/: a boolean value which indicates whether the object gained
    -- or lost focus.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `ObjectFocusEventCallback`@.
noObjectFocusEventCallback :: Maybe ObjectFocusEventCallback
noObjectFocusEventCallback :: Maybe ObjectFocusEventCallback
noObjectFocusEventCallback = Maybe ObjectFocusEventCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_ObjectFocusEventCallback =
    Ptr () ->                               -- object
    CInt ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_ObjectFocusEventCallback`.
foreign import ccall "wrapper"
    mk_ObjectFocusEventCallback :: C_ObjectFocusEventCallback -> IO (FunPtr C_ObjectFocusEventCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_ObjectFocusEvent :: MonadIO m => ObjectFocusEventCallback -> m (GClosure C_ObjectFocusEventCallback)
genClosure_ObjectFocusEvent :: ObjectFocusEventCallback -> m (GClosure C_ObjectFocusEventCallback)
genClosure_ObjectFocusEvent cb :: ObjectFocusEventCallback
cb = IO (GClosure C_ObjectFocusEventCallback)
-> m (GClosure C_ObjectFocusEventCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ObjectFocusEventCallback)
 -> m (GClosure C_ObjectFocusEventCallback))
-> IO (GClosure C_ObjectFocusEventCallback)
-> m (GClosure C_ObjectFocusEventCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ObjectFocusEventCallback
cb' = ObjectFocusEventCallback -> C_ObjectFocusEventCallback
wrap_ObjectFocusEventCallback ObjectFocusEventCallback
cb
    C_ObjectFocusEventCallback
-> IO (FunPtr C_ObjectFocusEventCallback)
mk_ObjectFocusEventCallback C_ObjectFocusEventCallback
cb' IO (FunPtr C_ObjectFocusEventCallback)
-> (FunPtr C_ObjectFocusEventCallback
    -> IO (GClosure C_ObjectFocusEventCallback))
-> IO (GClosure C_ObjectFocusEventCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ObjectFocusEventCallback
-> IO (GClosure C_ObjectFocusEventCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `ObjectFocusEventCallback` into a `C_ObjectFocusEventCallback`.
wrap_ObjectFocusEventCallback ::
    ObjectFocusEventCallback ->
    C_ObjectFocusEventCallback
wrap_ObjectFocusEventCallback :: ObjectFocusEventCallback -> C_ObjectFocusEventCallback
wrap_ObjectFocusEventCallback _cb :: ObjectFocusEventCallback
_cb _ arg1 :: CInt
arg1 _ = do
    let arg1' :: Bool
arg1' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
arg1
    ObjectFocusEventCallback
_cb  Bool
arg1'


-- | Connect a signal handler for the [focusEvent](#signal:focusEvent) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' object #focusEvent callback
-- @
-- 
-- 
onObjectFocusEvent :: (IsObject a, MonadIO m) => a -> ObjectFocusEventCallback -> m SignalHandlerId
onObjectFocusEvent :: a -> ObjectFocusEventCallback -> m SignalHandlerId
onObjectFocusEvent obj :: a
obj cb :: ObjectFocusEventCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ObjectFocusEventCallback
cb' = ObjectFocusEventCallback -> C_ObjectFocusEventCallback
wrap_ObjectFocusEventCallback ObjectFocusEventCallback
cb
    FunPtr C_ObjectFocusEventCallback
cb'' <- C_ObjectFocusEventCallback
-> IO (FunPtr C_ObjectFocusEventCallback)
mk_ObjectFocusEventCallback C_ObjectFocusEventCallback
cb'
    a
-> Text
-> FunPtr C_ObjectFocusEventCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "focus-event" FunPtr C_ObjectFocusEventCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [focusEvent](#signal:focusEvent) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' object #focusEvent callback
-- @
-- 
-- 
afterObjectFocusEvent :: (IsObject a, MonadIO m) => a -> ObjectFocusEventCallback -> m SignalHandlerId
afterObjectFocusEvent :: a -> ObjectFocusEventCallback -> m SignalHandlerId
afterObjectFocusEvent obj :: a
obj cb :: ObjectFocusEventCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ObjectFocusEventCallback
cb' = ObjectFocusEventCallback -> C_ObjectFocusEventCallback
wrap_ObjectFocusEventCallback ObjectFocusEventCallback
cb
    FunPtr C_ObjectFocusEventCallback
cb'' <- C_ObjectFocusEventCallback
-> IO (FunPtr C_ObjectFocusEventCallback)
mk_ObjectFocusEventCallback C_ObjectFocusEventCallback
cb'
    a
-> Text
-> FunPtr C_ObjectFocusEventCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "focus-event" FunPtr C_ObjectFocusEventCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data ObjectFocusEventSignalInfo
instance SignalInfo ObjectFocusEventSignalInfo where
    type HaskellCallbackType ObjectFocusEventSignalInfo = ObjectFocusEventCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ObjectFocusEventCallback cb
        cb'' <- mk_ObjectFocusEventCallback cb'
        connectSignalFunPtr obj "focus-event" cb'' connectMode detail

#endif

-- signal Object::property-change
-- | The signal \"property-change\" is emitted when an object\'s property
-- value changes. /@arg1@/ contains an t'GI.Atk.Structs.PropertyValues.PropertyValues' with the name
-- and the new value of the property whose value has changed. Note
-- that, as with GObject notify, getting this signal does not
-- guarantee that the value of the property has actually changed; it
-- may also be emitted when the setter of the property is called to
-- reinstate the previous value.
-- 
-- Toolkit implementor note: ATK implementors should use
-- 'GI.GObject.Objects.Object.objectNotify' to emit property-changed
-- notifications. t'GI.Atk.Objects.Object.Object'::@/property-changed/@ is needed by the
-- implementation of @/atk_add_global_event_listener()/@ because GObject
-- notify doesn\'t support emission hooks.
type ObjectPropertyChangeCallback =
    Maybe Atk.PropertyValues.PropertyValues
    -- ^ /@arg1@/: an t'GI.Atk.Structs.PropertyValues.PropertyValues' containing the new
    -- value of the property which changed.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `ObjectPropertyChangeCallback`@.
noObjectPropertyChangeCallback :: Maybe ObjectPropertyChangeCallback
noObjectPropertyChangeCallback :: Maybe ObjectPropertyChangeCallback
noObjectPropertyChangeCallback = Maybe ObjectPropertyChangeCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_ObjectPropertyChangeCallback =
    Ptr () ->                               -- object
    Ptr Atk.PropertyValues.PropertyValues ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_ObjectPropertyChangeCallback`.
foreign import ccall "wrapper"
    mk_ObjectPropertyChangeCallback :: C_ObjectPropertyChangeCallback -> IO (FunPtr C_ObjectPropertyChangeCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_ObjectPropertyChange :: MonadIO m => ObjectPropertyChangeCallback -> m (GClosure C_ObjectPropertyChangeCallback)
genClosure_ObjectPropertyChange :: ObjectPropertyChangeCallback
-> m (GClosure C_ObjectPropertyChangeCallback)
genClosure_ObjectPropertyChange cb :: ObjectPropertyChangeCallback
cb = IO (GClosure C_ObjectPropertyChangeCallback)
-> m (GClosure C_ObjectPropertyChangeCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ObjectPropertyChangeCallback)
 -> m (GClosure C_ObjectPropertyChangeCallback))
-> IO (GClosure C_ObjectPropertyChangeCallback)
-> m (GClosure C_ObjectPropertyChangeCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ObjectPropertyChangeCallback
cb' = ObjectPropertyChangeCallback -> C_ObjectPropertyChangeCallback
wrap_ObjectPropertyChangeCallback ObjectPropertyChangeCallback
cb
    C_ObjectPropertyChangeCallback
-> IO (FunPtr C_ObjectPropertyChangeCallback)
mk_ObjectPropertyChangeCallback C_ObjectPropertyChangeCallback
cb' IO (FunPtr C_ObjectPropertyChangeCallback)
-> (FunPtr C_ObjectPropertyChangeCallback
    -> IO (GClosure C_ObjectPropertyChangeCallback))
-> IO (GClosure C_ObjectPropertyChangeCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ObjectPropertyChangeCallback
-> IO (GClosure C_ObjectPropertyChangeCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `ObjectPropertyChangeCallback` into a `C_ObjectPropertyChangeCallback`.
wrap_ObjectPropertyChangeCallback ::
    ObjectPropertyChangeCallback ->
    C_ObjectPropertyChangeCallback
wrap_ObjectPropertyChangeCallback :: ObjectPropertyChangeCallback -> C_ObjectPropertyChangeCallback
wrap_ObjectPropertyChangeCallback _cb :: ObjectPropertyChangeCallback
_cb _ arg1 :: Ptr PropertyValues
arg1 _ = do
    Maybe PropertyValues
maybeArg1 <-
        if Ptr PropertyValues
arg1 Ptr PropertyValues -> Ptr PropertyValues -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr PropertyValues
forall a. Ptr a
nullPtr
        then Maybe PropertyValues -> IO (Maybe PropertyValues)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PropertyValues
forall a. Maybe a
Nothing
        else do
            PropertyValues
arg1' <- ((ManagedPtr PropertyValues -> PropertyValues)
-> Ptr PropertyValues -> IO PropertyValues
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr PropertyValues -> PropertyValues
Atk.PropertyValues.PropertyValues) Ptr PropertyValues
arg1
            Maybe PropertyValues -> IO (Maybe PropertyValues)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe PropertyValues -> IO (Maybe PropertyValues))
-> Maybe PropertyValues -> IO (Maybe PropertyValues)
forall a b. (a -> b) -> a -> b
$ PropertyValues -> Maybe PropertyValues
forall a. a -> Maybe a
Just PropertyValues
arg1'
    ObjectPropertyChangeCallback
_cb  Maybe PropertyValues
maybeArg1


-- | Connect a signal handler for the [propertyChange](#signal:propertyChange) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' object #propertyChange callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@property-change::detail@” instead.
-- 
onObjectPropertyChange :: (IsObject a, MonadIO m) => a -> P.Maybe T.Text -> ObjectPropertyChangeCallback -> m SignalHandlerId
onObjectPropertyChange :: a
-> Maybe Text -> ObjectPropertyChangeCallback -> m SignalHandlerId
onObjectPropertyChange obj :: a
obj detail :: Maybe Text
detail cb :: ObjectPropertyChangeCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ObjectPropertyChangeCallback
cb' = ObjectPropertyChangeCallback -> C_ObjectPropertyChangeCallback
wrap_ObjectPropertyChangeCallback ObjectPropertyChangeCallback
cb
    FunPtr C_ObjectPropertyChangeCallback
cb'' <- C_ObjectPropertyChangeCallback
-> IO (FunPtr C_ObjectPropertyChangeCallback)
mk_ObjectPropertyChangeCallback C_ObjectPropertyChangeCallback
cb'
    a
-> Text
-> FunPtr C_ObjectPropertyChangeCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "property-change" FunPtr C_ObjectPropertyChangeCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
detail

-- | Connect a signal handler for the [propertyChange](#signal:propertyChange) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' object #propertyChange callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@property-change::detail@” instead.
-- 
afterObjectPropertyChange :: (IsObject a, MonadIO m) => a -> P.Maybe T.Text -> ObjectPropertyChangeCallback -> m SignalHandlerId
afterObjectPropertyChange :: a
-> Maybe Text -> ObjectPropertyChangeCallback -> m SignalHandlerId
afterObjectPropertyChange obj :: a
obj detail :: Maybe Text
detail cb :: ObjectPropertyChangeCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ObjectPropertyChangeCallback
cb' = ObjectPropertyChangeCallback -> C_ObjectPropertyChangeCallback
wrap_ObjectPropertyChangeCallback ObjectPropertyChangeCallback
cb
    FunPtr C_ObjectPropertyChangeCallback
cb'' <- C_ObjectPropertyChangeCallback
-> IO (FunPtr C_ObjectPropertyChangeCallback)
mk_ObjectPropertyChangeCallback C_ObjectPropertyChangeCallback
cb'
    a
-> Text
-> FunPtr C_ObjectPropertyChangeCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "property-change" FunPtr C_ObjectPropertyChangeCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
detail


#if defined(ENABLE_OVERLOADING)
data ObjectPropertyChangeSignalInfo
instance SignalInfo ObjectPropertyChangeSignalInfo where
    type HaskellCallbackType ObjectPropertyChangeSignalInfo = ObjectPropertyChangeCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ObjectPropertyChangeCallback cb
        cb'' <- mk_ObjectPropertyChangeCallback cb'
        connectSignalFunPtr obj "property-change" cb'' connectMode detail

#endif

-- signal Object::state-change
-- | The \"state-change\" signal is emitted when an object\'s state
-- changes.  The detail value identifies the state type which has
-- changed.
type ObjectStateChangeCallback =
    T.Text
    -- ^ /@arg1@/: The name of the state which has changed
    -> Bool
    -- ^ /@arg2@/: A boolean which indicates whether the state has been set or unset.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `ObjectStateChangeCallback`@.
noObjectStateChangeCallback :: Maybe ObjectStateChangeCallback
noObjectStateChangeCallback :: Maybe ObjectStateChangeCallback
noObjectStateChangeCallback = Maybe ObjectStateChangeCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_ObjectStateChangeCallback =
    Ptr () ->                               -- object
    CString ->
    CInt ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_ObjectStateChangeCallback`.
foreign import ccall "wrapper"
    mk_ObjectStateChangeCallback :: C_ObjectStateChangeCallback -> IO (FunPtr C_ObjectStateChangeCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_ObjectStateChange :: MonadIO m => ObjectStateChangeCallback -> m (GClosure C_ObjectStateChangeCallback)
genClosure_ObjectStateChange :: ObjectStateChangeCallback
-> m (GClosure C_ObjectStateChangeCallback)
genClosure_ObjectStateChange cb :: ObjectStateChangeCallback
cb = IO (GClosure C_ObjectStateChangeCallback)
-> m (GClosure C_ObjectStateChangeCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ObjectStateChangeCallback)
 -> m (GClosure C_ObjectStateChangeCallback))
-> IO (GClosure C_ObjectStateChangeCallback)
-> m (GClosure C_ObjectStateChangeCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ObjectStateChangeCallback
cb' = ObjectStateChangeCallback -> C_ObjectStateChangeCallback
wrap_ObjectStateChangeCallback ObjectStateChangeCallback
cb
    C_ObjectStateChangeCallback
-> IO (FunPtr C_ObjectStateChangeCallback)
mk_ObjectStateChangeCallback C_ObjectStateChangeCallback
cb' IO (FunPtr C_ObjectStateChangeCallback)
-> (FunPtr C_ObjectStateChangeCallback
    -> IO (GClosure C_ObjectStateChangeCallback))
-> IO (GClosure C_ObjectStateChangeCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ObjectStateChangeCallback
-> IO (GClosure C_ObjectStateChangeCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `ObjectStateChangeCallback` into a `C_ObjectStateChangeCallback`.
wrap_ObjectStateChangeCallback ::
    ObjectStateChangeCallback ->
    C_ObjectStateChangeCallback
wrap_ObjectStateChangeCallback :: ObjectStateChangeCallback -> C_ObjectStateChangeCallback
wrap_ObjectStateChangeCallback _cb :: ObjectStateChangeCallback
_cb _ arg1 :: CString
arg1 arg2 :: CInt
arg2 _ = do
    Text
arg1' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
arg1
    let arg2' :: Bool
arg2' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
arg2
    ObjectStateChangeCallback
_cb  Text
arg1' Bool
arg2'


-- | Connect a signal handler for the [stateChange](#signal:stateChange) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' object #stateChange callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@state-change::detail@” instead.
-- 
onObjectStateChange :: (IsObject a, MonadIO m) => a -> P.Maybe T.Text -> ObjectStateChangeCallback -> m SignalHandlerId
onObjectStateChange :: a -> Maybe Text -> ObjectStateChangeCallback -> m SignalHandlerId
onObjectStateChange obj :: a
obj detail :: Maybe Text
detail cb :: ObjectStateChangeCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ObjectStateChangeCallback
cb' = ObjectStateChangeCallback -> C_ObjectStateChangeCallback
wrap_ObjectStateChangeCallback ObjectStateChangeCallback
cb
    FunPtr C_ObjectStateChangeCallback
cb'' <- C_ObjectStateChangeCallback
-> IO (FunPtr C_ObjectStateChangeCallback)
mk_ObjectStateChangeCallback C_ObjectStateChangeCallback
cb'
    a
-> Text
-> FunPtr C_ObjectStateChangeCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "state-change" FunPtr C_ObjectStateChangeCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
detail

-- | Connect a signal handler for the [stateChange](#signal:stateChange) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' object #stateChange callback
-- @
-- 
-- This signal admits a optional parameter @detail@.
-- If it's not @Nothing@, we will connect to “@state-change::detail@” instead.
-- 
afterObjectStateChange :: (IsObject a, MonadIO m) => a -> P.Maybe T.Text -> ObjectStateChangeCallback -> m SignalHandlerId
afterObjectStateChange :: a -> Maybe Text -> ObjectStateChangeCallback -> m SignalHandlerId
afterObjectStateChange obj :: a
obj detail :: Maybe Text
detail cb :: ObjectStateChangeCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ObjectStateChangeCallback
cb' = ObjectStateChangeCallback -> C_ObjectStateChangeCallback
wrap_ObjectStateChangeCallback ObjectStateChangeCallback
cb
    FunPtr C_ObjectStateChangeCallback
cb'' <- C_ObjectStateChangeCallback
-> IO (FunPtr C_ObjectStateChangeCallback)
mk_ObjectStateChangeCallback C_ObjectStateChangeCallback
cb'
    a
-> Text
-> FunPtr C_ObjectStateChangeCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "state-change" FunPtr C_ObjectStateChangeCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
detail


#if defined(ENABLE_OVERLOADING)
data ObjectStateChangeSignalInfo
instance SignalInfo ObjectStateChangeSignalInfo where
    type HaskellCallbackType ObjectStateChangeSignalInfo = ObjectStateChangeCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ObjectStateChangeCallback cb
        cb'' <- mk_ObjectStateChangeCallback cb'
        connectSignalFunPtr obj "state-change" cb'' connectMode detail

#endif

-- signal Object::visible-data-changed
-- | The \"visible-data-changed\" signal is emitted when the visual
-- appearance of the object changed.
type ObjectVisibleDataChangedCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `ObjectVisibleDataChangedCallback`@.
noObjectVisibleDataChangedCallback :: Maybe ObjectVisibleDataChangedCallback
noObjectVisibleDataChangedCallback :: Maybe (IO ())
noObjectVisibleDataChangedCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_ObjectVisibleDataChangedCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_ObjectVisibleDataChangedCallback`.
foreign import ccall "wrapper"
    mk_ObjectVisibleDataChangedCallback :: C_ObjectVisibleDataChangedCallback -> IO (FunPtr C_ObjectVisibleDataChangedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_ObjectVisibleDataChanged :: MonadIO m => ObjectVisibleDataChangedCallback -> m (GClosure C_ObjectVisibleDataChangedCallback)
genClosure_ObjectVisibleDataChanged :: IO () -> m (GClosure C_ObjectVisibleDataChangedCallback)
genClosure_ObjectVisibleDataChanged cb :: IO ()
cb = IO (GClosure C_ObjectVisibleDataChangedCallback)
-> m (GClosure C_ObjectVisibleDataChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_ObjectVisibleDataChangedCallback)
 -> m (GClosure C_ObjectVisibleDataChangedCallback))
-> IO (GClosure C_ObjectVisibleDataChangedCallback)
-> m (GClosure C_ObjectVisibleDataChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ObjectVisibleDataChangedCallback
cb' = IO () -> C_ObjectVisibleDataChangedCallback
wrap_ObjectVisibleDataChangedCallback IO ()
cb
    C_ObjectVisibleDataChangedCallback
-> IO (FunPtr C_ObjectVisibleDataChangedCallback)
mk_ObjectVisibleDataChangedCallback C_ObjectVisibleDataChangedCallback
cb' IO (FunPtr C_ObjectVisibleDataChangedCallback)
-> (FunPtr C_ObjectVisibleDataChangedCallback
    -> IO (GClosure C_ObjectVisibleDataChangedCallback))
-> IO (GClosure C_ObjectVisibleDataChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_ObjectVisibleDataChangedCallback
-> IO (GClosure C_ObjectVisibleDataChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `ObjectVisibleDataChangedCallback` into a `C_ObjectVisibleDataChangedCallback`.
wrap_ObjectVisibleDataChangedCallback ::
    ObjectVisibleDataChangedCallback ->
    C_ObjectVisibleDataChangedCallback
wrap_ObjectVisibleDataChangedCallback :: IO () -> C_ObjectVisibleDataChangedCallback
wrap_ObjectVisibleDataChangedCallback _cb :: IO ()
_cb _ _ = do
    IO ()
_cb 


-- | Connect a signal handler for the [visibleDataChanged](#signal:visibleDataChanged) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' object #visibleDataChanged callback
-- @
-- 
-- 
onObjectVisibleDataChanged :: (IsObject a, MonadIO m) => a -> ObjectVisibleDataChangedCallback -> m SignalHandlerId
onObjectVisibleDataChanged :: a -> IO () -> m SignalHandlerId
onObjectVisibleDataChanged obj :: a
obj cb :: IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ObjectVisibleDataChangedCallback
cb' = IO () -> C_ObjectVisibleDataChangedCallback
wrap_ObjectVisibleDataChangedCallback IO ()
cb
    FunPtr C_ObjectVisibleDataChangedCallback
cb'' <- C_ObjectVisibleDataChangedCallback
-> IO (FunPtr C_ObjectVisibleDataChangedCallback)
mk_ObjectVisibleDataChangedCallback C_ObjectVisibleDataChangedCallback
cb'
    a
-> Text
-> FunPtr C_ObjectVisibleDataChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "visible-data-changed" FunPtr C_ObjectVisibleDataChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [visibleDataChanged](#signal:visibleDataChanged) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' object #visibleDataChanged callback
-- @
-- 
-- 
afterObjectVisibleDataChanged :: (IsObject a, MonadIO m) => a -> ObjectVisibleDataChangedCallback -> m SignalHandlerId
afterObjectVisibleDataChanged :: a -> IO () -> m SignalHandlerId
afterObjectVisibleDataChanged obj :: a
obj cb :: IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_ObjectVisibleDataChangedCallback
cb' = IO () -> C_ObjectVisibleDataChangedCallback
wrap_ObjectVisibleDataChangedCallback IO ()
cb
    FunPtr C_ObjectVisibleDataChangedCallback
cb'' <- C_ObjectVisibleDataChangedCallback
-> IO (FunPtr C_ObjectVisibleDataChangedCallback)
mk_ObjectVisibleDataChangedCallback C_ObjectVisibleDataChangedCallback
cb'
    a
-> Text
-> FunPtr C_ObjectVisibleDataChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "visible-data-changed" FunPtr C_ObjectVisibleDataChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data ObjectVisibleDataChangedSignalInfo
instance SignalInfo ObjectVisibleDataChangedSignalInfo where
    type HaskellCallbackType ObjectVisibleDataChangedSignalInfo = ObjectVisibleDataChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ObjectVisibleDataChangedCallback cb
        cb'' <- mk_ObjectVisibleDataChangedCallback cb'
        connectSignalFunPtr obj "visible-data-changed" cb'' connectMode detail

#endif

-- VVV Prop "accessible-component-layer"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@accessible-component-layer@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' object #accessibleComponentLayer
-- @
getObjectAccessibleComponentLayer :: (MonadIO m, IsObject o) => o -> m Int32
getObjectAccessibleComponentLayer :: o -> m Int32
getObjectAccessibleComponentLayer obj :: o
obj = 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
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "accessible-component-layer"

#if defined(ENABLE_OVERLOADING)
data ObjectAccessibleComponentLayerPropertyInfo
instance AttrInfo ObjectAccessibleComponentLayerPropertyInfo where
    type AttrAllowedOps ObjectAccessibleComponentLayerPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint ObjectAccessibleComponentLayerPropertyInfo = IsObject
    type AttrSetTypeConstraint ObjectAccessibleComponentLayerPropertyInfo = (~) ()
    type AttrTransferTypeConstraint ObjectAccessibleComponentLayerPropertyInfo = (~) ()
    type AttrTransferType ObjectAccessibleComponentLayerPropertyInfo = ()
    type AttrGetType ObjectAccessibleComponentLayerPropertyInfo = Int32
    type AttrLabel ObjectAccessibleComponentLayerPropertyInfo = "accessible-component-layer"
    type AttrOrigin ObjectAccessibleComponentLayerPropertyInfo = Object
    attrGet = getObjectAccessibleComponentLayer
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "accessible-component-mdi-zorder"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@accessible-component-mdi-zorder@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' object #accessibleComponentMdiZorder
-- @
getObjectAccessibleComponentMdiZorder :: (MonadIO m, IsObject o) => o -> m Int32
getObjectAccessibleComponentMdiZorder :: o -> m Int32
getObjectAccessibleComponentMdiZorder obj :: o
obj = 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
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "accessible-component-mdi-zorder"

#if defined(ENABLE_OVERLOADING)
data ObjectAccessibleComponentMdiZorderPropertyInfo
instance AttrInfo ObjectAccessibleComponentMdiZorderPropertyInfo where
    type AttrAllowedOps ObjectAccessibleComponentMdiZorderPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint ObjectAccessibleComponentMdiZorderPropertyInfo = IsObject
    type AttrSetTypeConstraint ObjectAccessibleComponentMdiZorderPropertyInfo = (~) ()
    type AttrTransferTypeConstraint ObjectAccessibleComponentMdiZorderPropertyInfo = (~) ()
    type AttrTransferType ObjectAccessibleComponentMdiZorderPropertyInfo = ()
    type AttrGetType ObjectAccessibleComponentMdiZorderPropertyInfo = Int32
    type AttrLabel ObjectAccessibleComponentMdiZorderPropertyInfo = "accessible-component-mdi-zorder"
    type AttrOrigin ObjectAccessibleComponentMdiZorderPropertyInfo = Object
    attrGet = getObjectAccessibleComponentMdiZorder
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "accessible-description"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@accessible-description@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' object #accessibleDescription
-- @
getObjectAccessibleDescription :: (MonadIO m, IsObject o) => o -> m (Maybe T.Text)
getObjectAccessibleDescription :: o -> m (Maybe Text)
getObjectAccessibleDescription obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "accessible-description"

-- | Set the value of the “@accessible-description@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' object [ #accessibleDescription 'Data.GI.Base.Attributes.:=' value ]
-- @
setObjectAccessibleDescription :: (MonadIO m, IsObject o) => o -> T.Text -> m ()
setObjectAccessibleDescription :: o -> Text -> m ()
setObjectAccessibleDescription obj :: o
obj val :: Text
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "accessible-description" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@accessible-description@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructObjectAccessibleDescription :: (IsObject o) => T.Text -> IO (GValueConstruct o)
constructObjectAccessibleDescription :: Text -> IO (GValueConstruct o)
constructObjectAccessibleDescription val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "accessible-description" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@accessible-description@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #accessibleDescription
-- @
clearObjectAccessibleDescription :: (MonadIO m, IsObject o) => o -> m ()
clearObjectAccessibleDescription :: o -> m ()
clearObjectAccessibleDescription obj :: 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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "accessible-description" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data ObjectAccessibleDescriptionPropertyInfo
instance AttrInfo ObjectAccessibleDescriptionPropertyInfo where
    type AttrAllowedOps ObjectAccessibleDescriptionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ObjectAccessibleDescriptionPropertyInfo = IsObject
    type AttrSetTypeConstraint ObjectAccessibleDescriptionPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ObjectAccessibleDescriptionPropertyInfo = (~) T.Text
    type AttrTransferType ObjectAccessibleDescriptionPropertyInfo = T.Text
    type AttrGetType ObjectAccessibleDescriptionPropertyInfo = (Maybe T.Text)
    type AttrLabel ObjectAccessibleDescriptionPropertyInfo = "accessible-description"
    type AttrOrigin ObjectAccessibleDescriptionPropertyInfo = Object
    attrGet = getObjectAccessibleDescription
    attrSet = setObjectAccessibleDescription
    attrTransfer _ v = do
        return v
    attrConstruct = constructObjectAccessibleDescription
    attrClear = clearObjectAccessibleDescription
#endif

-- VVV Prop "accessible-hypertext-nlinks"
   -- Type: TBasicType TInt
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@accessible-hypertext-nlinks@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' object #accessibleHypertextNlinks
-- @
getObjectAccessibleHypertextNlinks :: (MonadIO m, IsObject o) => o -> m Int32
getObjectAccessibleHypertextNlinks :: o -> m Int32
getObjectAccessibleHypertextNlinks obj :: o
obj = 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
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj "accessible-hypertext-nlinks"

#if defined(ENABLE_OVERLOADING)
data ObjectAccessibleHypertextNlinksPropertyInfo
instance AttrInfo ObjectAccessibleHypertextNlinksPropertyInfo where
    type AttrAllowedOps ObjectAccessibleHypertextNlinksPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint ObjectAccessibleHypertextNlinksPropertyInfo = IsObject
    type AttrSetTypeConstraint ObjectAccessibleHypertextNlinksPropertyInfo = (~) ()
    type AttrTransferTypeConstraint ObjectAccessibleHypertextNlinksPropertyInfo = (~) ()
    type AttrTransferType ObjectAccessibleHypertextNlinksPropertyInfo = ()
    type AttrGetType ObjectAccessibleHypertextNlinksPropertyInfo = Int32
    type AttrLabel ObjectAccessibleHypertextNlinksPropertyInfo = "accessible-hypertext-nlinks"
    type AttrOrigin ObjectAccessibleHypertextNlinksPropertyInfo = Object
    attrGet = getObjectAccessibleHypertextNlinks
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "accessible-name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@accessible-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' object #accessibleName
-- @
getObjectAccessibleName :: (MonadIO m, IsObject o) => o -> m (Maybe T.Text)
getObjectAccessibleName :: o -> m (Maybe Text)
getObjectAccessibleName obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "accessible-name"

-- | Set the value of the “@accessible-name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' object [ #accessibleName 'Data.GI.Base.Attributes.:=' value ]
-- @
setObjectAccessibleName :: (MonadIO m, IsObject o) => o -> T.Text -> m ()
setObjectAccessibleName :: o -> Text -> m ()
setObjectAccessibleName obj :: o
obj val :: Text
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "accessible-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@accessible-name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructObjectAccessibleName :: (IsObject o) => T.Text -> IO (GValueConstruct o)
constructObjectAccessibleName :: Text -> IO (GValueConstruct o)
constructObjectAccessibleName val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "accessible-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@accessible-name@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #accessibleName
-- @
clearObjectAccessibleName :: (MonadIO m, IsObject o) => o -> m ()
clearObjectAccessibleName :: o -> m ()
clearObjectAccessibleName obj :: 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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "accessible-name" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data ObjectAccessibleNamePropertyInfo
instance AttrInfo ObjectAccessibleNamePropertyInfo where
    type AttrAllowedOps ObjectAccessibleNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ObjectAccessibleNamePropertyInfo = IsObject
    type AttrSetTypeConstraint ObjectAccessibleNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ObjectAccessibleNamePropertyInfo = (~) T.Text
    type AttrTransferType ObjectAccessibleNamePropertyInfo = T.Text
    type AttrGetType ObjectAccessibleNamePropertyInfo = (Maybe T.Text)
    type AttrLabel ObjectAccessibleNamePropertyInfo = "accessible-name"
    type AttrOrigin ObjectAccessibleNamePropertyInfo = Object
    attrGet = getObjectAccessibleName
    attrSet = setObjectAccessibleName
    attrTransfer _ v = do
        return v
    attrConstruct = constructObjectAccessibleName
    attrClear = clearObjectAccessibleName
#endif

-- VVV Prop "accessible-parent"
   -- Type: TInterface (Name {namespace = "Atk", name = "Object"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@accessible-parent@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' object #accessibleParent
-- @
getObjectAccessibleParent :: (MonadIO m, IsObject o) => o -> m (Maybe Object)
getObjectAccessibleParent :: o -> m (Maybe Object)
getObjectAccessibleParent obj :: o
obj = IO (Maybe Object) -> m (Maybe Object)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Object) -> m (Maybe Object))
-> IO (Maybe Object) -> m (Maybe Object)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Object -> Object) -> IO (Maybe Object)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "accessible-parent" ManagedPtr Object -> Object
Object

-- | Set the value of the “@accessible-parent@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' object [ #accessibleParent 'Data.GI.Base.Attributes.:=' value ]
-- @
setObjectAccessibleParent :: (MonadIO m, IsObject o, IsObject a) => o -> a -> m ()
setObjectAccessibleParent :: o -> a -> m ()
setObjectAccessibleParent obj :: o
obj val :: a
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 a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "accessible-parent" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@accessible-parent@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructObjectAccessibleParent :: (IsObject o, IsObject a) => a -> IO (GValueConstruct o)
constructObjectAccessibleParent :: a -> IO (GValueConstruct o)
constructObjectAccessibleParent val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "accessible-parent" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Set the value of the “@accessible-parent@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #accessibleParent
-- @
clearObjectAccessibleParent :: (MonadIO m, IsObject o) => o -> m ()
clearObjectAccessibleParent :: o -> m ()
clearObjectAccessibleParent obj :: 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 -> ObjectActiveDescendantChangedCallback
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "accessible-parent" (Maybe Object
forall a. Maybe a
Nothing :: Maybe Object)

#if defined(ENABLE_OVERLOADING)
data ObjectAccessibleParentPropertyInfo
instance AttrInfo ObjectAccessibleParentPropertyInfo where
    type AttrAllowedOps ObjectAccessibleParentPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ObjectAccessibleParentPropertyInfo = IsObject
    type AttrSetTypeConstraint ObjectAccessibleParentPropertyInfo = IsObject
    type AttrTransferTypeConstraint ObjectAccessibleParentPropertyInfo = IsObject
    type AttrTransferType ObjectAccessibleParentPropertyInfo = Object
    type AttrGetType ObjectAccessibleParentPropertyInfo = (Maybe Object)
    type AttrLabel ObjectAccessibleParentPropertyInfo = "accessible-parent"
    type AttrOrigin ObjectAccessibleParentPropertyInfo = Object
    attrGet = getObjectAccessibleParent
    attrSet = setObjectAccessibleParent
    attrTransfer _ v = do
        unsafeCastTo Object v
    attrConstruct = constructObjectAccessibleParent
    attrClear = clearObjectAccessibleParent
#endif

-- VVV Prop "accessible-role"
   -- Type: TInterface (Name {namespace = "Atk", name = "Role"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@accessible-role@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' object #accessibleRole
-- @
getObjectAccessibleRole :: (MonadIO m, IsObject o) => o -> m Atk.Enums.Role
getObjectAccessibleRole :: o -> m Role
getObjectAccessibleRole obj :: o
obj = IO Role -> m Role
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Role -> m Role) -> IO Role -> m Role
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Role
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj "accessible-role"

-- | Set the value of the “@accessible-role@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' object [ #accessibleRole 'Data.GI.Base.Attributes.:=' value ]
-- @
setObjectAccessibleRole :: (MonadIO m, IsObject o) => o -> Atk.Enums.Role -> m ()
setObjectAccessibleRole :: o -> Role -> m ()
setObjectAccessibleRole obj :: o
obj val :: Role
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 -> Role -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj "accessible-role" Role
val

-- | Construct a `GValueConstruct` with valid value for the “@accessible-role@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructObjectAccessibleRole :: (IsObject o) => Atk.Enums.Role -> IO (GValueConstruct o)
constructObjectAccessibleRole :: Role -> IO (GValueConstruct o)
constructObjectAccessibleRole val :: Role
val = String -> Role -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum "accessible-role" Role
val

#if defined(ENABLE_OVERLOADING)
data ObjectAccessibleRolePropertyInfo
instance AttrInfo ObjectAccessibleRolePropertyInfo where
    type AttrAllowedOps ObjectAccessibleRolePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ObjectAccessibleRolePropertyInfo = IsObject
    type AttrSetTypeConstraint ObjectAccessibleRolePropertyInfo = (~) Atk.Enums.Role
    type AttrTransferTypeConstraint ObjectAccessibleRolePropertyInfo = (~) Atk.Enums.Role
    type AttrTransferType ObjectAccessibleRolePropertyInfo = Atk.Enums.Role
    type AttrGetType ObjectAccessibleRolePropertyInfo = Atk.Enums.Role
    type AttrLabel ObjectAccessibleRolePropertyInfo = "accessible-role"
    type AttrOrigin ObjectAccessibleRolePropertyInfo = Object
    attrGet = getObjectAccessibleRole
    attrSet = setObjectAccessibleRole
    attrTransfer _ v = do
        return v
    attrConstruct = constructObjectAccessibleRole
    attrClear = undefined
#endif

-- VVV Prop "accessible-table-caption"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@accessible-table-caption@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' object #accessibleTableCaption
-- @
getObjectAccessibleTableCaption :: (MonadIO m, IsObject o) => o -> m (Maybe T.Text)
getObjectAccessibleTableCaption :: o -> m (Maybe Text)
getObjectAccessibleTableCaption obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "accessible-table-caption"

-- | Set the value of the “@accessible-table-caption@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' object [ #accessibleTableCaption 'Data.GI.Base.Attributes.:=' value ]
-- @
setObjectAccessibleTableCaption :: (MonadIO m, IsObject o) => o -> T.Text -> m ()
setObjectAccessibleTableCaption :: o -> Text -> m ()
setObjectAccessibleTableCaption obj :: o
obj val :: Text
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "accessible-table-caption" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@accessible-table-caption@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructObjectAccessibleTableCaption :: (IsObject o) => T.Text -> IO (GValueConstruct o)
constructObjectAccessibleTableCaption :: Text -> IO (GValueConstruct o)
constructObjectAccessibleTableCaption val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "accessible-table-caption" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@accessible-table-caption@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #accessibleTableCaption
-- @
clearObjectAccessibleTableCaption :: (MonadIO m, IsObject o) => o -> m ()
clearObjectAccessibleTableCaption :: o -> m ()
clearObjectAccessibleTableCaption obj :: 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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "accessible-table-caption" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data ObjectAccessibleTableCaptionPropertyInfo
instance AttrInfo ObjectAccessibleTableCaptionPropertyInfo where
    type AttrAllowedOps ObjectAccessibleTableCaptionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ObjectAccessibleTableCaptionPropertyInfo = IsObject
    type AttrSetTypeConstraint ObjectAccessibleTableCaptionPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ObjectAccessibleTableCaptionPropertyInfo = (~) T.Text
    type AttrTransferType ObjectAccessibleTableCaptionPropertyInfo = T.Text
    type AttrGetType ObjectAccessibleTableCaptionPropertyInfo = (Maybe T.Text)
    type AttrLabel ObjectAccessibleTableCaptionPropertyInfo = "accessible-table-caption"
    type AttrOrigin ObjectAccessibleTableCaptionPropertyInfo = Object
    attrGet = getObjectAccessibleTableCaption
    attrSet = setObjectAccessibleTableCaption
    attrTransfer _ v = do
        return v
    attrConstruct = constructObjectAccessibleTableCaption
    attrClear = clearObjectAccessibleTableCaption
#endif

-- VVV Prop "accessible-table-caption-object"
   -- Type: TInterface (Name {namespace = "Atk", name = "Object"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@accessible-table-caption-object@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' object #accessibleTableCaptionObject
-- @
getObjectAccessibleTableCaptionObject :: (MonadIO m, IsObject o) => o -> m (Maybe Object)
getObjectAccessibleTableCaptionObject :: o -> m (Maybe Object)
getObjectAccessibleTableCaptionObject obj :: o
obj = IO (Maybe Object) -> m (Maybe Object)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Object) -> m (Maybe Object))
-> IO (Maybe Object) -> m (Maybe Object)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Object -> Object) -> IO (Maybe Object)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "accessible-table-caption-object" ManagedPtr Object -> Object
Object

-- | Set the value of the “@accessible-table-caption-object@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' object [ #accessibleTableCaptionObject 'Data.GI.Base.Attributes.:=' value ]
-- @
setObjectAccessibleTableCaptionObject :: (MonadIO m, IsObject o, IsObject a) => o -> a -> m ()
setObjectAccessibleTableCaptionObject :: o -> a -> m ()
setObjectAccessibleTableCaptionObject obj :: o
obj val :: a
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 a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "accessible-table-caption-object" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@accessible-table-caption-object@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructObjectAccessibleTableCaptionObject :: (IsObject o, IsObject a) => a -> IO (GValueConstruct o)
constructObjectAccessibleTableCaptionObject :: a -> IO (GValueConstruct o)
constructObjectAccessibleTableCaptionObject val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "accessible-table-caption-object" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Set the value of the “@accessible-table-caption-object@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #accessibleTableCaptionObject
-- @
clearObjectAccessibleTableCaptionObject :: (MonadIO m, IsObject o) => o -> m ()
clearObjectAccessibleTableCaptionObject :: o -> m ()
clearObjectAccessibleTableCaptionObject obj :: 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 -> ObjectActiveDescendantChangedCallback
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "accessible-table-caption-object" (Maybe Object
forall a. Maybe a
Nothing :: Maybe Object)

#if defined(ENABLE_OVERLOADING)
data ObjectAccessibleTableCaptionObjectPropertyInfo
instance AttrInfo ObjectAccessibleTableCaptionObjectPropertyInfo where
    type AttrAllowedOps ObjectAccessibleTableCaptionObjectPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ObjectAccessibleTableCaptionObjectPropertyInfo = IsObject
    type AttrSetTypeConstraint ObjectAccessibleTableCaptionObjectPropertyInfo = IsObject
    type AttrTransferTypeConstraint ObjectAccessibleTableCaptionObjectPropertyInfo = IsObject
    type AttrTransferType ObjectAccessibleTableCaptionObjectPropertyInfo = Object
    type AttrGetType ObjectAccessibleTableCaptionObjectPropertyInfo = (Maybe Object)
    type AttrLabel ObjectAccessibleTableCaptionObjectPropertyInfo = "accessible-table-caption-object"
    type AttrOrigin ObjectAccessibleTableCaptionObjectPropertyInfo = Object
    attrGet = getObjectAccessibleTableCaptionObject
    attrSet = setObjectAccessibleTableCaptionObject
    attrTransfer _ v = do
        unsafeCastTo Object v
    attrConstruct = constructObjectAccessibleTableCaptionObject
    attrClear = clearObjectAccessibleTableCaptionObject
#endif

-- VVV Prop "accessible-table-column-description"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@accessible-table-column-description@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' object #accessibleTableColumnDescription
-- @
getObjectAccessibleTableColumnDescription :: (MonadIO m, IsObject o) => o -> m (Maybe T.Text)
getObjectAccessibleTableColumnDescription :: o -> m (Maybe Text)
getObjectAccessibleTableColumnDescription obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "accessible-table-column-description"

-- | Set the value of the “@accessible-table-column-description@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' object [ #accessibleTableColumnDescription 'Data.GI.Base.Attributes.:=' value ]
-- @
setObjectAccessibleTableColumnDescription :: (MonadIO m, IsObject o) => o -> T.Text -> m ()
setObjectAccessibleTableColumnDescription :: o -> Text -> m ()
setObjectAccessibleTableColumnDescription obj :: o
obj val :: Text
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "accessible-table-column-description" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@accessible-table-column-description@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructObjectAccessibleTableColumnDescription :: (IsObject o) => T.Text -> IO (GValueConstruct o)
constructObjectAccessibleTableColumnDescription :: Text -> IO (GValueConstruct o)
constructObjectAccessibleTableColumnDescription val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "accessible-table-column-description" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@accessible-table-column-description@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #accessibleTableColumnDescription
-- @
clearObjectAccessibleTableColumnDescription :: (MonadIO m, IsObject o) => o -> m ()
clearObjectAccessibleTableColumnDescription :: o -> m ()
clearObjectAccessibleTableColumnDescription obj :: 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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "accessible-table-column-description" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data ObjectAccessibleTableColumnDescriptionPropertyInfo
instance AttrInfo ObjectAccessibleTableColumnDescriptionPropertyInfo where
    type AttrAllowedOps ObjectAccessibleTableColumnDescriptionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ObjectAccessibleTableColumnDescriptionPropertyInfo = IsObject
    type AttrSetTypeConstraint ObjectAccessibleTableColumnDescriptionPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ObjectAccessibleTableColumnDescriptionPropertyInfo = (~) T.Text
    type AttrTransferType ObjectAccessibleTableColumnDescriptionPropertyInfo = T.Text
    type AttrGetType ObjectAccessibleTableColumnDescriptionPropertyInfo = (Maybe T.Text)
    type AttrLabel ObjectAccessibleTableColumnDescriptionPropertyInfo = "accessible-table-column-description"
    type AttrOrigin ObjectAccessibleTableColumnDescriptionPropertyInfo = Object
    attrGet = getObjectAccessibleTableColumnDescription
    attrSet = setObjectAccessibleTableColumnDescription
    attrTransfer _ v = do
        return v
    attrConstruct = constructObjectAccessibleTableColumnDescription
    attrClear = clearObjectAccessibleTableColumnDescription
#endif

-- VVV Prop "accessible-table-column-header"
   -- Type: TInterface (Name {namespace = "Atk", name = "Object"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@accessible-table-column-header@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' object #accessibleTableColumnHeader
-- @
getObjectAccessibleTableColumnHeader :: (MonadIO m, IsObject o) => o -> m (Maybe Object)
getObjectAccessibleTableColumnHeader :: o -> m (Maybe Object)
getObjectAccessibleTableColumnHeader obj :: o
obj = IO (Maybe Object) -> m (Maybe Object)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Object) -> m (Maybe Object))
-> IO (Maybe Object) -> m (Maybe Object)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Object -> Object) -> IO (Maybe Object)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "accessible-table-column-header" ManagedPtr Object -> Object
Object

-- | Set the value of the “@accessible-table-column-header@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' object [ #accessibleTableColumnHeader 'Data.GI.Base.Attributes.:=' value ]
-- @
setObjectAccessibleTableColumnHeader :: (MonadIO m, IsObject o, IsObject a) => o -> a -> m ()
setObjectAccessibleTableColumnHeader :: o -> a -> m ()
setObjectAccessibleTableColumnHeader obj :: o
obj val :: a
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 a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "accessible-table-column-header" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@accessible-table-column-header@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructObjectAccessibleTableColumnHeader :: (IsObject o, IsObject a) => a -> IO (GValueConstruct o)
constructObjectAccessibleTableColumnHeader :: a -> IO (GValueConstruct o)
constructObjectAccessibleTableColumnHeader val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "accessible-table-column-header" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Set the value of the “@accessible-table-column-header@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #accessibleTableColumnHeader
-- @
clearObjectAccessibleTableColumnHeader :: (MonadIO m, IsObject o) => o -> m ()
clearObjectAccessibleTableColumnHeader :: o -> m ()
clearObjectAccessibleTableColumnHeader obj :: 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 -> ObjectActiveDescendantChangedCallback
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "accessible-table-column-header" (Maybe Object
forall a. Maybe a
Nothing :: Maybe Object)

#if defined(ENABLE_OVERLOADING)
data ObjectAccessibleTableColumnHeaderPropertyInfo
instance AttrInfo ObjectAccessibleTableColumnHeaderPropertyInfo where
    type AttrAllowedOps ObjectAccessibleTableColumnHeaderPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ObjectAccessibleTableColumnHeaderPropertyInfo = IsObject
    type AttrSetTypeConstraint ObjectAccessibleTableColumnHeaderPropertyInfo = IsObject
    type AttrTransferTypeConstraint ObjectAccessibleTableColumnHeaderPropertyInfo = IsObject
    type AttrTransferType ObjectAccessibleTableColumnHeaderPropertyInfo = Object
    type AttrGetType ObjectAccessibleTableColumnHeaderPropertyInfo = (Maybe Object)
    type AttrLabel ObjectAccessibleTableColumnHeaderPropertyInfo = "accessible-table-column-header"
    type AttrOrigin ObjectAccessibleTableColumnHeaderPropertyInfo = Object
    attrGet = getObjectAccessibleTableColumnHeader
    attrSet = setObjectAccessibleTableColumnHeader
    attrTransfer _ v = do
        unsafeCastTo Object v
    attrConstruct = constructObjectAccessibleTableColumnHeader
    attrClear = clearObjectAccessibleTableColumnHeader
#endif

-- VVV Prop "accessible-table-row-description"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@accessible-table-row-description@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' object #accessibleTableRowDescription
-- @
getObjectAccessibleTableRowDescription :: (MonadIO m, IsObject o) => o -> m (Maybe T.Text)
getObjectAccessibleTableRowDescription :: o -> m (Maybe Text)
getObjectAccessibleTableRowDescription obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "accessible-table-row-description"

-- | Set the value of the “@accessible-table-row-description@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' object [ #accessibleTableRowDescription 'Data.GI.Base.Attributes.:=' value ]
-- @
setObjectAccessibleTableRowDescription :: (MonadIO m, IsObject o) => o -> T.Text -> m ()
setObjectAccessibleTableRowDescription :: o -> Text -> m ()
setObjectAccessibleTableRowDescription obj :: o
obj val :: Text
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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "accessible-table-row-description" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@accessible-table-row-description@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructObjectAccessibleTableRowDescription :: (IsObject o) => T.Text -> IO (GValueConstruct o)
constructObjectAccessibleTableRowDescription :: Text -> IO (GValueConstruct o)
constructObjectAccessibleTableRowDescription val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "accessible-table-row-description" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Set the value of the “@accessible-table-row-description@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #accessibleTableRowDescription
-- @
clearObjectAccessibleTableRowDescription :: (MonadIO m, IsObject o) => o -> m ()
clearObjectAccessibleTableRowDescription :: o -> m ()
clearObjectAccessibleTableRowDescription obj :: 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 Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj "accessible-table-row-description" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)

#if defined(ENABLE_OVERLOADING)
data ObjectAccessibleTableRowDescriptionPropertyInfo
instance AttrInfo ObjectAccessibleTableRowDescriptionPropertyInfo where
    type AttrAllowedOps ObjectAccessibleTableRowDescriptionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ObjectAccessibleTableRowDescriptionPropertyInfo = IsObject
    type AttrSetTypeConstraint ObjectAccessibleTableRowDescriptionPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint ObjectAccessibleTableRowDescriptionPropertyInfo = (~) T.Text
    type AttrTransferType ObjectAccessibleTableRowDescriptionPropertyInfo = T.Text
    type AttrGetType ObjectAccessibleTableRowDescriptionPropertyInfo = (Maybe T.Text)
    type AttrLabel ObjectAccessibleTableRowDescriptionPropertyInfo = "accessible-table-row-description"
    type AttrOrigin ObjectAccessibleTableRowDescriptionPropertyInfo = Object
    attrGet = getObjectAccessibleTableRowDescription
    attrSet = setObjectAccessibleTableRowDescription
    attrTransfer _ v = do
        return v
    attrConstruct = constructObjectAccessibleTableRowDescription
    attrClear = clearObjectAccessibleTableRowDescription
#endif

-- VVV Prop "accessible-table-row-header"
   -- Type: TInterface (Name {namespace = "Atk", name = "Object"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@accessible-table-row-header@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' object #accessibleTableRowHeader
-- @
getObjectAccessibleTableRowHeader :: (MonadIO m, IsObject o) => o -> m (Maybe Object)
getObjectAccessibleTableRowHeader :: o -> m (Maybe Object)
getObjectAccessibleTableRowHeader obj :: o
obj = IO (Maybe Object) -> m (Maybe Object)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Object) -> m (Maybe Object))
-> IO (Maybe Object) -> m (Maybe Object)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Object -> Object) -> IO (Maybe Object)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "accessible-table-row-header" ManagedPtr Object -> Object
Object

-- | Set the value of the “@accessible-table-row-header@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' object [ #accessibleTableRowHeader 'Data.GI.Base.Attributes.:=' value ]
-- @
setObjectAccessibleTableRowHeader :: (MonadIO m, IsObject o, IsObject a) => o -> a -> m ()
setObjectAccessibleTableRowHeader :: o -> a -> m ()
setObjectAccessibleTableRowHeader obj :: o
obj val :: a
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 a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "accessible-table-row-header" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@accessible-table-row-header@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructObjectAccessibleTableRowHeader :: (IsObject o, IsObject a) => a -> IO (GValueConstruct o)
constructObjectAccessibleTableRowHeader :: a -> IO (GValueConstruct o)
constructObjectAccessibleTableRowHeader val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "accessible-table-row-header" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Set the value of the “@accessible-table-row-header@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #accessibleTableRowHeader
-- @
clearObjectAccessibleTableRowHeader :: (MonadIO m, IsObject o) => o -> m ()
clearObjectAccessibleTableRowHeader :: o -> m ()
clearObjectAccessibleTableRowHeader obj :: 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 -> ObjectActiveDescendantChangedCallback
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "accessible-table-row-header" (Maybe Object
forall a. Maybe a
Nothing :: Maybe Object)

#if defined(ENABLE_OVERLOADING)
data ObjectAccessibleTableRowHeaderPropertyInfo
instance AttrInfo ObjectAccessibleTableRowHeaderPropertyInfo where
    type AttrAllowedOps ObjectAccessibleTableRowHeaderPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ObjectAccessibleTableRowHeaderPropertyInfo = IsObject
    type AttrSetTypeConstraint ObjectAccessibleTableRowHeaderPropertyInfo = IsObject
    type AttrTransferTypeConstraint ObjectAccessibleTableRowHeaderPropertyInfo = IsObject
    type AttrTransferType ObjectAccessibleTableRowHeaderPropertyInfo = Object
    type AttrGetType ObjectAccessibleTableRowHeaderPropertyInfo = (Maybe Object)
    type AttrLabel ObjectAccessibleTableRowHeaderPropertyInfo = "accessible-table-row-header"
    type AttrOrigin ObjectAccessibleTableRowHeaderPropertyInfo = Object
    attrGet = getObjectAccessibleTableRowHeader
    attrSet = setObjectAccessibleTableRowHeader
    attrTransfer _ v = do
        unsafeCastTo Object v
    attrConstruct = constructObjectAccessibleTableRowHeader
    attrClear = clearObjectAccessibleTableRowHeader
#endif

-- VVV Prop "accessible-table-summary"
   -- Type: TInterface (Name {namespace = "Atk", name = "Object"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@accessible-table-summary@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' object #accessibleTableSummary
-- @
getObjectAccessibleTableSummary :: (MonadIO m, IsObject o) => o -> m (Maybe Object)
getObjectAccessibleTableSummary :: o -> m (Maybe Object)
getObjectAccessibleTableSummary obj :: o
obj = IO (Maybe Object) -> m (Maybe Object)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Object) -> m (Maybe Object))
-> IO (Maybe Object) -> m (Maybe Object)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Object -> Object) -> IO (Maybe Object)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "accessible-table-summary" ManagedPtr Object -> Object
Object

-- | Set the value of the “@accessible-table-summary@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' object [ #accessibleTableSummary 'Data.GI.Base.Attributes.:=' value ]
-- @
setObjectAccessibleTableSummary :: (MonadIO m, IsObject o, IsObject a) => o -> a -> m ()
setObjectAccessibleTableSummary :: o -> a -> m ()
setObjectAccessibleTableSummary obj :: o
obj val :: a
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 a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "accessible-table-summary" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@accessible-table-summary@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructObjectAccessibleTableSummary :: (IsObject o, IsObject a) => a -> IO (GValueConstruct o)
constructObjectAccessibleTableSummary :: a -> IO (GValueConstruct o)
constructObjectAccessibleTableSummary val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "accessible-table-summary" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Set the value of the “@accessible-table-summary@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #accessibleTableSummary
-- @
clearObjectAccessibleTableSummary :: (MonadIO m, IsObject o) => o -> m ()
clearObjectAccessibleTableSummary :: o -> m ()
clearObjectAccessibleTableSummary obj :: 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 -> ObjectActiveDescendantChangedCallback
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "accessible-table-summary" (Maybe Object
forall a. Maybe a
Nothing :: Maybe Object)

#if defined(ENABLE_OVERLOADING)
data ObjectAccessibleTableSummaryPropertyInfo
instance AttrInfo ObjectAccessibleTableSummaryPropertyInfo where
    type AttrAllowedOps ObjectAccessibleTableSummaryPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ObjectAccessibleTableSummaryPropertyInfo = IsObject
    type AttrSetTypeConstraint ObjectAccessibleTableSummaryPropertyInfo = IsObject
    type AttrTransferTypeConstraint ObjectAccessibleTableSummaryPropertyInfo = IsObject
    type AttrTransferType ObjectAccessibleTableSummaryPropertyInfo = Object
    type AttrGetType ObjectAccessibleTableSummaryPropertyInfo = (Maybe Object)
    type AttrLabel ObjectAccessibleTableSummaryPropertyInfo = "accessible-table-summary"
    type AttrOrigin ObjectAccessibleTableSummaryPropertyInfo = Object
    attrGet = getObjectAccessibleTableSummary
    attrSet = setObjectAccessibleTableSummary
    attrTransfer _ v = do
        unsafeCastTo Object v
    attrConstruct = constructObjectAccessibleTableSummary
    attrClear = clearObjectAccessibleTableSummary
#endif

-- VVV Prop "accessible-value"
   -- Type: TBasicType TDouble
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@accessible-value@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' object #accessibleValue
-- @
getObjectAccessibleValue :: (MonadIO m, IsObject o) => o -> m Double
getObjectAccessibleValue :: o -> m Double
getObjectAccessibleValue obj :: o
obj = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Double
forall a. GObject a => a -> String -> IO Double
B.Properties.getObjectPropertyDouble o
obj "accessible-value"

-- | Set the value of the “@accessible-value@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' object [ #accessibleValue 'Data.GI.Base.Attributes.:=' value ]
-- @
setObjectAccessibleValue :: (MonadIO m, IsObject o) => o -> Double -> m ()
setObjectAccessibleValue :: o -> Double -> m ()
setObjectAccessibleValue obj :: o
obj val :: Double
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 -> Double -> IO ()
forall a. GObject a => a -> String -> Double -> IO ()
B.Properties.setObjectPropertyDouble o
obj "accessible-value" Double
val

-- | Construct a `GValueConstruct` with valid value for the “@accessible-value@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructObjectAccessibleValue :: (IsObject o) => Double -> IO (GValueConstruct o)
constructObjectAccessibleValue :: Double -> IO (GValueConstruct o)
constructObjectAccessibleValue val :: Double
val = String -> Double -> IO (GValueConstruct o)
forall o. String -> Double -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyDouble "accessible-value" Double
val

#if defined(ENABLE_OVERLOADING)
data ObjectAccessibleValuePropertyInfo
instance AttrInfo ObjectAccessibleValuePropertyInfo where
    type AttrAllowedOps ObjectAccessibleValuePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ObjectAccessibleValuePropertyInfo = IsObject
    type AttrSetTypeConstraint ObjectAccessibleValuePropertyInfo = (~) Double
    type AttrTransferTypeConstraint ObjectAccessibleValuePropertyInfo = (~) Double
    type AttrTransferType ObjectAccessibleValuePropertyInfo = Double
    type AttrGetType ObjectAccessibleValuePropertyInfo = Double
    type AttrLabel ObjectAccessibleValuePropertyInfo = "accessible-value"
    type AttrOrigin ObjectAccessibleValuePropertyInfo = Object
    attrGet = getObjectAccessibleValue
    attrSet = setObjectAccessibleValue
    attrTransfer _ v = do
        return v
    attrConstruct = constructObjectAccessibleValue
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Object
type instance O.AttributeList Object = ObjectAttributeList
type ObjectAttributeList = ('[ '("accessibleComponentLayer", ObjectAccessibleComponentLayerPropertyInfo), '("accessibleComponentMdiZorder", ObjectAccessibleComponentMdiZorderPropertyInfo), '("accessibleDescription", ObjectAccessibleDescriptionPropertyInfo), '("accessibleHypertextNlinks", ObjectAccessibleHypertextNlinksPropertyInfo), '("accessibleName", ObjectAccessibleNamePropertyInfo), '("accessibleParent", ObjectAccessibleParentPropertyInfo), '("accessibleRole", ObjectAccessibleRolePropertyInfo), '("accessibleTableCaption", ObjectAccessibleTableCaptionPropertyInfo), '("accessibleTableCaptionObject", ObjectAccessibleTableCaptionObjectPropertyInfo), '("accessibleTableColumnDescription", ObjectAccessibleTableColumnDescriptionPropertyInfo), '("accessibleTableColumnHeader", ObjectAccessibleTableColumnHeaderPropertyInfo), '("accessibleTableRowDescription", ObjectAccessibleTableRowDescriptionPropertyInfo), '("accessibleTableRowHeader", ObjectAccessibleTableRowHeaderPropertyInfo), '("accessibleTableSummary", ObjectAccessibleTableSummaryPropertyInfo), '("accessibleValue", ObjectAccessibleValuePropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
objectAccessibleComponentLayer :: AttrLabelProxy "accessibleComponentLayer"
objectAccessibleComponentLayer = AttrLabelProxy

objectAccessibleComponentMdiZorder :: AttrLabelProxy "accessibleComponentMdiZorder"
objectAccessibleComponentMdiZorder = AttrLabelProxy

objectAccessibleDescription :: AttrLabelProxy "accessibleDescription"
objectAccessibleDescription = AttrLabelProxy

objectAccessibleHypertextNlinks :: AttrLabelProxy "accessibleHypertextNlinks"
objectAccessibleHypertextNlinks = AttrLabelProxy

objectAccessibleName :: AttrLabelProxy "accessibleName"
objectAccessibleName = AttrLabelProxy

objectAccessibleParent :: AttrLabelProxy "accessibleParent"
objectAccessibleParent = AttrLabelProxy

objectAccessibleRole :: AttrLabelProxy "accessibleRole"
objectAccessibleRole = AttrLabelProxy

objectAccessibleTableCaption :: AttrLabelProxy "accessibleTableCaption"
objectAccessibleTableCaption = AttrLabelProxy

objectAccessibleTableCaptionObject :: AttrLabelProxy "accessibleTableCaptionObject"
objectAccessibleTableCaptionObject = AttrLabelProxy

objectAccessibleTableColumnDescription :: AttrLabelProxy "accessibleTableColumnDescription"
objectAccessibleTableColumnDescription = AttrLabelProxy

objectAccessibleTableColumnHeader :: AttrLabelProxy "accessibleTableColumnHeader"
objectAccessibleTableColumnHeader = AttrLabelProxy

objectAccessibleTableRowDescription :: AttrLabelProxy "accessibleTableRowDescription"
objectAccessibleTableRowDescription = AttrLabelProxy

objectAccessibleTableRowHeader :: AttrLabelProxy "accessibleTableRowHeader"
objectAccessibleTableRowHeader = AttrLabelProxy

objectAccessibleTableSummary :: AttrLabelProxy "accessibleTableSummary"
objectAccessibleTableSummary = AttrLabelProxy

objectAccessibleValue :: AttrLabelProxy "accessibleValue"
objectAccessibleValue = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Object = ObjectSignalList
type ObjectSignalList = ('[ '("activeDescendantChanged", ObjectActiveDescendantChangedSignalInfo), '("childrenChanged", ObjectChildrenChangedSignalInfo), '("focusEvent", ObjectFocusEventSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("propertyChange", ObjectPropertyChangeSignalInfo), '("stateChange", ObjectStateChangeSignalInfo), '("visibleDataChanged", ObjectVisibleDataChangedSignalInfo)] :: [(Symbol, *)])

#endif

-- method Object::add_relationship
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "object"
--           , argType = TInterface Name { namespace = "Atk" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #AtkObject to which an AtkRelation is to be added."
--                 , 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 "The #AtkRelationType of the relation"
--                 , 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 "The #AtkObject which is to be the target of the relation."
--                 , 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_object_add_relationship" atk_object_add_relationship :: 
    Ptr Object ->                           -- object : TInterface (Name {namespace = "Atk", name = "Object"})
    CUInt ->                                -- relationship : TInterface (Name {namespace = "Atk", name = "RelationType"})
    Ptr Object ->                           -- target : TInterface (Name {namespace = "Atk", name = "Object"})
    IO CInt

-- | Adds a relationship of the specified type with the specified target.
objectAddRelationship ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a, IsObject b) =>
    a
    -- ^ /@object@/: The t'GI.Atk.Objects.Object.Object' to which an AtkRelation is to be added.
    -> Atk.Enums.RelationType
    -- ^ /@relationship@/: The t'GI.Atk.Enums.RelationType' of the relation
    -> b
    -- ^ /@target@/: The t'GI.Atk.Objects.Object.Object' which is to be the target of the relation.
    -> m Bool
    -- ^ __Returns:__ TRUE if the relationship is added.
objectAddRelationship :: a -> RelationType -> b -> m Bool
objectAddRelationship object :: a
object relationship :: RelationType
relationship target :: 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
    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 Object -> CUInt -> Ptr Object -> IO CInt
atk_object_add_relationship Ptr Object
object' CUInt
relationship' Ptr Object
target'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
    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 ObjectAddRelationshipMethodInfo
instance (signature ~ (Atk.Enums.RelationType -> b -> m Bool), MonadIO m, IsObject a, IsObject b) => O.MethodInfo ObjectAddRelationshipMethodInfo a signature where
    overloadedMethod = objectAddRelationship

#endif

-- method Object::get_attributes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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 (TGSList (TBasicType TPtr))
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_get_attributes" atk_object_get_attributes :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    IO (Ptr (GSList (Ptr ())))

-- | Get a list of properties applied to this object as a whole, as an @/AtkAttributeSet/@ consisting of
-- name-value pairs. As such these attributes may be considered weakly-typed properties or annotations,
-- as distinct from strongly-typed object data available via other get\/set methods.
-- Not all objects have explicit \"name-value pair\" @/AtkAttributeSet/@ properties.
-- 
-- /Since: 1.12/
objectGetAttributes ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: An t'GI.Atk.Objects.Object.Object'.
    -> m ([Ptr ()])
    -- ^ __Returns:__ an @/AtkAttributeSet/@ consisting of all
    -- explicit properties\/annotations applied to the object, or an empty
    -- set if the object has no name-value pair attributes assigned to
    -- it. This @/atkattributeset/@ should be freed by a call to
    -- 'GI.Atk.Functions.attributeSetFree'.
objectGetAttributes :: a -> m [Ptr ()]
objectGetAttributes accessible :: a
accessible = IO [Ptr ()] -> m [Ptr ()]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Ptr ()] -> m [Ptr ()]) -> IO [Ptr ()] -> m [Ptr ()]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    Ptr (GSList (Ptr ()))
result <- Ptr Object -> IO (Ptr (GSList (Ptr ())))
atk_object_get_attributes Ptr Object
accessible'
    [Ptr ()]
result' <- Ptr (GSList (Ptr ())) -> IO [Ptr ()]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr ()))
result
    Ptr (GSList (Ptr ())) -> IO ()
forall a. Ptr (GSList a) -> IO ()
g_slist_free Ptr (GSList (Ptr ()))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    [Ptr ()] -> IO [Ptr ()]
forall (m :: * -> *) a. Monad m => a -> m a
return [Ptr ()]
result'

#if defined(ENABLE_OVERLOADING)
data ObjectGetAttributesMethodInfo
instance (signature ~ (m ([Ptr ()])), MonadIO m, IsObject a) => O.MethodInfo ObjectGetAttributesMethodInfo a signature where
    overloadedMethod = objectGetAttributes

#endif

-- method Object::get_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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 TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_get_description" atk_object_get_description :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    IO CString

-- | Gets the accessible description of the accessible.
objectGetDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> m T.Text
    -- ^ __Returns:__ a character string representing the accessible description
    -- of the accessible.
objectGetDescription :: a -> m Text
objectGetDescription accessible :: a
accessible = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    CString
result <- Ptr Object -> IO CString
atk_object_get_description Ptr Object
accessible'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "objectGetDescription" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ObjectGetDescriptionMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsObject a) => O.MethodInfo ObjectGetDescriptionMethodInfo a signature where
    overloadedMethod = objectGetDescription

#endif

-- method Object::get_index_in_parent
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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 TInt)
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_get_index_in_parent" atk_object_get_index_in_parent :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    IO Int32

-- | Gets the 0-based index of this accessible in its parent; returns -1 if the
-- accessible does not have an accessible parent.
objectGetIndexInParent ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> m Int32
    -- ^ __Returns:__ an integer which is the index of the accessible in its parent
objectGetIndexInParent :: a -> m Int32
objectGetIndexInParent accessible :: a
accessible = 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 Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    Int32
result <- Ptr Object -> IO Int32
atk_object_get_index_in_parent Ptr Object
accessible'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data ObjectGetIndexInParentMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsObject a) => O.MethodInfo ObjectGetIndexInParentMethodInfo a signature where
    overloadedMethod = objectGetIndexInParent

#endif

-- method Object::get_layer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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 (TInterface Name { namespace = "Atk" , name = "Layer" })
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_get_layer" atk_object_get_layer :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    IO CUInt

{-# DEPRECATED objectGetLayer ["Use atk_component_get_layer instead."] #-}
-- | Gets the layer of the accessible.
objectGetLayer ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> m Atk.Enums.Layer
    -- ^ __Returns:__ an t'GI.Atk.Enums.Layer' which is the layer of the accessible
objectGetLayer :: a -> m Layer
objectGetLayer accessible :: a
accessible = IO Layer -> m Layer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Layer -> m Layer) -> IO Layer -> m Layer
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    CUInt
result <- Ptr Object -> IO CUInt
atk_object_get_layer Ptr Object
accessible'
    let result' :: Layer
result' = (Int -> Layer
forall a. Enum a => Int -> a
toEnum (Int -> Layer) -> (CUInt -> Int) -> CUInt -> Layer
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
accessible
    Layer -> IO Layer
forall (m :: * -> *) a. Monad m => a -> m a
return Layer
result'

#if defined(ENABLE_OVERLOADING)
data ObjectGetLayerMethodInfo
instance (signature ~ (m Atk.Enums.Layer), MonadIO m, IsObject a) => O.MethodInfo ObjectGetLayerMethodInfo a signature where
    overloadedMethod = objectGetLayer

#endif

-- method Object::get_mdi_zorder
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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 TInt)
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_get_mdi_zorder" atk_object_get_mdi_zorder :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    IO Int32

{-# DEPRECATED objectGetMdiZorder ["Use atk_component_get_mdi_zorder instead."] #-}
-- | Gets the zorder of the accessible. The value G_MININT will be returned
-- if the layer of the accessible is not ATK_LAYER_MDI.
objectGetMdiZorder ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> m Int32
    -- ^ __Returns:__ a gint which is the zorder of the accessible, i.e. the depth at
    -- which the component is shown in relation to other components in the same
    -- container.
objectGetMdiZorder :: a -> m Int32
objectGetMdiZorder accessible :: a
accessible = 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 Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    Int32
result <- Ptr Object -> IO Int32
atk_object_get_mdi_zorder Ptr Object
accessible'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data ObjectGetMdiZorderMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsObject a) => O.MethodInfo ObjectGetMdiZorderMethodInfo a signature where
    overloadedMethod = objectGetMdiZorder

#endif

-- method Object::get_n_accessible_children
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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 TInt)
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_get_n_accessible_children" atk_object_get_n_accessible_children :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    IO Int32

-- | Gets the number of accessible children of the accessible.
objectGetNAccessibleChildren ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> m Int32
    -- ^ __Returns:__ an integer representing the number of accessible children
    -- of the accessible.
objectGetNAccessibleChildren :: a -> m Int32
objectGetNAccessibleChildren accessible :: a
accessible = 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 Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    Int32
result <- Ptr Object -> IO Int32
atk_object_get_n_accessible_children Ptr Object
accessible'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data ObjectGetNAccessibleChildrenMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsObject a) => O.MethodInfo ObjectGetNAccessibleChildrenMethodInfo a signature where
    overloadedMethod = objectGetNAccessibleChildren

#endif

-- method Object::get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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 TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_get_name" atk_object_get_name :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    IO CString

-- | Gets the accessible name of the accessible.
objectGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> m T.Text
    -- ^ __Returns:__ a character string representing the accessible name of the object.
objectGetName :: a -> m Text
objectGetName accessible :: a
accessible = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    CString
result <- Ptr Object -> IO CString
atk_object_get_name Ptr Object
accessible'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "objectGetName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ObjectGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsObject a) => O.MethodInfo ObjectGetNameMethodInfo a signature where
    overloadedMethod = objectGetName

#endif

-- method Object::get_object_locale
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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 TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_get_object_locale" atk_object_get_object_locale :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    IO CString

-- | Gets a UTF-8 string indicating the POSIX-style LC_MESSAGES locale
-- of /@accessible@/.
-- 
-- /Since: 2.8/
objectGetObjectLocale ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> m T.Text
    -- ^ __Returns:__ a UTF-8 string indicating the POSIX-style LC_MESSAGES
    --          locale of /@accessible@/.
objectGetObjectLocale :: a -> m Text
objectGetObjectLocale accessible :: a
accessible = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    CString
result <- Ptr Object -> IO CString
atk_object_get_object_locale Ptr Object
accessible'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "objectGetObjectLocale" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data ObjectGetObjectLocaleMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsObject a) => O.MethodInfo ObjectGetObjectLocaleMethodInfo a signature where
    overloadedMethod = objectGetObjectLocale

#endif

-- method Object::get_parent
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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 (TInterface Name { namespace = "Atk" , name = "Object" })
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_get_parent" atk_object_get_parent :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    IO (Ptr Object)

-- | Gets the accessible parent of the accessible. By default this is
-- the one assigned with 'GI.Atk.Objects.Object.objectSetParent', but it is assumed
-- that ATK implementors have ways to get the parent of the object
-- without the need of assigning it manually with
-- 'GI.Atk.Objects.Object.objectSetParent', and will return it with this method.
-- 
-- If you are only interested on the parent assigned with
-- 'GI.Atk.Objects.Object.objectSetParent', use 'GI.Atk.Objects.Object.objectPeekParent'.
objectGetParent ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> m Object
    -- ^ __Returns:__ an t'GI.Atk.Objects.Object.Object' representing the accessible
    -- parent of the accessible
objectGetParent :: a -> m Object
objectGetParent accessible :: a
accessible = IO Object -> m Object
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Object -> m Object) -> IO Object -> m Object
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    Ptr Object
result <- Ptr Object -> IO (Ptr Object)
atk_object_get_parent Ptr Object
accessible'
    Text -> Ptr Object -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "objectGetParent" Ptr Object
result
    Object
result' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
Object) Ptr Object
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result'

#if defined(ENABLE_OVERLOADING)
data ObjectGetParentMethodInfo
instance (signature ~ (m Object), MonadIO m, IsObject a) => O.MethodInfo ObjectGetParentMethodInfo a signature where
    overloadedMethod = objectGetParent

#endif

-- method Object::get_role
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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 (TInterface Name { namespace = "Atk" , name = "Role" })
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_get_role" atk_object_get_role :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    IO CUInt

-- | Gets the role of the accessible.
objectGetRole ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> m Atk.Enums.Role
    -- ^ __Returns:__ an t'GI.Atk.Enums.Role' which is the role of the accessible
objectGetRole :: a -> m Role
objectGetRole accessible :: a
accessible = IO Role -> m Role
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Role -> m Role) -> IO Role -> m Role
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    CUInt
result <- Ptr Object -> IO CUInt
atk_object_get_role Ptr Object
accessible'
    let result' :: Role
result' = (Int -> Role
forall a. Enum a => Int -> a
toEnum (Int -> Role) -> (CUInt -> Int) -> CUInt -> Role
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
accessible
    Role -> IO Role
forall (m :: * -> *) a. Monad m => a -> m a
return Role
result'

#if defined(ENABLE_OVERLOADING)
data ObjectGetRoleMethodInfo
instance (signature ~ (m Atk.Enums.Role), MonadIO m, IsObject a) => O.MethodInfo ObjectGetRoleMethodInfo a signature where
    overloadedMethod = objectGetRole

#endif

-- method Object::initialize
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , argType = TInterface Name { namespace = "Atk" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #AtkObject" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #gpointer which identifies the object for which the AtkObject was created."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_initialize" atk_object_initialize :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    Ptr () ->                               -- data : TBasicType TPtr
    IO ()

-- | This function is called when implementing subclasses of t'GI.Atk.Objects.Object.Object'.
-- It does initialization required for the new object. It is intended
-- that this function should called only in the ...@/_new()/@ functions used
-- to create an instance of a subclass of t'GI.Atk.Objects.Object.Object'
objectInitialize ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: a t'GI.Atk.Objects.Object.Object'
    -> Ptr ()
    -- ^ /@data@/: a @/gpointer/@ which identifies the object for which the AtkObject was created.
    -> m ()
objectInitialize :: a -> Ptr () -> m ()
objectInitialize accessible :: a
accessible data_ :: Ptr ()
data_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    Ptr Object -> Ptr () -> IO ()
atk_object_initialize Ptr Object
accessible' Ptr ()
data_
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ObjectInitializeMethodInfo
instance (signature ~ (Ptr () -> m ()), MonadIO m, IsObject a) => O.MethodInfo ObjectInitializeMethodInfo a signature where
    overloadedMethod = objectInitialize

#endif

-- method Object::notify_state_change
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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
--           }
--       , Arg
--           { argCName = "state"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkState whose state is changed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a gboolean which indicates whether the state is being set on or off"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_notify_state_change" atk_object_notify_state_change :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    Word64 ->                               -- state : TBasicType TUInt64
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()

-- | Emits a state-change signal for the specified state.
-- 
-- Note that as a general rule when the state of an existing object changes,
-- emitting a notification is expected.
objectNotifyStateChange ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> Word64
    -- ^ /@state@/: an @/AtkState/@ whose state is changed
    -> Bool
    -- ^ /@value@/: a gboolean which indicates whether the state is being set on or off
    -> m ()
objectNotifyStateChange :: a -> Word64 -> Bool -> m ()
objectNotifyStateChange accessible :: a
accessible state :: Word64
state value :: Bool
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    let value' :: CInt
value' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
value
    Ptr Object -> Word64 -> CInt -> IO ()
atk_object_notify_state_change Ptr Object
accessible' Word64
state CInt
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ObjectNotifyStateChangeMethodInfo
instance (signature ~ (Word64 -> Bool -> m ()), MonadIO m, IsObject a) => O.MethodInfo ObjectNotifyStateChangeMethodInfo a signature where
    overloadedMethod = objectNotifyStateChange

#endif

-- method Object::peek_parent
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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 (TInterface Name { namespace = "Atk" , name = "Object" })
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_peek_parent" atk_object_peek_parent :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    IO (Ptr Object)

-- | Gets the accessible parent of the accessible, if it has been
-- manually assigned with atk_object_set_parent. Otherwise, this
-- function returns 'P.Nothing'.
-- 
-- This method is intended as an utility for ATK implementors, and not
-- to be exposed to accessible tools. See 'GI.Atk.Objects.Object.objectGetParent' for
-- further reference.
objectPeekParent ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> m Object
    -- ^ __Returns:__ an t'GI.Atk.Objects.Object.Object' representing the accessible
    -- parent of the accessible if assigned
objectPeekParent :: a -> m Object
objectPeekParent accessible :: a
accessible = IO Object -> m Object
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Object -> m Object) -> IO Object -> m Object
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    Ptr Object
result <- Ptr Object -> IO (Ptr Object)
atk_object_peek_parent Ptr Object
accessible'
    Text -> Ptr Object -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "objectPeekParent" Ptr Object
result
    Object
result' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
Object) Ptr Object
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result'

#if defined(ENABLE_OVERLOADING)
data ObjectPeekParentMethodInfo
instance (signature ~ (m Object), MonadIO m, IsObject a) => O.MethodInfo ObjectPeekParentMethodInfo a signature where
    overloadedMethod = objectPeekParent

#endif

-- method Object::ref_accessible_child
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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
--           }
--       , Arg
--           { argCName = "i"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a gint representing the position of the child, starting from 0"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Atk" , name = "Object" })
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_ref_accessible_child" atk_object_ref_accessible_child :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    Int32 ->                                -- i : TBasicType TInt
    IO (Ptr Object)

-- | Gets a reference to the specified accessible child of the object.
-- The accessible children are 0-based so the first accessible child is
-- at index 0, the second at index 1 and so on.
objectRefAccessibleChild ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> Int32
    -- ^ /@i@/: a gint representing the position of the child, starting from 0
    -> m Object
    -- ^ __Returns:__ an t'GI.Atk.Objects.Object.Object' representing the specified
    -- accessible child of the accessible.
objectRefAccessibleChild :: a -> Int32 -> m Object
objectRefAccessibleChild accessible :: a
accessible i :: Int32
i = IO Object -> m Object
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Object -> m Object) -> IO Object -> m Object
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    Ptr Object
result <- Ptr Object -> Int32 -> IO (Ptr Object)
atk_object_ref_accessible_child Ptr Object
accessible' Int32
i
    Text -> Ptr Object -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "objectRefAccessibleChild" Ptr Object
result
    Object
result' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Object -> Object
Object) Ptr Object
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    Object -> IO Object
forall (m :: * -> *) a. Monad m => a -> m a
return Object
result'

#if defined(ENABLE_OVERLOADING)
data ObjectRefAccessibleChildMethodInfo
instance (signature ~ (Int32 -> m Object), MonadIO m, IsObject a) => O.MethodInfo ObjectRefAccessibleChildMethodInfo a signature where
    overloadedMethod = objectRefAccessibleChild

#endif

-- method Object::ref_relation_set
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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 (TInterface Name { namespace = "Atk" , name = "RelationSet" })
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_ref_relation_set" atk_object_ref_relation_set :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    IO (Ptr Atk.RelationSet.RelationSet)

-- | Gets the t'GI.Atk.Objects.RelationSet.RelationSet' associated with the object.
objectRefRelationSet ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> m Atk.RelationSet.RelationSet
    -- ^ __Returns:__ an t'GI.Atk.Objects.RelationSet.RelationSet' representing the relation set
    -- of the object.
objectRefRelationSet :: a -> m RelationSet
objectRefRelationSet accessible :: a
accessible = 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 Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    Ptr RelationSet
result <- Ptr Object -> IO (Ptr RelationSet)
atk_object_ref_relation_set Ptr Object
accessible'
    Text -> Ptr RelationSet -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "objectRefRelationSet" 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
Atk.RelationSet.RelationSet) Ptr RelationSet
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    RelationSet -> IO RelationSet
forall (m :: * -> *) a. Monad m => a -> m a
return RelationSet
result'

#if defined(ENABLE_OVERLOADING)
data ObjectRefRelationSetMethodInfo
instance (signature ~ (m Atk.RelationSet.RelationSet), MonadIO m, IsObject a) => O.MethodInfo ObjectRefRelationSetMethodInfo a signature where
    overloadedMethod = objectRefRelationSet

#endif

-- method Object::ref_state_set
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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 (TInterface Name { namespace = "Atk" , name = "StateSet" })
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_ref_state_set" atk_object_ref_state_set :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    IO (Ptr Atk.StateSet.StateSet)

-- | Gets a reference to the state set of the accessible; the caller must
-- unreference it when it is no longer needed.
objectRefStateSet ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> m Atk.StateSet.StateSet
    -- ^ __Returns:__ a reference to an t'GI.Atk.Objects.StateSet.StateSet' which is the state
    -- set of the accessible
objectRefStateSet :: a -> m StateSet
objectRefStateSet accessible :: a
accessible = IO StateSet -> m StateSet
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO StateSet -> m StateSet) -> IO StateSet -> m StateSet
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    Ptr StateSet
result <- Ptr Object -> IO (Ptr StateSet)
atk_object_ref_state_set Ptr Object
accessible'
    Text -> Ptr StateSet -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "objectRefStateSet" Ptr StateSet
result
    StateSet
result' <- ((ManagedPtr StateSet -> StateSet) -> Ptr StateSet -> IO StateSet
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr StateSet -> StateSet
Atk.StateSet.StateSet) Ptr StateSet
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    StateSet -> IO StateSet
forall (m :: * -> *) a. Monad m => a -> m a
return StateSet
result'

#if defined(ENABLE_OVERLOADING)
data ObjectRefStateSetMethodInfo
instance (signature ~ (m Atk.StateSet.StateSet), MonadIO m, IsObject a) => O.MethodInfo ObjectRefStateSetMethodInfo a signature where
    overloadedMethod = objectRefStateSet

#endif

-- method Object::remove_property_change_handler
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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
--           }
--       , Arg
--           { argCName = "handler_id"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a guint which identifies the handler to be removed."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_remove_property_change_handler" atk_object_remove_property_change_handler :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    Word32 ->                               -- handler_id : TBasicType TUInt
    IO ()

{-# DEPRECATED objectRemovePropertyChangeHandler ["Since 2.12.","","Removes a property change handler."] #-}
-- | /No description available in the introspection data./
objectRemovePropertyChangeHandler ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> Word32
    -- ^ /@handlerId@/: a guint which identifies the handler to be removed.
    -> m ()
objectRemovePropertyChangeHandler :: a -> Word32 -> m ()
objectRemovePropertyChangeHandler accessible :: a
accessible handlerId :: Word32
handlerId = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    Ptr Object -> Word32 -> IO ()
atk_object_remove_property_change_handler Ptr Object
accessible' Word32
handlerId
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ObjectRemovePropertyChangeHandlerMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsObject a) => O.MethodInfo ObjectRemovePropertyChangeHandlerMethodInfo a signature where
    overloadedMethod = objectRemovePropertyChangeHandler

#endif

-- method Object::remove_relationship
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "object"
--           , argType = TInterface Name { namespace = "Atk" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "The #AtkObject from which an AtkRelation is to be removed."
--                 , 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 "The #AtkRelationType of the relation"
--                 , 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
--                       "The #AtkObject which is the target of the relation to be removed."
--                 , 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_object_remove_relationship" atk_object_remove_relationship :: 
    Ptr Object ->                           -- object : TInterface (Name {namespace = "Atk", name = "Object"})
    CUInt ->                                -- relationship : TInterface (Name {namespace = "Atk", name = "RelationType"})
    Ptr Object ->                           -- target : TInterface (Name {namespace = "Atk", name = "Object"})
    IO CInt

-- | Removes a relationship of the specified type with the specified target.
objectRemoveRelationship ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a, IsObject b) =>
    a
    -- ^ /@object@/: The t'GI.Atk.Objects.Object.Object' from which an AtkRelation is to be removed.
    -> Atk.Enums.RelationType
    -- ^ /@relationship@/: The t'GI.Atk.Enums.RelationType' of the relation
    -> b
    -- ^ /@target@/: The t'GI.Atk.Objects.Object.Object' which is the target of the relation to be removed.
    -> m Bool
    -- ^ __Returns:__ TRUE if the relationship is removed.
objectRemoveRelationship :: a -> RelationType -> b -> m Bool
objectRemoveRelationship object :: a
object relationship :: RelationType
relationship target :: 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 Object
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
    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 Object -> CUInt -> Ptr Object -> IO CInt
atk_object_remove_relationship Ptr Object
object' CUInt
relationship' Ptr Object
target'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
    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 ObjectRemoveRelationshipMethodInfo
instance (signature ~ (Atk.Enums.RelationType -> b -> m Bool), MonadIO m, IsObject a, IsObject b) => O.MethodInfo ObjectRemoveRelationshipMethodInfo a signature where
    overloadedMethod = objectRemoveRelationship

#endif

-- method Object::set_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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
--           }
--       , Arg
--           { argCName = "description"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a character string to be set as the accessible description"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_set_description" atk_object_set_description :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    CString ->                              -- description : TBasicType TUTF8
    IO ()

-- | Sets the accessible description of the accessible. You can\'t set
-- the description to NULL. This is reserved for the initial value. In
-- this aspect NULL is similar to ATK_ROLE_UNKNOWN. If you want to set
-- the name to a empty value you can use \"\".
objectSetDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> T.Text
    -- ^ /@description@/: a character string to be set as the accessible description
    -> m ()
objectSetDescription :: a -> Text -> m ()
objectSetDescription accessible :: a
accessible description :: Text
description = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    CString
description' <- Text -> IO CString
textToCString Text
description
    Ptr Object -> CString -> IO ()
atk_object_set_description Ptr Object
accessible' CString
description'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
description'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ObjectSetDescriptionMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsObject a) => O.MethodInfo ObjectSetDescriptionMethodInfo a signature where
    overloadedMethod = objectSetDescription

#endif

-- method Object::set_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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
--           }
--       , Arg
--           { argCName = "name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a character string to be set as the accessible name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_set_name" atk_object_set_name :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    CString ->                              -- name : TBasicType TUTF8
    IO ()

-- | Sets the accessible name of the accessible. You can\'t set the name
-- to NULL. This is reserved for the initial value. In this aspect
-- NULL is similar to ATK_ROLE_UNKNOWN. If you want to set the name to
-- a empty value you can use \"\".
objectSetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> T.Text
    -- ^ /@name@/: a character string to be set as the accessible name
    -> m ()
objectSetName :: a -> Text -> m ()
objectSetName accessible :: a
accessible name :: Text
name = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr Object -> CString -> IO ()
atk_object_set_name Ptr Object
accessible' CString
name'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ObjectSetNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsObject a) => O.MethodInfo ObjectSetNameMethodInfo a signature where
    overloadedMethod = objectSetName

#endif

-- method Object::set_parent
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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
--           }
--       , Arg
--           { argCName = "parent"
--           , argType = TInterface Name { namespace = "Atk" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "an #AtkObject to be set as the accessible parent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_set_parent" atk_object_set_parent :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    Ptr Object ->                           -- parent : TInterface (Name {namespace = "Atk", name = "Object"})
    IO ()

-- | Sets the accessible parent of the accessible. /@parent@/ can be NULL.
objectSetParent ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a, IsObject b) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> b
    -- ^ /@parent@/: an t'GI.Atk.Objects.Object.Object' to be set as the accessible parent
    -> m ()
objectSetParent :: a -> b -> m ()
objectSetParent accessible :: a
accessible parent :: b
parent = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    Ptr Object
parent' <- b -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
parent
    Ptr Object -> Ptr Object -> IO ()
atk_object_set_parent Ptr Object
accessible' Ptr Object
parent'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
parent
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ObjectSetParentMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsObject a, IsObject b) => O.MethodInfo ObjectSetParentMethodInfo a signature where
    overloadedMethod = objectSetParent

#endif

-- method Object::set_role
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "accessible"
--           , 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
--           }
--       , Arg
--           { argCName = "role"
--           , argType = TInterface Name { namespace = "Atk" , name = "Role" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an #AtkRole to be set as the role"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "atk_object_set_role" atk_object_set_role :: 
    Ptr Object ->                           -- accessible : TInterface (Name {namespace = "Atk", name = "Object"})
    CUInt ->                                -- role : TInterface (Name {namespace = "Atk", name = "Role"})
    IO ()

-- | Sets the role of the accessible.
objectSetRole ::
    (B.CallStack.HasCallStack, MonadIO m, IsObject a) =>
    a
    -- ^ /@accessible@/: an t'GI.Atk.Objects.Object.Object'
    -> Atk.Enums.Role
    -- ^ /@role@/: an t'GI.Atk.Enums.Role' to be set as the role
    -> m ()
objectSetRole :: a -> Role -> m ()
objectSetRole accessible :: a
accessible role :: Role
role = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Object
accessible' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    let role' :: CUInt
role' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Role -> Int) -> Role -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Role -> Int
forall a. Enum a => a -> Int
fromEnum) Role
role
    Ptr Object -> CUInt -> IO ()
atk_object_set_role Ptr Object
accessible' CUInt
role'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
accessible
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data ObjectSetRoleMethodInfo
instance (signature ~ (Atk.Enums.Role -> m ()), MonadIO m, IsObject a) => O.MethodInfo ObjectSetRoleMethodInfo a signature where
    overloadedMethod = objectSetRole

#endif