{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Communicates with platform-specific assistive technologies API.
-- 
-- Each platform supported by GTK implements a @GtkATContext@ subclass, and
-- is responsible for updating the accessible state in response to state
-- changes in @GtkAccessible@.

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

module GI.Gtk.Objects.ATContext
    ( 

-- * Exported types
    ATContext(..)                           ,
    IsATContext                             ,
    toATContext                             ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAccessible]("GI.Gtk.Objects.ATContext#g:method:getAccessible"), [getAccessibleRole]("GI.Gtk.Objects.ATContext#g:method:getAccessibleRole"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveATContextMethod                  ,
#endif

-- ** create #method:create#

    aTContextCreate                         ,


-- ** getAccessible #method:getAccessible#

#if defined(ENABLE_OVERLOADING)
    ATContextGetAccessibleMethodInfo        ,
#endif
    aTContextGetAccessible                  ,


-- ** getAccessibleRole #method:getAccessibleRole#

#if defined(ENABLE_OVERLOADING)
    ATContextGetAccessibleRoleMethodInfo    ,
#endif
    aTContextGetAccessibleRole              ,




 -- * Properties


-- ** accessible #attr:accessible#
-- | The @GtkAccessible@ that created the @GtkATContext@ instance.

#if defined(ENABLE_OVERLOADING)
    ATContextAccessiblePropertyInfo         ,
#endif
#if defined(ENABLE_OVERLOADING)
    aTContextAccessible                     ,
#endif
    constructATContextAccessible            ,
    getATContextAccessible                  ,


-- ** accessibleRole #attr:accessibleRole#
-- | The accessible role used by the AT context.
-- 
-- Depending on the given role, different states and properties can be
-- set or retrieved.

#if defined(ENABLE_OVERLOADING)
    ATContextAccessibleRolePropertyInfo     ,
#endif
#if defined(ENABLE_OVERLOADING)
    aTContextAccessibleRole                 ,
#endif
    constructATContextAccessibleRole        ,
    getATContextAccessibleRole              ,
    setATContextAccessibleRole              ,


-- ** display #attr:display#
-- | The @GdkDisplay@ for the @GtkATContext@.

#if defined(ENABLE_OVERLOADING)
    ATContextDisplayPropertyInfo            ,
#endif
#if defined(ENABLE_OVERLOADING)
    aTContextDisplay                        ,
#endif
    clearATContextDisplay                   ,
    constructATContextDisplay               ,
    getATContextDisplay                     ,
    setATContextDisplay                     ,




 -- * Signals


-- ** stateChange #signal:stateChange#

    ATContextStateChangeCallback            ,
#if defined(ENABLE_OVERLOADING)
    ATContextStateChangeSignalInfo          ,
#endif
    afterATContextStateChange               ,
    onATContextStateChange                  ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Display as Gdk.Display
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible

#else
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Display as Gdk.Display
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible

#endif

-- | Memory-managed wrapper type.
newtype ATContext = ATContext (SP.ManagedPtr ATContext)
    deriving (ATContext -> ATContext -> Bool
(ATContext -> ATContext -> Bool)
-> (ATContext -> ATContext -> Bool) -> Eq ATContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ATContext -> ATContext -> Bool
== :: ATContext -> ATContext -> Bool
$c/= :: ATContext -> ATContext -> Bool
/= :: ATContext -> ATContext -> Bool
Eq)

instance SP.ManagedPtrNewtype ATContext where
    toManagedPtr :: ATContext -> ManagedPtr ATContext
toManagedPtr (ATContext ManagedPtr ATContext
p) = ManagedPtr ATContext
p

foreign import ccall "gtk_at_context_get_type"
    c_gtk_at_context_get_type :: IO B.Types.GType

instance B.Types.TypedObject ATContext where
    glibType :: IO GType
glibType = IO GType
c_gtk_at_context_get_type

instance B.Types.GObject ATContext

-- | Type class for types which can be safely cast to t'ATContext', for instance with `toATContext`.
class (SP.GObject o, O.IsDescendantOf ATContext o) => IsATContext o
instance (SP.GObject o, O.IsDescendantOf ATContext o) => IsATContext o

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

-- | Cast to t'ATContext', for types for which this is known to be safe. For general casts, use 'Data.GI.Base.ManagedPtr.castTo'.
toATContext :: (MIO.MonadIO m, IsATContext o) => o -> m ATContext
toATContext :: forall (m :: * -> *) o.
(MonadIO m, IsATContext o) =>
o -> m ATContext
toATContext = IO ATContext -> m ATContext
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO ATContext -> m ATContext)
-> (o -> IO ATContext) -> o -> m ATContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr ATContext -> ATContext) -> o -> IO ATContext
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr ATContext -> ATContext
ATContext

-- | Convert t'ATContext' to and from t'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe ATContext) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_at_context_get_type
    gvalueSet_ :: Ptr GValue -> Maybe ATContext -> IO ()
gvalueSet_ Ptr GValue
gv Maybe ATContext
P.Nothing = Ptr GValue -> Ptr ATContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr ATContext
forall a. Ptr a
FP.nullPtr :: FP.Ptr ATContext)
    gvalueSet_ Ptr GValue
gv (P.Just ATContext
obj) = ATContext -> (Ptr ATContext -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr ATContext
obj (Ptr GValue -> Ptr ATContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe ATContext)
gvalueGet_ Ptr GValue
gv = do
        ptr <- Ptr GValue -> IO (Ptr ATContext)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr ATContext)
        if ptr /= FP.nullPtr
        then P.Just <$> B.ManagedPtr.newObject ATContext ptr
        else return P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveATContextMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveATContextMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveATContextMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveATContextMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveATContextMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveATContextMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveATContextMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveATContextMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveATContextMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveATContextMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveATContextMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveATContextMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveATContextMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveATContextMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveATContextMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveATContextMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveATContextMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveATContextMethod "getAccessible" o = ATContextGetAccessibleMethodInfo
    ResolveATContextMethod "getAccessibleRole" o = ATContextGetAccessibleRoleMethodInfo
    ResolveATContextMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveATContextMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveATContextMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveATContextMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveATContextMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveATContextMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveATContextMethod l o = O.MethodResolutionFailed l o

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

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

#endif

instance (info ~ ResolveATContextMethod t ATContext, O.OverloadedMethodInfo info ATContext) => OL.IsLabel t (O.MethodProxy info ATContext) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- signal ATContext::state-change
-- | Emitted when the attributes of the accessible for the
-- @GtkATContext@ instance change.
type ATContextStateChangeCallback =
    IO ()

type C_ATContextStateChangeCallback =
    Ptr ATContext ->                        -- object
    Ptr () ->                               -- user_data
    IO ()

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

wrap_ATContextStateChangeCallback :: 
    GObject a => (a -> ATContextStateChangeCallback) ->
    C_ATContextStateChangeCallback
wrap_ATContextStateChangeCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_ATContextStateChangeCallback
wrap_ATContextStateChangeCallback a -> IO ()
gi'cb Ptr ATContext
gi'selfPtr Ptr ()
_ = do
    Ptr ATContext -> (ATContext -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr ATContext
gi'selfPtr ((ATContext -> IO ()) -> IO ()) -> (ATContext -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ATContext
gi'self -> a -> IO ()
gi'cb (ATContext -> a
forall a b. Coercible a b => a -> b
Coerce.coerce ATContext
gi'self) 


-- | 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' aTContext #stateChange callback
-- @
-- 
-- 
onATContextStateChange :: (IsATContext a, MonadIO m) => a -> ((?self :: a) => ATContextStateChangeCallback) -> m SignalHandlerId
onATContextStateChange :: forall a (m :: * -> *).
(IsATContext a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onATContextStateChange a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_ATContextStateChangeCallback
wrapped' = (a -> IO ()) -> C_ATContextStateChangeCallback
forall a.
GObject a =>
(a -> IO ()) -> C_ATContextStateChangeCallback
wrap_ATContextStateChangeCallback a -> IO ()
wrapped
    wrapped'' <- C_ATContextStateChangeCallback
-> IO (FunPtr C_ATContextStateChangeCallback)
mk_ATContextStateChangeCallback C_ATContextStateChangeCallback
wrapped'
    connectSignalFunPtr obj "state-change" wrapped'' SignalConnectBefore Nothing

-- | 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' aTContext #stateChange callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterATContextStateChange :: (IsATContext a, MonadIO m) => a -> ((?self :: a) => ATContextStateChangeCallback) -> m SignalHandlerId
afterATContextStateChange :: forall a (m :: * -> *).
(IsATContext a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterATContextStateChange a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_ATContextStateChangeCallback
wrapped' = (a -> IO ()) -> C_ATContextStateChangeCallback
forall a.
GObject a =>
(a -> IO ()) -> C_ATContextStateChangeCallback
wrap_ATContextStateChangeCallback a -> IO ()
wrapped
    wrapped'' <- C_ATContextStateChangeCallback
-> IO (FunPtr C_ATContextStateChangeCallback)
mk_ATContextStateChangeCallback C_ATContextStateChangeCallback
wrapped'
    connectSignalFunPtr obj "state-change" wrapped'' SignalConnectAfter Nothing


#if defined(ENABLE_OVERLOADING)
data ATContextStateChangeSignalInfo
instance SignalInfo ATContextStateChangeSignalInfo where
    type HaskellCallbackType ATContextStateChangeSignalInfo = ATContextStateChangeCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_ATContextStateChangeCallback cb
        cb'' <- mk_ATContextStateChangeCallback cb'
        connectSignalFunPtr obj "state-change" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ATContext::state-change"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-ATContext.html#g:signal:stateChange"})

#endif

-- VVV Prop "accessible"
   -- Type: TInterface (Name {namespace = "Gtk", name = "Accessible"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

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

-- | Construct a t'GValueConstruct' with valid value for the “@accessible@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructATContextAccessible :: (IsATContext o, MIO.MonadIO m, Gtk.Accessible.IsAccessible a) => a -> m (GValueConstruct o)
constructATContextAccessible :: forall o (m :: * -> *) a.
(IsATContext o, MonadIO m, IsAccessible a) =>
a -> m (GValueConstruct o)
constructATContextAccessible a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"accessible" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data ATContextAccessiblePropertyInfo
instance AttrInfo ATContextAccessiblePropertyInfo where
    type AttrAllowedOps ATContextAccessiblePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ATContextAccessiblePropertyInfo = IsATContext
    type AttrSetTypeConstraint ATContextAccessiblePropertyInfo = Gtk.Accessible.IsAccessible
    type AttrTransferTypeConstraint ATContextAccessiblePropertyInfo = Gtk.Accessible.IsAccessible
    type AttrTransferType ATContextAccessiblePropertyInfo = Gtk.Accessible.Accessible
    type AttrGetType ATContextAccessiblePropertyInfo = Gtk.Accessible.Accessible
    type AttrLabel ATContextAccessiblePropertyInfo = "accessible"
    type AttrOrigin ATContextAccessiblePropertyInfo = ATContext
    attrGet = getATContextAccessible
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gtk.Accessible.Accessible v
    attrConstruct = constructATContextAccessible
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ATContext.accessible"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-ATContext.html#g:attr:accessible"
        })
#endif

-- VVV Prop "accessible-role"
   -- Type: TInterface (Name {namespace = "Gtk", name = "AccessibleRole"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstruct]
   -- Nullable: (Just False,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' aTContext #accessibleRole
-- @
getATContextAccessibleRole :: (MonadIO m, IsATContext o) => o -> m Gtk.Enums.AccessibleRole
getATContextAccessibleRole :: forall (m :: * -> *) o.
(MonadIO m, IsATContext o) =>
o -> m AccessibleRole
getATContextAccessibleRole o
obj = IO AccessibleRole -> m AccessibleRole
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO AccessibleRole -> m AccessibleRole)
-> IO AccessibleRole -> m AccessibleRole
forall a b. (a -> b) -> a -> b
$ o -> String -> IO AccessibleRole
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"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' aTContext [ #accessibleRole 'Data.GI.Base.Attributes.:=' value ]
-- @
setATContextAccessibleRole :: (MonadIO m, IsATContext o) => o -> Gtk.Enums.AccessibleRole -> m ()
setATContextAccessibleRole :: forall (m :: * -> *) o.
(MonadIO m, IsATContext o) =>
o -> AccessibleRole -> m ()
setATContextAccessibleRole o
obj AccessibleRole
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> AccessibleRole -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"accessible-role" AccessibleRole
val

-- | Construct a t'GValueConstruct' with valid value for the “@accessible-role@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructATContextAccessibleRole :: (IsATContext o, MIO.MonadIO m) => Gtk.Enums.AccessibleRole -> m (GValueConstruct o)
constructATContextAccessibleRole :: forall o (m :: * -> *).
(IsATContext o, MonadIO m) =>
AccessibleRole -> m (GValueConstruct o)
constructATContextAccessibleRole AccessibleRole
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> AccessibleRole -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"accessible-role" AccessibleRole
val

#if defined(ENABLE_OVERLOADING)
data ATContextAccessibleRolePropertyInfo
instance AttrInfo ATContextAccessibleRolePropertyInfo where
    type AttrAllowedOps ATContextAccessibleRolePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint ATContextAccessibleRolePropertyInfo = IsATContext
    type AttrSetTypeConstraint ATContextAccessibleRolePropertyInfo = (~) Gtk.Enums.AccessibleRole
    type AttrTransferTypeConstraint ATContextAccessibleRolePropertyInfo = (~) Gtk.Enums.AccessibleRole
    type AttrTransferType ATContextAccessibleRolePropertyInfo = Gtk.Enums.AccessibleRole
    type AttrGetType ATContextAccessibleRolePropertyInfo = Gtk.Enums.AccessibleRole
    type AttrLabel ATContextAccessibleRolePropertyInfo = "accessible-role"
    type AttrOrigin ATContextAccessibleRolePropertyInfo = ATContext
    attrGet = getATContextAccessibleRole
    attrSet = setATContextAccessibleRole
    attrTransfer _ v = do
        return v
    attrConstruct = constructATContextAccessibleRole
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ATContext.accessibleRole"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-ATContext.html#g:attr:accessibleRole"
        })
#endif

-- VVV Prop "display"
   -- Type: TInterface (Name {namespace = "Gdk", name = "Display"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

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

-- | Set the value of the “@display@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' aTContext [ #display 'Data.GI.Base.Attributes.:=' value ]
-- @
setATContextDisplay :: (MonadIO m, IsATContext o, Gdk.Display.IsDisplay a) => o -> a -> m ()
setATContextDisplay :: forall (m :: * -> *) o a.
(MonadIO m, IsATContext o, IsDisplay a) =>
o -> a -> m ()
setATContextDisplay o
obj a
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"display" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a t'GValueConstruct' with valid value for the “@display@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructATContextDisplay :: (IsATContext o, MIO.MonadIO m, Gdk.Display.IsDisplay a) => a -> m (GValueConstruct o)
constructATContextDisplay :: forall o (m :: * -> *) a.
(IsATContext o, MonadIO m, IsDisplay a) =>
a -> m (GValueConstruct o)
constructATContextDisplay a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"display" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

-- | Set the value of the “@display@” 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' #display
-- @
clearATContextDisplay :: (MonadIO m, IsATContext o) => o -> m ()
clearATContextDisplay :: forall (m :: * -> *) o. (MonadIO m, IsATContext o) => o -> m ()
clearATContextDisplay o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Display -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"display" (Maybe Display
forall a. Maybe a
Nothing :: Maybe Gdk.Display.Display)

#if defined(ENABLE_OVERLOADING)
data ATContextDisplayPropertyInfo
instance AttrInfo ATContextDisplayPropertyInfo where
    type AttrAllowedOps ATContextDisplayPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint ATContextDisplayPropertyInfo = IsATContext
    type AttrSetTypeConstraint ATContextDisplayPropertyInfo = Gdk.Display.IsDisplay
    type AttrTransferTypeConstraint ATContextDisplayPropertyInfo = Gdk.Display.IsDisplay
    type AttrTransferType ATContextDisplayPropertyInfo = Gdk.Display.Display
    type AttrGetType ATContextDisplayPropertyInfo = (Maybe Gdk.Display.Display)
    type AttrLabel ATContextDisplayPropertyInfo = "display"
    type AttrOrigin ATContextDisplayPropertyInfo = ATContext
    attrGet = getATContextDisplay
    attrSet = setATContextDisplay
    attrTransfer _ v = do
        unsafeCastTo Gdk.Display.Display v
    attrConstruct = constructATContextDisplay
    attrClear = clearATContextDisplay
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ATContext.display"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-ATContext.html#g:attr:display"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList ATContext
type instance O.AttributeList ATContext = ATContextAttributeList
type ATContextAttributeList = ('[ '("accessible", ATContextAccessiblePropertyInfo), '("accessibleRole", ATContextAccessibleRolePropertyInfo), '("display", ATContextDisplayPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
aTContextAccessible :: AttrLabelProxy "accessible"
aTContextAccessible = AttrLabelProxy

aTContextAccessibleRole :: AttrLabelProxy "accessibleRole"
aTContextAccessibleRole = AttrLabelProxy

aTContextDisplay :: AttrLabelProxy "display"
aTContextDisplay = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList ATContext = ATContextSignalList
type ATContextSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo), '("stateChange", ATContextStateChangeSignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method ATContext::create
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "accessible_role"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "AccessibleRole" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the accessible role used by the `GtkATContext`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "accessible"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "Accessible" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the `GtkAccessible` implementation using the `GtkATContext`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GdkDisplay` used by the `GtkATContext`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "ATContext" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_at_context_create" gtk_at_context_create :: 
    CUInt ->                                -- accessible_role : TInterface (Name {namespace = "Gtk", name = "AccessibleRole"})
    Ptr Gtk.Accessible.Accessible ->        -- accessible : TInterface (Name {namespace = "Gtk", name = "Accessible"})
    Ptr Gdk.Display.Display ->              -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO (Ptr ATContext)

-- | Creates a new @GtkATContext@ instance for the given accessible role,
-- accessible instance, and display connection.
-- 
-- The @GtkATContext@ implementation being instantiated will depend on the
-- platform.
aTContextCreate ::
    (B.CallStack.HasCallStack, MonadIO m, Gtk.Accessible.IsAccessible a, Gdk.Display.IsDisplay b) =>
    Gtk.Enums.AccessibleRole
    -- ^ /@accessibleRole@/: the accessible role used by the @GtkATContext@
    -> a
    -- ^ /@accessible@/: the @GtkAccessible@ implementation using the @GtkATContext@
    -> b
    -- ^ /@display@/: the @GdkDisplay@ used by the @GtkATContext@
    -> m (Maybe ATContext)
    -- ^ __Returns:__ the @GtkATContext@
aTContextCreate :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsAccessible a, IsDisplay b) =>
AccessibleRole -> a -> b -> m (Maybe ATContext)
aTContextCreate AccessibleRole
accessibleRole a
accessible b
display = IO (Maybe ATContext) -> m (Maybe ATContext)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe ATContext) -> m (Maybe ATContext))
-> IO (Maybe ATContext) -> m (Maybe ATContext)
forall a b. (a -> b) -> a -> b
$ do
    let accessibleRole' :: CUInt
accessibleRole' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (AccessibleRole -> Int) -> AccessibleRole -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AccessibleRole -> Int
forall a. Enum a => a -> Int
fromEnum) AccessibleRole
accessibleRole
    accessible' <- a -> IO (Ptr Accessible)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
accessible
    display' <- unsafeManagedPtrCastPtr display
    result <- gtk_at_context_create accessibleRole' accessible' display'
    maybeResult <- convertIfNonNull result $ \Ptr ATContext
result' -> do
        result'' <- ((ManagedPtr ATContext -> ATContext)
-> Ptr ATContext -> IO ATContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr ATContext -> ATContext
ATContext) Ptr ATContext
result'
        return result''
    touchManagedPtr accessible
    touchManagedPtr display
    return maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

-- method ATContext::get_accessible
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ATContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkATContext`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Accessible" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_at_context_get_accessible" gtk_at_context_get_accessible :: 
    Ptr ATContext ->                        -- self : TInterface (Name {namespace = "Gtk", name = "ATContext"})
    IO (Ptr Gtk.Accessible.Accessible)

-- | Retrieves the @GtkAccessible@ using this context.
aTContextGetAccessible ::
    (B.CallStack.HasCallStack, MonadIO m, IsATContext a) =>
    a
    -- ^ /@self@/: a @GtkATContext@
    -> m Gtk.Accessible.Accessible
    -- ^ __Returns:__ a @GtkAccessible@
aTContextGetAccessible :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsATContext a) =>
a -> m Accessible
aTContextGetAccessible a
self = IO Accessible -> m Accessible
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Accessible -> m Accessible) -> IO Accessible -> m Accessible
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr ATContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    result <- gtk_at_context_get_accessible self'
    checkUnexpectedReturnNULL "aTContextGetAccessible" result
    result' <- (newObject Gtk.Accessible.Accessible) result
    touchManagedPtr self
    return result'

#if defined(ENABLE_OVERLOADING)
data ATContextGetAccessibleMethodInfo
instance (signature ~ (m Gtk.Accessible.Accessible), MonadIO m, IsATContext a) => O.OverloadedMethod ATContextGetAccessibleMethodInfo a signature where
    overloadedMethod = aTContextGetAccessible

instance O.OverloadedMethodInfo ATContextGetAccessibleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ATContext.aTContextGetAccessible",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-ATContext.html#v:aTContextGetAccessible"
        })


#endif

-- method ATContext::get_accessible_role
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "ATContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkATContext`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "AccessibleRole" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_at_context_get_accessible_role" gtk_at_context_get_accessible_role :: 
    Ptr ATContext ->                        -- self : TInterface (Name {namespace = "Gtk", name = "ATContext"})
    IO CUInt

-- | Retrieves the accessible role of this context.
aTContextGetAccessibleRole ::
    (B.CallStack.HasCallStack, MonadIO m, IsATContext a) =>
    a
    -- ^ /@self@/: a @GtkATContext@
    -> m Gtk.Enums.AccessibleRole
    -- ^ __Returns:__ a @GtkAccessibleRole@
aTContextGetAccessibleRole :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsATContext a) =>
a -> m AccessibleRole
aTContextGetAccessibleRole a
self = IO AccessibleRole -> m AccessibleRole
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AccessibleRole -> m AccessibleRole)
-> IO AccessibleRole -> m AccessibleRole
forall a b. (a -> b) -> a -> b
$ do
    self' <- a -> IO (Ptr ATContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    result <- gtk_at_context_get_accessible_role self'
    let result' = (Int -> AccessibleRole
forall a. Enum a => Int -> a
toEnum (Int -> AccessibleRole)
-> (CUInt -> Int) -> CUInt -> AccessibleRole
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    touchManagedPtr self
    return result'

#if defined(ENABLE_OVERLOADING)
data ATContextGetAccessibleRoleMethodInfo
instance (signature ~ (m Gtk.Enums.AccessibleRole), MonadIO m, IsATContext a) => O.OverloadedMethod ATContextGetAccessibleRoleMethodInfo a signature where
    overloadedMethod = aTContextGetAccessibleRole

instance O.OverloadedMethodInfo ATContextGetAccessibleRoleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.ATContext.aTContextGetAccessibleRole",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-ATContext.html#v:aTContextGetAccessibleRole"
        })


#endif