{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Used for button press and button release events. The
-- /@type@/ field will be one of 'GI.Gdk.Enums.EventTypeButtonPress',
-- 'GI.Gdk.Enums.EventType2buttonPress', 'GI.Gdk.Enums.EventType3buttonPress' or 'GI.Gdk.Enums.EventTypeButtonRelease',
-- 
-- Double and triple-clicks result in a sequence of events being received.
-- For double-clicks the order of events will be:
-- 
-- * 'GI.Gdk.Enums.EventTypeButtonPress'
-- * 'GI.Gdk.Enums.EventTypeButtonRelease'
-- * 'GI.Gdk.Enums.EventTypeButtonPress'
-- * 'GI.Gdk.Enums.EventType2buttonPress'
-- * 'GI.Gdk.Enums.EventTypeButtonRelease'
-- 
-- 
-- Note that the first click is received just like a normal
-- button press, while the second click results in a 'GI.Gdk.Enums.EventType2buttonPress'
-- being received just after the 'GI.Gdk.Enums.EventTypeButtonPress'.
-- 
-- Triple-clicks are very similar to double-clicks, except that
-- 'GI.Gdk.Enums.EventType3buttonPress' is inserted after the third click. The order of the
-- events is:
-- 
-- * 'GI.Gdk.Enums.EventTypeButtonPress'
-- * 'GI.Gdk.Enums.EventTypeButtonRelease'
-- * 'GI.Gdk.Enums.EventTypeButtonPress'
-- * 'GI.Gdk.Enums.EventType2buttonPress'
-- * 'GI.Gdk.Enums.EventTypeButtonRelease'
-- * 'GI.Gdk.Enums.EventTypeButtonPress'
-- * 'GI.Gdk.Enums.EventType3buttonPress'
-- * 'GI.Gdk.Enums.EventTypeButtonRelease'
-- 
-- 
-- For a double click to occur, the second button press must occur within
-- 1\/4 of a second of the first. For a triple click to occur, the third
-- button press must also occur within 1\/2 second of the first button press.

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

module GI.Gdk.Structs.EventButton
    ( 

-- * Exported types
    EventButton(..)                         ,
    newZeroEventButton                      ,
    noEventButton                           ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveEventButtonMethod                ,
#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)
    eventButton_axes                        ,
#endif
    getEventButtonAxes                      ,
    setEventButtonAxes                      ,


-- ** button #attr:button#
-- | the button which was pressed or released, numbered from 1 to 5.
--   Normally button 1 is the left mouse button, 2 is the middle button,
--   and 3 is the right button. On 2-button mice, the middle button can
--   often be simulated by pressing both mouse buttons together.

#if defined(ENABLE_OVERLOADING)
    eventButton_button                      ,
#endif
    getEventButtonButton                    ,
    setEventButtonButton                    ,


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

    clearEventButtonDevice                  ,
#if defined(ENABLE_OVERLOADING)
    eventButton_device                      ,
#endif
    getEventButtonDevice                    ,
    setEventButtonDevice                    ,


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

#if defined(ENABLE_OVERLOADING)
    eventButton_sendEvent                   ,
#endif
    getEventButtonSendEvent                 ,
    setEventButtonSendEvent                 ,


-- ** 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)
    eventButton_state                       ,
#endif
    getEventButtonState                     ,
    setEventButtonState                     ,


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

#if defined(ENABLE_OVERLOADING)
    eventButton_time                        ,
#endif
    getEventButtonTime                      ,
    setEventButtonTime                      ,


-- ** type #attr:type#
-- | the type of the event ('GI.Gdk.Enums.EventTypeButtonPress', 'GI.Gdk.Enums.EventType2buttonPress',
--   'GI.Gdk.Enums.EventType3buttonPress' or 'GI.Gdk.Enums.EventTypeButtonRelease').

#if defined(ENABLE_OVERLOADING)
    eventButton_type                        ,
#endif
    getEventButtonType                      ,
    setEventButtonType                      ,


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

    clearEventButtonWindow                  ,
#if defined(ENABLE_OVERLOADING)
    eventButton_window                      ,
#endif
    getEventButtonWindow                    ,
    setEventButtonWindow                    ,


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

#if defined(ENABLE_OVERLOADING)
    eventButton_x                           ,
#endif
    getEventButtonX                         ,
    setEventButtonX                         ,


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

#if defined(ENABLE_OVERLOADING)
    eventButton_xRoot                       ,
#endif
    getEventButtonXRoot                     ,
    setEventButtonXRoot                     ,


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

#if defined(ENABLE_OVERLOADING)
    eventButton_y                           ,
#endif
    getEventButtonY                         ,
    setEventButtonY                         ,


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

#if defined(ENABLE_OVERLOADING)
    eventButton_yRoot                       ,
#endif
    getEventButtonYRoot                     ,
    setEventButtonYRoot                     ,




    ) 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 {-# 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

-- | Memory-managed wrapper type.
newtype EventButton = EventButton (ManagedPtr EventButton)
    deriving (EventButton -> EventButton -> Bool
(EventButton -> EventButton -> Bool)
-> (EventButton -> EventButton -> Bool) -> Eq EventButton
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EventButton -> EventButton -> Bool
$c/= :: EventButton -> EventButton -> Bool
== :: EventButton -> EventButton -> Bool
$c== :: EventButton -> EventButton -> Bool
Eq)
instance WrappedPtr EventButton where
    wrappedPtrCalloc :: IO (Ptr EventButton)
wrappedPtrCalloc = Int -> IO (Ptr EventButton)
forall a. Int -> IO (Ptr a)
callocBytes 80
    wrappedPtrCopy :: EventButton -> IO EventButton
wrappedPtrCopy = \p :: EventButton
p -> EventButton
-> (Ptr EventButton -> IO EventButton) -> IO EventButton
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
p (Int -> Ptr EventButton -> IO (Ptr EventButton)
forall a. WrappedPtr a => Int -> Ptr a -> IO (Ptr a)
copyBytes 80 (Ptr EventButton -> IO (Ptr EventButton))
-> (Ptr EventButton -> IO EventButton)
-> Ptr EventButton
-> IO EventButton
forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> (ManagedPtr EventButton -> EventButton)
-> Ptr EventButton -> IO EventButton
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr EventButton -> EventButton
EventButton)
    wrappedPtrFree :: Maybe (GDestroyNotify EventButton)
wrappedPtrFree = GDestroyNotify EventButton -> Maybe (GDestroyNotify EventButton)
forall a. a -> Maybe a
Just GDestroyNotify EventButton
forall a. FunPtr (Ptr a -> IO ())
ptr_to_g_free

-- | Construct a `EventButton` struct initialized to zero.
newZeroEventButton :: MonadIO m => m EventButton
newZeroEventButton :: m EventButton
newZeroEventButton = IO EventButton -> m EventButton
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EventButton -> m EventButton)
-> IO EventButton -> m EventButton
forall a b. (a -> b) -> a -> b
$ IO (Ptr EventButton)
forall a. WrappedPtr a => IO (Ptr a)
wrappedPtrCalloc IO (Ptr EventButton)
-> (Ptr EventButton -> IO EventButton) -> IO EventButton
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr EventButton -> EventButton)
-> Ptr EventButton -> IO EventButton
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr EventButton -> EventButton
EventButton

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


-- | A convenience alias for `Nothing` :: `Maybe` `EventButton`.
noEventButton :: Maybe EventButton
noEventButton :: Maybe EventButton
noEventButton = Maybe EventButton
forall a. Maybe a
Nothing

-- | 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' eventButton #type
-- @
getEventButtonType :: MonadIO m => EventButton -> m Gdk.Enums.EventType
getEventButtonType :: EventButton -> m EventType
getEventButtonType s :: EventButton
s = IO EventType -> m EventType
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
$ EventButton -> (Ptr EventButton -> IO EventType) -> IO EventType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO EventType) -> IO EventType)
-> (Ptr EventButton -> IO EventType) -> IO EventType
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
ptr -> do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 (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' eventButton [ #type 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventButtonType :: MonadIO m => EventButton -> Gdk.Enums.EventType -> m ()
setEventButtonType :: EventButton -> EventType -> m ()
setEventButtonType s :: EventButton
s val :: EventType
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
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 EventButton
ptr Ptr EventButton -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (CInt
val' :: CInt)

#if defined(ENABLE_OVERLOADING)
data EventButtonTypeFieldInfo
instance AttrInfo EventButtonTypeFieldInfo where
    type AttrBaseTypeConstraint EventButtonTypeFieldInfo = (~) EventButton
    type AttrAllowedOps EventButtonTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventButtonTypeFieldInfo = (~) Gdk.Enums.EventType
    type AttrTransferTypeConstraint EventButtonTypeFieldInfo = (~)Gdk.Enums.EventType
    type AttrTransferType EventButtonTypeFieldInfo = Gdk.Enums.EventType
    type AttrGetType EventButtonTypeFieldInfo = Gdk.Enums.EventType
    type AttrLabel EventButtonTypeFieldInfo = "type"
    type AttrOrigin EventButtonTypeFieldInfo = EventButton
    attrGet = getEventButtonType
    attrSet = setEventButtonType
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventButton_type :: AttrLabelProxy "type"
eventButton_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' eventButton #window
-- @
getEventButtonWindow :: MonadIO m => EventButton -> m (Maybe Gdk.Window.Window)
getEventButtonWindow :: EventButton -> m (Maybe Window)
getEventButtonWindow s :: EventButton
s = IO (Maybe Window) -> m (Maybe Window)
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
$ EventButton
-> (Ptr EventButton -> IO (Maybe Window)) -> IO (Maybe Window)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO (Maybe Window)) -> IO (Maybe Window))
-> (Ptr EventButton -> IO (Maybe Window)) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
ptr -> do
    Ptr Window
val <- Ptr (Ptr Window) -> IO (Ptr Window)
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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
$ \val' :: 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 (m :: * -> *) a. Monad m => a -> m a
return Window
val''
    Maybe Window -> IO (Maybe Window)
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' eventButton [ #window 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventButtonWindow :: MonadIO m => EventButton -> Ptr Gdk.Window.Window -> m ()
setEventButtonWindow :: EventButton -> Ptr Window -> m ()
setEventButtonWindow s :: EventButton
s val :: Ptr Window
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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
-- @
clearEventButtonWindow :: MonadIO m => EventButton -> m ()
clearEventButtonWindow :: EventButton -> m ()
clearEventButtonWindow s :: EventButton
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr (Ptr Window)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Ptr Window
forall a. Ptr a
FP.nullPtr :: Ptr Gdk.Window.Window)

#if defined(ENABLE_OVERLOADING)
data EventButtonWindowFieldInfo
instance AttrInfo EventButtonWindowFieldInfo where
    type AttrBaseTypeConstraint EventButtonWindowFieldInfo = (~) EventButton
    type AttrAllowedOps EventButtonWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventButtonWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrTransferTypeConstraint EventButtonWindowFieldInfo = (~)(Ptr Gdk.Window.Window)
    type AttrTransferType EventButtonWindowFieldInfo = (Ptr Gdk.Window.Window)
    type AttrGetType EventButtonWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventButtonWindowFieldInfo = "window"
    type AttrOrigin EventButtonWindowFieldInfo = EventButton
    attrGet = getEventButtonWindow
    attrSet = setEventButtonWindow
    attrConstruct = undefined
    attrClear = clearEventButtonWindow
    attrTransfer _ v = do
        return v

eventButton_window :: AttrLabelProxy "window"
eventButton_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' eventButton #sendEvent
-- @
getEventButtonSendEvent :: MonadIO m => EventButton -> m Int8
getEventButtonSendEvent :: EventButton -> m Int8
getEventButtonSendEvent s :: EventButton
s = IO Int8 -> m Int8
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
$ EventButton -> (Ptr EventButton -> IO Int8) -> IO Int8
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO Int8) -> IO Int8)
-> (Ptr EventButton -> IO Int8) -> IO Int8
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
ptr -> do
    Int8
val <- Ptr Int8 -> IO Int8
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr Int8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) :: IO Int8
    Int8 -> IO Int8
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' eventButton [ #sendEvent 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventButtonSendEvent :: MonadIO m => EventButton -> Int8 -> m ()
setEventButtonSendEvent :: EventButton -> Int8 -> m ()
setEventButtonSendEvent s :: EventButton
s val :: Int8
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
ptr -> do
    Ptr Int8 -> Int8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr Int8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (Int8
val :: Int8)

#if defined(ENABLE_OVERLOADING)
data EventButtonSendEventFieldInfo
instance AttrInfo EventButtonSendEventFieldInfo where
    type AttrBaseTypeConstraint EventButtonSendEventFieldInfo = (~) EventButton
    type AttrAllowedOps EventButtonSendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventButtonSendEventFieldInfo = (~) Int8
    type AttrTransferTypeConstraint EventButtonSendEventFieldInfo = (~)Int8
    type AttrTransferType EventButtonSendEventFieldInfo = Int8
    type AttrGetType EventButtonSendEventFieldInfo = Int8
    type AttrLabel EventButtonSendEventFieldInfo = "send_event"
    type AttrOrigin EventButtonSendEventFieldInfo = EventButton
    attrGet = getEventButtonSendEvent
    attrSet = setEventButtonSendEvent
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventButton_sendEvent :: AttrLabelProxy "sendEvent"
eventButton_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' eventButton #time
-- @
getEventButtonTime :: MonadIO m => EventButton -> m Word32
getEventButtonTime :: EventButton -> m Word32
getEventButtonTime s :: EventButton
s = IO Word32 -> m Word32
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
$ EventButton -> (Ptr EventButton -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO Word32) -> IO Word32)
-> (Ptr EventButton -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20) :: IO Word32
    Word32 -> IO Word32
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' eventButton [ #time 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventButtonTime :: MonadIO m => EventButton -> Word32 -> m ()
setEventButtonTime :: EventButton -> Word32 -> m ()
setEventButtonTime s :: EventButton
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20) (Word32
val :: Word32)

#if defined(ENABLE_OVERLOADING)
data EventButtonTimeFieldInfo
instance AttrInfo EventButtonTimeFieldInfo where
    type AttrBaseTypeConstraint EventButtonTimeFieldInfo = (~) EventButton
    type AttrAllowedOps EventButtonTimeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventButtonTimeFieldInfo = (~) Word32
    type AttrTransferTypeConstraint EventButtonTimeFieldInfo = (~)Word32
    type AttrTransferType EventButtonTimeFieldInfo = Word32
    type AttrGetType EventButtonTimeFieldInfo = Word32
    type AttrLabel EventButtonTimeFieldInfo = "time"
    type AttrOrigin EventButtonTimeFieldInfo = EventButton
    attrGet = getEventButtonTime
    attrSet = setEventButtonTime
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventButton_time :: AttrLabelProxy "time"
eventButton_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' eventButton #x
-- @
getEventButtonX :: MonadIO m => EventButton -> m Double
getEventButtonX :: EventButton -> m Double
getEventButtonX s :: EventButton
s = IO Double -> m Double
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
$ EventButton -> (Ptr EventButton -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO Double) -> IO Double)
-> (Ptr EventButton -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 (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' eventButton [ #x 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventButtonX :: MonadIO m => EventButton -> Double -> m ()
setEventButtonX :: EventButton -> Double -> m ()
setEventButtonX s :: EventButton
s val :: Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
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 EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data EventButtonXFieldInfo
instance AttrInfo EventButtonXFieldInfo where
    type AttrBaseTypeConstraint EventButtonXFieldInfo = (~) EventButton
    type AttrAllowedOps EventButtonXFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventButtonXFieldInfo = (~) Double
    type AttrTransferTypeConstraint EventButtonXFieldInfo = (~)Double
    type AttrTransferType EventButtonXFieldInfo = Double
    type AttrGetType EventButtonXFieldInfo = Double
    type AttrLabel EventButtonXFieldInfo = "x"
    type AttrOrigin EventButtonXFieldInfo = EventButton
    attrGet = getEventButtonX
    attrSet = setEventButtonX
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventButton_x :: AttrLabelProxy "x"
eventButton_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' eventButton #y
-- @
getEventButtonY :: MonadIO m => EventButton -> m Double
getEventButtonY :: EventButton -> m Double
getEventButtonY s :: EventButton
s = IO Double -> m Double
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
$ EventButton -> (Ptr EventButton -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO Double) -> IO Double)
-> (Ptr EventButton -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 (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' eventButton [ #y 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventButtonY :: MonadIO m => EventButton -> Double -> m ()
setEventButtonY :: EventButton -> Double -> m ()
setEventButtonY s :: EventButton
s val :: Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
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 EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data EventButtonYFieldInfo
instance AttrInfo EventButtonYFieldInfo where
    type AttrBaseTypeConstraint EventButtonYFieldInfo = (~) EventButton
    type AttrAllowedOps EventButtonYFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventButtonYFieldInfo = (~) Double
    type AttrTransferTypeConstraint EventButtonYFieldInfo = (~)Double
    type AttrTransferType EventButtonYFieldInfo = Double
    type AttrGetType EventButtonYFieldInfo = Double
    type AttrLabel EventButtonYFieldInfo = "y"
    type AttrOrigin EventButtonYFieldInfo = EventButton
    attrGet = getEventButtonY
    attrSet = setEventButtonY
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventButton_y :: AttrLabelProxy "y"
eventButton_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' eventButton #axes
-- @
getEventButtonAxes :: MonadIO m => EventButton -> m Double
getEventButtonAxes :: EventButton -> m Double
getEventButtonAxes s :: EventButton
s = IO Double -> m Double
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
$ EventButton -> (Ptr EventButton -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO Double) -> IO Double)
-> (Ptr EventButton -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 (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' eventButton [ #axes 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventButtonAxes :: MonadIO m => EventButton -> Double -> m ()
setEventButtonAxes :: EventButton -> Double -> m ()
setEventButtonAxes s :: EventButton
s val :: Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
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 EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data EventButtonAxesFieldInfo
instance AttrInfo EventButtonAxesFieldInfo where
    type AttrBaseTypeConstraint EventButtonAxesFieldInfo = (~) EventButton
    type AttrAllowedOps EventButtonAxesFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventButtonAxesFieldInfo = (~) Double
    type AttrTransferTypeConstraint EventButtonAxesFieldInfo = (~)Double
    type AttrTransferType EventButtonAxesFieldInfo = Double
    type AttrGetType EventButtonAxesFieldInfo = Double
    type AttrLabel EventButtonAxesFieldInfo = "axes"
    type AttrOrigin EventButtonAxesFieldInfo = EventButton
    attrGet = getEventButtonAxes
    attrSet = setEventButtonAxes
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventButton_axes :: AttrLabelProxy "axes"
eventButton_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' eventButton #state
-- @
getEventButtonState :: MonadIO m => EventButton -> m [Gdk.Flags.ModifierType]
getEventButtonState :: EventButton -> m [ModifierType]
getEventButtonState s :: EventButton
s = IO [ModifierType] -> m [ModifierType]
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
$ EventButton
-> (Ptr EventButton -> IO [ModifierType]) -> IO [ModifierType]
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO [ModifierType]) -> IO [ModifierType])
-> (Ptr EventButton -> IO [ModifierType]) -> IO [ModifierType]
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
ptr -> do
    CUInt
val <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 (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' eventButton [ #state 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventButtonState :: MonadIO m => EventButton -> [Gdk.Flags.ModifierType] -> m ()
setEventButtonState :: EventButton -> [ModifierType] -> m ()
setEventButtonState s :: EventButton
s val :: [ModifierType]
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
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 EventButton
ptr Ptr EventButton -> Int -> Ptr CUInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48) (CUInt
val' :: CUInt)

#if defined(ENABLE_OVERLOADING)
data EventButtonStateFieldInfo
instance AttrInfo EventButtonStateFieldInfo where
    type AttrBaseTypeConstraint EventButtonStateFieldInfo = (~) EventButton
    type AttrAllowedOps EventButtonStateFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventButtonStateFieldInfo = (~) [Gdk.Flags.ModifierType]
    type AttrTransferTypeConstraint EventButtonStateFieldInfo = (~)[Gdk.Flags.ModifierType]
    type AttrTransferType EventButtonStateFieldInfo = [Gdk.Flags.ModifierType]
    type AttrGetType EventButtonStateFieldInfo = [Gdk.Flags.ModifierType]
    type AttrLabel EventButtonStateFieldInfo = "state"
    type AttrOrigin EventButtonStateFieldInfo = EventButton
    attrGet = getEventButtonState
    attrSet = setEventButtonState
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventButton_state :: AttrLabelProxy "state"
eventButton_state = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data EventButtonButtonFieldInfo
instance AttrInfo EventButtonButtonFieldInfo where
    type AttrBaseTypeConstraint EventButtonButtonFieldInfo = (~) EventButton
    type AttrAllowedOps EventButtonButtonFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventButtonButtonFieldInfo = (~) Word32
    type AttrTransferTypeConstraint EventButtonButtonFieldInfo = (~)Word32
    type AttrTransferType EventButtonButtonFieldInfo = Word32
    type AttrGetType EventButtonButtonFieldInfo = Word32
    type AttrLabel EventButtonButtonFieldInfo = "button"
    type AttrOrigin EventButtonButtonFieldInfo = EventButton
    attrGet = getEventButtonButton
    attrSet = setEventButtonButton
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventButton_button :: AttrLabelProxy "button"
eventButton_button = 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' eventButton #device
-- @
getEventButtonDevice :: MonadIO m => EventButton -> m (Maybe Gdk.Device.Device)
getEventButtonDevice :: EventButton -> m (Maybe Device)
getEventButtonDevice s :: EventButton
s = IO (Maybe Device) -> m (Maybe Device)
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
$ EventButton
-> (Ptr EventButton -> IO (Maybe Device)) -> IO (Maybe Device)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO (Maybe Device)) -> IO (Maybe Device))
-> (Ptr EventButton -> IO (Maybe Device)) -> IO (Maybe Device)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
ptr -> do
    Ptr Device
val <- Ptr (Ptr Device) -> IO (Ptr Device)
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr (Ptr Device)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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
$ \val' :: 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 (m :: * -> *) a. Monad m => a -> m a
return Device
val''
    Maybe Device -> IO (Maybe Device)
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' eventButton [ #device 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventButtonDevice :: MonadIO m => EventButton -> Ptr Gdk.Device.Device -> m ()
setEventButtonDevice :: EventButton -> Ptr Device -> m ()
setEventButtonDevice s :: EventButton
s val :: Ptr Device
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
ptr -> do
    Ptr (Ptr Device) -> Ptr Device -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr (Ptr Device)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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
-- @
clearEventButtonDevice :: MonadIO m => EventButton -> m ()
clearEventButtonDevice :: EventButton -> m ()
clearEventButtonDevice s :: EventButton
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
ptr -> do
    Ptr (Ptr Device) -> Ptr Device -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr (Ptr Device)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56) (Ptr Device
forall a. Ptr a
FP.nullPtr :: Ptr Gdk.Device.Device)

#if defined(ENABLE_OVERLOADING)
data EventButtonDeviceFieldInfo
instance AttrInfo EventButtonDeviceFieldInfo where
    type AttrBaseTypeConstraint EventButtonDeviceFieldInfo = (~) EventButton
    type AttrAllowedOps EventButtonDeviceFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventButtonDeviceFieldInfo = (~) (Ptr Gdk.Device.Device)
    type AttrTransferTypeConstraint EventButtonDeviceFieldInfo = (~)(Ptr Gdk.Device.Device)
    type AttrTransferType EventButtonDeviceFieldInfo = (Ptr Gdk.Device.Device)
    type AttrGetType EventButtonDeviceFieldInfo = Maybe Gdk.Device.Device
    type AttrLabel EventButtonDeviceFieldInfo = "device"
    type AttrOrigin EventButtonDeviceFieldInfo = EventButton
    attrGet = getEventButtonDevice
    attrSet = setEventButtonDevice
    attrConstruct = undefined
    attrClear = clearEventButtonDevice
    attrTransfer _ v = do
        return v

eventButton_device :: AttrLabelProxy "device"
eventButton_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' eventButton #xRoot
-- @
getEventButtonXRoot :: MonadIO m => EventButton -> m Double
getEventButtonXRoot :: EventButton -> m Double
getEventButtonXRoot s :: EventButton
s = IO Double -> m Double
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
$ EventButton -> (Ptr EventButton -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO Double) -> IO Double)
-> (Ptr EventButton -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 (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' eventButton [ #xRoot 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventButtonXRoot :: MonadIO m => EventButton -> Double -> m ()
setEventButtonXRoot :: EventButton -> Double -> m ()
setEventButtonXRoot s :: EventButton
s val :: Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
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 EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data EventButtonXRootFieldInfo
instance AttrInfo EventButtonXRootFieldInfo where
    type AttrBaseTypeConstraint EventButtonXRootFieldInfo = (~) EventButton
    type AttrAllowedOps EventButtonXRootFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventButtonXRootFieldInfo = (~) Double
    type AttrTransferTypeConstraint EventButtonXRootFieldInfo = (~)Double
    type AttrTransferType EventButtonXRootFieldInfo = Double
    type AttrGetType EventButtonXRootFieldInfo = Double
    type AttrLabel EventButtonXRootFieldInfo = "x_root"
    type AttrOrigin EventButtonXRootFieldInfo = EventButton
    attrGet = getEventButtonXRoot
    attrSet = setEventButtonXRoot
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventButton_xRoot :: AttrLabelProxy "xRoot"
eventButton_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' eventButton #yRoot
-- @
getEventButtonYRoot :: MonadIO m => EventButton -> m Double
getEventButtonYRoot :: EventButton -> m Double
getEventButtonYRoot s :: EventButton
s = IO Double -> m Double
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
$ EventButton -> (Ptr EventButton -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO Double) -> IO Double)
-> (Ptr EventButton -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 (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' eventButton [ #yRoot 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventButtonYRoot :: MonadIO m => EventButton -> Double -> m ()
setEventButtonYRoot :: EventButton -> Double -> m ()
setEventButtonYRoot s :: EventButton
s val :: Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventButton -> (Ptr EventButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventButton
s ((Ptr EventButton -> IO ()) -> IO ())
-> (Ptr EventButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventButton
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 EventButton
ptr Ptr EventButton -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72) (CDouble
val' :: CDouble)

#if defined(ENABLE_OVERLOADING)
data EventButtonYRootFieldInfo
instance AttrInfo EventButtonYRootFieldInfo where
    type AttrBaseTypeConstraint EventButtonYRootFieldInfo = (~) EventButton
    type AttrAllowedOps EventButtonYRootFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventButtonYRootFieldInfo = (~) Double
    type AttrTransferTypeConstraint EventButtonYRootFieldInfo = (~)Double
    type AttrTransferType EventButtonYRootFieldInfo = Double
    type AttrGetType EventButtonYRootFieldInfo = Double
    type AttrLabel EventButtonYRootFieldInfo = "y_root"
    type AttrOrigin EventButtonYRootFieldInfo = EventButton
    attrGet = getEventButtonYRoot
    attrSet = setEventButtonYRoot
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventButton_yRoot :: AttrLabelProxy "yRoot"
eventButton_yRoot = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList EventButton
type instance O.AttributeList EventButton = EventButtonAttributeList
type EventButtonAttributeList = ('[ '("type", EventButtonTypeFieldInfo), '("window", EventButtonWindowFieldInfo), '("sendEvent", EventButtonSendEventFieldInfo), '("time", EventButtonTimeFieldInfo), '("x", EventButtonXFieldInfo), '("y", EventButtonYFieldInfo), '("axes", EventButtonAxesFieldInfo), '("state", EventButtonStateFieldInfo), '("button", EventButtonButtonFieldInfo), '("device", EventButtonDeviceFieldInfo), '("xRoot", EventButtonXRootFieldInfo), '("yRoot", EventButtonYRootFieldInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveEventButtonMethod (t :: Symbol) (o :: *) :: * where
    ResolveEventButtonMethod l o = O.MethodResolutionFailed l o

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

#endif