-- | 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.Gdk.Callbacks
    ( 

 -- * Signals
-- ** EventFunc #signal:EventFunc#

    C_EventFunc                             ,
    EventFunc                               ,
    EventFunc_WithClosures                  ,
    drop_closures_EventFunc                 ,
    dynamic_EventFunc                       ,
    genClosure_EventFunc                    ,
    mk_EventFunc                            ,
    noEventFunc                             ,
    noEventFunc_WithClosures                ,
    wrap_EventFunc                          ,


-- ** FilterFunc #signal:FilterFunc#

    C_FilterFunc                            ,
    FilterFunc                              ,
    FilterFunc_WithClosures                 ,
    drop_closures_FilterFunc                ,
    dynamic_FilterFunc                      ,
    genClosure_FilterFunc                   ,
    mk_FilterFunc                           ,
    noFilterFunc                            ,
    noFilterFunc_WithClosures               ,
    wrap_FilterFunc                         ,


-- ** SeatGrabPrepareFunc #signal:SeatGrabPrepareFunc#

    C_SeatGrabPrepareFunc                   ,
    SeatGrabPrepareFunc                     ,
    SeatGrabPrepareFunc_WithClosures        ,
    drop_closures_SeatGrabPrepareFunc       ,
    dynamic_SeatGrabPrepareFunc             ,
    genClosure_SeatGrabPrepareFunc          ,
    mk_SeatGrabPrepareFunc                  ,
    noSeatGrabPrepareFunc                   ,
    noSeatGrabPrepareFunc_WithClosures      ,
    wrap_SeatGrabPrepareFunc                ,


-- ** WindowChildFunc #signal:WindowChildFunc#

    C_WindowChildFunc                       ,
    WindowChildFunc                         ,
    WindowChildFunc_WithClosures            ,
    drop_closures_WindowChildFunc           ,
    dynamic_WindowChildFunc                 ,
    genClosure_WindowChildFunc              ,
    mk_WindowChildFunc                      ,
    noWindowChildFunc                       ,
    noWindowChildFunc_WithClosures          ,
    wrap_WindowChildFunc                    ,


-- ** WindowInvalidateHandlerFunc #signal:WindowInvalidateHandlerFunc#

    C_WindowInvalidateHandlerFunc           ,
    WindowInvalidateHandlerFunc             ,
    dynamic_WindowInvalidateHandlerFunc     ,
    genClosure_WindowInvalidateHandlerFunc  ,
    mk_WindowInvalidateHandlerFunc          ,
    noWindowInvalidateHandlerFunc           ,
    wrap_WindowInvalidateHandlerFunc        ,




    ) 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 qualified GI.Cairo.Structs.Region as Cairo.Region
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Objects.Seat as Gdk.Seat
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window
import {-# SOURCE #-} qualified GI.Gdk.Unions.Event as Gdk.Event

-- callback WindowInvalidateHandlerFunc
--          -> Callable {returnType = Nothing, returnMayBeNull = False, returnTransfer = TransferNothing, returnDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, args = [Arg {argCName = "window", argType = TInterface (Name {namespace = "Gdk", name = "Window"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GdkWindow", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "region", argType = TInterface (Name {namespace = "cairo", name = "Region"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #cairo_region_t", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}], skipReturn = False, callableThrows = False, callableDeprecated = Nothing, callableDocumentation = Documentation {rawDocText = Just "Whenever some area of the window is invalidated (directly in the\nwindow or in a child window) this gets called with @region in\nthe coordinate space of @window. You can use @region to just\nkeep track of the dirty region, or you can actually change\n@region in case you are doing display tricks like showing\na child in multiple places.", sinceVersion = Just "3.10"}}
-- | Type for the callback on the (unwrapped) C side.
type C_WindowInvalidateHandlerFunc =
    Ptr Gdk.Window.Window ->
    Ptr Cairo.Region.Region ->
    IO ()

-- Args: [ Arg
--           { argCName = "window"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkWindow" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "region"
--           , argType =
--               TInterface Name { namespace = "cairo" , name = "Region" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #cairo_region_t" , 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_WindowInvalidateHandlerFunc :: FunPtr C_WindowInvalidateHandlerFunc -> C_WindowInvalidateHandlerFunc

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_WindowInvalidateHandlerFunc ::
    (B.CallStack.HasCallStack, MonadIO m, Gdk.Window.IsWindow a) =>
    FunPtr C_WindowInvalidateHandlerFunc
    -> a
    -- ^ /@window@/: a t'GI.Gdk.Objects.Window.Window'
    -> Cairo.Region.Region
    -- ^ /@region@/: a t'GI.Cairo.Structs.Region.Region'
    -> m ()
dynamic_WindowInvalidateHandlerFunc :: FunPtr C_WindowInvalidateHandlerFunc -> a -> Region -> m ()
dynamic_WindowInvalidateHandlerFunc __funPtr :: FunPtr C_WindowInvalidateHandlerFunc
__funPtr window :: a
window region :: Region
region = 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 Window
window' <- a -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
window
    Ptr Region
region' <- Region -> IO (Ptr Region)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Region
region
    (FunPtr C_WindowInvalidateHandlerFunc
-> C_WindowInvalidateHandlerFunc
__dynamic_C_WindowInvalidateHandlerFunc FunPtr C_WindowInvalidateHandlerFunc
__funPtr) Ptr Window
window' Ptr Region
region'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
window
    Region -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Region
region
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

-- | Whenever some area of the window is invalidated (directly in the
-- window or in a child window) this gets called with /@region@/ in
-- the coordinate space of /@window@/. You can use /@region@/ to just
-- keep track of the dirty region, or you can actually change
-- /@region@/ in case you are doing display tricks like showing
-- a child in multiple places.
-- 
-- /Since: 3.10/
type WindowInvalidateHandlerFunc =
    Gdk.Window.Window
    -- ^ /@window@/: a t'GI.Gdk.Objects.Window.Window'
    -> Cairo.Region.Region
    -- ^ /@region@/: a t'GI.Cairo.Structs.Region.Region'
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `WindowInvalidateHandlerFunc`@.
noWindowInvalidateHandlerFunc :: Maybe WindowInvalidateHandlerFunc
noWindowInvalidateHandlerFunc :: Maybe WindowInvalidateHandlerFunc
noWindowInvalidateHandlerFunc = Maybe WindowInvalidateHandlerFunc
forall a. Maybe a
Nothing

-- | Wrap the callback into a `GClosure`.
genClosure_WindowInvalidateHandlerFunc :: MonadIO m => WindowInvalidateHandlerFunc -> m (GClosure C_WindowInvalidateHandlerFunc)
genClosure_WindowInvalidateHandlerFunc :: WindowInvalidateHandlerFunc
-> m (GClosure C_WindowInvalidateHandlerFunc)
genClosure_WindowInvalidateHandlerFunc cb :: WindowInvalidateHandlerFunc
cb = IO (GClosure C_WindowInvalidateHandlerFunc)
-> m (GClosure C_WindowInvalidateHandlerFunc)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_WindowInvalidateHandlerFunc)
 -> m (GClosure C_WindowInvalidateHandlerFunc))
-> IO (GClosure C_WindowInvalidateHandlerFunc)
-> m (GClosure C_WindowInvalidateHandlerFunc)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_WindowInvalidateHandlerFunc
cb' = Maybe (Ptr (FunPtr C_WindowInvalidateHandlerFunc))
-> WindowInvalidateHandlerFunc -> C_WindowInvalidateHandlerFunc
wrap_WindowInvalidateHandlerFunc Maybe (Ptr (FunPtr C_WindowInvalidateHandlerFunc))
forall a. Maybe a
Nothing WindowInvalidateHandlerFunc
cb
    C_WindowInvalidateHandlerFunc
-> IO (FunPtr C_WindowInvalidateHandlerFunc)
mk_WindowInvalidateHandlerFunc C_WindowInvalidateHandlerFunc
cb' IO (FunPtr C_WindowInvalidateHandlerFunc)
-> (FunPtr C_WindowInvalidateHandlerFunc
    -> IO (GClosure C_WindowInvalidateHandlerFunc))
-> IO (GClosure C_WindowInvalidateHandlerFunc)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_WindowInvalidateHandlerFunc
-> IO (GClosure C_WindowInvalidateHandlerFunc)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `WindowInvalidateHandlerFunc` into a `C_WindowInvalidateHandlerFunc`.
wrap_WindowInvalidateHandlerFunc ::
    Maybe (Ptr (FunPtr C_WindowInvalidateHandlerFunc)) ->
    WindowInvalidateHandlerFunc ->
    C_WindowInvalidateHandlerFunc
wrap_WindowInvalidateHandlerFunc :: Maybe (Ptr (FunPtr C_WindowInvalidateHandlerFunc))
-> WindowInvalidateHandlerFunc -> C_WindowInvalidateHandlerFunc
wrap_WindowInvalidateHandlerFunc funptrptr :: Maybe (Ptr (FunPtr C_WindowInvalidateHandlerFunc))
funptrptr _cb :: WindowInvalidateHandlerFunc
_cb window :: Ptr Window
window region :: Ptr Region
region = do
    Window
window' <- ((ManagedPtr Window -> Window) -> Ptr Window -> IO Window
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Window -> Window
Gdk.Window.Window) Ptr Window
window
    (ManagedPtr Region -> Region)
-> Ptr Region -> (Region -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
(ManagedPtr a -> a) -> Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient ManagedPtr Region -> Region
Cairo.Region.Region Ptr Region
region ((Region -> IO ()) -> IO ()) -> (Region -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \region' :: Region
region' -> do
        WindowInvalidateHandlerFunc
_cb  Window
window' Region
region'
        Maybe (Ptr (FunPtr C_WindowInvalidateHandlerFunc)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_WindowInvalidateHandlerFunc))
funptrptr


-- callback WindowChildFunc
--          -> Callable {returnType = Just (TBasicType TBoolean), returnMayBeNull = False, returnTransfer = TransferNothing, returnDocumentation = Documentation {rawDocText = Just "%TRUE to invalidate @window recursively", sinceVersion = Nothing}, args = [Arg {argCName = "window", argType = TInterface (Name {namespace = "Gdk", name = "Window"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "a #GdkWindow", 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 "user data", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = 1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}], skipReturn = False, callableThrows = False, callableDeprecated = Nothing, callableDocumentation = Documentation {rawDocText = Just "A function of this type is passed to gdk_window_invalidate_maybe_recurse().\nIt gets called for each child of the window to determine whether to\nrecursively invalidate it or now.", sinceVersion = Nothing}}
-- | Type for the callback on the (unwrapped) C side.
type C_WindowChildFunc =
    Ptr Gdk.Window.Window ->
    Ptr () ->
    IO CInt

-- Args: [ Arg
--           { argCName = "window"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkWindow" , 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 "user data" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = 1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "dynamic" __dynamic_C_WindowChildFunc :: FunPtr C_WindowChildFunc -> C_WindowChildFunc

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_WindowChildFunc ::
    (B.CallStack.HasCallStack, MonadIO m, Gdk.Window.IsWindow a) =>
    FunPtr C_WindowChildFunc
    -> a
    -- ^ /@window@/: a t'GI.Gdk.Objects.Window.Window'
    -> Ptr ()
    -- ^ /@userData@/: user data
    -> m Bool
    -- ^ __Returns:__ 'P.True' to invalidate /@window@/ recursively
dynamic_WindowChildFunc :: FunPtr C_WindowChildFunc -> a -> Ptr () -> m Bool
dynamic_WindowChildFunc __funPtr :: FunPtr C_WindowChildFunc
__funPtr window :: a
window 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
    Ptr Window
window' <- a -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
window
    CInt
result <- (FunPtr C_WindowChildFunc -> C_WindowChildFunc
__dynamic_C_WindowChildFunc FunPtr C_WindowChildFunc
__funPtr) Ptr Window
window' Ptr ()
userData
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
window
    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_WindowChildFunc`.
foreign import ccall "wrapper"
    mk_WindowChildFunc :: C_WindowChildFunc -> IO (FunPtr C_WindowChildFunc)

-- | A function of this type is passed to 'GI.Gdk.Objects.Window.windowInvalidateMaybeRecurse'.
-- It gets called for each child of the window to determine whether to
-- recursively invalidate it or now.
type WindowChildFunc =
    Gdk.Window.Window
    -- ^ /@window@/: a t'GI.Gdk.Objects.Window.Window'
    -> IO Bool
    -- ^ __Returns:__ 'P.True' to invalidate /@window@/ recursively

-- | A convenience synonym for @`Nothing` :: `Maybe` `WindowChildFunc`@.
noWindowChildFunc :: Maybe WindowChildFunc
noWindowChildFunc :: Maybe WindowChildFunc
noWindowChildFunc = Maybe WindowChildFunc
forall a. Maybe a
Nothing

-- | A function of this type is passed to 'GI.Gdk.Objects.Window.windowInvalidateMaybeRecurse'.
-- It gets called for each child of the window to determine whether to
-- recursively invalidate it or now.
type WindowChildFunc_WithClosures =
    Gdk.Window.Window
    -- ^ /@window@/: a t'GI.Gdk.Objects.Window.Window'
    -> Ptr ()
    -- ^ /@userData@/: user data
    -> IO Bool
    -- ^ __Returns:__ 'P.True' to invalidate /@window@/ recursively

-- | A convenience synonym for @`Nothing` :: `Maybe` `WindowChildFunc_WithClosures`@.
noWindowChildFunc_WithClosures :: Maybe WindowChildFunc_WithClosures
noWindowChildFunc_WithClosures :: Maybe WindowChildFunc_WithClosures
noWindowChildFunc_WithClosures = Maybe WindowChildFunc_WithClosures
forall a. Maybe a
Nothing

-- | A simple wrapper that ignores the closure arguments.
drop_closures_WindowChildFunc :: WindowChildFunc -> WindowChildFunc_WithClosures
drop_closures_WindowChildFunc :: WindowChildFunc -> WindowChildFunc_WithClosures
drop_closures_WindowChildFunc _f :: WindowChildFunc
_f window :: Window
window _ = WindowChildFunc
_f Window
window

-- | Wrap the callback into a `GClosure`.
genClosure_WindowChildFunc :: MonadIO m => WindowChildFunc -> m (GClosure C_WindowChildFunc)
genClosure_WindowChildFunc :: WindowChildFunc -> m (GClosure C_WindowChildFunc)
genClosure_WindowChildFunc cb :: WindowChildFunc
cb = IO (GClosure C_WindowChildFunc) -> m (GClosure C_WindowChildFunc)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_WindowChildFunc) -> m (GClosure C_WindowChildFunc))
-> IO (GClosure C_WindowChildFunc)
-> m (GClosure C_WindowChildFunc)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: WindowChildFunc_WithClosures
cb' = WindowChildFunc -> WindowChildFunc_WithClosures
drop_closures_WindowChildFunc WindowChildFunc
cb
    let cb'' :: C_WindowChildFunc
cb'' = Maybe (Ptr (FunPtr C_WindowChildFunc))
-> WindowChildFunc_WithClosures -> C_WindowChildFunc
wrap_WindowChildFunc Maybe (Ptr (FunPtr C_WindowChildFunc))
forall a. Maybe a
Nothing WindowChildFunc_WithClosures
cb'
    C_WindowChildFunc -> IO (FunPtr C_WindowChildFunc)
mk_WindowChildFunc C_WindowChildFunc
cb'' IO (FunPtr C_WindowChildFunc)
-> (FunPtr C_WindowChildFunc -> IO (GClosure C_WindowChildFunc))
-> IO (GClosure C_WindowChildFunc)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_WindowChildFunc -> IO (GClosure C_WindowChildFunc)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `WindowChildFunc` into a `C_WindowChildFunc`.
wrap_WindowChildFunc ::
    Maybe (Ptr (FunPtr C_WindowChildFunc)) ->
    WindowChildFunc_WithClosures ->
    C_WindowChildFunc
wrap_WindowChildFunc :: Maybe (Ptr (FunPtr C_WindowChildFunc))
-> WindowChildFunc_WithClosures -> C_WindowChildFunc
wrap_WindowChildFunc funptrptr :: Maybe (Ptr (FunPtr C_WindowChildFunc))
funptrptr _cb :: WindowChildFunc_WithClosures
_cb window :: Ptr Window
window userData :: Ptr ()
userData = do
    Window
window' <- ((ManagedPtr Window -> Window) -> Ptr Window -> IO Window
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Window -> Window
Gdk.Window.Window) Ptr Window
window
    Bool
result <- WindowChildFunc_WithClosures
_cb  Window
window' Ptr ()
userData
    Maybe (Ptr (FunPtr C_WindowChildFunc)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_WindowChildFunc))
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 SeatGrabPrepareFunc
--          -> Callable {returnType = Nothing, returnMayBeNull = False, returnTransfer = TransferNothing, returnDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, args = [Arg {argCName = "seat", argType = TInterface (Name {namespace = "Gdk", name = "Seat"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the #GdkSeat being grabbed", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "window", argType = TInterface (Name {namespace = "Gdk", name = "Window"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the #GdkWindow being grabbed", 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 "user data passed in gdk_seat_grab()", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = 2, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}], skipReturn = False, callableThrows = False, callableDeprecated = Nothing, callableDocumentation = Documentation {rawDocText = Just "Type of the callback used to set up @window so it can be\ngrabbed. A typical action would be ensuring the window is\nvisible, although there's room for other initialization\nactions.", sinceVersion = Just "3.20"}}
-- | Type for the callback on the (unwrapped) C side.
type C_SeatGrabPrepareFunc =
    Ptr Gdk.Seat.Seat ->
    Ptr Gdk.Window.Window ->
    Ptr () ->
    IO ()

-- Args: [ Arg
--           { argCName = "seat"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Seat" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GdkSeat being grabbed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "window"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GdkWindow being grabbed"
--                 , 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 "user data passed in gdk_seat_grab()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = 2
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "dynamic" __dynamic_C_SeatGrabPrepareFunc :: FunPtr C_SeatGrabPrepareFunc -> C_SeatGrabPrepareFunc

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_SeatGrabPrepareFunc ::
    (B.CallStack.HasCallStack, MonadIO m, Gdk.Seat.IsSeat a, Gdk.Window.IsWindow b) =>
    FunPtr C_SeatGrabPrepareFunc
    -> a
    -- ^ /@seat@/: the t'GI.Gdk.Objects.Seat.Seat' being grabbed
    -> b
    -- ^ /@window@/: the t'GI.Gdk.Objects.Window.Window' being grabbed
    -> Ptr ()
    -- ^ /@userData@/: user data passed in 'GI.Gdk.Objects.Seat.seatGrab'
    -> m ()
dynamic_SeatGrabPrepareFunc :: FunPtr C_SeatGrabPrepareFunc -> a -> b -> Ptr () -> m ()
dynamic_SeatGrabPrepareFunc __funPtr :: FunPtr C_SeatGrabPrepareFunc
__funPtr seat :: a
seat window :: b
window userData :: Ptr ()
userData = 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 Seat
seat' <- a -> IO (Ptr Seat)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
seat
    Ptr Window
window' <- b -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
window
    (FunPtr C_SeatGrabPrepareFunc -> C_SeatGrabPrepareFunc
__dynamic_C_SeatGrabPrepareFunc FunPtr C_SeatGrabPrepareFunc
__funPtr) Ptr Seat
seat' Ptr Window
window' Ptr ()
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
seat
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
window
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

-- | Type of the callback used to set up /@window@/ so it can be
-- grabbed. A typical action would be ensuring the window is
-- visible, although there\'s room for other initialization
-- actions.
-- 
-- /Since: 3.20/
type SeatGrabPrepareFunc =
    Gdk.Seat.Seat
    -- ^ /@seat@/: the t'GI.Gdk.Objects.Seat.Seat' being grabbed
    -> Gdk.Window.Window
    -- ^ /@window@/: the t'GI.Gdk.Objects.Window.Window' being grabbed
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `SeatGrabPrepareFunc`@.
noSeatGrabPrepareFunc :: Maybe SeatGrabPrepareFunc
noSeatGrabPrepareFunc :: Maybe SeatGrabPrepareFunc
noSeatGrabPrepareFunc = Maybe SeatGrabPrepareFunc
forall a. Maybe a
Nothing

-- | Type of the callback used to set up /@window@/ so it can be
-- grabbed. A typical action would be ensuring the window is
-- visible, although there\'s room for other initialization
-- actions.
-- 
-- /Since: 3.20/
type SeatGrabPrepareFunc_WithClosures =
    Gdk.Seat.Seat
    -- ^ /@seat@/: the t'GI.Gdk.Objects.Seat.Seat' being grabbed
    -> Gdk.Window.Window
    -- ^ /@window@/: the t'GI.Gdk.Objects.Window.Window' being grabbed
    -> Ptr ()
    -- ^ /@userData@/: user data passed in 'GI.Gdk.Objects.Seat.seatGrab'
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `SeatGrabPrepareFunc_WithClosures`@.
noSeatGrabPrepareFunc_WithClosures :: Maybe SeatGrabPrepareFunc_WithClosures
noSeatGrabPrepareFunc_WithClosures :: Maybe SeatGrabPrepareFunc_WithClosures
noSeatGrabPrepareFunc_WithClosures = Maybe SeatGrabPrepareFunc_WithClosures
forall a. Maybe a
Nothing

-- | A simple wrapper that ignores the closure arguments.
drop_closures_SeatGrabPrepareFunc :: SeatGrabPrepareFunc -> SeatGrabPrepareFunc_WithClosures
drop_closures_SeatGrabPrepareFunc :: SeatGrabPrepareFunc -> SeatGrabPrepareFunc_WithClosures
drop_closures_SeatGrabPrepareFunc _f :: SeatGrabPrepareFunc
_f seat :: Seat
seat window :: Window
window _ = SeatGrabPrepareFunc
_f Seat
seat Window
window

-- | Wrap the callback into a `GClosure`.
genClosure_SeatGrabPrepareFunc :: MonadIO m => SeatGrabPrepareFunc -> m (GClosure C_SeatGrabPrepareFunc)
genClosure_SeatGrabPrepareFunc :: SeatGrabPrepareFunc -> m (GClosure C_SeatGrabPrepareFunc)
genClosure_SeatGrabPrepareFunc cb :: SeatGrabPrepareFunc
cb = IO (GClosure C_SeatGrabPrepareFunc)
-> m (GClosure C_SeatGrabPrepareFunc)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_SeatGrabPrepareFunc)
 -> m (GClosure C_SeatGrabPrepareFunc))
-> IO (GClosure C_SeatGrabPrepareFunc)
-> m (GClosure C_SeatGrabPrepareFunc)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: SeatGrabPrepareFunc_WithClosures
cb' = SeatGrabPrepareFunc -> SeatGrabPrepareFunc_WithClosures
drop_closures_SeatGrabPrepareFunc SeatGrabPrepareFunc
cb
    let cb'' :: C_SeatGrabPrepareFunc
cb'' = Maybe (Ptr (FunPtr C_SeatGrabPrepareFunc))
-> SeatGrabPrepareFunc_WithClosures -> C_SeatGrabPrepareFunc
wrap_SeatGrabPrepareFunc Maybe (Ptr (FunPtr C_SeatGrabPrepareFunc))
forall a. Maybe a
Nothing SeatGrabPrepareFunc_WithClosures
cb'
    C_SeatGrabPrepareFunc -> IO (FunPtr C_SeatGrabPrepareFunc)
mk_SeatGrabPrepareFunc C_SeatGrabPrepareFunc
cb'' IO (FunPtr C_SeatGrabPrepareFunc)
-> (FunPtr C_SeatGrabPrepareFunc
    -> IO (GClosure C_SeatGrabPrepareFunc))
-> IO (GClosure C_SeatGrabPrepareFunc)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_SeatGrabPrepareFunc -> IO (GClosure C_SeatGrabPrepareFunc)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `SeatGrabPrepareFunc` into a `C_SeatGrabPrepareFunc`.
wrap_SeatGrabPrepareFunc ::
    Maybe (Ptr (FunPtr C_SeatGrabPrepareFunc)) ->
    SeatGrabPrepareFunc_WithClosures ->
    C_SeatGrabPrepareFunc
wrap_SeatGrabPrepareFunc :: Maybe (Ptr (FunPtr C_SeatGrabPrepareFunc))
-> SeatGrabPrepareFunc_WithClosures -> C_SeatGrabPrepareFunc
wrap_SeatGrabPrepareFunc funptrptr :: Maybe (Ptr (FunPtr C_SeatGrabPrepareFunc))
funptrptr _cb :: SeatGrabPrepareFunc_WithClosures
_cb seat :: Ptr Seat
seat window :: Ptr Window
window userData :: Ptr ()
userData = do
    Seat
seat' <- ((ManagedPtr Seat -> Seat) -> Ptr Seat -> IO Seat
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Seat -> Seat
Gdk.Seat.Seat) Ptr Seat
seat
    Window
window' <- ((ManagedPtr Window -> Window) -> Ptr Window -> IO Window
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Window -> Window
Gdk.Window.Window) Ptr Window
window
    SeatGrabPrepareFunc_WithClosures
_cb  Seat
seat' Window
window' Ptr ()
userData
    Maybe (Ptr (FunPtr C_SeatGrabPrepareFunc)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_SeatGrabPrepareFunc))
funptrptr


-- callback FilterFunc
--          -> Callable {returnType = Just (TInterface (Name {namespace = "Gdk", name = "FilterReturn"})), returnMayBeNull = False, returnTransfer = TransferNothing, returnDocumentation = Documentation {rawDocText = Just "a #GdkFilterReturn value.", sinceVersion = Nothing}, args = [Arg {argCName = "xevent", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the native event to filter.", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "event", argType = TInterface (Name {namespace = "Gdk", name = "Event"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the GDK event to which the X event will be translated.", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = True, argDoc = Documentation {rawDocText = Just "user data set when the filter was installed.", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = 2, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}], skipReturn = False, callableThrows = False, callableDeprecated = Nothing, callableDocumentation = Documentation {rawDocText = Just "Specifies the type of function used to filter native events before they are\nconverted to GDK events.\n\nWhen a filter is called, @event is unpopulated, except for\n`event->window`. The filter may translate the native\nevent to a GDK event and store the result in @event, or handle it without\ntranslation. If the filter translates the event and processing should\ncontinue, it should return %GDK_FILTER_TRANSLATE.", sinceVersion = Nothing}}
-- | Type for the callback on the (unwrapped) C side.
type C_FilterFunc =
    Ptr () ->
    Ptr Gdk.Event.Event ->
    Ptr () ->
    IO CUInt

-- Args: [ Arg
--           { argCName = "xevent"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the native event to filter."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "event"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Event" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the GDK event to which the X event will be translated."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data set when the filter was installed."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = 2
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gdk" , name = "FilterReturn" })
-- throws : False
-- Skip return : False

foreign import ccall "dynamic" __dynamic_C_FilterFunc :: FunPtr C_FilterFunc -> C_FilterFunc

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_FilterFunc ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FunPtr C_FilterFunc
    -> Ptr ()
    -- ^ /@xevent@/: the native event to filter.
    -> Gdk.Event.Event
    -- ^ /@event@/: the GDK event to which the X event will be translated.
    -> Ptr ()
    -- ^ /@data@/: user data set when the filter was installed.
    -> m Gdk.Enums.FilterReturn
    -- ^ __Returns:__ a t'GI.Gdk.Enums.FilterReturn' value.
dynamic_FilterFunc :: FunPtr C_FilterFunc -> Ptr () -> Event -> Ptr () -> m FilterReturn
dynamic_FilterFunc __funPtr :: FunPtr C_FilterFunc
__funPtr xevent :: Ptr ()
xevent event :: Event
event data_ :: Ptr ()
data_ = IO FilterReturn -> m FilterReturn
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FilterReturn -> m FilterReturn)
-> IO FilterReturn -> m FilterReturn
forall a b. (a -> b) -> a -> b
$ do
    Ptr Event
event' <- Event -> IO (Ptr Event)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Event
event
    CUInt
result <- (FunPtr C_FilterFunc -> C_FilterFunc
__dynamic_C_FilterFunc FunPtr C_FilterFunc
__funPtr) Ptr ()
xevent Ptr Event
event' Ptr ()
data_
    let result' :: FilterReturn
result' = (Int -> FilterReturn
forall a. Enum a => Int -> a
toEnum (Int -> FilterReturn) -> (CUInt -> Int) -> CUInt -> FilterReturn
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    Event -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Event
event
    FilterReturn -> IO FilterReturn
forall (m :: * -> *) a. Monad m => a -> m a
return FilterReturn
result'

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

-- | Specifies the type of function used to filter native events before they are
-- converted to GDK events.
-- 
-- When a filter is called, /@event@/ is unpopulated, except for
-- @event->window@. The filter may translate the native
-- event to a GDK event and store the result in /@event@/, or handle it without
-- translation. If the filter translates the event and processing should
-- continue, it should return 'GI.Gdk.Enums.FilterReturnTranslate'.
type FilterFunc =
    Ptr ()
    -- ^ /@xevent@/: the native event to filter.
    -> Gdk.Event.Event
    -- ^ /@event@/: the GDK event to which the X event will be translated.
    -> IO Gdk.Enums.FilterReturn
    -- ^ __Returns:__ a t'GI.Gdk.Enums.FilterReturn' value.

-- | A convenience synonym for @`Nothing` :: `Maybe` `FilterFunc`@.
noFilterFunc :: Maybe FilterFunc
noFilterFunc :: Maybe FilterFunc
noFilterFunc = Maybe FilterFunc
forall a. Maybe a
Nothing

-- | Specifies the type of function used to filter native events before they are
-- converted to GDK events.
-- 
-- When a filter is called, /@event@/ is unpopulated, except for
-- @event->window@. The filter may translate the native
-- event to a GDK event and store the result in /@event@/, or handle it without
-- translation. If the filter translates the event and processing should
-- continue, it should return 'GI.Gdk.Enums.FilterReturnTranslate'.
type FilterFunc_WithClosures =
    Ptr ()
    -- ^ /@xevent@/: the native event to filter.
    -> Gdk.Event.Event
    -- ^ /@event@/: the GDK event to which the X event will be translated.
    -> Ptr ()
    -- ^ /@data@/: user data set when the filter was installed.
    -> IO Gdk.Enums.FilterReturn
    -- ^ __Returns:__ a t'GI.Gdk.Enums.FilterReturn' value.

-- | A convenience synonym for @`Nothing` :: `Maybe` `FilterFunc_WithClosures`@.
noFilterFunc_WithClosures :: Maybe FilterFunc_WithClosures
noFilterFunc_WithClosures :: Maybe FilterFunc_WithClosures
noFilterFunc_WithClosures = Maybe FilterFunc_WithClosures
forall a. Maybe a
Nothing

-- | A simple wrapper that ignores the closure arguments.
drop_closures_FilterFunc :: FilterFunc -> FilterFunc_WithClosures
drop_closures_FilterFunc :: FilterFunc -> FilterFunc_WithClosures
drop_closures_FilterFunc _f :: FilterFunc
_f xevent :: Ptr ()
xevent event :: Event
event _ = FilterFunc
_f Ptr ()
xevent Event
event

-- | Wrap the callback into a `GClosure`.
genClosure_FilterFunc :: MonadIO m => FilterFunc -> m (GClosure C_FilterFunc)
genClosure_FilterFunc :: FilterFunc -> m (GClosure C_FilterFunc)
genClosure_FilterFunc cb :: FilterFunc
cb = IO (GClosure C_FilterFunc) -> m (GClosure C_FilterFunc)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_FilterFunc) -> m (GClosure C_FilterFunc))
-> IO (GClosure C_FilterFunc) -> m (GClosure C_FilterFunc)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: FilterFunc_WithClosures
cb' = FilterFunc -> FilterFunc_WithClosures
drop_closures_FilterFunc FilterFunc
cb
    let cb'' :: C_FilterFunc
cb'' = Maybe (Ptr (FunPtr C_FilterFunc))
-> FilterFunc_WithClosures -> C_FilterFunc
wrap_FilterFunc Maybe (Ptr (FunPtr C_FilterFunc))
forall a. Maybe a
Nothing FilterFunc_WithClosures
cb'
    C_FilterFunc -> IO (FunPtr C_FilterFunc)
mk_FilterFunc C_FilterFunc
cb'' IO (FunPtr C_FilterFunc)
-> (FunPtr C_FilterFunc -> IO (GClosure C_FilterFunc))
-> IO (GClosure C_FilterFunc)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_FilterFunc -> IO (GClosure C_FilterFunc)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `FilterFunc` into a `C_FilterFunc`.
wrap_FilterFunc ::
    Maybe (Ptr (FunPtr C_FilterFunc)) ->
    FilterFunc_WithClosures ->
    C_FilterFunc
wrap_FilterFunc :: Maybe (Ptr (FunPtr C_FilterFunc))
-> FilterFunc_WithClosures -> C_FilterFunc
wrap_FilterFunc funptrptr :: Maybe (Ptr (FunPtr C_FilterFunc))
funptrptr _cb :: FilterFunc_WithClosures
_cb xevent :: Ptr ()
xevent event :: Ptr Event
event data_ :: Ptr ()
data_ = do
    (ManagedPtr Event -> Event)
-> Ptr Event -> (Event -> IO CUInt) -> IO CUInt
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
(ManagedPtr a -> a) -> Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient ManagedPtr Event -> Event
Gdk.Event.Event Ptr Event
event ((Event -> IO CUInt) -> IO CUInt)
-> (Event -> IO CUInt) -> IO CUInt
forall a b. (a -> b) -> a -> b
$ \event' :: Event
event' -> do
        FilterReturn
result <- FilterFunc_WithClosures
_cb  Ptr ()
xevent Event
event' Ptr ()
data_
        Maybe (Ptr (FunPtr C_FilterFunc)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_FilterFunc))
funptrptr
        let result' :: CUInt
result' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (FilterReturn -> Int) -> FilterReturn -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilterReturn -> Int
forall a. Enum a => a -> Int
fromEnum) FilterReturn
result
        CUInt -> IO CUInt
forall (m :: * -> *) a. Monad m => a -> m a
return CUInt
result'


-- callback EventFunc
--          -> Callable {returnType = Nothing, returnMayBeNull = False, returnTransfer = TransferNothing, returnDocumentation = Documentation {rawDocText = Nothing, sinceVersion = Nothing}, args = [Arg {argCName = "event", argType = TInterface (Name {namespace = "Gdk", name = "Event"}), direction = DirectionIn, mayBeNull = False, argDoc = Documentation {rawDocText = Just "the #GdkEvent to process.", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing},Arg {argCName = "data", argType = TBasicType TPtr, direction = DirectionIn, mayBeNull = True, argDoc = Documentation {rawDocText = Just "user data set when the event handler was installed with\n  gdk_event_handler_set().", sinceVersion = Nothing}, argScope = ScopeTypeInvalid, argClosure = 1, argDestroy = -1, argCallerAllocates = False, transfer = TransferNothing}], skipReturn = False, callableThrows = False, callableDeprecated = Nothing, callableDocumentation = Documentation {rawDocText = Just "Specifies the type of function passed to gdk_event_handler_set() to\nhandle all GDK events.", sinceVersion = Nothing}}
-- | Type for the callback on the (unwrapped) C side.
type C_EventFunc =
    Ptr Gdk.Event.Event ->
    Ptr () ->
    IO ()

-- Args: [ Arg
--           { argCName = "event"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Event" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GdkEvent to process."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "user data set when the event handler was installed with\n  gdk_event_handler_set()."
--                 , 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_EventFunc :: FunPtr C_EventFunc -> C_EventFunc

-- | Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
dynamic_EventFunc ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    FunPtr C_EventFunc
    -> Gdk.Event.Event
    -- ^ /@event@/: the t'GI.Gdk.Unions.Event.Event' to process.
    -> Ptr ()
    -- ^ /@data@/: user data set when the event handler was installed with
    --   'GI.Gdk.Functions.eventHandlerSet'.
    -> m ()
dynamic_EventFunc :: FunPtr C_EventFunc -> Event -> Ptr () -> m ()
dynamic_EventFunc __funPtr :: FunPtr C_EventFunc
__funPtr event :: Event
event data_ :: Ptr ()
data_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Event
event' <- Event -> IO (Ptr Event)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Event
event
    (FunPtr C_EventFunc -> C_EventFunc
__dynamic_C_EventFunc FunPtr C_EventFunc
__funPtr) Ptr Event
event' Ptr ()
data_
    Event -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Event
event
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

-- | Specifies the type of function passed to 'GI.Gdk.Functions.eventHandlerSet' to
-- handle all GDK events.
type EventFunc =
    Gdk.Event.Event
    -- ^ /@event@/: the t'GI.Gdk.Unions.Event.Event' to process.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `EventFunc`@.
noEventFunc :: Maybe EventFunc
noEventFunc :: Maybe (Event -> IO ())
noEventFunc = Maybe (Event -> IO ())
forall a. Maybe a
Nothing

-- | Specifies the type of function passed to 'GI.Gdk.Functions.eventHandlerSet' to
-- handle all GDK events.
type EventFunc_WithClosures =
    Gdk.Event.Event
    -- ^ /@event@/: the t'GI.Gdk.Unions.Event.Event' to process.
    -> Ptr ()
    -- ^ /@data@/: user data set when the event handler was installed with
    --   'GI.Gdk.Functions.eventHandlerSet'.
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `EventFunc_WithClosures`@.
noEventFunc_WithClosures :: Maybe EventFunc_WithClosures
noEventFunc_WithClosures :: Maybe EventFunc_WithClosures
noEventFunc_WithClosures = Maybe EventFunc_WithClosures
forall a. Maybe a
Nothing

-- | A simple wrapper that ignores the closure arguments.
drop_closures_EventFunc :: EventFunc -> EventFunc_WithClosures
drop_closures_EventFunc :: (Event -> IO ()) -> EventFunc_WithClosures
drop_closures_EventFunc _f :: Event -> IO ()
_f event :: Event
event _ = Event -> IO ()
_f Event
event

-- | Wrap the callback into a `GClosure`.
genClosure_EventFunc :: MonadIO m => EventFunc -> m (GClosure C_EventFunc)
genClosure_EventFunc :: (Event -> IO ()) -> m (GClosure C_EventFunc)
genClosure_EventFunc cb :: Event -> IO ()
cb = IO (GClosure C_EventFunc) -> m (GClosure C_EventFunc)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_EventFunc) -> m (GClosure C_EventFunc))
-> IO (GClosure C_EventFunc) -> m (GClosure C_EventFunc)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: EventFunc_WithClosures
cb' = (Event -> IO ()) -> EventFunc_WithClosures
drop_closures_EventFunc Event -> IO ()
cb
    let cb'' :: C_EventFunc
cb'' = Maybe (Ptr (FunPtr C_EventFunc))
-> EventFunc_WithClosures -> C_EventFunc
wrap_EventFunc Maybe (Ptr (FunPtr C_EventFunc))
forall a. Maybe a
Nothing EventFunc_WithClosures
cb'
    C_EventFunc -> IO (FunPtr C_EventFunc)
mk_EventFunc C_EventFunc
cb'' IO (FunPtr C_EventFunc)
-> (FunPtr C_EventFunc -> IO (GClosure C_EventFunc))
-> IO (GClosure C_EventFunc)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_EventFunc -> IO (GClosure C_EventFunc)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `EventFunc` into a `C_EventFunc`.
wrap_EventFunc ::
    Maybe (Ptr (FunPtr C_EventFunc)) ->
    EventFunc_WithClosures ->
    C_EventFunc
wrap_EventFunc :: Maybe (Ptr (FunPtr C_EventFunc))
-> EventFunc_WithClosures -> C_EventFunc
wrap_EventFunc funptrptr :: Maybe (Ptr (FunPtr C_EventFunc))
funptrptr _cb :: EventFunc_WithClosures
_cb event :: Ptr Event
event data_ :: Ptr ()
data_ = do
    (ManagedPtr Event -> Event)
-> Ptr Event -> (Event -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
(ManagedPtr a -> a) -> Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient ManagedPtr Event -> Event
Gdk.Event.Event Ptr Event
event ((Event -> IO ()) -> IO ()) -> (Event -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \event' :: Event
event' -> do
        EventFunc_WithClosures
_cb  Event
event' Ptr ()
data_
        Maybe (Ptr (FunPtr C_EventFunc)) -> IO ()
forall a. Maybe (Ptr (FunPtr a)) -> IO ()
maybeReleaseFunPtr Maybe (Ptr (FunPtr C_EventFunc))
funptrptr