{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Generated when the pointer moves.

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

module GI.Gdk.Structs.EventMotion
    ( 

-- * Exported types
    EventMotion(..)                         ,
    newZeroEventMotion                      ,


 -- * Methods

#if defined(ENABLE_OVERLOADING)
    ResolveEventMotionMethod                ,
#endif



 -- * Properties


-- ** axes #attr:axes#
-- | /@x@/, /@y@/ translated to the axes of /@device@/, or 'P.Nothing' if /@device@/ is
--   the mouse.

#if defined(ENABLE_OVERLOADING)
    eventMotion_axes                        ,
#endif
    getEventMotionAxes                      ,
    setEventMotionAxes                      ,


-- ** device #attr:device#
-- | the master device that the event originated from. Use
-- 'GI.Gdk.Unions.Event.eventGetSourceDevice' to get the slave device.

    clearEventMotionDevice                  ,
#if defined(ENABLE_OVERLOADING)
    eventMotion_device                      ,
#endif
    getEventMotionDevice                    ,
    setEventMotionDevice                    ,


-- ** isHint #attr:isHint#
-- | set to 1 if this event is just a hint, see the
--   'GI.Gdk.Flags.EventMaskPointerMotionHintMask' value of t'GI.Gdk.Flags.EventMask'.

#if defined(ENABLE_OVERLOADING)
    eventMotion_isHint                      ,
#endif
    getEventMotionIsHint                    ,
    setEventMotionIsHint                    ,


-- ** sendEvent #attr:sendEvent#
-- | 'P.True' if the event was sent explicitly.

#if defined(ENABLE_OVERLOADING)
    eventMotion_sendEvent                   ,
#endif
    getEventMotionSendEvent                 ,
    setEventMotionSendEvent                 ,


-- ** state #attr:state#
-- | a bit-mask representing the state of
--   the modifier keys (e.g. Control, Shift and Alt) and the pointer
--   buttons. See t'GI.Gdk.Flags.ModifierType'.

#if defined(ENABLE_OVERLOADING)
    eventMotion_state                       ,
#endif
    getEventMotionState                     ,
    setEventMotionState                     ,


-- ** time #attr:time#
-- | the time of the event in milliseconds.

#if defined(ENABLE_OVERLOADING)
    eventMotion_time                        ,
#endif
    getEventMotionTime                      ,
    setEventMotionTime                      ,


-- ** type #attr:type#
-- | the type of the event.

#if defined(ENABLE_OVERLOADING)
    eventMotion_type                        ,
#endif
    getEventMotionType                      ,
    setEventMotionType                      ,


-- ** window #attr:window#
-- | the window which received the event.

    clearEventMotionWindow                  ,
#if defined(ENABLE_OVERLOADING)
    eventMotion_window                      ,
#endif
    getEventMotionWindow                    ,
    setEventMotionWindow                    ,


-- ** x #attr:x#
-- | the x coordinate of the pointer relative to the window.

#if defined(ENABLE_OVERLOADING)
    eventMotion_x                           ,
#endif
    getEventMotionX                         ,
    setEventMotionX                         ,


-- ** xRoot #attr:xRoot#
-- | the x coordinate of the pointer relative to the root of the
--   screen.

#if defined(ENABLE_OVERLOADING)
    eventMotion_xRoot                       ,
#endif
    getEventMotionXRoot                     ,
    setEventMotionXRoot                     ,


-- ** y #attr:y#
-- | the y coordinate of the pointer relative to the window.

#if defined(ENABLE_OVERLOADING)
    eventMotion_y                           ,
#endif
    getEventMotionY                         ,
    setEventMotionY                         ,


-- ** yRoot #attr:yRoot#
-- | the y coordinate of the pointer relative to the root of the
--   screen.

#if defined(ENABLE_OVERLOADING)
    eventMotion_yRoot                       ,
#endif
    getEventMotionYRoot                     ,
    setEventMotionYRoot                     ,




    ) 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.Enums as Cairo.Enums
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.Cairo.Structs.Pattern as Cairo.Pattern
import qualified GI.Cairo.Structs.Region as Cairo.Region
import qualified GI.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Callbacks as Gdk.Callbacks
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Objects.AppLaunchContext as Gdk.AppLaunchContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Cursor as Gdk.Cursor
import {-# SOURCE #-} qualified GI.Gdk.Objects.Device as Gdk.Device
import {-# SOURCE #-} qualified GI.Gdk.Objects.DeviceManager as Gdk.DeviceManager
import {-# SOURCE #-} qualified GI.Gdk.Objects.DeviceTool as Gdk.DeviceTool
import {-# SOURCE #-} qualified GI.Gdk.Objects.Display as Gdk.Display
import {-# SOURCE #-} qualified GI.Gdk.Objects.DragContext as Gdk.DragContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.DrawingContext as Gdk.DrawingContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import {-# SOURCE #-} qualified GI.Gdk.Objects.GLContext as Gdk.GLContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Monitor as Gdk.Monitor
import {-# SOURCE #-} qualified GI.Gdk.Objects.Screen as Gdk.Screen
import {-# SOURCE #-} qualified GI.Gdk.Objects.Seat as Gdk.Seat
import {-# SOURCE #-} qualified GI.Gdk.Objects.Visual as Gdk.Visual
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window
import {-# SOURCE #-} qualified GI.Gdk.Structs.Atom as Gdk.Atom
import {-# SOURCE #-} qualified GI.Gdk.Structs.Color as Gdk.Color
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventAny as Gdk.EventAny
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventButton as Gdk.EventButton
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventConfigure as Gdk.EventConfigure
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventCrossing as Gdk.EventCrossing
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventDND as Gdk.EventDND
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventExpose as Gdk.EventExpose
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventFocus as Gdk.EventFocus
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventGrabBroken as Gdk.EventGrabBroken
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventKey as Gdk.EventKey
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventOwnerChange as Gdk.EventOwnerChange
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadAxis as Gdk.EventPadAxis
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadButton as Gdk.EventPadButton
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadGroupMode as Gdk.EventPadGroupMode
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventProperty as Gdk.EventProperty
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventProximity as Gdk.EventProximity
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventScroll as Gdk.EventScroll
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSelection as Gdk.EventSelection
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSequence as Gdk.EventSequence
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSetting as Gdk.EventSetting
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouch as Gdk.EventTouch
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouchpadPinch as Gdk.EventTouchpadPinch
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouchpadSwipe as Gdk.EventTouchpadSwipe
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventVisibility as Gdk.EventVisibility
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventWindowState as Gdk.EventWindowState
import {-# SOURCE #-} qualified GI.Gdk.Structs.FrameTimings as Gdk.FrameTimings
import {-# SOURCE #-} qualified GI.Gdk.Structs.Geometry as Gdk.Geometry
import {-# SOURCE #-} qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import {-# SOURCE #-} qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import {-# SOURCE #-} qualified GI.Gdk.Structs.WindowAttr as Gdk.WindowAttr
import {-# SOURCE #-} qualified GI.Gdk.Unions.Event as Gdk.Event
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Objects.AppLaunchContext as Gio.AppLaunchContext

#else
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Objects.Device as Gdk.Device
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window

#endif

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

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

instance BoxedPtr EventMotion where
    boxedPtrCopy :: EventMotion -> IO EventMotion
boxedPtrCopy = \EventMotion
p -> EventMotion
-> (Ptr EventMotion -> IO EventMotion) -> IO EventMotion
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr EventMotion
p (Int -> Ptr EventMotion -> IO (Ptr EventMotion)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
80 (Ptr EventMotion -> IO (Ptr EventMotion))
-> (Ptr EventMotion -> IO EventMotion)
-> Ptr EventMotion
-> IO EventMotion
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr EventMotion -> EventMotion)
-> Ptr EventMotion -> IO EventMotion
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr EventMotion -> EventMotion
EventMotion)
    boxedPtrFree :: EventMotion -> IO ()
boxedPtrFree = \EventMotion
x -> EventMotion -> (Ptr EventMotion -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr EventMotion
x Ptr EventMotion -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr EventMotion where
    boxedPtrCalloc :: IO (Ptr EventMotion)
boxedPtrCalloc = Int -> IO (Ptr EventMotion)
forall a. Int -> IO (Ptr a)
callocBytes Int
80


-- | Construct a `EventMotion` struct initialized to zero.
newZeroEventMotion :: MonadIO m => m EventMotion
newZeroEventMotion :: forall (m :: * -> *). MonadIO m => m EventMotion
newZeroEventMotion = IO EventMotion -> m EventMotion
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EventMotion -> m EventMotion)
-> IO EventMotion -> m EventMotion
forall a b. (a -> b) -> a -> b
$ IO (Ptr EventMotion)
forall a. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr EventMotion)
-> (Ptr EventMotion -> IO EventMotion) -> IO EventMotion
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr EventMotion -> EventMotion)
-> Ptr EventMotion -> IO EventMotion
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr EventMotion -> EventMotion
EventMotion

instance tag ~ 'AttrSet => Constructible EventMotion tag where
    new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr EventMotion -> EventMotion)
-> [AttrOp EventMotion tag] -> m EventMotion
new ManagedPtr EventMotion -> EventMotion
_ [AttrOp EventMotion tag]
attrs = do
        EventMotion
o <- m EventMotion
forall (m :: * -> *). MonadIO m => m EventMotion
newZeroEventMotion
        EventMotion -> [AttrOp EventMotion 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set EventMotion
o [AttrOp EventMotion tag]
[AttrOp EventMotion 'AttrSet]
attrs
        EventMotion -> m EventMotion
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return EventMotion
o


-- | Get the value of the “@type@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventMotion #type
-- @
getEventMotionType :: MonadIO m => EventMotion -> m Gdk.Enums.EventType
getEventMotionType :: forall (m :: * -> *). MonadIO m => EventMotion -> m EventType
getEventMotionType EventMotion
s = IO EventType -> m EventType
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EventType -> m EventType) -> IO EventType -> m EventType
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO EventType) -> IO EventType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO EventType) -> IO EventType)
-> (Ptr EventMotion -> IO EventType) -> IO EventType
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CInt
    let val' :: EventType
val' = (Int -> EventType
forall a. Enum a => Int -> a
toEnum (Int -> EventType) -> (CInt -> Int) -> CInt -> EventType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CInt
val
    EventType -> IO EventType
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return EventType
val'

-- | Set the value of the “@type@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventMotion [ #type 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventMotionType :: MonadIO m => EventMotion -> Gdk.Enums.EventType -> m ()
setEventMotionType :: forall (m :: * -> *). MonadIO m => EventMotion -> EventType -> m ()
setEventMotionType EventMotion
s EventType
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO ()) -> IO ())
-> (Ptr EventMotion -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    let val' :: CInt
val' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (EventType -> Int) -> EventType -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EventType -> Int
forall a. Enum a => a -> Int
fromEnum) EventType
val
    Ptr CInt -> CInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CInt
val' :: CInt)

#if defined(ENABLE_OVERLOADING)
data EventMotionTypeFieldInfo
instance AttrInfo EventMotionTypeFieldInfo where
    type AttrBaseTypeConstraint EventMotionTypeFieldInfo = (~) EventMotion
    type AttrAllowedOps EventMotionTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventMotionTypeFieldInfo = (~) Gdk.Enums.EventType
    type AttrTransferTypeConstraint EventMotionTypeFieldInfo = (~)Gdk.Enums.EventType
    type AttrTransferType EventMotionTypeFieldInfo = Gdk.Enums.EventType
    type AttrGetType EventMotionTypeFieldInfo = Gdk.Enums.EventType
    type AttrLabel EventMotionTypeFieldInfo = "type"
    type AttrOrigin EventMotionTypeFieldInfo = EventMotion
    attrGet = getEventMotionType
    attrSet = setEventMotionType
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventMotion.type"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventMotion.html#g:attr:type"
        })

eventMotion_type :: AttrLabelProxy "type"
eventMotion_type = AttrLabelProxy

#endif


-- | Get the value of the “@window@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventMotion #window
-- @
getEventMotionWindow :: MonadIO m => EventMotion -> m (Maybe Gdk.Window.Window)
getEventMotionWindow :: forall (m :: * -> *). MonadIO m => EventMotion -> m (Maybe Window)
getEventMotionWindow EventMotion
s = IO (Maybe Window) -> m (Maybe Window)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Window) -> m (Maybe Window))
-> IO (Maybe Window) -> m (Maybe Window)
forall a b. (a -> b) -> a -> b
$ EventMotion
-> (Ptr EventMotion -> IO (Maybe Window)) -> IO (Maybe Window)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO (Maybe Window)) -> IO (Maybe Window))
-> (Ptr EventMotion -> IO (Maybe Window)) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    Ptr Window
val <- Ptr (Ptr Window) -> IO (Ptr Window)
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO (Ptr Gdk.Window.Window)
    Maybe Window
result <- Ptr Window -> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Window
val ((Ptr Window -> IO Window) -> IO (Maybe Window))
-> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \Ptr Window
val' -> do
        Window
val'' <- ((ManagedPtr Window -> Window) -> Ptr Window -> IO Window
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Window -> Window
Gdk.Window.Window) Ptr Window
val'
        Window -> IO Window
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Window
val''
    Maybe Window -> IO (Maybe Window)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Window
result

-- | Set the value of the “@window@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventMotion [ #window 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventMotionWindow :: MonadIO m => EventMotion -> Ptr Gdk.Window.Window -> m ()
setEventMotionWindow :: forall (m :: * -> *).
MonadIO m =>
EventMotion -> Ptr Window -> m ()
setEventMotionWindow EventMotion
s Ptr Window
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO ()) -> IO ())
-> (Ptr EventMotion -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr Window
val :: Ptr Gdk.Window.Window)

-- | Set the value of the “@window@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #window
-- @
clearEventMotionWindow :: MonadIO m => EventMotion -> m ()
clearEventMotionWindow :: forall (m :: * -> *). MonadIO m => EventMotion -> m ()
clearEventMotionWindow EventMotion
s = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO ()) -> IO ())
-> (Ptr EventMotion -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (Ptr Window
forall a. Ptr a
FP.nullPtr :: Ptr Gdk.Window.Window)

#if defined(ENABLE_OVERLOADING)
data EventMotionWindowFieldInfo
instance AttrInfo EventMotionWindowFieldInfo where
    type AttrBaseTypeConstraint EventMotionWindowFieldInfo = (~) EventMotion
    type AttrAllowedOps EventMotionWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventMotionWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrTransferTypeConstraint EventMotionWindowFieldInfo = (~)(Ptr Gdk.Window.Window)
    type AttrTransferType EventMotionWindowFieldInfo = (Ptr Gdk.Window.Window)
    type AttrGetType EventMotionWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventMotionWindowFieldInfo = "window"
    type AttrOrigin EventMotionWindowFieldInfo = EventMotion
    attrGet = getEventMotionWindow
    attrSet = setEventMotionWindow
    attrConstruct = undefined
    attrClear = clearEventMotionWindow
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventMotion.window"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventMotion.html#g:attr:window"
        })

eventMotion_window :: AttrLabelProxy "window"
eventMotion_window = AttrLabelProxy

#endif


-- | Get the value of the “@send_event@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventMotion #sendEvent
-- @
getEventMotionSendEvent :: MonadIO m => EventMotion -> m Int8
getEventMotionSendEvent :: forall (m :: * -> *). MonadIO m => EventMotion -> m Int8
getEventMotionSendEvent EventMotion
s = IO Int8 -> m Int8
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int8 -> m Int8) -> IO Int8 -> m Int8
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO Int8) -> IO Int8
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO Int8) -> IO Int8)
-> (Ptr EventMotion -> IO Int8) -> IO Int8
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    Int8
val <- Ptr Int8 -> IO Int8
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr Int8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO Int8
    Int8 -> IO Int8
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int8
val

-- | Set the value of the “@send_event@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventMotion [ #sendEvent 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventMotionSendEvent :: MonadIO m => EventMotion -> Int8 -> m ()
setEventMotionSendEvent :: forall (m :: * -> *). MonadIO m => EventMotion -> Int8 -> m ()
setEventMotionSendEvent EventMotion
s Int8
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO ()) -> IO ())
-> (Ptr EventMotion -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    Ptr Int8 -> Int8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr Int8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (Int8
val :: Int8)

#if defined(ENABLE_OVERLOADING)
data EventMotionSendEventFieldInfo
instance AttrInfo EventMotionSendEventFieldInfo where
    type AttrBaseTypeConstraint EventMotionSendEventFieldInfo = (~) EventMotion
    type AttrAllowedOps EventMotionSendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventMotionSendEventFieldInfo = (~) Int8
    type AttrTransferTypeConstraint EventMotionSendEventFieldInfo = (~)Int8
    type AttrTransferType EventMotionSendEventFieldInfo = Int8
    type AttrGetType EventMotionSendEventFieldInfo = Int8
    type AttrLabel EventMotionSendEventFieldInfo = "send_event"
    type AttrOrigin EventMotionSendEventFieldInfo = EventMotion
    attrGet = getEventMotionSendEvent
    attrSet = setEventMotionSendEvent
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventMotion.sendEvent"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventMotion.html#g:attr:sendEvent"
        })

eventMotion_sendEvent :: AttrLabelProxy "sendEvent"
eventMotion_sendEvent = AttrLabelProxy

#endif


-- | Get the value of the “@time@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventMotion #time
-- @
getEventMotionTime :: MonadIO m => EventMotion -> m Word32
getEventMotionTime :: forall (m :: * -> *). MonadIO m => EventMotion -> m Word32
getEventMotionTime EventMotion
s = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO Word32) -> IO Word32)
-> (Ptr EventMotion -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) :: IO Word32
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@time@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventMotion [ #time 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventMotionTime :: MonadIO m => EventMotion -> Word32 -> m ()
setEventMotionTime :: forall (m :: * -> *). MonadIO m => EventMotion -> Word32 -> m ()
setEventMotionTime EventMotion
s Word32
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO ()) -> IO ())
-> (Ptr EventMotion -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data EventMotionTimeFieldInfo
instance AttrInfo EventMotionTimeFieldInfo where
    type AttrBaseTypeConstraint EventMotionTimeFieldInfo = (~) EventMotion
    type AttrAllowedOps EventMotionTimeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventMotionTimeFieldInfo = (~) Word32
    type AttrTransferTypeConstraint EventMotionTimeFieldInfo = (~)Word32
    type AttrTransferType EventMotionTimeFieldInfo = Word32
    type AttrGetType EventMotionTimeFieldInfo = Word32
    type AttrLabel EventMotionTimeFieldInfo = "time"
    type AttrOrigin EventMotionTimeFieldInfo = EventMotion
    attrGet = getEventMotionTime
    attrSet = setEventMotionTime
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventMotion.time"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventMotion.html#g:attr:time"
        })

eventMotion_time :: AttrLabelProxy "time"
eventMotion_time = AttrLabelProxy

#endif


-- | Get the value of the “@x@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventMotion #x
-- @
getEventMotionX :: MonadIO m => EventMotion -> m Double
getEventMotionX :: forall (m :: * -> *). MonadIO m => EventMotion -> m Double
getEventMotionX EventMotion
s = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO Double) -> IO Double)
-> (Ptr EventMotion -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'

-- | Set the value of the “@x@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventMotion [ #x 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventMotionX :: MonadIO m => EventMotion -> Double -> m ()
setEventMotionX :: forall (m :: * -> *). MonadIO m => EventMotion -> Double -> m ()
setEventMotionX EventMotion
s Double
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO ()) -> IO ())
-> (Ptr EventMotion -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data EventMotionXFieldInfo
instance AttrInfo EventMotionXFieldInfo where
    type AttrBaseTypeConstraint EventMotionXFieldInfo = (~) EventMotion
    type AttrAllowedOps EventMotionXFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventMotionXFieldInfo = (~) Double
    type AttrTransferTypeConstraint EventMotionXFieldInfo = (~)Double
    type AttrTransferType EventMotionXFieldInfo = Double
    type AttrGetType EventMotionXFieldInfo = Double
    type AttrLabel EventMotionXFieldInfo = "x"
    type AttrOrigin EventMotionXFieldInfo = EventMotion
    attrGet = getEventMotionX
    attrSet = setEventMotionX
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventMotion.x"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventMotion.html#g:attr:x"
        })

eventMotion_x :: AttrLabelProxy "x"
eventMotion_x = AttrLabelProxy

#endif


-- | Get the value of the “@y@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventMotion #y
-- @
getEventMotionY :: MonadIO m => EventMotion -> m Double
getEventMotionY :: forall (m :: * -> *). MonadIO m => EventMotion -> m Double
getEventMotionY EventMotion
s = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO Double) -> IO Double)
-> (Ptr EventMotion -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'

-- | Set the value of the “@y@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventMotion [ #y 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventMotionY :: MonadIO m => EventMotion -> Double -> m ()
setEventMotionY :: forall (m :: * -> *). MonadIO m => EventMotion -> Double -> m ()
setEventMotionY EventMotion
s Double
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO ()) -> IO ())
-> (Ptr EventMotion -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data EventMotionYFieldInfo
instance AttrInfo EventMotionYFieldInfo where
    type AttrBaseTypeConstraint EventMotionYFieldInfo = (~) EventMotion
    type AttrAllowedOps EventMotionYFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventMotionYFieldInfo = (~) Double
    type AttrTransferTypeConstraint EventMotionYFieldInfo = (~)Double
    type AttrTransferType EventMotionYFieldInfo = Double
    type AttrGetType EventMotionYFieldInfo = Double
    type AttrLabel EventMotionYFieldInfo = "y"
    type AttrOrigin EventMotionYFieldInfo = EventMotion
    attrGet = getEventMotionY
    attrSet = setEventMotionY
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventMotion.y"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventMotion.html#g:attr:y"
        })

eventMotion_y :: AttrLabelProxy "y"
eventMotion_y = AttrLabelProxy

#endif


-- | Get the value of the “@axes@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventMotion #axes
-- @
getEventMotionAxes :: MonadIO m => EventMotion -> m Double
getEventMotionAxes :: forall (m :: * -> *). MonadIO m => EventMotion -> m Double
getEventMotionAxes EventMotion
s = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO Double) -> IO Double)
-> (Ptr EventMotion -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'

-- | Set the value of the “@axes@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventMotion [ #axes 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventMotionAxes :: MonadIO m => EventMotion -> Double -> m ()
setEventMotionAxes :: forall (m :: * -> *). MonadIO m => EventMotion -> Double -> m ()
setEventMotionAxes EventMotion
s Double
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO ()) -> IO ())
-> (Ptr EventMotion -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data EventMotionAxesFieldInfo
instance AttrInfo EventMotionAxesFieldInfo where
    type AttrBaseTypeConstraint EventMotionAxesFieldInfo = (~) EventMotion
    type AttrAllowedOps EventMotionAxesFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventMotionAxesFieldInfo = (~) Double
    type AttrTransferTypeConstraint EventMotionAxesFieldInfo = (~)Double
    type AttrTransferType EventMotionAxesFieldInfo = Double
    type AttrGetType EventMotionAxesFieldInfo = Double
    type AttrLabel EventMotionAxesFieldInfo = "axes"
    type AttrOrigin EventMotionAxesFieldInfo = EventMotion
    attrGet = getEventMotionAxes
    attrSet = setEventMotionAxes
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventMotion.axes"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventMotion.html#g:attr:axes"
        })

eventMotion_axes :: AttrLabelProxy "axes"
eventMotion_axes = AttrLabelProxy

#endif


-- | Get the value of the “@state@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventMotion #state
-- @
getEventMotionState :: MonadIO m => EventMotion -> m [Gdk.Flags.ModifierType]
getEventMotionState :: forall (m :: * -> *). MonadIO m => EventMotion -> m [ModifierType]
getEventMotionState EventMotion
s = IO [ModifierType] -> m [ModifierType]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [ModifierType] -> m [ModifierType])
-> IO [ModifierType] -> m [ModifierType]
forall a b. (a -> b) -> a -> b
$ EventMotion
-> (Ptr EventMotion -> IO [ModifierType]) -> IO [ModifierType]
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO [ModifierType]) -> IO [ModifierType])
-> (Ptr EventMotion -> IO [ModifierType]) -> IO [ModifierType]
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48) :: IO CUInt
    let val' :: [ModifierType]
val' = CUInt -> [ModifierType]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
val
    [ModifierType] -> IO [ModifierType]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [ModifierType]
val'

-- | Set the value of the “@state@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventMotion [ #state 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventMotionState :: MonadIO m => EventMotion -> [Gdk.Flags.ModifierType] -> m ()
setEventMotionState :: forall (m :: * -> *).
MonadIO m =>
EventMotion -> [ModifierType] -> m ()
setEventMotionState EventMotion
s [ModifierType]
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO ()) -> IO ())
-> (Ptr EventMotion -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    let val' :: CUInt
val' = [ModifierType] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ModifierType]
val
    Ptr CUInt -> CUInt -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48) (CUInt
val' :: CUInt)

#if defined(ENABLE_OVERLOADING)
data EventMotionStateFieldInfo
instance AttrInfo EventMotionStateFieldInfo where
    type AttrBaseTypeConstraint EventMotionStateFieldInfo = (~) EventMotion
    type AttrAllowedOps EventMotionStateFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventMotionStateFieldInfo = (~) [Gdk.Flags.ModifierType]
    type AttrTransferTypeConstraint EventMotionStateFieldInfo = (~)[Gdk.Flags.ModifierType]
    type AttrTransferType EventMotionStateFieldInfo = [Gdk.Flags.ModifierType]
    type AttrGetType EventMotionStateFieldInfo = [Gdk.Flags.ModifierType]
    type AttrLabel EventMotionStateFieldInfo = "state"
    type AttrOrigin EventMotionStateFieldInfo = EventMotion
    attrGet = getEventMotionState
    attrSet = setEventMotionState
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventMotion.state"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventMotion.html#g:attr:state"
        })

eventMotion_state :: AttrLabelProxy "state"
eventMotion_state = AttrLabelProxy

#endif


-- | Get the value of the “@is_hint@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventMotion #isHint
-- @
getEventMotionIsHint :: MonadIO m => EventMotion -> m Int16
getEventMotionIsHint :: forall (m :: * -> *). MonadIO m => EventMotion -> m Int16
getEventMotionIsHint EventMotion
s = IO Int16 -> m Int16
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int16 -> m Int16) -> IO Int16 -> m Int16
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO Int16) -> IO Int16
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO Int16) -> IO Int16)
-> (Ptr EventMotion -> IO Int16) -> IO Int16
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    Int16
val <- Ptr Int16 -> IO Int16
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr Int16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52) :: IO Int16
    Int16 -> IO Int16
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int16
val

-- | Set the value of the “@is_hint@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventMotion [ #isHint 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventMotionIsHint :: MonadIO m => EventMotion -> Int16 -> m ()
setEventMotionIsHint :: forall (m :: * -> *). MonadIO m => EventMotion -> Int16 -> m ()
setEventMotionIsHint EventMotion
s Int16
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO ()) -> IO ())
-> (Ptr EventMotion -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    Ptr Int16 -> Int16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr Int16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52) (Int16
val :: Int16)

#if defined(ENABLE_OVERLOADING)
data EventMotionIsHintFieldInfo
instance AttrInfo EventMotionIsHintFieldInfo where
    type AttrBaseTypeConstraint EventMotionIsHintFieldInfo = (~) EventMotion
    type AttrAllowedOps EventMotionIsHintFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventMotionIsHintFieldInfo = (~) Int16
    type AttrTransferTypeConstraint EventMotionIsHintFieldInfo = (~)Int16
    type AttrTransferType EventMotionIsHintFieldInfo = Int16
    type AttrGetType EventMotionIsHintFieldInfo = Int16
    type AttrLabel EventMotionIsHintFieldInfo = "is_hint"
    type AttrOrigin EventMotionIsHintFieldInfo = EventMotion
    attrGet = getEventMotionIsHint
    attrSet = setEventMotionIsHint
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventMotion.isHint"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventMotion.html#g:attr:isHint"
        })

eventMotion_isHint :: AttrLabelProxy "isHint"
eventMotion_isHint = AttrLabelProxy

#endif


-- | Get the value of the “@device@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventMotion #device
-- @
getEventMotionDevice :: MonadIO m => EventMotion -> m (Maybe Gdk.Device.Device)
getEventMotionDevice :: forall (m :: * -> *). MonadIO m => EventMotion -> m (Maybe Device)
getEventMotionDevice EventMotion
s = IO (Maybe Device) -> m (Maybe Device)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Device) -> m (Maybe Device))
-> IO (Maybe Device) -> m (Maybe Device)
forall a b. (a -> b) -> a -> b
$ EventMotion
-> (Ptr EventMotion -> IO (Maybe Device)) -> IO (Maybe Device)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO (Maybe Device)) -> IO (Maybe Device))
-> (Ptr EventMotion -> IO (Maybe Device)) -> IO (Maybe Device)
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    Ptr Device
val <- Ptr (Ptr Device) -> IO (Ptr Device)
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr (Ptr Device)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) :: IO (Ptr Gdk.Device.Device)
    Maybe Device
result <- Ptr Device -> (Ptr Device -> IO Device) -> IO (Maybe Device)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Device
val ((Ptr Device -> IO Device) -> IO (Maybe Device))
-> (Ptr Device -> IO Device) -> IO (Maybe Device)
forall a b. (a -> b) -> a -> b
$ \Ptr Device
val' -> do
        Device
val'' <- ((ManagedPtr Device -> Device) -> Ptr Device -> IO Device
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Device -> Device
Gdk.Device.Device) Ptr Device
val'
        Device -> IO Device
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Device
val''
    Maybe Device -> IO (Maybe Device)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Device
result

-- | Set the value of the “@device@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventMotion [ #device 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventMotionDevice :: MonadIO m => EventMotion -> Ptr Gdk.Device.Device -> m ()
setEventMotionDevice :: forall (m :: * -> *).
MonadIO m =>
EventMotion -> Ptr Device -> m ()
setEventMotionDevice EventMotion
s Ptr Device
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO ()) -> IO ())
-> (Ptr EventMotion -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    Ptr (Ptr Device) -> Ptr Device -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr (Ptr Device)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) (Ptr Device
val :: Ptr Gdk.Device.Device)

-- | Set the value of the “@device@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #device
-- @
clearEventMotionDevice :: MonadIO m => EventMotion -> m ()
clearEventMotionDevice :: forall (m :: * -> *). MonadIO m => EventMotion -> m ()
clearEventMotionDevice EventMotion
s = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO ()) -> IO ())
-> (Ptr EventMotion -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    Ptr (Ptr Device) -> Ptr Device -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr (Ptr Device)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56) (Ptr Device
forall a. Ptr a
FP.nullPtr :: Ptr Gdk.Device.Device)

#if defined(ENABLE_OVERLOADING)
data EventMotionDeviceFieldInfo
instance AttrInfo EventMotionDeviceFieldInfo where
    type AttrBaseTypeConstraint EventMotionDeviceFieldInfo = (~) EventMotion
    type AttrAllowedOps EventMotionDeviceFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventMotionDeviceFieldInfo = (~) (Ptr Gdk.Device.Device)
    type AttrTransferTypeConstraint EventMotionDeviceFieldInfo = (~)(Ptr Gdk.Device.Device)
    type AttrTransferType EventMotionDeviceFieldInfo = (Ptr Gdk.Device.Device)
    type AttrGetType EventMotionDeviceFieldInfo = Maybe Gdk.Device.Device
    type AttrLabel EventMotionDeviceFieldInfo = "device"
    type AttrOrigin EventMotionDeviceFieldInfo = EventMotion
    attrGet = getEventMotionDevice
    attrSet = setEventMotionDevice
    attrConstruct = undefined
    attrClear = clearEventMotionDevice
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventMotion.device"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventMotion.html#g:attr:device"
        })

eventMotion_device :: AttrLabelProxy "device"
eventMotion_device = AttrLabelProxy

#endif


-- | Get the value of the “@x_root@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventMotion #xRoot
-- @
getEventMotionXRoot :: MonadIO m => EventMotion -> m Double
getEventMotionXRoot :: forall (m :: * -> *). MonadIO m => EventMotion -> m Double
getEventMotionXRoot EventMotion
s = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO Double) -> IO Double)
-> (Ptr EventMotion -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'

-- | Set the value of the “@x_root@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventMotion [ #xRoot 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventMotionXRoot :: MonadIO m => EventMotion -> Double -> m ()
setEventMotionXRoot :: forall (m :: * -> *). MonadIO m => EventMotion -> Double -> m ()
setEventMotionXRoot EventMotion
s Double
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO ()) -> IO ())
-> (Ptr EventMotion -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data EventMotionXRootFieldInfo
instance AttrInfo EventMotionXRootFieldInfo where
    type AttrBaseTypeConstraint EventMotionXRootFieldInfo = (~) EventMotion
    type AttrAllowedOps EventMotionXRootFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventMotionXRootFieldInfo = (~) Double
    type AttrTransferTypeConstraint EventMotionXRootFieldInfo = (~)Double
    type AttrTransferType EventMotionXRootFieldInfo = Double
    type AttrGetType EventMotionXRootFieldInfo = Double
    type AttrLabel EventMotionXRootFieldInfo = "x_root"
    type AttrOrigin EventMotionXRootFieldInfo = EventMotion
    attrGet = getEventMotionXRoot
    attrSet = setEventMotionXRoot
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventMotion.xRoot"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventMotion.html#g:attr:xRoot"
        })

eventMotion_xRoot :: AttrLabelProxy "xRoot"
eventMotion_xRoot = AttrLabelProxy

#endif


-- | Get the value of the “@y_root@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' eventMotion #yRoot
-- @
getEventMotionYRoot :: MonadIO m => EventMotion -> m Double
getEventMotionYRoot :: forall (m :: * -> *). MonadIO m => EventMotion -> m Double
getEventMotionYRoot EventMotion
s = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO Double) -> IO Double)
-> (Ptr EventMotion -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'

-- | Set the value of the “@y_root@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' eventMotion [ #yRoot 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventMotionYRoot :: MonadIO m => EventMotion -> Double -> m ()
setEventMotionYRoot :: forall (m :: * -> *). MonadIO m => EventMotion -> Double -> m ()
setEventMotionYRoot EventMotion
s Double
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventMotion -> (Ptr EventMotion -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventMotion
s ((Ptr EventMotion -> IO ()) -> IO ())
-> (Ptr EventMotion -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr EventMotion
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventMotion
ptr Ptr EventMotion -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data EventMotionYRootFieldInfo
instance AttrInfo EventMotionYRootFieldInfo where
    type AttrBaseTypeConstraint EventMotionYRootFieldInfo = (~) EventMotion
    type AttrAllowedOps EventMotionYRootFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventMotionYRootFieldInfo = (~) Double
    type AttrTransferTypeConstraint EventMotionYRootFieldInfo = (~)Double
    type AttrTransferType EventMotionYRootFieldInfo = Double
    type AttrGetType EventMotionYRootFieldInfo = Double
    type AttrLabel EventMotionYRootFieldInfo = "y_root"
    type AttrOrigin EventMotionYRootFieldInfo = EventMotion
    attrGet = getEventMotionYRoot
    attrSet = setEventMotionYRoot
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Structs.EventMotion.yRoot"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventMotion.html#g:attr:yRoot"
        })

eventMotion_yRoot :: AttrLabelProxy "yRoot"
eventMotion_yRoot = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList EventMotion
type instance O.AttributeList EventMotion = EventMotionAttributeList
type EventMotionAttributeList = ('[ '("type", EventMotionTypeFieldInfo), '("window", EventMotionWindowFieldInfo), '("sendEvent", EventMotionSendEventFieldInfo), '("time", EventMotionTimeFieldInfo), '("x", EventMotionXFieldInfo), '("y", EventMotionYFieldInfo), '("axes", EventMotionAxesFieldInfo), '("state", EventMotionStateFieldInfo), '("isHint", EventMotionIsHintFieldInfo), '("device", EventMotionDeviceFieldInfo), '("xRoot", EventMotionXRootFieldInfo), '("yRoot", EventMotionYRootFieldInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveEventMotionMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveEventMotionMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveEventMotionMethod t EventMotion, O.OverloadedMethod info EventMotion p) => OL.IsLabel t (EventMotion -> 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 ~ ResolveEventMotionMethod t EventMotion, O.OverloadedMethod info EventMotion p, R.HasField t EventMotion p) => R.HasField t EventMotion p where
    getField = O.overloadedMethod @info

#endif

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

#endif