-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria

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

module GI.Atk.Callbacks
    ( 

 -- * Signals
-- ** EventListener #signal:EventListener#

    C_EventListener                         ,
    EventListener                           ,
    dynamic_EventListener                   ,
    genClosure_EventListener                ,
    mk_EventListener                        ,
    noEventListener                         ,
    wrap_EventListener                      ,


-- ** EventListenerInit #signal:EventListenerInit#

    C_EventListenerInit                     ,
    EventListenerInit                       ,
    dynamic_EventListenerInit               ,
    genClosure_EventListenerInit            ,
    mk_EventListenerInit                    ,
    noEventListenerInit                     ,
    wrap_EventListenerInit                  ,


-- ** FocusHandler #signal:FocusHandler#

    C_FocusHandler                          ,
    FocusHandler                            ,
    dynamic_FocusHandler                    ,
    genClosure_FocusHandler                 ,
    mk_FocusHandler                         ,
    noFocusHandler                          ,
    wrap_FocusHandler                       ,


-- ** Function #signal:Function#

    C_Function                              ,
    Function                                ,
    Function_WithClosures                   ,
    drop_closures_Function                  ,
    dynamic_Function                        ,
    genClosure_Function                     ,
    mk_Function                             ,
    noFunction                              ,
    noFunction_WithClosures                 ,
    wrap_Function                           ,


-- ** KeySnoopFunc #signal:KeySnoopFunc#

    C_KeySnoopFunc                          ,
    KeySnoopFunc                            ,
    KeySnoopFunc_WithClosures               ,
    drop_closures_KeySnoopFunc              ,
    dynamic_KeySnoopFunc                    ,
    genClosure_KeySnoopFunc                 ,
    mk_KeySnoopFunc                         ,
    noKeySnoopFunc                          ,
    noKeySnoopFunc_WithClosures             ,
    wrap_KeySnoopFunc                       ,


-- ** PropertyChangeHandler #signal:PropertyChangeHandler#

    C_PropertyChangeHandler                 ,
    PropertyChangeHandler                   ,
    dynamic_PropertyChangeHandler           ,
    genClosure_PropertyChangeHandler        ,
    mk_PropertyChangeHandler                ,
    noPropertyChangeHandler                 ,
    wrap_PropertyChangeHandler              ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import {-# SOURCE #-} qualified GI.Atk.Objects.Object as Atk.Object
import {-# SOURCE #-} qualified GI.Atk.Structs.KeyEventStruct as Atk.KeyEventStruct
import {-# SOURCE #-} qualified GI.Atk.Structs.PropertyValues as Atk.PropertyValues

-- callback PropertyChangeHandler
{- Callable
  { returnType = Nothing
  , returnMayBeNull = False
  , returnTransfer = TransferNothing
  , returnDocumentation =
      Documentation { rawDocText = Nothing , sinceVersion = Nothing }
  , args =
      [ Arg
          { argCName = "obj"
          , argType = TInterface Name { namespace = "Atk" , name = "Object" }
          , direction = DirectionIn
          , mayBeNull = False
          , argDoc =
              Documentation
                { rawDocText = Just "atkobject which property changes"
                , sinceVersion = Nothing
                }
          , argScope = ScopeTypeInvalid
          , argClosure = -1
          , argDestroy = -1
          , argCallerAllocates = False
          , transfer = TransferNothing
          }
      , Arg
          { argCName = "vals"
          , argType =
              TInterface Name { namespace = "Atk" , name = "PropertyValues" }
          , direction = DirectionIn
          , mayBeNull = False
          , argDoc =
              Documentation
                { rawDocText = Just "values changed" , sinceVersion = Nothing }
          , argScope = ScopeTypeInvalid
          , argClosure = -1
          , argDestroy = -1
          , argCallerAllocates = False
          , transfer = TransferNothing
          }
      ]
  , skipReturn = False
  , callableThrows = False
  , callableDeprecated =
      Just
        DeprecationInfo
          { deprecatedSinceVersion = Nothing
          , deprecationMessage = Just "Since 2.12."
          }
  , callableDocumentation =
      Documentation
        { rawDocText =
            Just
              "An AtkPropertyChangeHandler is a function which is executed when an\nAtkObject's property changes value. It is specified in a call to\natk_object_connect_property_change_handler()."
        , sinceVersion = Nothing
        }
  , callableResolvable = Nothing
  }
-}
-- | Type for the callback on the (unwrapped) C side.
type C_PropertyChangeHandler =
    Ptr Atk.Object.Object ->
    Ptr Atk.PropertyValues.PropertyValues ->
    IO ()

-- Args: [ Arg
--           { argCName = "obj"
--           , argType = TInterface Name { namespace = "Atk" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "atkobject which property changes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "vals"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "PropertyValues" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "values changed" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dynamic" __dynamic_C_PropertyChangeHandler :: FunPtr C_PropertyChangeHandler -> C_PropertyChangeHandler

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_PropertyChangeHandler ::
    (B.CallStack.HasCallStack, MonadIO m, Atk.Object.IsObject a) =>
    FunPtr C_PropertyChangeHandler
    -> a
    -- ^ /@obj@/: atkobject which property changes
    -> Atk.PropertyValues.PropertyValues
    -- ^ /@vals@/: values changed
    -> m ()
dynamic_PropertyChangeHandler :: FunPtr C_PropertyChangeHandler -> a -> PropertyValues -> m ()
dynamic_PropertyChangeHandler FunPtr C_PropertyChangeHandler
__funPtr a
obj PropertyValues
vals = 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
obj' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
obj
    Ptr PropertyValues
vals' <- PropertyValues -> IO (Ptr PropertyValues)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PropertyValues
vals
    (FunPtr C_PropertyChangeHandler -> C_PropertyChangeHandler
__dynamic_C_PropertyChangeHandler FunPtr C_PropertyChangeHandler
__funPtr) Ptr Object
obj' Ptr PropertyValues
vals'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
obj
    PropertyValues -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PropertyValues
vals
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

{-# DEPRECATED PropertyChangeHandler ["Since 2.12."] #-}
-- | An AtkPropertyChangeHandler is a function which is executed when an
-- AtkObject\'s property changes value. It is specified in a call to
-- @/atk_object_connect_property_change_handler()/@.
type PropertyChangeHandler =
    Atk.Object.Object
    -- ^ /@obj@/: atkobject which property changes
    -> Atk.PropertyValues.PropertyValues
    -- ^ /@vals@/: values changed
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `PropertyChangeHandler`@.
noPropertyChangeHandler :: Maybe PropertyChangeHandler
noPropertyChangeHandler :: Maybe PropertyChangeHandler
noPropertyChangeHandler = Maybe PropertyChangeHandler
forall a. Maybe a
Nothing

-- | Wrap the callback into a `GClosure`.
genClosure_PropertyChangeHandler :: MonadIO m => PropertyChangeHandler -> m (GClosure C_PropertyChangeHandler)
genClosure_PropertyChangeHandler :: PropertyChangeHandler -> m (GClosure C_PropertyChangeHandler)
genClosure_PropertyChangeHandler PropertyChangeHandler
cb = IO (GClosure C_PropertyChangeHandler)
-> m (GClosure C_PropertyChangeHandler)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_PropertyChangeHandler)
 -> m (GClosure C_PropertyChangeHandler))
-> IO (GClosure C_PropertyChangeHandler)
-> m (GClosure C_PropertyChangeHandler)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PropertyChangeHandler
cb' = Maybe (Ptr (FunPtr C_PropertyChangeHandler))
-> PropertyChangeHandler -> C_PropertyChangeHandler
wrap_PropertyChangeHandler Maybe (Ptr (FunPtr C_PropertyChangeHandler))
forall a. Maybe a
Nothing PropertyChangeHandler
cb
    C_PropertyChangeHandler -> IO (FunPtr C_PropertyChangeHandler)
mk_PropertyChangeHandler C_PropertyChangeHandler
cb' IO (FunPtr C_PropertyChangeHandler)
-> (FunPtr C_PropertyChangeHandler
    -> IO (GClosure C_PropertyChangeHandler))
-> IO (GClosure C_PropertyChangeHandler)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_PropertyChangeHandler
-> IO (GClosure C_PropertyChangeHandler)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `PropertyChangeHandler` into a `C_PropertyChangeHandler`.
wrap_PropertyChangeHandler ::
    Maybe (Ptr (FunPtr C_PropertyChangeHandler)) ->
    PropertyChangeHandler ->
    C_PropertyChangeHandler
wrap_PropertyChangeHandler :: Maybe (Ptr (FunPtr C_PropertyChangeHandler))
-> PropertyChangeHandler -> C_PropertyChangeHandler
wrap_PropertyChangeHandler Maybe (Ptr (FunPtr C_PropertyChangeHandler))
funptrptr PropertyChangeHandler
_cb Ptr Object
obj Ptr PropertyValues
vals = do
    Object
obj' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
Atk.Object.Object) Ptr Object
obj
    PropertyValues
vals' <- ((ManagedPtr PropertyValues -> PropertyValues)
-> Ptr PropertyValues -> IO PropertyValues
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr PropertyValues -> PropertyValues
Atk.PropertyValues.PropertyValues) Ptr PropertyValues
vals
    PropertyChangeHandler
_cb  Object
obj' PropertyValues
vals'
    Maybe (Ptr (FunPtr C_PropertyChangeHandler)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_PropertyChangeHandler))
funptrptr


-- callback KeySnoopFunc
{- Callable
  { returnType = Just (TBasicType TInt)
  , returnMayBeNull = False
  , returnTransfer = TransferNothing
  , returnDocumentation =
      Documentation
        { rawDocText =
            Just
              "TRUE (nonzero) if the event emission should be stopped and the event\ndiscarded without being passed to the normal GUI recipient; FALSE (zero) if the\nevent dispatch to the client application should proceed as normal.\n\nsee atk_add_key_event_listener."
        , sinceVersion = Nothing
        }
  , args =
      [ Arg
          { argCName = "event"
          , argType =
              TInterface Name { namespace = "Atk" , name = "KeyEventStruct" }
          , direction = DirectionIn
          , mayBeNull = False
          , argDoc =
              Documentation
                { rawDocText =
                    Just
                      "an AtkKeyEventStruct containing information about the key event for which\nnotification is being given."
                , sinceVersion = Nothing
                }
          , argScope = ScopeTypeInvalid
          , argClosure = -1
          , argDestroy = -1
          , argCallerAllocates = False
          , transfer = TransferNothing
          }
      , Arg
          { argCName = "user_data"
          , argType = TBasicType TPtr
          , direction = DirectionIn
          , mayBeNull = True
          , argDoc =
              Documentation
                { rawDocText =
                    Just
                      "a block of data which will be passed to the event listener, on notification."
                , sinceVersion = Nothing
                }
          , argScope = ScopeTypeInvalid
          , argClosure = 1
          , argDestroy = -1
          , argCallerAllocates = False
          , transfer = TransferNothing
          }
      ]
  , skipReturn = False
  , callableThrows = False
  , callableDeprecated = Nothing
  , callableDocumentation =
      Documentation
        { rawDocText =
            Just
              "An #AtkKeySnoopFunc is a type of callback which is called whenever a key event occurs,\nif registered via atk_add_key_event_listener.  It allows for pre-emptive\ninterception of key events via the return code as described below."
        , sinceVersion = Nothing
        }
  , callableResolvable = Nothing
  }
-}
-- | Type for the callback on the (unwrapped) C side.
type C_KeySnoopFunc =
    Ptr Atk.KeyEventStruct.KeyEventStruct ->
    Ptr () ->
    IO Int32

-- Args: [ Arg
--           { argCName = "event"
--           , argType =
--               TInterface Name { namespace = "Atk" , name = "KeyEventStruct" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "an AtkKeyEventStruct containing information about the key event for which\nnotification is being given."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a block of data which will be passed to the event listener, on notification."
--                 , 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 "dynamic" __dynamic_C_KeySnoopFunc :: FunPtr C_KeySnoopFunc -> C_KeySnoopFunc

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_KeySnoopFunc ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FunPtr C_KeySnoopFunc
    -> Atk.KeyEventStruct.KeyEventStruct
    -- ^ /@event@/: an AtkKeyEventStruct containing information about the key event for which
    -- notification is being given.
    -> Ptr ()
    -- ^ /@userData@/: a block of data which will be passed to the event listener, on notification.
    -> m Int32
    -- ^ __Returns:__ TRUE (nonzero) if the event emission should be stopped and the event
    -- discarded without being passed to the normal GUI recipient; FALSE (zero) if the
    -- event dispatch to the client application should proceed as normal.
    -- 
    -- see atk_add_key_event_listener.
dynamic_KeySnoopFunc :: FunPtr C_KeySnoopFunc -> KeyEventStruct -> Ptr () -> m Int32
dynamic_KeySnoopFunc FunPtr C_KeySnoopFunc
__funPtr KeyEventStruct
event Ptr ()
userData = 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 KeyEventStruct
event' <- KeyEventStruct -> IO (Ptr KeyEventStruct)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyEventStruct
event
    Int32
result <- (FunPtr C_KeySnoopFunc -> C_KeySnoopFunc
__dynamic_C_KeySnoopFunc FunPtr C_KeySnoopFunc
__funPtr) Ptr KeyEventStruct
event' Ptr ()
userData
    KeyEventStruct -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyEventStruct
event
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

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

-- | An t'GI.Atk.Callbacks.KeySnoopFunc' is a type of callback which is called whenever a key event occurs,
-- if registered via atk_add_key_event_listener.  It allows for pre-emptive
-- interception of key events via the return code as described below.
type KeySnoopFunc =
    Atk.KeyEventStruct.KeyEventStruct
    -- ^ /@event@/: an AtkKeyEventStruct containing information about the key event for which
    -- notification is being given.
    -> IO Int32
    -- ^ __Returns:__ TRUE (nonzero) if the event emission should be stopped and the event
    -- discarded without being passed to the normal GUI recipient; FALSE (zero) if the
    -- event dispatch to the client application should proceed as normal.
    -- 
    -- see atk_add_key_event_listener.

-- | A convenience synonym for @`Nothing` :: `Maybe` `KeySnoopFunc`@.
noKeySnoopFunc :: Maybe KeySnoopFunc
noKeySnoopFunc :: Maybe KeySnoopFunc
noKeySnoopFunc = Maybe KeySnoopFunc
forall a. Maybe a
Nothing

-- | An t'GI.Atk.Callbacks.KeySnoopFunc' is a type of callback which is called whenever a key event occurs,
-- if registered via atk_add_key_event_listener.  It allows for pre-emptive
-- interception of key events via the return code as described below.
type KeySnoopFunc_WithClosures =
    Atk.KeyEventStruct.KeyEventStruct
    -- ^ /@event@/: an AtkKeyEventStruct containing information about the key event for which
    -- notification is being given.
    -> Ptr ()
    -- ^ /@userData@/: a block of data which will be passed to the event listener, on notification.
    -> IO Int32
    -- ^ __Returns:__ TRUE (nonzero) if the event emission should be stopped and the event
    -- discarded without being passed to the normal GUI recipient; FALSE (zero) if the
    -- event dispatch to the client application should proceed as normal.
    -- 
    -- see atk_add_key_event_listener.

-- | A convenience synonym for @`Nothing` :: `Maybe` `KeySnoopFunc_WithClosures`@.
noKeySnoopFunc_WithClosures :: Maybe KeySnoopFunc_WithClosures
noKeySnoopFunc_WithClosures :: Maybe KeySnoopFunc_WithClosures
noKeySnoopFunc_WithClosures = Maybe KeySnoopFunc_WithClosures
forall a. Maybe a
Nothing

-- | A simple wrapper that ignores the closure arguments.
drop_closures_KeySnoopFunc :: KeySnoopFunc -> KeySnoopFunc_WithClosures
drop_closures_KeySnoopFunc :: KeySnoopFunc -> KeySnoopFunc_WithClosures
drop_closures_KeySnoopFunc KeySnoopFunc
_f KeyEventStruct
event Ptr ()
_ = KeySnoopFunc
_f KeyEventStruct
event

-- | Wrap the callback into a `GClosure`.
genClosure_KeySnoopFunc :: MonadIO m => KeySnoopFunc -> m (GClosure C_KeySnoopFunc)
genClosure_KeySnoopFunc :: KeySnoopFunc -> m (GClosure C_KeySnoopFunc)
genClosure_KeySnoopFunc KeySnoopFunc
cb = IO (GClosure C_KeySnoopFunc) -> m (GClosure C_KeySnoopFunc)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_KeySnoopFunc) -> m (GClosure C_KeySnoopFunc))
-> IO (GClosure C_KeySnoopFunc) -> m (GClosure C_KeySnoopFunc)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: KeySnoopFunc_WithClosures
cb' = KeySnoopFunc -> KeySnoopFunc_WithClosures
drop_closures_KeySnoopFunc KeySnoopFunc
cb
    let cb'' :: C_KeySnoopFunc
cb'' = Maybe (Ptr (FunPtr C_KeySnoopFunc))
-> KeySnoopFunc_WithClosures -> C_KeySnoopFunc
wrap_KeySnoopFunc Maybe (Ptr (FunPtr C_KeySnoopFunc))
forall a. Maybe a
Nothing KeySnoopFunc_WithClosures
cb'
    C_KeySnoopFunc -> IO (FunPtr C_KeySnoopFunc)
mk_KeySnoopFunc C_KeySnoopFunc
cb'' IO (FunPtr C_KeySnoopFunc)
-> (FunPtr C_KeySnoopFunc -> IO (GClosure C_KeySnoopFunc))
-> IO (GClosure C_KeySnoopFunc)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_KeySnoopFunc -> IO (GClosure C_KeySnoopFunc)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `KeySnoopFunc` into a `C_KeySnoopFunc`.
wrap_KeySnoopFunc ::
    Maybe (Ptr (FunPtr C_KeySnoopFunc)) ->
    KeySnoopFunc_WithClosures ->
    C_KeySnoopFunc
wrap_KeySnoopFunc :: Maybe (Ptr (FunPtr C_KeySnoopFunc))
-> KeySnoopFunc_WithClosures -> C_KeySnoopFunc
wrap_KeySnoopFunc Maybe (Ptr (FunPtr C_KeySnoopFunc))
funptrptr KeySnoopFunc_WithClosures
_cb Ptr KeyEventStruct
event Ptr ()
userData = do
    KeyEventStruct
event' <- ((ManagedPtr KeyEventStruct -> KeyEventStruct)
-> Ptr KeyEventStruct -> IO KeyEventStruct
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr KeyEventStruct -> KeyEventStruct
Atk.KeyEventStruct.KeyEventStruct) Ptr KeyEventStruct
event
    Int32
result <- KeySnoopFunc_WithClosures
_cb  KeyEventStruct
event' Ptr ()
userData
    Maybe (Ptr (FunPtr C_KeySnoopFunc)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_KeySnoopFunc))
funptrptr
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result


-- callback Function
{- Callable
  { returnType = Just (TBasicType TBoolean)
  , returnMayBeNull = False
  , returnTransfer = TransferNothing
  , returnDocumentation =
      Documentation
        { rawDocText = Just "not used" , sinceVersion = Nothing }
  , args =
      [ Arg
          { argCName = "user_data"
          , argType = TBasicType TPtr
          , direction = DirectionIn
          , mayBeNull = True
          , argDoc =
              Documentation
                { rawDocText = Just "custom data defined by the user"
                , sinceVersion = Nothing
                }
          , argScope = ScopeTypeInvalid
          , argClosure = 0
          , argDestroy = -1
          , argCallerAllocates = False
          , transfer = TransferNothing
          }
      ]
  , skipReturn = False
  , callableThrows = False
  , callableDeprecated = Nothing
  , callableDocumentation =
      Documentation
        { rawDocText =
            Just
              "An AtkFunction is a function definition used for padding which has\nbeen added to class and interface structures to allow for expansion\nin the future."
        , sinceVersion = Nothing
        }
  , callableResolvable = Nothing
  }
-}
-- | Type for the callback on the (unwrapped) C side.
type C_Function =
    Ptr () ->
    IO CInt

-- Args: [ Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "custom data defined by the user"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = 0
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dynamic" __dynamic_C_Function :: FunPtr C_Function -> C_Function

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_Function ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FunPtr C_Function
    -> Ptr ()
    -- ^ /@userData@/: custom data defined by the user
    -> m Bool
    -- ^ __Returns:__ not used
dynamic_Function :: FunPtr C_Function -> Ptr () -> m Bool
dynamic_Function FunPtr C_Function
__funPtr Ptr ()
userData = 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
    CInt
result <- (FunPtr C_Function -> C_Function
__dynamic_C_Function FunPtr C_Function
__funPtr) Ptr ()
userData
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

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

-- | An AtkFunction is a function definition used for padding which has
-- been added to class and interface structures to allow for expansion
-- in the future.
type Function =
    IO Bool
    -- ^ __Returns:__ not used

-- | A convenience synonym for @`Nothing` :: `Maybe` `Function`@.
noFunction :: Maybe Function
noFunction :: Maybe (IO Bool)
noFunction = Maybe (IO Bool)
forall a. Maybe a
Nothing

-- | An AtkFunction is a function definition used for padding which has
-- been added to class and interface structures to allow for expansion
-- in the future.
type Function_WithClosures =
    Ptr ()
    -- ^ /@userData@/: custom data defined by the user
    -> IO Bool
    -- ^ __Returns:__ not used

-- | A convenience synonym for @`Nothing` :: `Maybe` `Function_WithClosures`@.
noFunction_WithClosures :: Maybe Function_WithClosures
noFunction_WithClosures :: Maybe Function_WithClosures
noFunction_WithClosures = Maybe Function_WithClosures
forall a. Maybe a
Nothing

-- | A simple wrapper that ignores the closure arguments.
drop_closures_Function :: Function -> Function_WithClosures
drop_closures_Function :: IO Bool -> Function_WithClosures
drop_closures_Function IO Bool
_f Ptr ()
_ = IO Bool
_f 

-- | Wrap the callback into a `GClosure`.
genClosure_Function :: MonadIO m => Function -> m (GClosure C_Function)
genClosure_Function :: IO Bool -> m (GClosure C_Function)
genClosure_Function IO Bool
cb = IO (GClosure C_Function) -> m (GClosure C_Function)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_Function) -> m (GClosure C_Function))
-> IO (GClosure C_Function) -> m (GClosure C_Function)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: Function_WithClosures
cb' = IO Bool -> Function_WithClosures
drop_closures_Function IO Bool
cb
    let cb'' :: C_Function
cb'' = Maybe (Ptr (FunPtr C_Function))
-> Function_WithClosures -> C_Function
wrap_Function Maybe (Ptr (FunPtr C_Function))
forall a. Maybe a
Nothing Function_WithClosures
cb'
    C_Function -> IO (FunPtr C_Function)
mk_Function C_Function
cb'' IO (FunPtr C_Function)
-> (FunPtr C_Function -> IO (GClosure C_Function))
-> IO (GClosure C_Function)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_Function -> IO (GClosure C_Function)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `Function` into a `C_Function`.
wrap_Function ::
    Maybe (Ptr (FunPtr C_Function)) ->
    Function_WithClosures ->
    C_Function
wrap_Function :: Maybe (Ptr (FunPtr C_Function))
-> Function_WithClosures -> C_Function
wrap_Function Maybe (Ptr (FunPtr C_Function))
funptrptr Function_WithClosures
_cb Ptr ()
userData = do
    Bool
result <- Function_WithClosures
_cb  Ptr ()
userData
    Maybe (Ptr (FunPtr C_Function)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_Function))
funptrptr
    let result' :: CInt
result' = (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
result
    CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'


-- callback FocusHandler
{- Callable
  { returnType = Nothing
  , returnMayBeNull = False
  , returnTransfer = TransferNothing
  , returnDocumentation =
      Documentation { rawDocText = Nothing , sinceVersion = Nothing }
  , args =
      [ Arg
          { argCName = "object"
          , argType = TInterface Name { namespace = "Atk" , name = "Object" }
          , direction = DirectionIn
          , mayBeNull = False
          , argDoc =
              Documentation
                { rawDocText = Just "the #AtkObject that receives/lose the focus"
                , sinceVersion = Nothing
                }
          , argScope = ScopeTypeInvalid
          , argClosure = -1
          , argDestroy = -1
          , argCallerAllocates = False
          , transfer = TransferNothing
          }
      , Arg
          { argCName = "focus_in"
          , argType = TBasicType TBoolean
          , direction = DirectionIn
          , mayBeNull = False
          , argDoc =
              Documentation
                { rawDocText = Just "TRUE if the object receives the focus"
                , sinceVersion = Nothing
                }
          , argScope = ScopeTypeInvalid
          , argClosure = -1
          , argDestroy = -1
          , argCallerAllocates = False
          , transfer = TransferNothing
          }
      ]
  , skipReturn = False
  , callableThrows = False
  , callableDeprecated =
      Just
        DeprecationInfo
          { deprecatedSinceVersion = Just "2.9.4"
          , deprecationMessage =
              Just
                "Deprecated with atk_component_add_focus_handler()\nand atk_component_remove_focus_handler(). See those\nmethods for more information."
          }
  , callableDocumentation =
      Documentation
        { rawDocText =
            Just
              "The type of callback function used for\natk_component_add_focus_handler() and\natk_component_remove_focus_handler()"
        , sinceVersion = Nothing
        }
  , callableResolvable = Nothing
  }
-}
-- | Type for the callback on the (unwrapped) C side.
type C_FocusHandler =
    Ptr Atk.Object.Object ->
    CInt ->
    IO ()

-- Args: [ Arg
--           { argCName = "object"
--           , argType = TInterface Name { namespace = "Atk" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #AtkObject that receives/lose the focus"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "focus_in"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "TRUE if the object receives the focus"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dynamic" __dynamic_C_FocusHandler :: FunPtr C_FocusHandler -> C_FocusHandler

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_FocusHandler ::
    (B.CallStack.HasCallStack, MonadIO m, Atk.Object.IsObject a) =>
    FunPtr C_FocusHandler
    -> a
    -- ^ /@object@/: the t'GI.Atk.Objects.Object.Object' that receives\/lose the focus
    -> Bool
    -- ^ /@focusIn@/: TRUE if the object receives the focus
    -> m ()
dynamic_FocusHandler :: FunPtr C_FocusHandler -> a -> Bool -> m ()
dynamic_FocusHandler FunPtr C_FocusHandler
__funPtr a
object Bool
focusIn = 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
object' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
object
    let focusIn' :: CInt
focusIn' = (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
focusIn
    (FunPtr C_FocusHandler -> C_FocusHandler
__dynamic_C_FocusHandler FunPtr C_FocusHandler
__funPtr) Ptr Object
object' CInt
focusIn'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
object
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

{-# DEPRECATED FocusHandler ["(Since version 2.9.4)","Deprecated with @/atk_component_add_focus_handler()/@","and 'GI.Atk.Interfaces.Component.componentRemoveFocusHandler'. See those","methods for more information."] #-}
-- | The type of callback function used for
-- @/atk_component_add_focus_handler()/@ and
-- 'GI.Atk.Interfaces.Component.componentRemoveFocusHandler'
type FocusHandler =
    Atk.Object.Object
    -- ^ /@object@/: the t'GI.Atk.Objects.Object.Object' that receives\/lose the focus
    -> Bool
    -- ^ /@focusIn@/: TRUE if the object receives the focus
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `FocusHandler`@.
noFocusHandler :: Maybe FocusHandler
noFocusHandler :: Maybe FocusHandler
noFocusHandler = Maybe FocusHandler
forall a. Maybe a
Nothing

-- | Wrap the callback into a `GClosure`.
genClosure_FocusHandler :: MonadIO m => FocusHandler -> m (GClosure C_FocusHandler)
genClosure_FocusHandler :: FocusHandler -> m (GClosure C_FocusHandler)
genClosure_FocusHandler FocusHandler
cb = IO (GClosure C_FocusHandler) -> m (GClosure C_FocusHandler)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_FocusHandler) -> m (GClosure C_FocusHandler))
-> IO (GClosure C_FocusHandler) -> m (GClosure C_FocusHandler)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_FocusHandler
cb' = Maybe (Ptr (FunPtr C_FocusHandler))
-> FocusHandler -> C_FocusHandler
wrap_FocusHandler Maybe (Ptr (FunPtr C_FocusHandler))
forall a. Maybe a
Nothing FocusHandler
cb
    C_FocusHandler -> IO (FunPtr C_FocusHandler)
mk_FocusHandler C_FocusHandler
cb' IO (FunPtr C_FocusHandler)
-> (FunPtr C_FocusHandler -> IO (GClosure C_FocusHandler))
-> IO (GClosure C_FocusHandler)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_FocusHandler -> IO (GClosure C_FocusHandler)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `FocusHandler` into a `C_FocusHandler`.
wrap_FocusHandler ::
    Maybe (Ptr (FunPtr C_FocusHandler)) ->
    FocusHandler ->
    C_FocusHandler
wrap_FocusHandler :: Maybe (Ptr (FunPtr C_FocusHandler))
-> FocusHandler -> C_FocusHandler
wrap_FocusHandler Maybe (Ptr (FunPtr C_FocusHandler))
funptrptr FocusHandler
_cb Ptr Object
object CInt
focusIn = do
    Object
object' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
Atk.Object.Object) Ptr Object
object
    let focusIn' :: Bool
focusIn' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
focusIn
    FocusHandler
_cb  Object
object' Bool
focusIn'
    Maybe (Ptr (FunPtr C_FocusHandler)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_FocusHandler))
funptrptr


-- callback EventListenerInit
{- Callable
  { returnType = Nothing
  , returnMayBeNull = False
  , returnTransfer = TransferNothing
  , returnDocumentation =
      Documentation { rawDocText = Nothing , sinceVersion = Nothing }
  , args = []
  , skipReturn = False
  , callableThrows = False
  , callableDeprecated = Nothing
  , callableDocumentation =
      Documentation
        { rawDocText =
            Just
              "An #AtkEventListenerInit function is a special function that is\ncalled in order to initialize the per-object event registration system\nused by #AtkEventListener, if any preparation is required.\n\nsee atk_focus_tracker_init."
        , sinceVersion = Nothing
        }
  , callableResolvable = Nothing
  }
-}
-- | Type for the callback on the (unwrapped) C side.
type C_EventListenerInit =
    IO ()

-- Args: []
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dynamic" __dynamic_C_EventListenerInit :: FunPtr C_EventListenerInit -> C_EventListenerInit

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_EventListenerInit ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FunPtr C_EventListenerInit
    -> m ()
dynamic_EventListenerInit :: FunPtr (IO ()) -> m ()
dynamic_EventListenerInit FunPtr (IO ())
__funPtr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    (FunPtr (IO ()) -> IO ()
__dynamic_C_EventListenerInit FunPtr (IO ())
__funPtr)
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

-- | An t'GI.Atk.Callbacks.EventListenerInit' function is a special function that is
-- called in order to initialize the per-object event registration system
-- used by t'GI.Atk.Callbacks.EventListener', if any preparation is required.
-- 
-- see atk_focus_tracker_init.
type EventListenerInit =
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_EventListenerInit :: MonadIO m => EventListenerInit -> m (GClosure C_EventListenerInit)
genClosure_EventListenerInit :: IO () -> m (GClosure (IO ()))
genClosure_EventListenerInit IO ()
cb = IO (GClosure (IO ())) -> m (GClosure (IO ()))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure (IO ())) -> m (GClosure (IO ())))
-> IO (GClosure (IO ())) -> m (GClosure (IO ()))
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: IO ()
cb' = Maybe (Ptr (FunPtr (IO ()))) -> IO () -> IO ()
wrap_EventListenerInit Maybe (Ptr (FunPtr (IO ())))
forall a. Maybe a
Nothing IO ()
cb
    IO () -> IO (FunPtr (IO ()))
mk_EventListenerInit IO ()
cb' IO (FunPtr (IO ()))
-> (FunPtr (IO ()) -> IO (GClosure (IO ())))
-> IO (GClosure (IO ()))
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr (IO ()) -> IO (GClosure (IO ()))
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `EventListenerInit` into a `C_EventListenerInit`.
wrap_EventListenerInit ::
    Maybe (Ptr (FunPtr C_EventListenerInit)) ->
    EventListenerInit ->
    C_EventListenerInit
wrap_EventListenerInit :: Maybe (Ptr (FunPtr (IO ()))) -> IO () -> IO ()
wrap_EventListenerInit Maybe (Ptr (FunPtr (IO ())))
funptrptr IO ()
_cb = do
    IO ()
_cb 
    Maybe (Ptr (FunPtr (IO ()))) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr (IO ())))
funptrptr


-- callback EventListener
{- Callable
  { returnType = Nothing
  , returnMayBeNull = False
  , returnTransfer = TransferNothing
  , returnDocumentation =
      Documentation { rawDocText = Nothing , sinceVersion = Nothing }
  , args =
      [ Arg
          { argCName = "obj"
          , argType = TInterface Name { namespace = "Atk" , name = "Object" }
          , direction = DirectionIn
          , mayBeNull = False
          , argDoc =
              Documentation
                { rawDocText =
                    Just
                      "An #AtkObject instance for whom the callback will be called when\nthe specified event (e.g. 'focus:') takes place."
                , sinceVersion = Nothing
                }
          , argScope = ScopeTypeInvalid
          , argClosure = -1
          , argDestroy = -1
          , argCallerAllocates = False
          , transfer = TransferNothing
          }
      ]
  , skipReturn = False
  , callableThrows = False
  , callableDeprecated = Nothing
  , callableDocumentation =
      Documentation
        { rawDocText =
            Just
              "A function which is called when an object emits a matching event,\nas used in #atk_add_focus_tracker.\nCurrently the only events for which object-specific handlers are\nsupported are events of type \"focus:\".  Most clients of ATK will prefer to\nattach signal handlers for the various ATK signals instead.\n\nsee atk_add_focus_tracker."
        , sinceVersion = Nothing
        }
  , callableResolvable = Nothing
  }
-}
-- | Type for the callback on the (unwrapped) C side.
type C_EventListener =
    Ptr Atk.Object.Object ->
    IO ()

-- Args: [ Arg
--           { argCName = "obj"
--           , argType = TInterface Name { namespace = "Atk" , name = "Object" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "An #AtkObject instance for whom the callback will be called when\nthe specified event (e.g. 'focus:') takes place."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dynamic" __dynamic_C_EventListener :: FunPtr C_EventListener -> C_EventListener

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_EventListener ::
    (B.CallStack.HasCallStack, MonadIO m, Atk.Object.IsObject a) =>
    FunPtr C_EventListener
    -> a
    -- ^ /@obj@/: An t'GI.Atk.Objects.Object.Object' instance for whom the callback will be called when
    -- the specified event (e.g. \'focus:\') takes place.
    -> m ()
dynamic_EventListener :: FunPtr C_EventListener -> a -> m ()
dynamic_EventListener FunPtr C_EventListener
__funPtr a
obj = 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
obj' <- a -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
obj
    (FunPtr C_EventListener -> C_EventListener
__dynamic_C_EventListener FunPtr C_EventListener
__funPtr) Ptr Object
obj'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
obj
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

-- | A function which is called when an object emits a matching event,
-- as used in @/atk_add_focus_tracker/@.
-- Currently the only events for which object-specific handlers are
-- supported are events of type \"focus:\".  Most clients of ATK will prefer to
-- attach signal handlers for the various ATK signals instead.
-- 
-- see atk_add_focus_tracker.
type EventListener =
    Atk.Object.Object
    -- ^ /@obj@/: An t'GI.Atk.Objects.Object.Object' instance for whom the callback will be called when
    -- the specified event (e.g. \'focus:\') takes place.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `EventListener`@.
noEventListener :: Maybe EventListener
noEventListener :: Maybe EventListener
noEventListener = Maybe EventListener
forall a. Maybe a
Nothing

-- | Wrap the callback into a `GClosure`.
genClosure_EventListener :: MonadIO m => EventListener -> m (GClosure C_EventListener)
genClosure_EventListener :: EventListener -> m (GClosure C_EventListener)
genClosure_EventListener EventListener
cb = IO (GClosure C_EventListener) -> m (GClosure C_EventListener)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_EventListener) -> m (GClosure C_EventListener))
-> IO (GClosure C_EventListener) -> m (GClosure C_EventListener)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_EventListener
cb' = Maybe (Ptr (FunPtr C_EventListener))
-> EventListener -> C_EventListener
wrap_EventListener Maybe (Ptr (FunPtr C_EventListener))
forall a. Maybe a
Nothing EventListener
cb
    C_EventListener -> IO (FunPtr C_EventListener)
mk_EventListener C_EventListener
cb' IO (FunPtr C_EventListener)
-> (FunPtr C_EventListener -> IO (GClosure C_EventListener))
-> IO (GClosure C_EventListener)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_EventListener -> IO (GClosure C_EventListener)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `EventListener` into a `C_EventListener`.
wrap_EventListener ::
    Maybe (Ptr (FunPtr C_EventListener)) ->
    EventListener ->
    C_EventListener
wrap_EventListener :: Maybe (Ptr (FunPtr C_EventListener))
-> EventListener -> C_EventListener
wrap_EventListener Maybe (Ptr (FunPtr C_EventListener))
funptrptr EventListener
_cb Ptr Object
obj = do
    Object
obj' <- ((ManagedPtr Object -> Object) -> Ptr Object -> IO Object
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Object -> Object
Atk.Object.Object) Ptr Object
obj
    EventListener
_cb  Object
obj'
    Maybe (Ptr (FunPtr C_EventListener)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_EventListener))
funptrptr