{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Generated during 'GI.Gdk.Enums.InputSourceTabletPad' button presses and releases.
-- 
-- /Since: 3.22/

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

module GI.Gdk.Structs.EventPadButton
    ( 

-- * Exported types
    EventPadButton(..)                      ,
    newZeroEventPadButton                   ,
    noEventPadButton                        ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveEventPadButtonMethod             ,
#endif




 -- * Properties
-- ** button #attr:button#
-- | The pad button that was pressed.

#if defined(ENABLE_OVERLOADING)
    eventPadButton_button                   ,
#endif
    getEventPadButtonButton                 ,
    setEventPadButtonButton                 ,


-- ** group #attr:group#
-- | the pad group the button belongs to. A 'GI.Gdk.Enums.InputSourceTabletPad' device
--   may have one or more groups containing a set of buttons\/rings\/strips each.

#if defined(ENABLE_OVERLOADING)
    eventPadButton_group                    ,
#endif
    getEventPadButtonGroup                  ,
    setEventPadButtonGroup                  ,


-- ** mode #attr:mode#
-- | The current mode of /@group@/. Different groups in a 'GI.Gdk.Enums.InputSourceTabletPad'
--   device may have different current modes.

#if defined(ENABLE_OVERLOADING)
    eventPadButton_mode                     ,
#endif
    getEventPadButtonMode                   ,
    setEventPadButtonMode                   ,


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

#if defined(ENABLE_OVERLOADING)
    eventPadButton_sendEvent                ,
#endif
    getEventPadButtonSendEvent              ,
    setEventPadButtonSendEvent              ,


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

#if defined(ENABLE_OVERLOADING)
    eventPadButton_time                     ,
#endif
    getEventPadButtonTime                   ,
    setEventPadButtonTime                   ,


-- ** type #attr:type#
-- | the type of the event ('GI.Gdk.Enums.EventTypePadButtonPress' or 'GI.Gdk.Enums.EventTypePadButtonRelease').

#if defined(ENABLE_OVERLOADING)
    eventPadButton_type                     ,
#endif
    getEventPadButtonType                   ,
    setEventPadButtonType                   ,


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

    clearEventPadButtonWindow               ,
#if defined(ENABLE_OVERLOADING)
    eventPadButton_window                   ,
#endif
    getEventPadButtonWindow                 ,
    setEventPadButtonWindow                 ,




    ) 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.Objects.Window as Gdk.Window

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

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

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


-- | A convenience alias for `Nothing` :: `Maybe` `EventPadButton`.
noEventPadButton :: Maybe EventPadButton
noEventPadButton :: Maybe EventPadButton
noEventPadButton = Maybe EventPadButton
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' eventPadButton #type
-- @
getEventPadButtonType :: MonadIO m => EventPadButton -> m Gdk.Enums.EventType
getEventPadButtonType :: EventPadButton -> m EventType
getEventPadButtonType s :: EventPadButton
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
$ EventPadButton
-> (Ptr EventPadButton -> IO EventType) -> IO EventType
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventPadButton
s ((Ptr EventPadButton -> IO EventType) -> IO EventType)
-> (Ptr EventPadButton -> IO EventType) -> IO EventType
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventPadButton
ptr -> do
    CInt
val <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventPadButton
ptr Ptr EventPadButton -> 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' eventPadButton [ #type 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventPadButtonType :: MonadIO m => EventPadButton -> Gdk.Enums.EventType -> m ()
setEventPadButtonType :: EventPadButton -> EventType -> m ()
setEventPadButtonType s :: EventPadButton
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
$ EventPadButton -> (Ptr EventPadButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventPadButton
s ((Ptr EventPadButton -> IO ()) -> IO ())
-> (Ptr EventPadButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventPadButton
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 EventPadButton
ptr Ptr EventPadButton -> Int -> Ptr CInt
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (CInt
val' :: CInt)

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

eventPadButton_type :: AttrLabelProxy "type"
eventPadButton_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' eventPadButton #window
-- @
getEventPadButtonWindow :: MonadIO m => EventPadButton -> m (Maybe Gdk.Window.Window)
getEventPadButtonWindow :: EventPadButton -> m (Maybe Window)
getEventPadButtonWindow s :: EventPadButton
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
$ EventPadButton
-> (Ptr EventPadButton -> IO (Maybe Window)) -> IO (Maybe Window)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventPadButton
s ((Ptr EventPadButton -> IO (Maybe Window)) -> IO (Maybe Window))
-> (Ptr EventPadButton -> IO (Maybe Window)) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventPadButton
ptr -> do
    Ptr Window
val <- Ptr (Ptr Window) -> IO (Ptr Window)
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventPadButton
ptr Ptr EventPadButton -> 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' eventPadButton [ #window 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventPadButtonWindow :: MonadIO m => EventPadButton -> Ptr Gdk.Window.Window -> m ()
setEventPadButtonWindow :: EventPadButton -> Ptr Window -> m ()
setEventPadButtonWindow s :: EventPadButton
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
$ EventPadButton -> (Ptr EventPadButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventPadButton
s ((Ptr EventPadButton -> IO ()) -> IO ())
-> (Ptr EventPadButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventPadButton
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventPadButton
ptr Ptr EventPadButton -> 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
-- @
clearEventPadButtonWindow :: MonadIO m => EventPadButton -> m ()
clearEventPadButtonWindow :: EventPadButton -> m ()
clearEventPadButtonWindow s :: EventPadButton
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ EventPadButton -> (Ptr EventPadButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventPadButton
s ((Ptr EventPadButton -> IO ()) -> IO ())
-> (Ptr EventPadButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventPadButton
ptr -> do
    Ptr (Ptr Window) -> Ptr Window -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventPadButton
ptr Ptr EventPadButton -> 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 EventPadButtonWindowFieldInfo
instance AttrInfo EventPadButtonWindowFieldInfo where
    type AttrBaseTypeConstraint EventPadButtonWindowFieldInfo = (~) EventPadButton
    type AttrAllowedOps EventPadButtonWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint EventPadButtonWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
    type AttrTransferTypeConstraint EventPadButtonWindowFieldInfo = (~)(Ptr Gdk.Window.Window)
    type AttrTransferType EventPadButtonWindowFieldInfo = (Ptr Gdk.Window.Window)
    type AttrGetType EventPadButtonWindowFieldInfo = Maybe Gdk.Window.Window
    type AttrLabel EventPadButtonWindowFieldInfo = "window"
    type AttrOrigin EventPadButtonWindowFieldInfo = EventPadButton
    attrGet = getEventPadButtonWindow
    attrSet = setEventPadButtonWindow
    attrConstruct = undefined
    attrClear = clearEventPadButtonWindow
    attrTransfer _ v = do
        return v

eventPadButton_window :: AttrLabelProxy "window"
eventPadButton_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' eventPadButton #sendEvent
-- @
getEventPadButtonSendEvent :: MonadIO m => EventPadButton -> m Int8
getEventPadButtonSendEvent :: EventPadButton -> m Int8
getEventPadButtonSendEvent s :: EventPadButton
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
$ EventPadButton -> (Ptr EventPadButton -> IO Int8) -> IO Int8
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventPadButton
s ((Ptr EventPadButton -> IO Int8) -> IO Int8)
-> (Ptr EventPadButton -> IO Int8) -> IO Int8
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventPadButton
ptr -> do
    Int8
val <- Ptr Int8 -> IO Int8
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventPadButton
ptr Ptr EventPadButton -> 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' eventPadButton [ #sendEvent 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventPadButtonSendEvent :: MonadIO m => EventPadButton -> Int8 -> m ()
setEventPadButtonSendEvent :: EventPadButton -> Int8 -> m ()
setEventPadButtonSendEvent s :: EventPadButton
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
$ EventPadButton -> (Ptr EventPadButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventPadButton
s ((Ptr EventPadButton -> IO ()) -> IO ())
-> (Ptr EventPadButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventPadButton
ptr -> do
    Ptr Int8 -> Int8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventPadButton
ptr Ptr EventPadButton -> Int -> Ptr Int8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (Int8
val :: Int8)

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

eventPadButton_sendEvent :: AttrLabelProxy "sendEvent"
eventPadButton_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' eventPadButton #time
-- @
getEventPadButtonTime :: MonadIO m => EventPadButton -> m Word32
getEventPadButtonTime :: EventPadButton -> m Word32
getEventPadButtonTime s :: EventPadButton
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
$ EventPadButton -> (Ptr EventPadButton -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventPadButton
s ((Ptr EventPadButton -> IO Word32) -> IO Word32)
-> (Ptr EventPadButton -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventPadButton
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventPadButton
ptr Ptr EventPadButton -> 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' eventPadButton [ #time 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventPadButtonTime :: MonadIO m => EventPadButton -> Word32 -> m ()
setEventPadButtonTime :: EventPadButton -> Word32 -> m ()
setEventPadButtonTime s :: EventPadButton
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
$ EventPadButton -> (Ptr EventPadButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventPadButton
s ((Ptr EventPadButton -> IO ()) -> IO ())
-> (Ptr EventPadButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventPadButton
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventPadButton
ptr Ptr EventPadButton -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20) (Word32
val :: Word32)

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

eventPadButton_time :: AttrLabelProxy "time"
eventPadButton_time = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data EventPadButtonGroupFieldInfo
instance AttrInfo EventPadButtonGroupFieldInfo where
    type AttrBaseTypeConstraint EventPadButtonGroupFieldInfo = (~) EventPadButton
    type AttrAllowedOps EventPadButtonGroupFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventPadButtonGroupFieldInfo = (~) Word32
    type AttrTransferTypeConstraint EventPadButtonGroupFieldInfo = (~)Word32
    type AttrTransferType EventPadButtonGroupFieldInfo = Word32
    type AttrGetType EventPadButtonGroupFieldInfo = Word32
    type AttrLabel EventPadButtonGroupFieldInfo = "group"
    type AttrOrigin EventPadButtonGroupFieldInfo = EventPadButton
    attrGet = getEventPadButtonGroup
    attrSet = setEventPadButtonGroup
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventPadButton_group :: AttrLabelProxy "group"
eventPadButton_group = 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' eventPadButton #button
-- @
getEventPadButtonButton :: MonadIO m => EventPadButton -> m Word32
getEventPadButtonButton :: EventPadButton -> m Word32
getEventPadButtonButton s :: EventPadButton
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
$ EventPadButton -> (Ptr EventPadButton -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventPadButton
s ((Ptr EventPadButton -> IO Word32) -> IO Word32)
-> (Ptr EventPadButton -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventPadButton
ptr -> do
    Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr EventPadButton
ptr Ptr EventPadButton -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28) :: 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' eventPadButton [ #button 'Data.GI.Base.Attributes.:=' value ]
-- @
setEventPadButtonButton :: MonadIO m => EventPadButton -> Word32 -> m ()
setEventPadButtonButton :: EventPadButton -> Word32 -> m ()
setEventPadButtonButton s :: EventPadButton
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
$ EventPadButton -> (Ptr EventPadButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr EventPadButton
s ((Ptr EventPadButton -> IO ()) -> IO ())
-> (Ptr EventPadButton -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr EventPadButton
ptr -> do
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr EventPadButton
ptr Ptr EventPadButton -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28) (Word32
val :: Word32)

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

eventPadButton_button :: AttrLabelProxy "button"
eventPadButton_button = AttrLabelProxy

#endif


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

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

#if defined(ENABLE_OVERLOADING)
data EventPadButtonModeFieldInfo
instance AttrInfo EventPadButtonModeFieldInfo where
    type AttrBaseTypeConstraint EventPadButtonModeFieldInfo = (~) EventPadButton
    type AttrAllowedOps EventPadButtonModeFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint EventPadButtonModeFieldInfo = (~) Word32
    type AttrTransferTypeConstraint EventPadButtonModeFieldInfo = (~)Word32
    type AttrTransferType EventPadButtonModeFieldInfo = Word32
    type AttrGetType EventPadButtonModeFieldInfo = Word32
    type AttrLabel EventPadButtonModeFieldInfo = "mode"
    type AttrOrigin EventPadButtonModeFieldInfo = EventPadButton
    attrGet = getEventPadButtonMode
    attrSet = setEventPadButtonMode
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

eventPadButton_mode :: AttrLabelProxy "mode"
eventPadButton_mode = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList EventPadButton
type instance O.AttributeList EventPadButton = EventPadButtonAttributeList
type EventPadButtonAttributeList = ('[ '("type", EventPadButtonTypeFieldInfo), '("window", EventPadButtonWindowFieldInfo), '("sendEvent", EventPadButtonSendEventFieldInfo), '("time", EventPadButtonTimeFieldInfo), '("group", EventPadButtonGroupFieldInfo), '("button", EventPadButtonButtonFieldInfo), '("mode", EventPadButtonModeFieldInfo)] :: [(Symbol, *)])
#endif

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

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

#endif