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


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkDropControllerMotion@ is an event controller tracking
-- the pointer during Drag-and-Drop operations.
-- 
-- It is modeled after t'GI.Gtk.Objects.EventControllerMotion.EventControllerMotion' so if you
-- have used that, this should feel really familiar.
-- 
-- This controller is not able to accept drops, use t'GI.Gtk.Objects.DropTarget.DropTarget'
-- for that purpose.

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

module GI.Gtk.Objects.DropControllerMotion
    ( 

-- * Exported types
    DropControllerMotion(..)                ,
    IsDropControllerMotion                  ,
    toDropControllerMotion                  ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [containsPointer]("GI.Gtk.Objects.DropControllerMotion#g:method:containsPointer"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isPointer]("GI.Gtk.Objects.DropControllerMotion#g:method:isPointer"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [reset]("GI.Gtk.Objects.EventController#g:method:reset"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getCurrentEvent]("GI.Gtk.Objects.EventController#g:method:getCurrentEvent"), [getCurrentEventDevice]("GI.Gtk.Objects.EventController#g:method:getCurrentEventDevice"), [getCurrentEventState]("GI.Gtk.Objects.EventController#g:method:getCurrentEventState"), [getCurrentEventTime]("GI.Gtk.Objects.EventController#g:method:getCurrentEventTime"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDrop]("GI.Gtk.Objects.DropControllerMotion#g:method:getDrop"), [getName]("GI.Gtk.Objects.EventController#g:method:getName"), [getPropagationLimit]("GI.Gtk.Objects.EventController#g:method:getPropagationLimit"), [getPropagationPhase]("GI.Gtk.Objects.EventController#g:method:getPropagationPhase"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getWidget]("GI.Gtk.Objects.EventController#g:method:getWidget").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setName]("GI.Gtk.Objects.EventController#g:method:setName"), [setPropagationLimit]("GI.Gtk.Objects.EventController#g:method:setPropagationLimit"), [setPropagationPhase]("GI.Gtk.Objects.EventController#g:method:setPropagationPhase"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setStaticName]("GI.Gtk.Objects.EventController#g:method:setStaticName").

#if defined(ENABLE_OVERLOADING)
    ResolveDropControllerMotionMethod       ,
#endif

-- ** containsPointer #method:containsPointer#

#if defined(ENABLE_OVERLOADING)
    DropControllerMotionContainsPointerMethodInfo,
#endif
    dropControllerMotionContainsPointer     ,


-- ** getDrop #method:getDrop#

#if defined(ENABLE_OVERLOADING)
    DropControllerMotionGetDropMethodInfo   ,
#endif
    dropControllerMotionGetDrop             ,


-- ** isPointer #method:isPointer#

#if defined(ENABLE_OVERLOADING)
    DropControllerMotionIsPointerMethodInfo ,
#endif
    dropControllerMotionIsPointer           ,


-- ** new #method:new#

    dropControllerMotionNew                 ,




 -- * Properties


-- ** containsPointer #attr:containsPointer#
-- | Whether the pointer of a Drag-and-Drop operation is in
-- the controller\'s widget or a descendant.
-- 
-- See also [DropControllerMotion:isPointer]("GI.Gtk.Objects.DropControllerMotion#g:attr:isPointer").
-- 
-- When handling crossing events, this property is updated
-- before [DropControllerMotion::enter]("GI.Gtk.Objects.DropControllerMotion#g:signal:enter"), but after
-- [DropControllerMotion::leave]("GI.Gtk.Objects.DropControllerMotion#g:signal:leave") is emitted.

#if defined(ENABLE_OVERLOADING)
    DropControllerMotionContainsPointerPropertyInfo,
#endif
    getDropControllerMotionContainsPointer  ,


-- ** drop #attr:drop#
-- | The ongoing drop operation over the controller\'s widget or
-- its descendant.
-- 
-- If no drop operation is going on, this property returns 'P.Nothing'.
-- 
-- The event controller should not modify the /@drop@/, but it might
-- want to query its properties.
-- 
-- When handling crossing events, this property is updated
-- before [DropControllerMotion::enter]("GI.Gtk.Objects.DropControllerMotion#g:signal:enter"), but after
-- [DropControllerMotion::leave]("GI.Gtk.Objects.DropControllerMotion#g:signal:leave") is emitted.

#if defined(ENABLE_OVERLOADING)
    DropControllerMotionDropPropertyInfo    ,
#endif
#if defined(ENABLE_OVERLOADING)
    dropControllerMotionDrop                ,
#endif
    getDropControllerMotionDrop             ,


-- ** isPointer #attr:isPointer#
-- | Whether the pointer is in the controllers widget itself,
-- as opposed to in a descendent widget.
-- 
-- See also [DropControllerMotion:containsPointer]("GI.Gtk.Objects.DropControllerMotion#g:attr:containsPointer").
-- 
-- When handling crossing events, this property is updated
-- before [DropControllerMotion::enter]("GI.Gtk.Objects.DropControllerMotion#g:signal:enter"), but after
-- [DropControllerMotion::leave]("GI.Gtk.Objects.DropControllerMotion#g:signal:leave") is emitted.

#if defined(ENABLE_OVERLOADING)
    DropControllerMotionIsPointerPropertyInfo,
#endif
    getDropControllerMotionIsPointer        ,




 -- * Signals


-- ** enter #signal:enter#

    DropControllerMotionEnterCallback       ,
#if defined(ENABLE_OVERLOADING)
    DropControllerMotionEnterSignalInfo     ,
#endif
    afterDropControllerMotionEnter          ,
    onDropControllerMotionEnter             ,


-- ** leave #signal:leave#

    DropControllerMotionLeaveCallback       ,
#if defined(ENABLE_OVERLOADING)
    DropControllerMotionLeaveSignalInfo     ,
#endif
    afterDropControllerMotionLeave          ,
    onDropControllerMotionLeave             ,


-- ** motion #signal:motion#

    DropControllerMotionMotionCallback      ,
#if defined(ENABLE_OVERLOADING)
    DropControllerMotionMotionSignalInfo    ,
#endif
    afterDropControllerMotionMotion         ,
    onDropControllerMotionMotion            ,




    ) where

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

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

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Flags as Gdk.Flags
import qualified GI.Gdk.Interfaces.Paintable as Gdk.Paintable
import qualified GI.Gdk.Objects.Clipboard as Gdk.Clipboard
import qualified GI.Gdk.Objects.Cursor as Gdk.Cursor
import qualified GI.Gdk.Objects.Device as Gdk.Device
import qualified GI.Gdk.Objects.Display as Gdk.Display
import qualified GI.Gdk.Objects.Drop as Gdk.Drop
import qualified GI.Gdk.Objects.Event as Gdk.Event
import qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import qualified GI.Gdk.Objects.Snapshot as Gdk.Snapshot
import qualified GI.Gdk.Objects.Surface as Gdk.Surface
import qualified GI.Gdk.Objects.Texture as Gdk.Texture
import qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import qualified GI.Gio.Interfaces.ActionGroup as Gio.ActionGroup
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import qualified GI.Graphene.Structs.Matrix as Graphene.Matrix
import qualified GI.Graphene.Structs.Point as Graphene.Point
import qualified GI.Graphene.Structs.Point3D as Graphene.Point3D
import qualified GI.Graphene.Structs.Rect as Graphene.Rect
import qualified GI.Graphene.Structs.Size as Graphene.Size
import qualified GI.Graphene.Structs.Vec3 as Graphene.Vec3
import qualified GI.Graphene.Structs.Vec4 as Graphene.Vec4
import qualified GI.Gsk.Enums as Gsk.Enums
import qualified GI.Gsk.Objects.GLShader as Gsk.GLShader
import qualified GI.Gsk.Objects.RenderNode as Gsk.RenderNode
import qualified GI.Gsk.Objects.Renderer as Gsk.Renderer
import qualified GI.Gsk.Structs.ColorStop as Gsk.ColorStop
import qualified GI.Gsk.Structs.Path as Gsk.Path
import qualified GI.Gsk.Structs.RoundedRect as Gsk.RoundedRect
import qualified GI.Gsk.Structs.Shadow as Gsk.Shadow
import qualified GI.Gsk.Structs.Stroke as Gsk.Stroke
import qualified GI.Gsk.Structs.Transform as Gsk.Transform
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Native as Gtk.Native
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Root as Gtk.Root
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.StyleProvider as Gtk.StyleProvider
import {-# SOURCE #-} qualified GI.Gtk.Objects.ATContext as Gtk.ATContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.EventController as Gtk.EventController
import {-# SOURCE #-} qualified GI.Gtk.Objects.LayoutChild as Gtk.LayoutChild
import {-# SOURCE #-} qualified GI.Gtk.Objects.LayoutManager as Gtk.LayoutManager
import {-# SOURCE #-} qualified GI.Gtk.Objects.Settings as Gtk.Settings
import {-# SOURCE #-} qualified GI.Gtk.Objects.Snapshot as Gtk.Snapshot
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleContext as Gtk.StyleContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.Tooltip as Gtk.Tooltip
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Gtk.Structs.Border as Gtk.Border
import {-# SOURCE #-} qualified GI.Gtk.Structs.Requisition as Gtk.Requisition
import qualified GI.Pango.Enums as Pango.Enums
import qualified GI.Pango.Objects.Context as Pango.Context
import qualified GI.Pango.Objects.FontMap as Pango.FontMap
import qualified GI.Pango.Objects.Layout as Pango.Layout

#else
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Drop as Gdk.Drop
import {-# SOURCE #-} qualified GI.Gtk.Objects.EventController as Gtk.EventController

#endif

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

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

foreign import ccall "gtk_drop_controller_motion_get_type"
    c_gtk_drop_controller_motion_get_type :: IO B.Types.GType

instance B.Types.TypedObject DropControllerMotion where
    glibType :: IO GType
glibType = IO GType
c_gtk_drop_controller_motion_get_type

instance B.Types.GObject DropControllerMotion

-- | Type class for types which can be safely cast to `DropControllerMotion`, for instance with `toDropControllerMotion`.
class (SP.GObject o, O.IsDescendantOf DropControllerMotion o) => IsDropControllerMotion o
instance (SP.GObject o, O.IsDescendantOf DropControllerMotion o) => IsDropControllerMotion o

instance O.HasParentTypes DropControllerMotion
type instance O.ParentTypes DropControllerMotion = '[Gtk.EventController.EventController, GObject.Object.Object]

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveDropControllerMotionMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveDropControllerMotionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDropControllerMotionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDropControllerMotionMethod "containsPointer" o = DropControllerMotionContainsPointerMethodInfo
    ResolveDropControllerMotionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDropControllerMotionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDropControllerMotionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDropControllerMotionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDropControllerMotionMethod "isPointer" o = DropControllerMotionIsPointerMethodInfo
    ResolveDropControllerMotionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDropControllerMotionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDropControllerMotionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDropControllerMotionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDropControllerMotionMethod "reset" o = Gtk.EventController.EventControllerResetMethodInfo
    ResolveDropControllerMotionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDropControllerMotionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDropControllerMotionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDropControllerMotionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDropControllerMotionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDropControllerMotionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDropControllerMotionMethod "getCurrentEvent" o = Gtk.EventController.EventControllerGetCurrentEventMethodInfo
    ResolveDropControllerMotionMethod "getCurrentEventDevice" o = Gtk.EventController.EventControllerGetCurrentEventDeviceMethodInfo
    ResolveDropControllerMotionMethod "getCurrentEventState" o = Gtk.EventController.EventControllerGetCurrentEventStateMethodInfo
    ResolveDropControllerMotionMethod "getCurrentEventTime" o = Gtk.EventController.EventControllerGetCurrentEventTimeMethodInfo
    ResolveDropControllerMotionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDropControllerMotionMethod "getDrop" o = DropControllerMotionGetDropMethodInfo
    ResolveDropControllerMotionMethod "getName" o = Gtk.EventController.EventControllerGetNameMethodInfo
    ResolveDropControllerMotionMethod "getPropagationLimit" o = Gtk.EventController.EventControllerGetPropagationLimitMethodInfo
    ResolveDropControllerMotionMethod "getPropagationPhase" o = Gtk.EventController.EventControllerGetPropagationPhaseMethodInfo
    ResolveDropControllerMotionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDropControllerMotionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDropControllerMotionMethod "getWidget" o = Gtk.EventController.EventControllerGetWidgetMethodInfo
    ResolveDropControllerMotionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDropControllerMotionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDropControllerMotionMethod "setName" o = Gtk.EventController.EventControllerSetNameMethodInfo
    ResolveDropControllerMotionMethod "setPropagationLimit" o = Gtk.EventController.EventControllerSetPropagationLimitMethodInfo
    ResolveDropControllerMotionMethod "setPropagationPhase" o = Gtk.EventController.EventControllerSetPropagationPhaseMethodInfo
    ResolveDropControllerMotionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDropControllerMotionMethod "setStaticName" o = Gtk.EventController.EventControllerSetStaticNameMethodInfo
    ResolveDropControllerMotionMethod l o = O.MethodResolutionFailed l o

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

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

#endif

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

#endif

-- signal DropControllerMotion::enter
-- | Signals that the pointer has entered the widget.
type DropControllerMotionEnterCallback =
    Double
    -- ^ /@x@/: coordinates of pointer location
    -> Double
    -- ^ /@y@/: coordinates of pointer location
    -> IO ()

type C_DropControllerMotionEnterCallback =
    Ptr DropControllerMotion ->             -- object
    CDouble ->
    CDouble ->
    Ptr () ->                               -- user_data
    IO ()

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

wrap_DropControllerMotionEnterCallback :: 
    GObject a => (a -> DropControllerMotionEnterCallback) ->
    C_DropControllerMotionEnterCallback
wrap_DropControllerMotionEnterCallback :: forall a.
GObject a =>
(a -> DropControllerMotionEnterCallback)
-> C_DropControllerMotionEnterCallback
wrap_DropControllerMotionEnterCallback a -> DropControllerMotionEnterCallback
gi'cb Ptr DropControllerMotion
gi'selfPtr CDouble
x CDouble
y Ptr ()
_ = do
    let x' :: Double
x' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
x
    let y' :: Double
y' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
y
    Ptr DropControllerMotion
-> (DropControllerMotion -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr DropControllerMotion
gi'selfPtr ((DropControllerMotion -> IO ()) -> IO ())
-> (DropControllerMotion -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \DropControllerMotion
gi'self -> a -> DropControllerMotionEnterCallback
gi'cb (DropControllerMotion -> a
forall a b. Coercible a b => a -> b
Coerce.coerce DropControllerMotion
gi'self)  Double
x' Double
y'


-- | Connect a signal handler for the [enter](#signal:enter) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' dropControllerMotion #enter callback
-- @
-- 
-- 
onDropControllerMotionEnter :: (IsDropControllerMotion a, MonadIO m) => a -> ((?self :: a) => DropControllerMotionEnterCallback) -> m SignalHandlerId
onDropControllerMotionEnter :: forall a (m :: * -> *).
(IsDropControllerMotion a, MonadIO m) =>
a
-> ((?self::a) => DropControllerMotionEnterCallback)
-> m SignalHandlerId
onDropControllerMotionEnter a
obj (?self::a) => DropControllerMotionEnterCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> DropControllerMotionEnterCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DropControllerMotionEnterCallback
DropControllerMotionEnterCallback
cb
    let wrapped' :: C_DropControllerMotionEnterCallback
wrapped' = (a -> DropControllerMotionEnterCallback)
-> C_DropControllerMotionEnterCallback
forall a.
GObject a =>
(a -> DropControllerMotionEnterCallback)
-> C_DropControllerMotionEnterCallback
wrap_DropControllerMotionEnterCallback a -> DropControllerMotionEnterCallback
wrapped
    FunPtr C_DropControllerMotionEnterCallback
wrapped'' <- C_DropControllerMotionEnterCallback
-> IO (FunPtr C_DropControllerMotionEnterCallback)
mk_DropControllerMotionEnterCallback C_DropControllerMotionEnterCallback
wrapped'
    a
-> Text
-> FunPtr C_DropControllerMotionEnterCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"enter" FunPtr C_DropControllerMotionEnterCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [enter](#signal:enter) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' dropControllerMotion #enter callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterDropControllerMotionEnter :: (IsDropControllerMotion a, MonadIO m) => a -> ((?self :: a) => DropControllerMotionEnterCallback) -> m SignalHandlerId
afterDropControllerMotionEnter :: forall a (m :: * -> *).
(IsDropControllerMotion a, MonadIO m) =>
a
-> ((?self::a) => DropControllerMotionEnterCallback)
-> m SignalHandlerId
afterDropControllerMotionEnter a
obj (?self::a) => DropControllerMotionEnterCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> DropControllerMotionEnterCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DropControllerMotionEnterCallback
DropControllerMotionEnterCallback
cb
    let wrapped' :: C_DropControllerMotionEnterCallback
wrapped' = (a -> DropControllerMotionEnterCallback)
-> C_DropControllerMotionEnterCallback
forall a.
GObject a =>
(a -> DropControllerMotionEnterCallback)
-> C_DropControllerMotionEnterCallback
wrap_DropControllerMotionEnterCallback a -> DropControllerMotionEnterCallback
wrapped
    FunPtr C_DropControllerMotionEnterCallback
wrapped'' <- C_DropControllerMotionEnterCallback
-> IO (FunPtr C_DropControllerMotionEnterCallback)
mk_DropControllerMotionEnterCallback C_DropControllerMotionEnterCallback
wrapped'
    a
-> Text
-> FunPtr C_DropControllerMotionEnterCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"enter" FunPtr C_DropControllerMotionEnterCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DropControllerMotionEnterSignalInfo
instance SignalInfo DropControllerMotionEnterSignalInfo where
    type HaskellCallbackType DropControllerMotionEnterSignalInfo = DropControllerMotionEnterCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DropControllerMotionEnterCallback cb
        cb'' <- mk_DropControllerMotionEnterCallback cb'
        connectSignalFunPtr obj "enter" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.DropControllerMotion::enter"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-DropControllerMotion.html#g:signal:enter"})

#endif

-- signal DropControllerMotion::leave
-- | Signals that the pointer has left the widget.
type DropControllerMotionLeaveCallback =
    IO ()

type C_DropControllerMotionLeaveCallback =
    Ptr DropControllerMotion ->             -- object
    Ptr () ->                               -- user_data
    IO ()

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

wrap_DropControllerMotionLeaveCallback :: 
    GObject a => (a -> DropControllerMotionLeaveCallback) ->
    C_DropControllerMotionLeaveCallback
wrap_DropControllerMotionLeaveCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_DropControllerMotionLeaveCallback
wrap_DropControllerMotionLeaveCallback a -> IO ()
gi'cb Ptr DropControllerMotion
gi'selfPtr Ptr ()
_ = do
    Ptr DropControllerMotion
-> (DropControllerMotion -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr DropControllerMotion
gi'selfPtr ((DropControllerMotion -> IO ()) -> IO ())
-> (DropControllerMotion -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \DropControllerMotion
gi'self -> a -> IO ()
gi'cb (DropControllerMotion -> a
forall a b. Coercible a b => a -> b
Coerce.coerce DropControllerMotion
gi'self) 


-- | Connect a signal handler for the [leave](#signal:leave) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' dropControllerMotion #leave callback
-- @
-- 
-- 
onDropControllerMotionLeave :: (IsDropControllerMotion a, MonadIO m) => a -> ((?self :: a) => DropControllerMotionLeaveCallback) -> m SignalHandlerId
onDropControllerMotionLeave :: forall a (m :: * -> *).
(IsDropControllerMotion a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onDropControllerMotionLeave a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_DropControllerMotionLeaveCallback
wrapped' = (a -> IO ()) -> C_DropControllerMotionLeaveCallback
forall a.
GObject a =>
(a -> IO ()) -> C_DropControllerMotionLeaveCallback
wrap_DropControllerMotionLeaveCallback a -> IO ()
wrapped
    FunPtr C_DropControllerMotionLeaveCallback
wrapped'' <- C_DropControllerMotionLeaveCallback
-> IO (FunPtr C_DropControllerMotionLeaveCallback)
mk_DropControllerMotionLeaveCallback C_DropControllerMotionLeaveCallback
wrapped'
    a
-> Text
-> FunPtr C_DropControllerMotionLeaveCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"leave" FunPtr C_DropControllerMotionLeaveCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [leave](#signal:leave) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' dropControllerMotion #leave callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterDropControllerMotionLeave :: (IsDropControllerMotion a, MonadIO m) => a -> ((?self :: a) => DropControllerMotionLeaveCallback) -> m SignalHandlerId
afterDropControllerMotionLeave :: forall a (m :: * -> *).
(IsDropControllerMotion a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterDropControllerMotionLeave a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_DropControllerMotionLeaveCallback
wrapped' = (a -> IO ()) -> C_DropControllerMotionLeaveCallback
forall a.
GObject a =>
(a -> IO ()) -> C_DropControllerMotionLeaveCallback
wrap_DropControllerMotionLeaveCallback a -> IO ()
wrapped
    FunPtr C_DropControllerMotionLeaveCallback
wrapped'' <- C_DropControllerMotionLeaveCallback
-> IO (FunPtr C_DropControllerMotionLeaveCallback)
mk_DropControllerMotionLeaveCallback C_DropControllerMotionLeaveCallback
wrapped'
    a
-> Text
-> FunPtr C_DropControllerMotionLeaveCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"leave" FunPtr C_DropControllerMotionLeaveCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DropControllerMotionLeaveSignalInfo
instance SignalInfo DropControllerMotionLeaveSignalInfo where
    type HaskellCallbackType DropControllerMotionLeaveSignalInfo = DropControllerMotionLeaveCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DropControllerMotionLeaveCallback cb
        cb'' <- mk_DropControllerMotionLeaveCallback cb'
        connectSignalFunPtr obj "leave" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.DropControllerMotion::leave"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-DropControllerMotion.html#g:signal:leave"})

#endif

-- signal DropControllerMotion::motion
-- | Emitted when the pointer moves inside the widget.
type DropControllerMotionMotionCallback =
    Double
    -- ^ /@x@/: the x coordinate
    -> Double
    -- ^ /@y@/: the y coordinate
    -> IO ()

type C_DropControllerMotionMotionCallback =
    Ptr DropControllerMotion ->             -- object
    CDouble ->
    CDouble ->
    Ptr () ->                               -- user_data
    IO ()

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

wrap_DropControllerMotionMotionCallback :: 
    GObject a => (a -> DropControllerMotionMotionCallback) ->
    C_DropControllerMotionMotionCallback
wrap_DropControllerMotionMotionCallback :: forall a.
GObject a =>
(a -> DropControllerMotionEnterCallback)
-> C_DropControllerMotionEnterCallback
wrap_DropControllerMotionMotionCallback a -> DropControllerMotionEnterCallback
gi'cb Ptr DropControllerMotion
gi'selfPtr CDouble
x CDouble
y Ptr ()
_ = do
    let x' :: Double
x' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
x
    let y' :: Double
y' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
y
    Ptr DropControllerMotion
-> (DropControllerMotion -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr DropControllerMotion
gi'selfPtr ((DropControllerMotion -> IO ()) -> IO ())
-> (DropControllerMotion -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \DropControllerMotion
gi'self -> a -> DropControllerMotionEnterCallback
gi'cb (DropControllerMotion -> a
forall a b. Coercible a b => a -> b
Coerce.coerce DropControllerMotion
gi'self)  Double
x' Double
y'


-- | Connect a signal handler for the [motion](#signal:motion) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' dropControllerMotion #motion callback
-- @
-- 
-- 
onDropControllerMotionMotion :: (IsDropControllerMotion a, MonadIO m) => a -> ((?self :: a) => DropControllerMotionMotionCallback) -> m SignalHandlerId
onDropControllerMotionMotion :: forall a (m :: * -> *).
(IsDropControllerMotion a, MonadIO m) =>
a
-> ((?self::a) => DropControllerMotionEnterCallback)
-> m SignalHandlerId
onDropControllerMotionMotion a
obj (?self::a) => DropControllerMotionEnterCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> DropControllerMotionEnterCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DropControllerMotionEnterCallback
DropControllerMotionEnterCallback
cb
    let wrapped' :: C_DropControllerMotionEnterCallback
wrapped' = (a -> DropControllerMotionEnterCallback)
-> C_DropControllerMotionEnterCallback
forall a.
GObject a =>
(a -> DropControllerMotionEnterCallback)
-> C_DropControllerMotionEnterCallback
wrap_DropControllerMotionMotionCallback a -> DropControllerMotionEnterCallback
wrapped
    FunPtr C_DropControllerMotionEnterCallback
wrapped'' <- C_DropControllerMotionEnterCallback
-> IO (FunPtr C_DropControllerMotionEnterCallback)
mk_DropControllerMotionMotionCallback C_DropControllerMotionEnterCallback
wrapped'
    a
-> Text
-> FunPtr C_DropControllerMotionEnterCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"motion" FunPtr C_DropControllerMotionEnterCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [motion](#signal:motion) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' dropControllerMotion #motion callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterDropControllerMotionMotion :: (IsDropControllerMotion a, MonadIO m) => a -> ((?self :: a) => DropControllerMotionMotionCallback) -> m SignalHandlerId
afterDropControllerMotionMotion :: forall a (m :: * -> *).
(IsDropControllerMotion a, MonadIO m) =>
a
-> ((?self::a) => DropControllerMotionEnterCallback)
-> m SignalHandlerId
afterDropControllerMotionMotion a
obj (?self::a) => DropControllerMotionEnterCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> DropControllerMotionEnterCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DropControllerMotionEnterCallback
DropControllerMotionEnterCallback
cb
    let wrapped' :: C_DropControllerMotionEnterCallback
wrapped' = (a -> DropControllerMotionEnterCallback)
-> C_DropControllerMotionEnterCallback
forall a.
GObject a =>
(a -> DropControllerMotionEnterCallback)
-> C_DropControllerMotionEnterCallback
wrap_DropControllerMotionMotionCallback a -> DropControllerMotionEnterCallback
wrapped
    FunPtr C_DropControllerMotionEnterCallback
wrapped'' <- C_DropControllerMotionEnterCallback
-> IO (FunPtr C_DropControllerMotionEnterCallback)
mk_DropControllerMotionMotionCallback C_DropControllerMotionEnterCallback
wrapped'
    a
-> Text
-> FunPtr C_DropControllerMotionEnterCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"motion" FunPtr C_DropControllerMotionEnterCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DropControllerMotionMotionSignalInfo
instance SignalInfo DropControllerMotionMotionSignalInfo where
    type HaskellCallbackType DropControllerMotionMotionSignalInfo = DropControllerMotionMotionCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DropControllerMotionMotionCallback cb
        cb'' <- mk_DropControllerMotionMotionCallback cb'
        connectSignalFunPtr obj "motion" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.DropControllerMotion::motion"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-DropControllerMotion.html#g:signal:motion"})

#endif

-- VVV Prop "contains-pointer"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@contains-pointer@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dropControllerMotion #containsPointer
-- @
getDropControllerMotionContainsPointer :: (MonadIO m, IsDropControllerMotion o) => o -> m Bool
getDropControllerMotionContainsPointer :: forall (m :: * -> *) o.
(MonadIO m, IsDropControllerMotion o) =>
o -> m Bool
getDropControllerMotionContainsPointer o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"contains-pointer"

#if defined(ENABLE_OVERLOADING)
data DropControllerMotionContainsPointerPropertyInfo
instance AttrInfo DropControllerMotionContainsPointerPropertyInfo where
    type AttrAllowedOps DropControllerMotionContainsPointerPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DropControllerMotionContainsPointerPropertyInfo = IsDropControllerMotion
    type AttrSetTypeConstraint DropControllerMotionContainsPointerPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DropControllerMotionContainsPointerPropertyInfo = (~) ()
    type AttrTransferType DropControllerMotionContainsPointerPropertyInfo = ()
    type AttrGetType DropControllerMotionContainsPointerPropertyInfo = Bool
    type AttrLabel DropControllerMotionContainsPointerPropertyInfo = "contains-pointer"
    type AttrOrigin DropControllerMotionContainsPointerPropertyInfo = DropControllerMotion
    attrGet = getDropControllerMotionContainsPointer
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.DropControllerMotion.containsPointer"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-DropControllerMotion.html#g:attr:containsPointer"
        })
#endif

-- VVV Prop "drop"
   -- Type: TInterface (Name {namespace = "Gdk", name = "Drop"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just True,Nothing)

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

#if defined(ENABLE_OVERLOADING)
data DropControllerMotionDropPropertyInfo
instance AttrInfo DropControllerMotionDropPropertyInfo where
    type AttrAllowedOps DropControllerMotionDropPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DropControllerMotionDropPropertyInfo = IsDropControllerMotion
    type AttrSetTypeConstraint DropControllerMotionDropPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DropControllerMotionDropPropertyInfo = (~) ()
    type AttrTransferType DropControllerMotionDropPropertyInfo = ()
    type AttrGetType DropControllerMotionDropPropertyInfo = (Maybe Gdk.Drop.Drop)
    type AttrLabel DropControllerMotionDropPropertyInfo = "drop"
    type AttrOrigin DropControllerMotionDropPropertyInfo = DropControllerMotion
    attrGet = getDropControllerMotionDrop
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.DropControllerMotion.drop"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-DropControllerMotion.html#g:attr:drop"
        })
#endif

-- VVV Prop "is-pointer"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@is-pointer@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' dropControllerMotion #isPointer
-- @
getDropControllerMotionIsPointer :: (MonadIO m, IsDropControllerMotion o) => o -> m Bool
getDropControllerMotionIsPointer :: forall (m :: * -> *) o.
(MonadIO m, IsDropControllerMotion o) =>
o -> m Bool
getDropControllerMotionIsPointer o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"is-pointer"

#if defined(ENABLE_OVERLOADING)
data DropControllerMotionIsPointerPropertyInfo
instance AttrInfo DropControllerMotionIsPointerPropertyInfo where
    type AttrAllowedOps DropControllerMotionIsPointerPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DropControllerMotionIsPointerPropertyInfo = IsDropControllerMotion
    type AttrSetTypeConstraint DropControllerMotionIsPointerPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DropControllerMotionIsPointerPropertyInfo = (~) ()
    type AttrTransferType DropControllerMotionIsPointerPropertyInfo = ()
    type AttrGetType DropControllerMotionIsPointerPropertyInfo = Bool
    type AttrLabel DropControllerMotionIsPointerPropertyInfo = "is-pointer"
    type AttrOrigin DropControllerMotionIsPointerPropertyInfo = DropControllerMotion
    attrGet = getDropControllerMotionIsPointer
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.DropControllerMotion.isPointer"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-DropControllerMotion.html#g:attr:isPointer"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DropControllerMotion
type instance O.AttributeList DropControllerMotion = DropControllerMotionAttributeList
type DropControllerMotionAttributeList = ('[ '("containsPointer", DropControllerMotionContainsPointerPropertyInfo), '("drop", DropControllerMotionDropPropertyInfo), '("isPointer", DropControllerMotionIsPointerPropertyInfo), '("name", Gtk.EventController.EventControllerNamePropertyInfo), '("propagationLimit", Gtk.EventController.EventControllerPropagationLimitPropertyInfo), '("propagationPhase", Gtk.EventController.EventControllerPropagationPhasePropertyInfo), '("widget", Gtk.EventController.EventControllerWidgetPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
dropControllerMotionDrop :: AttrLabelProxy "drop"
dropControllerMotionDrop = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DropControllerMotion = DropControllerMotionSignalList
type DropControllerMotionSignalList = ('[ '("enter", DropControllerMotionEnterSignalInfo), '("leave", DropControllerMotionLeaveSignalInfo), '("motion", DropControllerMotionMotionSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method DropControllerMotion::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gtk" , name = "DropControllerMotion" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_drop_controller_motion_new" gtk_drop_controller_motion_new :: 
    IO (Ptr DropControllerMotion)

-- | Creates a new event controller that will handle pointer motion
-- events during drag and drop.
dropControllerMotionNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m DropControllerMotion
    -- ^ __Returns:__ a new @GtkDropControllerMotion@
dropControllerMotionNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m DropControllerMotion
dropControllerMotionNew  = IO DropControllerMotion -> m DropControllerMotion
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DropControllerMotion -> m DropControllerMotion)
-> IO DropControllerMotion -> m DropControllerMotion
forall a b. (a -> b) -> a -> b
$ do
    Ptr DropControllerMotion
result <- IO (Ptr DropControllerMotion)
gtk_drop_controller_motion_new
    Text -> Ptr DropControllerMotion -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"dropControllerMotionNew" Ptr DropControllerMotion
result
    DropControllerMotion
result' <- ((ManagedPtr DropControllerMotion -> DropControllerMotion)
-> Ptr DropControllerMotion -> IO DropControllerMotion
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DropControllerMotion -> DropControllerMotion
DropControllerMotion) Ptr DropControllerMotion
result
    DropControllerMotion -> IO DropControllerMotion
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DropControllerMotion
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "gtk_drop_controller_motion_contains_pointer" gtk_drop_controller_motion_contains_pointer :: 
    Ptr DropControllerMotion ->             -- self : TInterface (Name {namespace = "Gtk", name = "DropControllerMotion"})
    IO CInt

-- | Returns if a Drag-and-Drop operation is within the widget
-- /@self@/ or one of its children.
dropControllerMotionContainsPointer ::
    (B.CallStack.HasCallStack, MonadIO m, IsDropControllerMotion a) =>
    a
    -- ^ /@self@/: a @GtkDropControllerMotion@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if a dragging pointer is within /@self@/ or one of its children.
dropControllerMotionContainsPointer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDropControllerMotion a) =>
a -> m Bool
dropControllerMotionContainsPointer a
self = IO Bool -> m Bool
forall a. IO a -> m a
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 DropControllerMotion
self' <- a -> IO (Ptr DropControllerMotion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr DropControllerMotion -> IO CInt
gtk_drop_controller_motion_contains_pointer Ptr DropControllerMotion
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DropControllerMotionContainsPointerMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDropControllerMotion a) => O.OverloadedMethod DropControllerMotionContainsPointerMethodInfo a signature where
    overloadedMethod = dropControllerMotionContainsPointer

instance O.OverloadedMethodInfo DropControllerMotionContainsPointerMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.DropControllerMotion.dropControllerMotionContainsPointer",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-DropControllerMotion.html#v:dropControllerMotionContainsPointer"
        })


#endif

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

foreign import ccall "gtk_drop_controller_motion_get_drop" gtk_drop_controller_motion_get_drop :: 
    Ptr DropControllerMotion ->             -- self : TInterface (Name {namespace = "Gtk", name = "DropControllerMotion"})
    IO (Ptr Gdk.Drop.Drop)

-- | Returns the @GdkDrop@ of a current Drag-and-Drop operation
-- over the widget of /@self@/.
dropControllerMotionGetDrop ::
    (B.CallStack.HasCallStack, MonadIO m, IsDropControllerMotion a) =>
    a
    -- ^ /@self@/: a @GtkDropControllerMotion@
    -> m (Maybe Gdk.Drop.Drop)
    -- ^ __Returns:__ The @GdkDrop@ currently
    --   happening within /@self@/
dropControllerMotionGetDrop :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDropControllerMotion a) =>
a -> m (Maybe Drop)
dropControllerMotionGetDrop a
self = IO (Maybe Drop) -> m (Maybe Drop)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Drop) -> m (Maybe Drop))
-> IO (Maybe Drop) -> m (Maybe Drop)
forall a b. (a -> b) -> a -> b
$ do
    Ptr DropControllerMotion
self' <- a -> IO (Ptr DropControllerMotion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Drop
result <- Ptr DropControllerMotion -> IO (Ptr Drop)
gtk_drop_controller_motion_get_drop Ptr DropControllerMotion
self'
    Maybe Drop
maybeResult <- Ptr Drop -> (Ptr Drop -> IO Drop) -> IO (Maybe Drop)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Drop
result ((Ptr Drop -> IO Drop) -> IO (Maybe Drop))
-> (Ptr Drop -> IO Drop) -> IO (Maybe Drop)
forall a b. (a -> b) -> a -> b
$ \Ptr Drop
result' -> do
        Drop
result'' <- ((ManagedPtr Drop -> Drop) -> Ptr Drop -> IO Drop
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Drop -> Drop
Gdk.Drop.Drop) Ptr Drop
result'
        Drop -> IO Drop
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Drop
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe Drop -> IO (Maybe Drop)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Drop
maybeResult

#if defined(ENABLE_OVERLOADING)
data DropControllerMotionGetDropMethodInfo
instance (signature ~ (m (Maybe Gdk.Drop.Drop)), MonadIO m, IsDropControllerMotion a) => O.OverloadedMethod DropControllerMotionGetDropMethodInfo a signature where
    overloadedMethod = dropControllerMotionGetDrop

instance O.OverloadedMethodInfo DropControllerMotionGetDropMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.DropControllerMotion.dropControllerMotionGetDrop",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-DropControllerMotion.html#v:dropControllerMotionGetDrop"
        })


#endif

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

foreign import ccall "gtk_drop_controller_motion_is_pointer" gtk_drop_controller_motion_is_pointer :: 
    Ptr DropControllerMotion ->             -- self : TInterface (Name {namespace = "Gtk", name = "DropControllerMotion"})
    IO CInt

-- | Returns if a Drag-and-Drop operation is within the widget
-- /@self@/, not one of its children.
dropControllerMotionIsPointer ::
    (B.CallStack.HasCallStack, MonadIO m, IsDropControllerMotion a) =>
    a
    -- ^ /@self@/: a @GtkDropControllerMotion@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if a dragging pointer is within /@self@/ but
    --   not one of its children
dropControllerMotionIsPointer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDropControllerMotion a) =>
a -> m Bool
dropControllerMotionIsPointer a
self = IO Bool -> m Bool
forall a. IO a -> m a
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 DropControllerMotion
self' <- a -> IO (Ptr DropControllerMotion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr DropControllerMotion -> IO CInt
gtk_drop_controller_motion_is_pointer Ptr DropControllerMotion
self'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DropControllerMotionIsPointerMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDropControllerMotion a) => O.OverloadedMethod DropControllerMotionIsPointerMethodInfo a signature where
    overloadedMethod = dropControllerMotionIsPointer

instance O.OverloadedMethodInfo DropControllerMotionIsPointerMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.DropControllerMotion.dropControllerMotionIsPointer",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-DropControllerMotion.html#v:dropControllerMotionIsPointer"
        })


#endif