{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gtk.Objects.EventControllerMotion.EventControllerMotion' is an event controller meant for situations
-- where you need to track the position of the pointer.

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

module GI.Gtk.Objects.EventControllerMotion
    ( 

-- * Exported types
    EventControllerMotion(..)               ,
    IsEventControllerMotion                 ,
    toEventControllerMotion                 ,
    noEventControllerMotion                 ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveEventControllerMotionMethod      ,
#endif


-- ** getPointerOrigin #method:getPointerOrigin#

#if defined(ENABLE_OVERLOADING)
    EventControllerMotionGetPointerOriginMethodInfo,
#endif
    eventControllerMotionGetPointerOrigin   ,


-- ** getPointerTarget #method:getPointerTarget#

#if defined(ENABLE_OVERLOADING)
    EventControllerMotionGetPointerTargetMethodInfo,
#endif
    eventControllerMotionGetPointerTarget   ,


-- ** new #method:new#

    eventControllerMotionNew                ,




 -- * Properties
-- ** containsPointerFocus #attr:containsPointerFocus#
-- | Whether the pointer is in a descendant of the controllers widget.
-- See t'GI.Gtk.Objects.EventControllerMotion.EventControllerMotion':@/is-pointer-focus/@.
-- 
-- When handling crossing events, this property is updated
-- before [enter]("GI.Gtk.Objects.EventControllerMotion#signal:enter") or
-- [leave]("GI.Gtk.Objects.EventControllerMotion#signal:leave") are emitted.

#if defined(ENABLE_OVERLOADING)
    EventControllerMotionContainsPointerFocusPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    eventControllerMotionContainsPointerFocus,
#endif
    getEventControllerMotionContainsPointerFocus,


-- ** isPointerFocus #attr:isPointerFocus#
-- | Whether the pointer is in the controllers widget itself,
-- as opposed to in a descendent widget. See
-- t'GI.Gtk.Objects.EventControllerMotion.EventControllerMotion':@/contains-pointer-focus/@.
-- 
-- When handling crossing events, this property is updated
-- before [enter]("GI.Gtk.Objects.EventControllerMotion#signal:enter") or
-- [leave]("GI.Gtk.Objects.EventControllerMotion#signal:leave") are emitted.

#if defined(ENABLE_OVERLOADING)
    EventControllerMotionIsPointerFocusPropertyInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    eventControllerMotionIsPointerFocus     ,
#endif
    getEventControllerMotionIsPointerFocus  ,




 -- * Signals
-- ** enter #signal:enter#

    C_EventControllerMotionEnterCallback    ,
    EventControllerMotionEnterCallback      ,
#if defined(ENABLE_OVERLOADING)
    EventControllerMotionEnterSignalInfo    ,
#endif
    afterEventControllerMotionEnter         ,
    genClosure_EventControllerMotionEnter   ,
    mk_EventControllerMotionEnterCallback   ,
    noEventControllerMotionEnterCallback    ,
    onEventControllerMotionEnter            ,
    wrap_EventControllerMotionEnterCallback ,


-- ** leave #signal:leave#

    C_EventControllerMotionLeaveCallback    ,
    EventControllerMotionLeaveCallback      ,
#if defined(ENABLE_OVERLOADING)
    EventControllerMotionLeaveSignalInfo    ,
#endif
    afterEventControllerMotionLeave         ,
    genClosure_EventControllerMotionLeave   ,
    mk_EventControllerMotionLeaveCallback   ,
    noEventControllerMotionLeaveCallback    ,
    onEventControllerMotionLeave            ,
    wrap_EventControllerMotionLeaveCallback ,


-- ** motion #signal:motion#

    C_EventControllerMotionMotionCallback   ,
    EventControllerMotionMotionCallback     ,
#if defined(ENABLE_OVERLOADING)
    EventControllerMotionMotionSignalInfo   ,
#endif
    afterEventControllerMotionMotion        ,
    genClosure_EventControllerMotionMotion  ,
    mk_EventControllerMotionMotionCallback  ,
    noEventControllerMotionMotionCallback   ,
    onEventControllerMotionMotion           ,
    wrap_EventControllerMotionMotionCallback,




    ) where

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

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

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

-- | Memory-managed wrapper type.
newtype EventControllerMotion = EventControllerMotion (ManagedPtr EventControllerMotion)
    deriving (EventControllerMotion -> EventControllerMotion -> Bool
(EventControllerMotion -> EventControllerMotion -> Bool)
-> (EventControllerMotion -> EventControllerMotion -> Bool)
-> Eq EventControllerMotion
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventControllerMotion -> EventControllerMotion -> Bool
$c/= :: EventControllerMotion -> EventControllerMotion -> Bool
== :: EventControllerMotion -> EventControllerMotion -> Bool
$c== :: EventControllerMotion -> EventControllerMotion -> Bool
Eq)
foreign import ccall "gtk_event_controller_motion_get_type"
    c_gtk_event_controller_motion_get_type :: IO GType

instance GObject EventControllerMotion where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_event_controller_motion_get_type
    

-- | Convert 'EventControllerMotion' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue EventControllerMotion where
    toGValue :: EventControllerMotion -> IO GValue
toGValue o :: EventControllerMotion
o = do
        GType
gtype <- IO GType
c_gtk_event_controller_motion_get_type
        EventControllerMotion
-> (Ptr EventControllerMotion -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr EventControllerMotion
o (GType
-> (GValue -> Ptr EventControllerMotion -> IO ())
-> Ptr EventControllerMotion
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr EventControllerMotion -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO EventControllerMotion
fromGValue gv :: GValue
gv = do
        Ptr EventControllerMotion
ptr <- GValue -> IO (Ptr EventControllerMotion)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr EventControllerMotion)
        (ManagedPtr EventControllerMotion -> EventControllerMotion)
-> Ptr EventControllerMotion -> IO EventControllerMotion
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr EventControllerMotion -> EventControllerMotion
EventControllerMotion Ptr EventControllerMotion
ptr
        
    

-- | Type class for types which can be safely cast to `EventControllerMotion`, for instance with `toEventControllerMotion`.
class (GObject o, O.IsDescendantOf EventControllerMotion o) => IsEventControllerMotion o
instance (GObject o, O.IsDescendantOf EventControllerMotion o) => IsEventControllerMotion o

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

-- | Cast to `EventControllerMotion`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toEventControllerMotion :: (MonadIO m, IsEventControllerMotion o) => o -> m EventControllerMotion
toEventControllerMotion :: o -> m EventControllerMotion
toEventControllerMotion = IO EventControllerMotion -> m EventControllerMotion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EventControllerMotion -> m EventControllerMotion)
-> (o -> IO EventControllerMotion) -> o -> m EventControllerMotion
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr EventControllerMotion -> EventControllerMotion)
-> o -> IO EventControllerMotion
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr EventControllerMotion -> EventControllerMotion
EventControllerMotion

-- | A convenience alias for `Nothing` :: `Maybe` `EventControllerMotion`.
noEventControllerMotion :: Maybe EventControllerMotion
noEventControllerMotion :: Maybe EventControllerMotion
noEventControllerMotion = Maybe EventControllerMotion
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveEventControllerMotionMethod (t :: Symbol) (o :: *) :: * where
    ResolveEventControllerMotionMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveEventControllerMotionMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveEventControllerMotionMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveEventControllerMotionMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveEventControllerMotionMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveEventControllerMotionMethod "handleEvent" o = Gtk.EventController.EventControllerHandleEventMethodInfo
    ResolveEventControllerMotionMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveEventControllerMotionMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveEventControllerMotionMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveEventControllerMotionMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveEventControllerMotionMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveEventControllerMotionMethod "reset" o = Gtk.EventController.EventControllerResetMethodInfo
    ResolveEventControllerMotionMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveEventControllerMotionMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveEventControllerMotionMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveEventControllerMotionMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveEventControllerMotionMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveEventControllerMotionMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveEventControllerMotionMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveEventControllerMotionMethod "getPointerOrigin" o = EventControllerMotionGetPointerOriginMethodInfo
    ResolveEventControllerMotionMethod "getPointerTarget" o = EventControllerMotionGetPointerTargetMethodInfo
    ResolveEventControllerMotionMethod "getPropagationPhase" o = Gtk.EventController.EventControllerGetPropagationPhaseMethodInfo
    ResolveEventControllerMotionMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveEventControllerMotionMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveEventControllerMotionMethod "getWidget" o = Gtk.EventController.EventControllerGetWidgetMethodInfo
    ResolveEventControllerMotionMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveEventControllerMotionMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveEventControllerMotionMethod "setPropagationPhase" o = Gtk.EventController.EventControllerSetPropagationPhaseMethodInfo
    ResolveEventControllerMotionMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveEventControllerMotionMethod l o = O.MethodResolutionFailed l o

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

#endif

-- signal EventControllerMotion::enter
-- | Signals that the pointer has entered the widget.
type EventControllerMotionEnterCallback =
    Double
    -- ^ /@x@/: the x coordinate
    -> Double
    -- ^ /@y@/: the y coordinate
    -> Gdk.Enums.CrossingMode
    -- ^ /@crossingMode@/: the crossing mode of this event
    -> Gdk.Enums.NotifyType
    -- ^ /@notifyType@/: the kind of crossing event
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `EventControllerMotionEnterCallback`@.
noEventControllerMotionEnterCallback :: Maybe EventControllerMotionEnterCallback
noEventControllerMotionEnterCallback :: Maybe EventControllerMotionEnterCallback
noEventControllerMotionEnterCallback = Maybe EventControllerMotionEnterCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_EventControllerMotionEnterCallback =
    Ptr () ->                               -- object
    CDouble ->
    CDouble ->
    CUInt ->
    CUInt ->
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_EventControllerMotionEnter :: MonadIO m => EventControllerMotionEnterCallback -> m (GClosure C_EventControllerMotionEnterCallback)
genClosure_EventControllerMotionEnter :: EventControllerMotionEnterCallback
-> m (GClosure C_EventControllerMotionEnterCallback)
genClosure_EventControllerMotionEnter cb :: EventControllerMotionEnterCallback
cb = IO (GClosure C_EventControllerMotionEnterCallback)
-> m (GClosure C_EventControllerMotionEnterCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_EventControllerMotionEnterCallback)
 -> m (GClosure C_EventControllerMotionEnterCallback))
-> IO (GClosure C_EventControllerMotionEnterCallback)
-> m (GClosure C_EventControllerMotionEnterCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_EventControllerMotionEnterCallback
cb' = EventControllerMotionEnterCallback
-> C_EventControllerMotionEnterCallback
wrap_EventControllerMotionEnterCallback EventControllerMotionEnterCallback
cb
    C_EventControllerMotionEnterCallback
-> IO (FunPtr C_EventControllerMotionEnterCallback)
mk_EventControllerMotionEnterCallback C_EventControllerMotionEnterCallback
cb' IO (FunPtr C_EventControllerMotionEnterCallback)
-> (FunPtr C_EventControllerMotionEnterCallback
    -> IO (GClosure C_EventControllerMotionEnterCallback))
-> IO (GClosure C_EventControllerMotionEnterCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_EventControllerMotionEnterCallback
-> IO (GClosure C_EventControllerMotionEnterCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `EventControllerMotionEnterCallback` into a `C_EventControllerMotionEnterCallback`.
wrap_EventControllerMotionEnterCallback ::
    EventControllerMotionEnterCallback ->
    C_EventControllerMotionEnterCallback
wrap_EventControllerMotionEnterCallback :: EventControllerMotionEnterCallback
-> C_EventControllerMotionEnterCallback
wrap_EventControllerMotionEnterCallback _cb :: EventControllerMotionEnterCallback
_cb _ x :: CDouble
x y :: CDouble
y crossingMode :: CUInt
crossingMode notifyType :: CUInt
notifyType _ = 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
    let crossingMode' :: CrossingMode
crossingMode' = (Int -> CrossingMode
forall a. Enum a => Int -> a
toEnum (Int -> CrossingMode) -> (CUInt -> Int) -> CUInt -> CrossingMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
crossingMode
    let notifyType' :: NotifyType
notifyType' = (Int -> NotifyType
forall a. Enum a => Int -> a
toEnum (Int -> NotifyType) -> (CUInt -> Int) -> CUInt -> NotifyType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
notifyType
    EventControllerMotionEnterCallback
_cb  Double
x' Double
y' CrossingMode
crossingMode' NotifyType
notifyType'


-- | 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' eventControllerMotion #enter callback
-- @
-- 
-- 
onEventControllerMotionEnter :: (IsEventControllerMotion a, MonadIO m) => a -> EventControllerMotionEnterCallback -> m SignalHandlerId
onEventControllerMotionEnter :: a -> EventControllerMotionEnterCallback -> m SignalHandlerId
onEventControllerMotionEnter obj :: a
obj cb :: EventControllerMotionEnterCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_EventControllerMotionEnterCallback
cb' = EventControllerMotionEnterCallback
-> C_EventControllerMotionEnterCallback
wrap_EventControllerMotionEnterCallback EventControllerMotionEnterCallback
cb
    FunPtr C_EventControllerMotionEnterCallback
cb'' <- C_EventControllerMotionEnterCallback
-> IO (FunPtr C_EventControllerMotionEnterCallback)
mk_EventControllerMotionEnterCallback C_EventControllerMotionEnterCallback
cb'
    a
-> Text
-> FunPtr C_EventControllerMotionEnterCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "enter" FunPtr C_EventControllerMotionEnterCallback
cb'' 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' eventControllerMotion #enter callback
-- @
-- 
-- 
afterEventControllerMotionEnter :: (IsEventControllerMotion a, MonadIO m) => a -> EventControllerMotionEnterCallback -> m SignalHandlerId
afterEventControllerMotionEnter :: a -> EventControllerMotionEnterCallback -> m SignalHandlerId
afterEventControllerMotionEnter obj :: a
obj cb :: EventControllerMotionEnterCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_EventControllerMotionEnterCallback
cb' = EventControllerMotionEnterCallback
-> C_EventControllerMotionEnterCallback
wrap_EventControllerMotionEnterCallback EventControllerMotionEnterCallback
cb
    FunPtr C_EventControllerMotionEnterCallback
cb'' <- C_EventControllerMotionEnterCallback
-> IO (FunPtr C_EventControllerMotionEnterCallback)
mk_EventControllerMotionEnterCallback C_EventControllerMotionEnterCallback
cb'
    a
-> Text
-> FunPtr C_EventControllerMotionEnterCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "enter" FunPtr C_EventControllerMotionEnterCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data EventControllerMotionEnterSignalInfo
instance SignalInfo EventControllerMotionEnterSignalInfo where
    type HaskellCallbackType EventControllerMotionEnterSignalInfo = EventControllerMotionEnterCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_EventControllerMotionEnterCallback cb
        cb'' <- mk_EventControllerMotionEnterCallback cb'
        connectSignalFunPtr obj "enter" cb'' connectMode detail

#endif

-- signal EventControllerMotion::leave
-- | Signals that pointer has left the widget.
type EventControllerMotionLeaveCallback =
    Gdk.Enums.CrossingMode
    -- ^ /@crossingMode@/: the crossing mode of this event
    -> Gdk.Enums.NotifyType
    -- ^ /@notifyType@/: the kind of crossing event
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `EventControllerMotionLeaveCallback`@.
noEventControllerMotionLeaveCallback :: Maybe EventControllerMotionLeaveCallback
noEventControllerMotionLeaveCallback :: Maybe EventControllerMotionLeaveCallback
noEventControllerMotionLeaveCallback = Maybe EventControllerMotionLeaveCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_EventControllerMotionLeaveCallback =
    Ptr () ->                               -- object
    CUInt ->
    CUInt ->
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_EventControllerMotionLeave :: MonadIO m => EventControllerMotionLeaveCallback -> m (GClosure C_EventControllerMotionLeaveCallback)
genClosure_EventControllerMotionLeave :: EventControllerMotionLeaveCallback
-> m (GClosure C_EventControllerMotionLeaveCallback)
genClosure_EventControllerMotionLeave cb :: EventControllerMotionLeaveCallback
cb = IO (GClosure C_EventControllerMotionLeaveCallback)
-> m (GClosure C_EventControllerMotionLeaveCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_EventControllerMotionLeaveCallback)
 -> m (GClosure C_EventControllerMotionLeaveCallback))
-> IO (GClosure C_EventControllerMotionLeaveCallback)
-> m (GClosure C_EventControllerMotionLeaveCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_EventControllerMotionLeaveCallback
cb' = EventControllerMotionLeaveCallback
-> C_EventControllerMotionLeaveCallback
wrap_EventControllerMotionLeaveCallback EventControllerMotionLeaveCallback
cb
    C_EventControllerMotionLeaveCallback
-> IO (FunPtr C_EventControllerMotionLeaveCallback)
mk_EventControllerMotionLeaveCallback C_EventControllerMotionLeaveCallback
cb' IO (FunPtr C_EventControllerMotionLeaveCallback)
-> (FunPtr C_EventControllerMotionLeaveCallback
    -> IO (GClosure C_EventControllerMotionLeaveCallback))
-> IO (GClosure C_EventControllerMotionLeaveCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_EventControllerMotionLeaveCallback
-> IO (GClosure C_EventControllerMotionLeaveCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `EventControllerMotionLeaveCallback` into a `C_EventControllerMotionLeaveCallback`.
wrap_EventControllerMotionLeaveCallback ::
    EventControllerMotionLeaveCallback ->
    C_EventControllerMotionLeaveCallback
wrap_EventControllerMotionLeaveCallback :: EventControllerMotionLeaveCallback
-> C_EventControllerMotionLeaveCallback
wrap_EventControllerMotionLeaveCallback _cb :: EventControllerMotionLeaveCallback
_cb _ crossingMode :: CUInt
crossingMode notifyType :: CUInt
notifyType _ = do
    let crossingMode' :: CrossingMode
crossingMode' = (Int -> CrossingMode
forall a. Enum a => Int -> a
toEnum (Int -> CrossingMode) -> (CUInt -> Int) -> CUInt -> CrossingMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
crossingMode
    let notifyType' :: NotifyType
notifyType' = (Int -> NotifyType
forall a. Enum a => Int -> a
toEnum (Int -> NotifyType) -> (CUInt -> Int) -> CUInt -> NotifyType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
notifyType
    EventControllerMotionLeaveCallback
_cb  CrossingMode
crossingMode' NotifyType
notifyType'


-- | 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' eventControllerMotion #leave callback
-- @
-- 
-- 
onEventControllerMotionLeave :: (IsEventControllerMotion a, MonadIO m) => a -> EventControllerMotionLeaveCallback -> m SignalHandlerId
onEventControllerMotionLeave :: a -> EventControllerMotionLeaveCallback -> m SignalHandlerId
onEventControllerMotionLeave obj :: a
obj cb :: EventControllerMotionLeaveCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_EventControllerMotionLeaveCallback
cb' = EventControllerMotionLeaveCallback
-> C_EventControllerMotionLeaveCallback
wrap_EventControllerMotionLeaveCallback EventControllerMotionLeaveCallback
cb
    FunPtr C_EventControllerMotionLeaveCallback
cb'' <- C_EventControllerMotionLeaveCallback
-> IO (FunPtr C_EventControllerMotionLeaveCallback)
mk_EventControllerMotionLeaveCallback C_EventControllerMotionLeaveCallback
cb'
    a
-> Text
-> FunPtr C_EventControllerMotionLeaveCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "leave" FunPtr C_EventControllerMotionLeaveCallback
cb'' 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' eventControllerMotion #leave callback
-- @
-- 
-- 
afterEventControllerMotionLeave :: (IsEventControllerMotion a, MonadIO m) => a -> EventControllerMotionLeaveCallback -> m SignalHandlerId
afterEventControllerMotionLeave :: a -> EventControllerMotionLeaveCallback -> m SignalHandlerId
afterEventControllerMotionLeave obj :: a
obj cb :: EventControllerMotionLeaveCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_EventControllerMotionLeaveCallback
cb' = EventControllerMotionLeaveCallback
-> C_EventControllerMotionLeaveCallback
wrap_EventControllerMotionLeaveCallback EventControllerMotionLeaveCallback
cb
    FunPtr C_EventControllerMotionLeaveCallback
cb'' <- C_EventControllerMotionLeaveCallback
-> IO (FunPtr C_EventControllerMotionLeaveCallback)
mk_EventControllerMotionLeaveCallback C_EventControllerMotionLeaveCallback
cb'
    a
-> Text
-> FunPtr C_EventControllerMotionLeaveCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "leave" FunPtr C_EventControllerMotionLeaveCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data EventControllerMotionLeaveSignalInfo
instance SignalInfo EventControllerMotionLeaveSignalInfo where
    type HaskellCallbackType EventControllerMotionLeaveSignalInfo = EventControllerMotionLeaveCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_EventControllerMotionLeaveCallback cb
        cb'' <- mk_EventControllerMotionLeaveCallback cb'
        connectSignalFunPtr obj "leave" cb'' connectMode detail

#endif

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

-- | A convenience synonym for @`Nothing` :: `Maybe` `EventControllerMotionMotionCallback`@.
noEventControllerMotionMotionCallback :: Maybe EventControllerMotionMotionCallback
noEventControllerMotionMotionCallback :: Maybe EventControllerMotionMotionCallback
noEventControllerMotionMotionCallback = Maybe EventControllerMotionMotionCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_EventControllerMotionMotionCallback =
    Ptr () ->                               -- object
    CDouble ->
    CDouble ->
    Ptr () ->                               -- user_data
    IO ()

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

-- | Wrap the callback into a `GClosure`.
genClosure_EventControllerMotionMotion :: MonadIO m => EventControllerMotionMotionCallback -> m (GClosure C_EventControllerMotionMotionCallback)
genClosure_EventControllerMotionMotion :: EventControllerMotionMotionCallback
-> m (GClosure C_EventControllerMotionMotionCallback)
genClosure_EventControllerMotionMotion cb :: EventControllerMotionMotionCallback
cb = IO (GClosure C_EventControllerMotionMotionCallback)
-> m (GClosure C_EventControllerMotionMotionCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_EventControllerMotionMotionCallback)
 -> m (GClosure C_EventControllerMotionMotionCallback))
-> IO (GClosure C_EventControllerMotionMotionCallback)
-> m (GClosure C_EventControllerMotionMotionCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_EventControllerMotionMotionCallback
cb' = EventControllerMotionMotionCallback
-> C_EventControllerMotionMotionCallback
wrap_EventControllerMotionMotionCallback EventControllerMotionMotionCallback
cb
    C_EventControllerMotionMotionCallback
-> IO (FunPtr C_EventControllerMotionMotionCallback)
mk_EventControllerMotionMotionCallback C_EventControllerMotionMotionCallback
cb' IO (FunPtr C_EventControllerMotionMotionCallback)
-> (FunPtr C_EventControllerMotionMotionCallback
    -> IO (GClosure C_EventControllerMotionMotionCallback))
-> IO (GClosure C_EventControllerMotionMotionCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_EventControllerMotionMotionCallback
-> IO (GClosure C_EventControllerMotionMotionCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `EventControllerMotionMotionCallback` into a `C_EventControllerMotionMotionCallback`.
wrap_EventControllerMotionMotionCallback ::
    EventControllerMotionMotionCallback ->
    C_EventControllerMotionMotionCallback
wrap_EventControllerMotionMotionCallback :: EventControllerMotionMotionCallback
-> C_EventControllerMotionMotionCallback
wrap_EventControllerMotionMotionCallback _cb :: EventControllerMotionMotionCallback
_cb _ x :: CDouble
x y :: CDouble
y _ = 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
    EventControllerMotionMotionCallback
_cb  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' eventControllerMotion #motion callback
-- @
-- 
-- 
onEventControllerMotionMotion :: (IsEventControllerMotion a, MonadIO m) => a -> EventControllerMotionMotionCallback -> m SignalHandlerId
onEventControllerMotionMotion :: a -> EventControllerMotionMotionCallback -> m SignalHandlerId
onEventControllerMotionMotion obj :: a
obj cb :: EventControllerMotionMotionCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_EventControllerMotionMotionCallback
cb' = EventControllerMotionMotionCallback
-> C_EventControllerMotionMotionCallback
wrap_EventControllerMotionMotionCallback EventControllerMotionMotionCallback
cb
    FunPtr C_EventControllerMotionMotionCallback
cb'' <- C_EventControllerMotionMotionCallback
-> IO (FunPtr C_EventControllerMotionMotionCallback)
mk_EventControllerMotionMotionCallback C_EventControllerMotionMotionCallback
cb'
    a
-> Text
-> FunPtr C_EventControllerMotionMotionCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "motion" FunPtr C_EventControllerMotionMotionCallback
cb'' 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' eventControllerMotion #motion callback
-- @
-- 
-- 
afterEventControllerMotionMotion :: (IsEventControllerMotion a, MonadIO m) => a -> EventControllerMotionMotionCallback -> m SignalHandlerId
afterEventControllerMotionMotion :: a -> EventControllerMotionMotionCallback -> m SignalHandlerId
afterEventControllerMotionMotion obj :: a
obj cb :: EventControllerMotionMotionCallback
cb = IO SignalHandlerId -> m SignalHandlerId
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 cb' :: C_EventControllerMotionMotionCallback
cb' = EventControllerMotionMotionCallback
-> C_EventControllerMotionMotionCallback
wrap_EventControllerMotionMotionCallback EventControllerMotionMotionCallback
cb
    FunPtr C_EventControllerMotionMotionCallback
cb'' <- C_EventControllerMotionMotionCallback
-> IO (FunPtr C_EventControllerMotionMotionCallback)
mk_EventControllerMotionMotionCallback C_EventControllerMotionMotionCallback
cb'
    a
-> Text
-> FunPtr C_EventControllerMotionMotionCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "motion" FunPtr C_EventControllerMotionMotionCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data EventControllerMotionMotionSignalInfo
instance SignalInfo EventControllerMotionMotionSignalInfo where
    type HaskellCallbackType EventControllerMotionMotionSignalInfo = EventControllerMotionMotionCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_EventControllerMotionMotionCallback cb
        cb'' <- mk_EventControllerMotionMotionCallback cb'
        connectSignalFunPtr obj "motion" cb'' connectMode detail

#endif

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

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

#if defined(ENABLE_OVERLOADING)
data EventControllerMotionContainsPointerFocusPropertyInfo
instance AttrInfo EventControllerMotionContainsPointerFocusPropertyInfo where
    type AttrAllowedOps EventControllerMotionContainsPointerFocusPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint EventControllerMotionContainsPointerFocusPropertyInfo = IsEventControllerMotion
    type AttrSetTypeConstraint EventControllerMotionContainsPointerFocusPropertyInfo = (~) ()
    type AttrTransferTypeConstraint EventControllerMotionContainsPointerFocusPropertyInfo = (~) ()
    type AttrTransferType EventControllerMotionContainsPointerFocusPropertyInfo = ()
    type AttrGetType EventControllerMotionContainsPointerFocusPropertyInfo = Bool
    type AttrLabel EventControllerMotionContainsPointerFocusPropertyInfo = "contains-pointer-focus"
    type AttrOrigin EventControllerMotionContainsPointerFocusPropertyInfo = EventControllerMotion
    attrGet = getEventControllerMotionContainsPointerFocus
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

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

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

#if defined(ENABLE_OVERLOADING)
data EventControllerMotionIsPointerFocusPropertyInfo
instance AttrInfo EventControllerMotionIsPointerFocusPropertyInfo where
    type AttrAllowedOps EventControllerMotionIsPointerFocusPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint EventControllerMotionIsPointerFocusPropertyInfo = IsEventControllerMotion
    type AttrSetTypeConstraint EventControllerMotionIsPointerFocusPropertyInfo = (~) ()
    type AttrTransferTypeConstraint EventControllerMotionIsPointerFocusPropertyInfo = (~) ()
    type AttrTransferType EventControllerMotionIsPointerFocusPropertyInfo = ()
    type AttrGetType EventControllerMotionIsPointerFocusPropertyInfo = Bool
    type AttrLabel EventControllerMotionIsPointerFocusPropertyInfo = "is-pointer-focus"
    type AttrOrigin EventControllerMotionIsPointerFocusPropertyInfo = EventControllerMotion
    attrGet = getEventControllerMotionIsPointerFocus
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList EventControllerMotion
type instance O.AttributeList EventControllerMotion = EventControllerMotionAttributeList
type EventControllerMotionAttributeList = ('[ '("containsPointerFocus", EventControllerMotionContainsPointerFocusPropertyInfo), '("isPointerFocus", EventControllerMotionIsPointerFocusPropertyInfo), '("propagationPhase", Gtk.EventController.EventControllerPropagationPhasePropertyInfo), '("widget", Gtk.EventController.EventControllerWidgetPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
eventControllerMotionContainsPointerFocus :: AttrLabelProxy "containsPointerFocus"
eventControllerMotionContainsPointerFocus = AttrLabelProxy

eventControllerMotionIsPointerFocus :: AttrLabelProxy "isPointerFocus"
eventControllerMotionIsPointerFocus = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList EventControllerMotion = EventControllerMotionSignalList
type EventControllerMotionSignalList = ('[ '("enter", EventControllerMotionEnterSignalInfo), '("leave", EventControllerMotionLeaveSignalInfo), '("motion", EventControllerMotionMotionSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "gtk_event_controller_motion_new" gtk_event_controller_motion_new :: 
    IO (Ptr EventControllerMotion)

-- | Creates a new event controller that will handle motion events.
eventControllerMotionNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m EventControllerMotion
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.EventControllerMotion.EventControllerMotion'
eventControllerMotionNew :: m EventControllerMotion
eventControllerMotionNew  = IO EventControllerMotion -> m EventControllerMotion
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EventControllerMotion -> m EventControllerMotion)
-> IO EventControllerMotion -> m EventControllerMotion
forall a b. (a -> b) -> a -> b
$ do
    Ptr EventControllerMotion
result <- IO (Ptr EventControllerMotion)
gtk_event_controller_motion_new
    Text -> Ptr EventControllerMotion -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "eventControllerMotionNew" Ptr EventControllerMotion
result
    EventControllerMotion
result' <- ((ManagedPtr EventControllerMotion -> EventControllerMotion)
-> Ptr EventControllerMotion -> IO EventControllerMotion
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr EventControllerMotion -> EventControllerMotion
EventControllerMotion) Ptr EventControllerMotion
result
    EventControllerMotion -> IO EventControllerMotion
forall (m :: * -> *) a. Monad m => a -> m a
return EventControllerMotion
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method EventControllerMotion::get_pointer_origin
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "controller"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "EventControllerMotion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkEventControllerMotion"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Widget" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_event_controller_motion_get_pointer_origin" gtk_event_controller_motion_get_pointer_origin :: 
    Ptr EventControllerMotion ->            -- controller : TInterface (Name {namespace = "Gtk", name = "EventControllerMotion"})
    IO (Ptr Gtk.Widget.Widget)

-- | Returns the widget that contained the pointer before.
-- 
-- This function can only be used in handlers for the
-- [enter]("GI.Gtk.Objects.EventControllerMotion#signal:enter") and
-- [leave]("GI.Gtk.Objects.EventControllerMotion#signal:leave") signals.
eventControllerMotionGetPointerOrigin ::
    (B.CallStack.HasCallStack, MonadIO m, IsEventControllerMotion a) =>
    a
    -- ^ /@controller@/: a t'GI.Gtk.Objects.EventControllerMotion.EventControllerMotion'
    -> m Gtk.Widget.Widget
    -- ^ __Returns:__ the previous pointer focus
eventControllerMotionGetPointerOrigin :: a -> m Widget
eventControllerMotionGetPointerOrigin controller :: a
controller = IO Widget -> m Widget
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Widget -> m Widget) -> IO Widget -> m Widget
forall a b. (a -> b) -> a -> b
$ do
    Ptr EventControllerMotion
controller' <- a -> IO (Ptr EventControllerMotion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
controller
    Ptr Widget
result <- Ptr EventControllerMotion -> IO (Ptr Widget)
gtk_event_controller_motion_get_pointer_origin Ptr EventControllerMotion
controller'
    Text -> Ptr Widget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "eventControllerMotionGetPointerOrigin" Ptr Widget
result
    Widget
result' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
controller
    Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result'

#if defined(ENABLE_OVERLOADING)
data EventControllerMotionGetPointerOriginMethodInfo
instance (signature ~ (m Gtk.Widget.Widget), MonadIO m, IsEventControllerMotion a) => O.MethodInfo EventControllerMotionGetPointerOriginMethodInfo a signature where
    overloadedMethod = eventControllerMotionGetPointerOrigin

#endif

-- method EventControllerMotion::get_pointer_target
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "controller"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "EventControllerMotion" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkEventControllerMotion"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "Widget" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_event_controller_motion_get_pointer_target" gtk_event_controller_motion_get_pointer_target :: 
    Ptr EventControllerMotion ->            -- controller : TInterface (Name {namespace = "Gtk", name = "EventControllerMotion"})
    IO (Ptr Gtk.Widget.Widget)

-- | Returns the widget that will contain the pointer afterwards.
-- 
-- This function can only be used in handlers for the
-- [enter]("GI.Gtk.Objects.EventControllerMotion#signal:enter") and
-- [leave]("GI.Gtk.Objects.EventControllerMotion#signal:leave") signals.
eventControllerMotionGetPointerTarget ::
    (B.CallStack.HasCallStack, MonadIO m, IsEventControllerMotion a) =>
    a
    -- ^ /@controller@/: a t'GI.Gtk.Objects.EventControllerMotion.EventControllerMotion'
    -> m Gtk.Widget.Widget
    -- ^ __Returns:__ the next pointer focus
eventControllerMotionGetPointerTarget :: a -> m Widget
eventControllerMotionGetPointerTarget controller :: a
controller = IO Widget -> m Widget
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Widget -> m Widget) -> IO Widget -> m Widget
forall a b. (a -> b) -> a -> b
$ do
    Ptr EventControllerMotion
controller' <- a -> IO (Ptr EventControllerMotion)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
controller
    Ptr Widget
result <- Ptr EventControllerMotion -> IO (Ptr Widget)
gtk_event_controller_motion_get_pointer_target Ptr EventControllerMotion
controller'
    Text -> Ptr Widget -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "eventControllerMotionGetPointerTarget" Ptr Widget
result
    Widget
result' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
controller
    Widget -> IO Widget
forall (m :: * -> *) a. Monad m => a -> m a
return Widget
result'

#if defined(ENABLE_OVERLOADING)
data EventControllerMotionGetPointerTargetMethodInfo
instance (signature ~ (m Gtk.Widget.Widget), MonadIO m, IsEventControllerMotion a) => O.MethodInfo EventControllerMotionGetPointerTargetMethodInfo a signature where
    overloadedMethod = eventControllerMotionGetPointerTarget

#endif