{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Structs.EventPadButton
(
EventPadButton(..) ,
newZeroEventPadButton ,
#if defined(ENABLE_OVERLOADING)
ResolveEventPadButtonMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
eventPadButton_button ,
#endif
getEventPadButtonButton ,
setEventPadButtonButton ,
#if defined(ENABLE_OVERLOADING)
eventPadButton_group ,
#endif
getEventPadButtonGroup ,
setEventPadButtonGroup ,
#if defined(ENABLE_OVERLOADING)
eventPadButton_mode ,
#endif
getEventPadButtonMode ,
setEventPadButtonMode ,
#if defined(ENABLE_OVERLOADING)
eventPadButton_sendEvent ,
#endif
getEventPadButtonSendEvent ,
setEventPadButtonSendEvent ,
#if defined(ENABLE_OVERLOADING)
eventPadButton_time ,
#endif
getEventPadButtonTime ,
setEventPadButtonTime ,
#if defined(ENABLE_OVERLOADING)
eventPadButton_type ,
#endif
getEventPadButtonType ,
setEventPadButtonType ,
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.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
#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.EventMotion as Gdk.EventMotion
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.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.Objects.Window as Gdk.Window
#endif
newtype EventPadButton = EventPadButton (SP.ManagedPtr EventPadButton)
deriving (EventPadButton -> EventPadButton -> Bool
(EventPadButton -> EventPadButton -> Bool)
-> (EventPadButton -> EventPadButton -> Bool) -> Eq EventPadButton
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EventPadButton -> EventPadButton -> Bool
== :: EventPadButton -> EventPadButton -> Bool
$c/= :: EventPadButton -> EventPadButton -> Bool
/= :: EventPadButton -> EventPadButton -> Bool
Eq)
instance SP.ManagedPtrNewtype EventPadButton where
toManagedPtr :: EventPadButton -> ManagedPtr EventPadButton
toManagedPtr (EventPadButton ManagedPtr EventPadButton
p) = ManagedPtr EventPadButton
p
instance BoxedPtr EventPadButton where
boxedPtrCopy :: EventPadButton -> IO EventPadButton
boxedPtrCopy = \EventPadButton
p -> EventPadButton
-> (Ptr EventPadButton -> IO EventPadButton) -> IO EventPadButton
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr EventPadButton
p (Int -> Ptr EventPadButton -> IO (Ptr EventPadButton)
forall a. (HasCallStack, CallocPtr a) => Int -> Ptr a -> IO (Ptr a)
copyBytes Int
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, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.wrapPtr ManagedPtr EventPadButton -> EventPadButton
EventPadButton)
boxedPtrFree :: EventPadButton -> IO ()
boxedPtrFree = \EventPadButton
x -> EventPadButton -> (Ptr EventPadButton -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
SP.withManagedPtr EventPadButton
x Ptr EventPadButton -> IO ()
forall a. Ptr a -> IO ()
SP.freeMem
instance CallocPtr EventPadButton where
boxedPtrCalloc :: IO (Ptr EventPadButton)
boxedPtrCalloc = Int -> IO (Ptr EventPadButton)
forall a. Int -> IO (Ptr a)
callocBytes Int
40
newZeroEventPadButton :: MonadIO m => m EventPadButton
newZeroEventPadButton :: forall (m :: * -> *). MonadIO m => m EventPadButton
newZeroEventPadButton = IO EventPadButton -> m EventPadButton
forall a. IO a -> m a
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. CallocPtr a => IO (Ptr a)
boxedPtrCalloc IO (Ptr EventPadButton)
-> (Ptr EventPadButton -> IO EventPadButton) -> IO EventPadButton
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr EventPadButton -> EventPadButton)
-> Ptr EventPadButton -> IO EventPadButton
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr EventPadButton -> EventPadButton
EventPadButton
instance tag ~ 'AttrSet => Constructible EventPadButton tag where
new :: forall (m :: * -> *).
MonadIO m =>
(ManagedPtr EventPadButton -> EventPadButton)
-> [AttrOp EventPadButton tag] -> m EventPadButton
new ManagedPtr EventPadButton -> EventPadButton
_ [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 a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return EventPadButton
o
getEventPadButtonType :: MonadIO m => EventPadButton -> m Gdk.Enums.EventType
getEventPadButtonType :: forall (m :: * -> *). MonadIO m => EventPadButton -> m EventType
getEventPadButtonType EventPadButton
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
$ 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 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` 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'
setEventPadButtonType :: MonadIO m => EventPadButton -> Gdk.Enums.EventType -> m ()
setEventPadButtonType :: forall (m :: * -> *).
MonadIO m =>
EventPadButton -> EventType -> m ()
setEventPadButtonType EventPadButton
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
$ 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 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` Int
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventPadButton.type"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventPadButton.html#g:attr:type"
})
eventPadButton_type :: AttrLabelProxy "type"
eventPadButton_type = AttrLabelProxy
#endif
getEventPadButtonWindow :: MonadIO m => EventPadButton -> m (Maybe Gdk.Window.Window)
getEventPadButtonWindow :: forall (m :: * -> *).
MonadIO m =>
EventPadButton -> m (Maybe Window)
getEventPadButtonWindow EventPadButton
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
$ 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 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` 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
setEventPadButtonWindow :: MonadIO m => EventPadButton -> Ptr Gdk.Window.Window -> m ()
setEventPadButtonWindow :: forall (m :: * -> *).
MonadIO m =>
EventPadButton -> Ptr Window -> m ()
setEventPadButtonWindow EventPadButton
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
$ 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 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` Int
8) (Ptr Window
val :: Ptr Gdk.Window.Window)
clearEventPadButtonWindow :: MonadIO m => EventPadButton -> m ()
clearEventPadButtonWindow :: forall (m :: * -> *). MonadIO m => EventPadButton -> m ()
clearEventPadButtonWindow EventPadButton
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
$ 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 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` Int
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventPadButton.window"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventPadButton.html#g:attr:window"
})
eventPadButton_window :: AttrLabelProxy "window"
eventPadButton_window = AttrLabelProxy
#endif
getEventPadButtonSendEvent :: MonadIO m => EventPadButton -> m Int8
getEventPadButtonSendEvent :: forall (m :: * -> *). MonadIO m => EventPadButton -> m Int8
getEventPadButtonSendEvent EventPadButton
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
$ 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 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` Int
16) :: IO Int8
Int8 -> IO Int8
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int8
val
setEventPadButtonSendEvent :: MonadIO m => EventPadButton -> Int8 -> m ()
setEventPadButtonSendEvent :: forall (m :: * -> *). MonadIO m => EventPadButton -> Int8 -> m ()
setEventPadButtonSendEvent EventPadButton
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
$ 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 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` Int
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventPadButton.sendEvent"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventPadButton.html#g:attr:sendEvent"
})
eventPadButton_sendEvent :: AttrLabelProxy "sendEvent"
eventPadButton_sendEvent = AttrLabelProxy
#endif
getEventPadButtonTime :: MonadIO m => EventPadButton -> m Word32
getEventPadButtonTime :: forall (m :: * -> *). MonadIO m => EventPadButton -> m Word32
getEventPadButtonTime EventPadButton
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
$ 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 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` Int
20) :: IO Word32
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setEventPadButtonTime :: MonadIO m => EventPadButton -> Word32 -> m ()
setEventPadButtonTime :: forall (m :: * -> *). MonadIO m => EventPadButton -> Word32 -> m ()
setEventPadButtonTime EventPadButton
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
$ 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 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` Int
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventPadButton.time"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventPadButton.html#g:attr:time"
})
eventPadButton_time :: AttrLabelProxy "time"
eventPadButton_time = AttrLabelProxy
#endif
getEventPadButtonGroup :: MonadIO m => EventPadButton -> m Word32
getEventPadButtonGroup :: forall (m :: * -> *). MonadIO m => EventPadButton -> m Word32
getEventPadButtonGroup EventPadButton
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
$ 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 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` Int
24) :: IO Word32
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setEventPadButtonGroup :: MonadIO m => EventPadButton -> Word32 -> m ()
setEventPadButtonGroup :: forall (m :: * -> *). MonadIO m => EventPadButton -> Word32 -> m ()
setEventPadButtonGroup EventPadButton
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
$ 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 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` Int
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventPadButton.group"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventPadButton.html#g:attr:group"
})
eventPadButton_group :: AttrLabelProxy "group"
eventPadButton_group = AttrLabelProxy
#endif
getEventPadButtonButton :: MonadIO m => EventPadButton -> m Word32
getEventPadButtonButton :: forall (m :: * -> *). MonadIO m => EventPadButton -> m Word32
getEventPadButtonButton EventPadButton
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
$ 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 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` Int
28) :: IO Word32
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setEventPadButtonButton :: MonadIO m => EventPadButton -> Word32 -> m ()
setEventPadButtonButton :: forall (m :: * -> *). MonadIO m => EventPadButton -> Word32 -> m ()
setEventPadButtonButton EventPadButton
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
$ 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 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` Int
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventPadButton.button"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventPadButton.html#g:attr:button"
})
eventPadButton_button :: AttrLabelProxy "button"
eventPadButton_button = AttrLabelProxy
#endif
getEventPadButtonMode :: MonadIO m => EventPadButton -> m Word32
getEventPadButtonMode :: forall (m :: * -> *). MonadIO m => EventPadButton -> m Word32
getEventPadButtonMode EventPadButton
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
$ 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 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` Int
32) :: IO Word32
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setEventPadButtonMode :: MonadIO m => EventPadButton -> Word32 -> m ()
setEventPadButtonMode :: forall (m :: * -> *). MonadIO m => EventPadButton -> Word32 -> m ()
setEventPadButtonMode EventPadButton
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
$ 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 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` Int
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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Structs.EventPadButton.mode"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Structs-EventPadButton.html#g:attr:mode"
})
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, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveEventPadButtonMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveEventPadButtonMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveEventPadButtonMethod t EventPadButton, O.OverloadedMethod 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
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveEventPadButtonMethod t EventPadButton, O.OverloadedMethod info EventPadButton p, R.HasField t EventPadButton p) => R.HasField t EventPadButton p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveEventPadButtonMethod t EventPadButton, O.OverloadedMethodInfo info EventPadButton) => OL.IsLabel t (O.MethodProxy info EventPadButton) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif