{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

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

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.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.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP

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 'GI.Gdk.Objects.Window.Window' -}
    -> Cairo.Region.Region
    {- ^ /@region@/: a 'GI.Cairo.Structs.Region.Region' -}
    -> m ()
dynamic_WindowInvalidateHandlerFunc __funPtr window region = liftIO $ do
    window' <- unsafeManagedPtrCastPtr window
    region' <- unsafeManagedPtrGetPtr region
    (__dynamic_C_WindowInvalidateHandlerFunc __funPtr) window' region'
    touchManagedPtr window
    touchManagedPtr region
    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 'GI.Gdk.Objects.Window.Window' -}
    -> Cairo.Region.Region
    {- ^ /@region@/: a 'GI.Cairo.Structs.Region.Region' -}
    -> IO ()

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

-- | Wrap the callback into a `Closure`.
genClosure_WindowInvalidateHandlerFunc :: WindowInvalidateHandlerFunc -> IO Closure
genClosure_WindowInvalidateHandlerFunc cb = do
    let cb' = wrap_WindowInvalidateHandlerFunc Nothing cb
    mk_WindowInvalidateHandlerFunc cb' >>= newCClosure


-- | Wrap a `WindowInvalidateHandlerFunc` into a `C_WindowInvalidateHandlerFunc`.
wrap_WindowInvalidateHandlerFunc ::
    Maybe (Ptr (FunPtr C_WindowInvalidateHandlerFunc)) ->
    WindowInvalidateHandlerFunc ->
    C_WindowInvalidateHandlerFunc
wrap_WindowInvalidateHandlerFunc funptrptr _cb window region = do
    window' <- (newObject Gdk.Window.Window) window
    B.ManagedPtr.withTransient Cairo.Region.Region region $ \region' -> do
        _cb  window' region'
        maybeReleaseFunPtr 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 'GI.Gdk.Objects.Window.Window' -}
    -> Ptr ()
    {- ^ /@userData@/: user data -}
    -> m Bool
    {- ^ __Returns:__ 'True' to invalidate /@window@/ recursively -}
dynamic_WindowChildFunc __funPtr window userData = liftIO $ do
    window' <- unsafeManagedPtrCastPtr window
    result <- (__dynamic_C_WindowChildFunc __funPtr) window' userData
    let result' = (/= 0) result
    touchManagedPtr window
    return 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 'GI.Gdk.Objects.Window.Window' -}
    -> IO Bool
    {- ^ __Returns:__ 'True' to invalidate /@window@/ recursively -}

-- | A convenience synonym for @`Nothing` :: `Maybe` `WindowChildFunc`@.
noWindowChildFunc :: Maybe WindowChildFunc
noWindowChildFunc = 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 'GI.Gdk.Objects.Window.Window' -}
    -> Ptr ()
    {- ^ /@userData@/: user data -}
    -> IO Bool
    {- ^ __Returns:__ 'True' to invalidate /@window@/ recursively -}

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

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

-- | Wrap the callback into a `Closure`.
genClosure_WindowChildFunc :: WindowChildFunc -> IO Closure
genClosure_WindowChildFunc cb = do
    let cb' = drop_closures_WindowChildFunc cb
    let cb'' = wrap_WindowChildFunc Nothing cb'
    mk_WindowChildFunc cb'' >>= newCClosure


-- | Wrap a `WindowChildFunc` into a `C_WindowChildFunc`.
wrap_WindowChildFunc ::
    Maybe (Ptr (FunPtr C_WindowChildFunc)) ->
    WindowChildFunc_WithClosures ->
    C_WindowChildFunc
wrap_WindowChildFunc funptrptr _cb window userData = do
    window' <- (newObject Gdk.Window.Window) window
    result <- _cb  window' userData
    maybeReleaseFunPtr funptrptr
    let result' = (fromIntegral . fromEnum) result
    return 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 'GI.Gdk.Objects.Seat.Seat' being grabbed -}
    -> b
    {- ^ /@window@/: the 'GI.Gdk.Objects.Window.Window' being grabbed -}
    -> Ptr ()
    {- ^ /@userData@/: user data passed in 'GI.Gdk.Objects.Seat.seatGrab' -}
    -> m ()
dynamic_SeatGrabPrepareFunc __funPtr seat window userData = liftIO $ do
    seat' <- unsafeManagedPtrCastPtr seat
    window' <- unsafeManagedPtrCastPtr window
    (__dynamic_C_SeatGrabPrepareFunc __funPtr) seat' window' userData
    touchManagedPtr seat
    touchManagedPtr window
    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 'GI.Gdk.Objects.Seat.Seat' being grabbed -}
    -> Gdk.Window.Window
    {- ^ /@window@/: the 'GI.Gdk.Objects.Window.Window' being grabbed -}
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `SeatGrabPrepareFunc`@.
noSeatGrabPrepareFunc :: Maybe SeatGrabPrepareFunc
noSeatGrabPrepareFunc = 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 'GI.Gdk.Objects.Seat.Seat' being grabbed -}
    -> Gdk.Window.Window
    {- ^ /@window@/: the '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 = Nothing

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

-- | Wrap the callback into a `Closure`.
genClosure_SeatGrabPrepareFunc :: SeatGrabPrepareFunc -> IO Closure
genClosure_SeatGrabPrepareFunc cb = do
    let cb' = drop_closures_SeatGrabPrepareFunc cb
    let cb'' = wrap_SeatGrabPrepareFunc Nothing cb'
    mk_SeatGrabPrepareFunc cb'' >>= newCClosure


-- | Wrap a `SeatGrabPrepareFunc` into a `C_SeatGrabPrepareFunc`.
wrap_SeatGrabPrepareFunc ::
    Maybe (Ptr (FunPtr C_SeatGrabPrepareFunc)) ->
    SeatGrabPrepareFunc_WithClosures ->
    C_SeatGrabPrepareFunc
wrap_SeatGrabPrepareFunc funptrptr _cb seat window userData = do
    seat' <- (newObject Gdk.Seat.Seat) seat
    window' <- (newObject Gdk.Window.Window) window
    _cb  seat' window' userData
    maybeReleaseFunPtr 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 'GI.Gdk.Enums.FilterReturn' value. -}
dynamic_FilterFunc __funPtr xevent event data_ = liftIO $ do
    event' <- unsafeManagedPtrGetPtr event
    result <- (__dynamic_C_FilterFunc __funPtr) xevent event' data_
    let result' = (toEnum . fromIntegral) result
    touchManagedPtr event
    return 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 'GI.Gdk.Enums.FilterReturn' value. -}

-- | A convenience synonym for @`Nothing` :: `Maybe` `FilterFunc`@.
noFilterFunc :: Maybe FilterFunc
noFilterFunc = 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 'GI.Gdk.Enums.FilterReturn' value. -}

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

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

-- | Wrap the callback into a `Closure`.
genClosure_FilterFunc :: FilterFunc -> IO Closure
genClosure_FilterFunc cb = do
    let cb' = drop_closures_FilterFunc cb
    let cb'' = wrap_FilterFunc Nothing cb'
    mk_FilterFunc cb'' >>= newCClosure


-- | Wrap a `FilterFunc` into a `C_FilterFunc`.
wrap_FilterFunc ::
    Maybe (Ptr (FunPtr C_FilterFunc)) ->
    FilterFunc_WithClosures ->
    C_FilterFunc
wrap_FilterFunc funptrptr _cb xevent event data_ = do
    B.ManagedPtr.withTransient Gdk.Event.Event event $ \event' -> do
        result <- _cb  xevent event' data_
        maybeReleaseFunPtr funptrptr
        let result' = (fromIntegral . fromEnum) result
        return 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 '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 event data_ = liftIO $ do
    event' <- unsafeManagedPtrGetPtr event
    (__dynamic_C_EventFunc __funPtr) event' data_
    touchManagedPtr event
    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 'GI.Gdk.Unions.Event.Event' to process. -}
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `EventFunc`@.
noEventFunc :: Maybe EventFunc
noEventFunc = 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 '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 = Nothing

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

-- | Wrap the callback into a `Closure`.
genClosure_EventFunc :: EventFunc -> IO Closure
genClosure_EventFunc cb = do
    let cb' = drop_closures_EventFunc cb
    let cb'' = wrap_EventFunc Nothing cb'
    mk_EventFunc cb'' >>= newCClosure


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