#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
&& !defined(__HADDOCK_VERSION__))
module GI.Gdk.Structs.EventPadButton
(
EventPadButton(..) ,
newZeroEventPadButton ,
noEventPadButton ,
#if ENABLE_OVERLOADING
eventPadButton_button ,
#endif
getEventPadButtonButton ,
setEventPadButtonButton ,
#if ENABLE_OVERLOADING
eventPadButton_group ,
#endif
getEventPadButtonGroup ,
setEventPadButtonGroup ,
#if ENABLE_OVERLOADING
eventPadButton_mode ,
#endif
getEventPadButtonMode ,
setEventPadButtonMode ,
#if ENABLE_OVERLOADING
eventPadButton_sendEvent ,
#endif
getEventPadButtonSendEvent ,
setEventPadButtonSendEvent ,
#if ENABLE_OVERLOADING
eventPadButton_time ,
#endif
getEventPadButtonTime ,
setEventPadButtonTime ,
#if ENABLE_OVERLOADING
eventPadButton_type ,
#endif
getEventPadButtonType ,
setEventPadButtonType ,
clearEventPadButtonWindow ,
#if 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.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
newtype EventPadButton = EventPadButton (ManagedPtr EventPadButton)
instance WrappedPtr EventPadButton where
wrappedPtrCalloc = callocBytes 40
wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 40 >=> wrapPtr EventPadButton)
wrappedPtrFree = Just ptr_to_g_free
newZeroEventPadButton :: MonadIO m => m EventPadButton
newZeroEventPadButton = liftIO $ wrappedPtrCalloc >>= wrapPtr EventPadButton
instance tag ~ 'AttrSet => Constructible EventPadButton tag where
new _ attrs = do
o <- newZeroEventPadButton
GI.Attributes.set o attrs
return o
noEventPadButton :: Maybe EventPadButton
noEventPadButton = Nothing
getEventPadButtonType :: MonadIO m => EventPadButton -> m Gdk.Enums.EventType
getEventPadButtonType s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 0) :: IO CInt
let val' = (toEnum . fromIntegral) val
return val'
setEventPadButtonType :: MonadIO m => EventPadButton -> Gdk.Enums.EventType -> m ()
setEventPadButtonType s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = (fromIntegral . fromEnum) val
poke (ptr `plusPtr` 0) (val' :: CInt)
#if ENABLE_OVERLOADING
data EventPadButtonTypeFieldInfo
instance AttrInfo EventPadButtonTypeFieldInfo where
type AttrAllowedOps EventPadButtonTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventPadButtonTypeFieldInfo = (~) Gdk.Enums.EventType
type AttrBaseTypeConstraint EventPadButtonTypeFieldInfo = (~) EventPadButton
type AttrGetType EventPadButtonTypeFieldInfo = Gdk.Enums.EventType
type AttrLabel EventPadButtonTypeFieldInfo = "type"
type AttrOrigin EventPadButtonTypeFieldInfo = EventPadButton
attrGet _ = getEventPadButtonType
attrSet _ = setEventPadButtonType
attrConstruct = undefined
attrClear _ = undefined
eventPadButton_type :: AttrLabelProxy "type"
eventPadButton_type = AttrLabelProxy
#endif
getEventPadButtonWindow :: MonadIO m => EventPadButton -> m (Maybe Gdk.Window.Window)
getEventPadButtonWindow s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 8) :: IO (Ptr Gdk.Window.Window)
result <- SP.convertIfNonNull val $ \val' -> do
val'' <- (newObject Gdk.Window.Window) val'
return val''
return result
setEventPadButtonWindow :: MonadIO m => EventPadButton -> Ptr Gdk.Window.Window -> m ()
setEventPadButtonWindow s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (val :: Ptr Gdk.Window.Window)
clearEventPadButtonWindow :: MonadIO m => EventPadButton -> m ()
clearEventPadButtonWindow s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gdk.Window.Window)
#if ENABLE_OVERLOADING
data EventPadButtonWindowFieldInfo
instance AttrInfo EventPadButtonWindowFieldInfo where
type AttrAllowedOps EventPadButtonWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint EventPadButtonWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
type AttrBaseTypeConstraint EventPadButtonWindowFieldInfo = (~) EventPadButton
type AttrGetType EventPadButtonWindowFieldInfo = Maybe Gdk.Window.Window
type AttrLabel EventPadButtonWindowFieldInfo = "window"
type AttrOrigin EventPadButtonWindowFieldInfo = EventPadButton
attrGet _ = getEventPadButtonWindow
attrSet _ = setEventPadButtonWindow
attrConstruct = undefined
attrClear _ = clearEventPadButtonWindow
eventPadButton_window :: AttrLabelProxy "window"
eventPadButton_window = AttrLabelProxy
#endif
getEventPadButtonSendEvent :: MonadIO m => EventPadButton -> m Int8
getEventPadButtonSendEvent s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 16) :: IO Int8
return val
setEventPadButtonSendEvent :: MonadIO m => EventPadButton -> Int8 -> m ()
setEventPadButtonSendEvent s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 16) (val :: Int8)
#if ENABLE_OVERLOADING
data EventPadButtonSendEventFieldInfo
instance AttrInfo EventPadButtonSendEventFieldInfo where
type AttrAllowedOps EventPadButtonSendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventPadButtonSendEventFieldInfo = (~) Int8
type AttrBaseTypeConstraint EventPadButtonSendEventFieldInfo = (~) EventPadButton
type AttrGetType EventPadButtonSendEventFieldInfo = Int8
type AttrLabel EventPadButtonSendEventFieldInfo = "send_event"
type AttrOrigin EventPadButtonSendEventFieldInfo = EventPadButton
attrGet _ = getEventPadButtonSendEvent
attrSet _ = setEventPadButtonSendEvent
attrConstruct = undefined
attrClear _ = undefined
eventPadButton_sendEvent :: AttrLabelProxy "sendEvent"
eventPadButton_sendEvent = AttrLabelProxy
#endif
getEventPadButtonTime :: MonadIO m => EventPadButton -> m Word32
getEventPadButtonTime s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 20) :: IO Word32
return val
setEventPadButtonTime :: MonadIO m => EventPadButton -> Word32 -> m ()
setEventPadButtonTime s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 20) (val :: Word32)
#if ENABLE_OVERLOADING
data EventPadButtonTimeFieldInfo
instance AttrInfo EventPadButtonTimeFieldInfo where
type AttrAllowedOps EventPadButtonTimeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventPadButtonTimeFieldInfo = (~) Word32
type AttrBaseTypeConstraint EventPadButtonTimeFieldInfo = (~) EventPadButton
type AttrGetType EventPadButtonTimeFieldInfo = Word32
type AttrLabel EventPadButtonTimeFieldInfo = "time"
type AttrOrigin EventPadButtonTimeFieldInfo = EventPadButton
attrGet _ = getEventPadButtonTime
attrSet _ = setEventPadButtonTime
attrConstruct = undefined
attrClear _ = undefined
eventPadButton_time :: AttrLabelProxy "time"
eventPadButton_time = AttrLabelProxy
#endif
getEventPadButtonGroup :: MonadIO m => EventPadButton -> m Word32
getEventPadButtonGroup s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 24) :: IO Word32
return val
setEventPadButtonGroup :: MonadIO m => EventPadButton -> Word32 -> m ()
setEventPadButtonGroup s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 24) (val :: Word32)
#if ENABLE_OVERLOADING
data EventPadButtonGroupFieldInfo
instance AttrInfo EventPadButtonGroupFieldInfo where
type AttrAllowedOps EventPadButtonGroupFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventPadButtonGroupFieldInfo = (~) Word32
type AttrBaseTypeConstraint EventPadButtonGroupFieldInfo = (~) EventPadButton
type AttrGetType EventPadButtonGroupFieldInfo = Word32
type AttrLabel EventPadButtonGroupFieldInfo = "group"
type AttrOrigin EventPadButtonGroupFieldInfo = EventPadButton
attrGet _ = getEventPadButtonGroup
attrSet _ = setEventPadButtonGroup
attrConstruct = undefined
attrClear _ = undefined
eventPadButton_group :: AttrLabelProxy "group"
eventPadButton_group = AttrLabelProxy
#endif
getEventPadButtonButton :: MonadIO m => EventPadButton -> m Word32
getEventPadButtonButton s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 28) :: IO Word32
return val
setEventPadButtonButton :: MonadIO m => EventPadButton -> Word32 -> m ()
setEventPadButtonButton s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 28) (val :: Word32)
#if ENABLE_OVERLOADING
data EventPadButtonButtonFieldInfo
instance AttrInfo EventPadButtonButtonFieldInfo where
type AttrAllowedOps EventPadButtonButtonFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventPadButtonButtonFieldInfo = (~) Word32
type AttrBaseTypeConstraint EventPadButtonButtonFieldInfo = (~) EventPadButton
type AttrGetType EventPadButtonButtonFieldInfo = Word32
type AttrLabel EventPadButtonButtonFieldInfo = "button"
type AttrOrigin EventPadButtonButtonFieldInfo = EventPadButton
attrGet _ = getEventPadButtonButton
attrSet _ = setEventPadButtonButton
attrConstruct = undefined
attrClear _ = undefined
eventPadButton_button :: AttrLabelProxy "button"
eventPadButton_button = AttrLabelProxy
#endif
getEventPadButtonMode :: MonadIO m => EventPadButton -> m Word32
getEventPadButtonMode s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 32) :: IO Word32
return val
setEventPadButtonMode :: MonadIO m => EventPadButton -> Word32 -> m ()
setEventPadButtonMode s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 32) (val :: Word32)
#if ENABLE_OVERLOADING
data EventPadButtonModeFieldInfo
instance AttrInfo EventPadButtonModeFieldInfo where
type AttrAllowedOps EventPadButtonModeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventPadButtonModeFieldInfo = (~) Word32
type AttrBaseTypeConstraint EventPadButtonModeFieldInfo = (~) EventPadButton
type AttrGetType EventPadButtonModeFieldInfo = Word32
type AttrLabel EventPadButtonModeFieldInfo = "mode"
type AttrOrigin EventPadButtonModeFieldInfo = EventPadButton
attrGet _ = getEventPadButtonMode
attrSet _ = setEventPadButtonMode
attrConstruct = undefined
attrClear _ = undefined
eventPadButton_mode :: AttrLabelProxy "mode"
eventPadButton_mode = AttrLabelProxy
#endif
#if 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 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 (O.MethodProxy :: O.MethodProxy info)
#else
fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif
#endif