#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Atk.Callbacks
(
C_EventListener ,
EventListener ,
dynamic_EventListener ,
genClosure_EventListener ,
mk_EventListener ,
noEventListener ,
wrap_EventListener ,
C_EventListenerInit ,
EventListenerInit ,
dynamic_EventListenerInit ,
genClosure_EventListenerInit ,
mk_EventListenerInit ,
noEventListenerInit ,
wrap_EventListenerInit ,
C_FocusHandler ,
FocusHandler ,
dynamic_FocusHandler ,
genClosure_FocusHandler ,
mk_FocusHandler ,
noFocusHandler ,
wrap_FocusHandler ,
C_Function ,
Function ,
Function_WithClosures ,
drop_closures_Function ,
dynamic_Function ,
genClosure_Function ,
mk_Function ,
noFunction ,
noFunction_WithClosures ,
wrap_Function ,
C_KeySnoopFunc ,
KeySnoopFunc ,
KeySnoopFunc_WithClosures ,
drop_closures_KeySnoopFunc ,
dynamic_KeySnoopFunc ,
genClosure_KeySnoopFunc ,
mk_KeySnoopFunc ,
noKeySnoopFunc ,
noKeySnoopFunc_WithClosures ,
wrap_KeySnoopFunc ,
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.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.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
type C_PropertyChangeHandler =
Ptr Atk.Object.Object ->
Ptr Atk.PropertyValues.PropertyValues ->
IO ()
foreign import ccall "dynamic" __dynamic_C_PropertyChangeHandler :: FunPtr C_PropertyChangeHandler -> C_PropertyChangeHandler
dynamic_PropertyChangeHandler ::
(B.CallStack.HasCallStack, MonadIO m, Atk.Object.IsObject a) =>
FunPtr C_PropertyChangeHandler
-> a
-> Atk.PropertyValues.PropertyValues
-> m ()
dynamic_PropertyChangeHandler :: FunPtr C_PropertyChangeHandler -> a -> PropertyValues -> m ()
dynamic_PropertyChangeHandler __funPtr :: FunPtr C_PropertyChangeHandler
__funPtr obj :: a
obj vals :: 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 ()
foreign import ccall "wrapper"
mk_PropertyChangeHandler :: C_PropertyChangeHandler -> IO (FunPtr C_PropertyChangeHandler)
{-# DEPRECATED PropertyChangeHandler ["Since 2.12."] #-}
type PropertyChangeHandler =
Atk.Object.Object
-> Atk.PropertyValues.PropertyValues
-> IO ()
noPropertyChangeHandler :: Maybe PropertyChangeHandler
noPropertyChangeHandler :: Maybe PropertyChangeHandler
noPropertyChangeHandler = Maybe PropertyChangeHandler
forall a. Maybe a
Nothing
genClosure_PropertyChangeHandler :: MonadIO m => PropertyChangeHandler -> m (GClosure C_PropertyChangeHandler)
genClosure_PropertyChangeHandler :: PropertyChangeHandler -> m (GClosure C_PropertyChangeHandler)
genClosure_PropertyChangeHandler cb :: 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_PropertyChangeHandler ::
Maybe (Ptr (FunPtr C_PropertyChangeHandler)) ->
PropertyChangeHandler ->
C_PropertyChangeHandler
wrap_PropertyChangeHandler :: Maybe (Ptr (FunPtr C_PropertyChangeHandler))
-> PropertyChangeHandler -> C_PropertyChangeHandler
wrap_PropertyChangeHandler funptrptr :: Maybe (Ptr (FunPtr C_PropertyChangeHandler))
funptrptr _cb :: PropertyChangeHandler
_cb obj :: Ptr Object
obj vals :: 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, WrappedPtr 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
type C_KeySnoopFunc =
Ptr Atk.KeyEventStruct.KeyEventStruct ->
Ptr () ->
IO Int32
foreign import ccall "dynamic" __dynamic_C_KeySnoopFunc :: FunPtr C_KeySnoopFunc -> C_KeySnoopFunc
dynamic_KeySnoopFunc ::
(B.CallStack.HasCallStack, MonadIO m) =>
FunPtr C_KeySnoopFunc
-> Atk.KeyEventStruct.KeyEventStruct
-> Ptr ()
-> m Int32
dynamic_KeySnoopFunc :: FunPtr C_KeySnoopFunc -> KeyEventStruct -> Ptr () -> m Int32
dynamic_KeySnoopFunc __funPtr :: FunPtr C_KeySnoopFunc
__funPtr event :: KeyEventStruct
event userData :: 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
foreign import ccall "wrapper"
mk_KeySnoopFunc :: C_KeySnoopFunc -> IO (FunPtr C_KeySnoopFunc)
type KeySnoopFunc =
Atk.KeyEventStruct.KeyEventStruct
-> IO Int32
noKeySnoopFunc :: Maybe KeySnoopFunc
noKeySnoopFunc :: Maybe KeySnoopFunc
noKeySnoopFunc = Maybe KeySnoopFunc
forall a. Maybe a
Nothing
type KeySnoopFunc_WithClosures =
Atk.KeyEventStruct.KeyEventStruct
-> Ptr ()
-> IO Int32
noKeySnoopFunc_WithClosures :: Maybe KeySnoopFunc_WithClosures
noKeySnoopFunc_WithClosures :: Maybe KeySnoopFunc_WithClosures
noKeySnoopFunc_WithClosures = Maybe KeySnoopFunc_WithClosures
forall a. Maybe a
Nothing
drop_closures_KeySnoopFunc :: KeySnoopFunc -> KeySnoopFunc_WithClosures
drop_closures_KeySnoopFunc :: KeySnoopFunc -> KeySnoopFunc_WithClosures
drop_closures_KeySnoopFunc _f :: KeySnoopFunc
_f event :: KeyEventStruct
event _ = KeySnoopFunc
_f KeyEventStruct
event
genClosure_KeySnoopFunc :: MonadIO m => KeySnoopFunc -> m (GClosure C_KeySnoopFunc)
genClosure_KeySnoopFunc :: KeySnoopFunc -> m (GClosure C_KeySnoopFunc)
genClosure_KeySnoopFunc cb :: 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_KeySnoopFunc ::
Maybe (Ptr (FunPtr C_KeySnoopFunc)) ->
KeySnoopFunc_WithClosures ->
C_KeySnoopFunc
wrap_KeySnoopFunc :: Maybe (Ptr (FunPtr C_KeySnoopFunc))
-> KeySnoopFunc_WithClosures -> C_KeySnoopFunc
wrap_KeySnoopFunc funptrptr :: Maybe (Ptr (FunPtr C_KeySnoopFunc))
funptrptr _cb :: KeySnoopFunc_WithClosures
_cb event :: Ptr KeyEventStruct
event userData :: Ptr ()
userData = do
KeyEventStruct
event' <- ((ManagedPtr KeyEventStruct -> KeyEventStruct)
-> Ptr KeyEventStruct -> IO KeyEventStruct
forall a.
(HasCallStack, WrappedPtr 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
type C_Function =
Ptr () ->
IO CInt
foreign import ccall "dynamic" __dynamic_C_Function :: FunPtr C_Function -> C_Function
dynamic_Function ::
(B.CallStack.HasCallStack, MonadIO m) =>
FunPtr C_Function
-> Ptr ()
-> m Bool
dynamic_Function :: FunPtr C_Function -> Ptr () -> m Bool
dynamic_Function __funPtr :: FunPtr C_Function
__funPtr userData :: 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
/= 0) CInt
result
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
foreign import ccall "wrapper"
mk_Function :: C_Function -> IO (FunPtr C_Function)
type Function =
IO Bool
noFunction :: Maybe Function
noFunction :: Maybe (IO Bool)
noFunction = Maybe (IO Bool)
forall a. Maybe a
Nothing
type Function_WithClosures =
Ptr ()
-> IO Bool
noFunction_WithClosures :: Maybe Function_WithClosures
noFunction_WithClosures :: Maybe Function_WithClosures
noFunction_WithClosures = Maybe Function_WithClosures
forall a. Maybe a
Nothing
drop_closures_Function :: Function -> Function_WithClosures
drop_closures_Function :: IO Bool -> Function_WithClosures
drop_closures_Function _f :: IO Bool
_f _ = IO Bool
_f
genClosure_Function :: MonadIO m => Function -> m (GClosure C_Function)
genClosure_Function :: IO Bool -> m (GClosure C_Function)
genClosure_Function cb :: 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_Function ::
Maybe (Ptr (FunPtr C_Function)) ->
Function_WithClosures ->
C_Function
wrap_Function :: Maybe (Ptr (FunPtr C_Function))
-> Function_WithClosures -> C_Function
wrap_Function funptrptr :: Maybe (Ptr (FunPtr C_Function))
funptrptr _cb :: Function_WithClosures
_cb userData :: 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'
type C_FocusHandler =
Ptr Atk.Object.Object ->
CInt ->
IO ()
foreign import ccall "dynamic" __dynamic_C_FocusHandler :: FunPtr C_FocusHandler -> C_FocusHandler
dynamic_FocusHandler ::
(B.CallStack.HasCallStack, MonadIO m, Atk.Object.IsObject a) =>
FunPtr C_FocusHandler
-> a
-> Bool
-> m ()
dynamic_FocusHandler :: FunPtr C_FocusHandler -> a -> Bool -> m ()
dynamic_FocusHandler __funPtr :: FunPtr C_FocusHandler
__funPtr object :: a
object focusIn :: 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 ()
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."] #-}
type FocusHandler =
Atk.Object.Object
-> Bool
-> IO ()
noFocusHandler :: Maybe FocusHandler
noFocusHandler :: Maybe FocusHandler
noFocusHandler = Maybe FocusHandler
forall a. Maybe a
Nothing
genClosure_FocusHandler :: MonadIO m => FocusHandler -> m (GClosure C_FocusHandler)
genClosure_FocusHandler :: FocusHandler -> m (GClosure C_FocusHandler)
genClosure_FocusHandler cb :: 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_FocusHandler ::
Maybe (Ptr (FunPtr C_FocusHandler)) ->
FocusHandler ->
C_FocusHandler
wrap_FocusHandler :: Maybe (Ptr (FunPtr C_FocusHandler))
-> FocusHandler -> C_FocusHandler
wrap_FocusHandler funptrptr :: Maybe (Ptr (FunPtr C_FocusHandler))
funptrptr _cb :: FocusHandler
_cb object :: Ptr Object
object focusIn :: 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
/= 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
type C_EventListenerInit =
IO ()
foreign import ccall "dynamic" __dynamic_C_EventListenerInit :: FunPtr C_EventListenerInit -> C_EventListenerInit
dynamic_EventListenerInit ::
(B.CallStack.HasCallStack, MonadIO m) =>
FunPtr C_EventListenerInit
-> m ()
dynamic_EventListenerInit :: FunPtr (IO ()) -> m ()
dynamic_EventListenerInit __funPtr :: 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 ()
foreign import ccall "wrapper"
mk_EventListenerInit :: C_EventListenerInit -> IO (FunPtr C_EventListenerInit)
type EventListenerInit =
IO ()
noEventListenerInit :: Maybe EventListenerInit
noEventListenerInit :: Maybe (IO ())
noEventListenerInit = Maybe (IO ())
forall a. Maybe a
Nothing
genClosure_EventListenerInit :: MonadIO m => EventListenerInit -> m (GClosure C_EventListenerInit)
genClosure_EventListenerInit :: IO () -> m (GClosure (IO ()))
genClosure_EventListenerInit cb :: 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_EventListenerInit ::
Maybe (Ptr (FunPtr C_EventListenerInit)) ->
EventListenerInit ->
C_EventListenerInit
wrap_EventListenerInit :: Maybe (Ptr (FunPtr (IO ()))) -> IO () -> IO ()
wrap_EventListenerInit funptrptr :: Maybe (Ptr (FunPtr (IO ())))
funptrptr _cb :: IO ()
_cb = do
IO ()
_cb
Maybe (Ptr (FunPtr (IO ()))) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr (IO ())))
funptrptr
type C_EventListener =
Ptr Atk.Object.Object ->
IO ()
foreign import ccall "dynamic" __dynamic_C_EventListener :: FunPtr C_EventListener -> C_EventListener
dynamic_EventListener ::
(B.CallStack.HasCallStack, MonadIO m, Atk.Object.IsObject a) =>
FunPtr C_EventListener
-> a
-> m ()
dynamic_EventListener :: FunPtr C_EventListener -> a -> m ()
dynamic_EventListener __funPtr :: FunPtr C_EventListener
__funPtr obj :: 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 ()
foreign import ccall "wrapper"
mk_EventListener :: C_EventListener -> IO (FunPtr C_EventListener)
type EventListener =
Atk.Object.Object
-> IO ()
noEventListener :: Maybe EventListener
noEventListener :: Maybe EventListener
noEventListener = Maybe EventListener
forall a. Maybe a
Nothing
genClosure_EventListener :: MonadIO m => EventListener -> m (GClosure C_EventListener)
genClosure_EventListener :: EventListener -> m (GClosure C_EventListener)
genClosure_EventListener cb :: 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_EventListener ::
Maybe (Ptr (FunPtr C_EventListener)) ->
EventListener ->
C_EventListener
wrap_EventListener :: Maybe (Ptr (FunPtr C_EventListener))
-> EventListener -> C_EventListener
wrap_EventListener funptrptr :: Maybe (Ptr (FunPtr C_EventListener))
funptrptr _cb :: EventListener
_cb obj :: 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