#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
&& !defined(__HADDOCK_VERSION__))
module GI.Gdk.Structs.EventButton
(
EventButton(..) ,
newZeroEventButton ,
noEventButton ,
#if ENABLE_OVERLOADING
eventButton_axes ,
#endif
getEventButtonAxes ,
setEventButtonAxes ,
#if ENABLE_OVERLOADING
eventButton_button ,
#endif
getEventButtonButton ,
setEventButtonButton ,
clearEventButtonDevice ,
#if ENABLE_OVERLOADING
eventButton_device ,
#endif
getEventButtonDevice ,
setEventButtonDevice ,
#if ENABLE_OVERLOADING
eventButton_sendEvent ,
#endif
getEventButtonSendEvent ,
setEventButtonSendEvent ,
#if ENABLE_OVERLOADING
eventButton_state ,
#endif
getEventButtonState ,
setEventButtonState ,
#if ENABLE_OVERLOADING
eventButton_time ,
#endif
getEventButtonTime ,
setEventButtonTime ,
#if ENABLE_OVERLOADING
eventButton_type ,
#endif
getEventButtonType ,
setEventButtonType ,
clearEventButtonWindow ,
#if ENABLE_OVERLOADING
eventButton_window ,
#endif
getEventButtonWindow ,
setEventButtonWindow ,
#if ENABLE_OVERLOADING
eventButton_x ,
#endif
getEventButtonX ,
setEventButtonX ,
#if ENABLE_OVERLOADING
eventButton_xRoot ,
#endif
getEventButtonXRoot ,
setEventButtonXRoot ,
#if ENABLE_OVERLOADING
eventButton_y ,
#endif
getEventButtonY ,
setEventButtonY ,
#if 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.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.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
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
newtype EventButton = EventButton (ManagedPtr EventButton)
instance WrappedPtr EventButton where
wrappedPtrCalloc = callocBytes 80
wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 80 >=> wrapPtr EventButton)
wrappedPtrFree = Just ptr_to_g_free
newZeroEventButton :: MonadIO m => m EventButton
newZeroEventButton = liftIO $ wrappedPtrCalloc >>= wrapPtr EventButton
instance tag ~ 'AttrSet => Constructible EventButton tag where
new _ attrs = do
o <- newZeroEventButton
GI.Attributes.set o attrs
return o
noEventButton :: Maybe EventButton
noEventButton = Nothing
getEventButtonType :: MonadIO m => EventButton -> m Gdk.Enums.EventType
getEventButtonType s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 0) :: IO CUInt
let val' = (toEnum . fromIntegral) val
return val'
setEventButtonType :: MonadIO m => EventButton -> Gdk.Enums.EventType -> m ()
setEventButtonType s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = (fromIntegral . fromEnum) val
poke (ptr `plusPtr` 0) (val' :: CUInt)
#if ENABLE_OVERLOADING
data EventButtonTypeFieldInfo
instance AttrInfo EventButtonTypeFieldInfo where
type AttrAllowedOps EventButtonTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonTypeFieldInfo = (~) Gdk.Enums.EventType
type AttrBaseTypeConstraint EventButtonTypeFieldInfo = (~) EventButton
type AttrGetType EventButtonTypeFieldInfo = Gdk.Enums.EventType
type AttrLabel EventButtonTypeFieldInfo = "type"
type AttrOrigin EventButtonTypeFieldInfo = EventButton
attrGet _ = getEventButtonType
attrSet _ = setEventButtonType
attrConstruct = undefined
attrClear _ = undefined
eventButton_type :: AttrLabelProxy "type"
eventButton_type = AttrLabelProxy
#endif
getEventButtonWindow :: MonadIO m => EventButton -> m (Maybe Gdk.Window.Window)
getEventButtonWindow 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
setEventButtonWindow :: MonadIO m => EventButton -> Ptr Gdk.Window.Window -> m ()
setEventButtonWindow s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (val :: Ptr Gdk.Window.Window)
clearEventButtonWindow :: MonadIO m => EventButton -> m ()
clearEventButtonWindow s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gdk.Window.Window)
#if ENABLE_OVERLOADING
data EventButtonWindowFieldInfo
instance AttrInfo EventButtonWindowFieldInfo where
type AttrAllowedOps EventButtonWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint EventButtonWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
type AttrBaseTypeConstraint EventButtonWindowFieldInfo = (~) EventButton
type AttrGetType EventButtonWindowFieldInfo = Maybe Gdk.Window.Window
type AttrLabel EventButtonWindowFieldInfo = "window"
type AttrOrigin EventButtonWindowFieldInfo = EventButton
attrGet _ = getEventButtonWindow
attrSet _ = setEventButtonWindow
attrConstruct = undefined
attrClear _ = clearEventButtonWindow
eventButton_window :: AttrLabelProxy "window"
eventButton_window = AttrLabelProxy
#endif
getEventButtonSendEvent :: MonadIO m => EventButton -> m Int8
getEventButtonSendEvent s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 16) :: IO Int8
return val
setEventButtonSendEvent :: MonadIO m => EventButton -> Int8 -> m ()
setEventButtonSendEvent s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 16) (val :: Int8)
#if ENABLE_OVERLOADING
data EventButtonSendEventFieldInfo
instance AttrInfo EventButtonSendEventFieldInfo where
type AttrAllowedOps EventButtonSendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonSendEventFieldInfo = (~) Int8
type AttrBaseTypeConstraint EventButtonSendEventFieldInfo = (~) EventButton
type AttrGetType EventButtonSendEventFieldInfo = Int8
type AttrLabel EventButtonSendEventFieldInfo = "send_event"
type AttrOrigin EventButtonSendEventFieldInfo = EventButton
attrGet _ = getEventButtonSendEvent
attrSet _ = setEventButtonSendEvent
attrConstruct = undefined
attrClear _ = undefined
eventButton_sendEvent :: AttrLabelProxy "sendEvent"
eventButton_sendEvent = AttrLabelProxy
#endif
getEventButtonTime :: MonadIO m => EventButton -> m Word32
getEventButtonTime s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 20) :: IO Word32
return val
setEventButtonTime :: MonadIO m => EventButton -> Word32 -> m ()
setEventButtonTime s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 20) (val :: Word32)
#if ENABLE_OVERLOADING
data EventButtonTimeFieldInfo
instance AttrInfo EventButtonTimeFieldInfo where
type AttrAllowedOps EventButtonTimeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonTimeFieldInfo = (~) Word32
type AttrBaseTypeConstraint EventButtonTimeFieldInfo = (~) EventButton
type AttrGetType EventButtonTimeFieldInfo = Word32
type AttrLabel EventButtonTimeFieldInfo = "time"
type AttrOrigin EventButtonTimeFieldInfo = EventButton
attrGet _ = getEventButtonTime
attrSet _ = setEventButtonTime
attrConstruct = undefined
attrClear _ = undefined
eventButton_time :: AttrLabelProxy "time"
eventButton_time = AttrLabelProxy
#endif
getEventButtonX :: MonadIO m => EventButton -> m Double
getEventButtonX s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 24) :: IO CDouble
let val' = realToFrac val
return val'
setEventButtonX :: MonadIO m => EventButton -> Double -> m ()
setEventButtonX s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 24) (val' :: CDouble)
#if ENABLE_OVERLOADING
data EventButtonXFieldInfo
instance AttrInfo EventButtonXFieldInfo where
type AttrAllowedOps EventButtonXFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonXFieldInfo = (~) Double
type AttrBaseTypeConstraint EventButtonXFieldInfo = (~) EventButton
type AttrGetType EventButtonXFieldInfo = Double
type AttrLabel EventButtonXFieldInfo = "x"
type AttrOrigin EventButtonXFieldInfo = EventButton
attrGet _ = getEventButtonX
attrSet _ = setEventButtonX
attrConstruct = undefined
attrClear _ = undefined
eventButton_x :: AttrLabelProxy "x"
eventButton_x = AttrLabelProxy
#endif
getEventButtonY :: MonadIO m => EventButton -> m Double
getEventButtonY s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 32) :: IO CDouble
let val' = realToFrac val
return val'
setEventButtonY :: MonadIO m => EventButton -> Double -> m ()
setEventButtonY s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 32) (val' :: CDouble)
#if ENABLE_OVERLOADING
data EventButtonYFieldInfo
instance AttrInfo EventButtonYFieldInfo where
type AttrAllowedOps EventButtonYFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonYFieldInfo = (~) Double
type AttrBaseTypeConstraint EventButtonYFieldInfo = (~) EventButton
type AttrGetType EventButtonYFieldInfo = Double
type AttrLabel EventButtonYFieldInfo = "y"
type AttrOrigin EventButtonYFieldInfo = EventButton
attrGet _ = getEventButtonY
attrSet _ = setEventButtonY
attrConstruct = undefined
attrClear _ = undefined
eventButton_y :: AttrLabelProxy "y"
eventButton_y = AttrLabelProxy
#endif
getEventButtonAxes :: MonadIO m => EventButton -> m Double
getEventButtonAxes s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 40) :: IO CDouble
let val' = realToFrac val
return val'
setEventButtonAxes :: MonadIO m => EventButton -> Double -> m ()
setEventButtonAxes s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 40) (val' :: CDouble)
#if ENABLE_OVERLOADING
data EventButtonAxesFieldInfo
instance AttrInfo EventButtonAxesFieldInfo where
type AttrAllowedOps EventButtonAxesFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonAxesFieldInfo = (~) Double
type AttrBaseTypeConstraint EventButtonAxesFieldInfo = (~) EventButton
type AttrGetType EventButtonAxesFieldInfo = Double
type AttrLabel EventButtonAxesFieldInfo = "axes"
type AttrOrigin EventButtonAxesFieldInfo = EventButton
attrGet _ = getEventButtonAxes
attrSet _ = setEventButtonAxes
attrConstruct = undefined
attrClear _ = undefined
eventButton_axes :: AttrLabelProxy "axes"
eventButton_axes = AttrLabelProxy
#endif
getEventButtonState :: MonadIO m => EventButton -> m [Gdk.Flags.ModifierType]
getEventButtonState s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 48) :: IO CUInt
let val' = wordToGFlags val
return val'
setEventButtonState :: MonadIO m => EventButton -> [Gdk.Flags.ModifierType] -> m ()
setEventButtonState s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = gflagsToWord val
poke (ptr `plusPtr` 48) (val' :: CUInt)
#if ENABLE_OVERLOADING
data EventButtonStateFieldInfo
instance AttrInfo EventButtonStateFieldInfo where
type AttrAllowedOps EventButtonStateFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonStateFieldInfo = (~) [Gdk.Flags.ModifierType]
type AttrBaseTypeConstraint EventButtonStateFieldInfo = (~) EventButton
type AttrGetType EventButtonStateFieldInfo = [Gdk.Flags.ModifierType]
type AttrLabel EventButtonStateFieldInfo = "state"
type AttrOrigin EventButtonStateFieldInfo = EventButton
attrGet _ = getEventButtonState
attrSet _ = setEventButtonState
attrConstruct = undefined
attrClear _ = undefined
eventButton_state :: AttrLabelProxy "state"
eventButton_state = AttrLabelProxy
#endif
getEventButtonButton :: MonadIO m => EventButton -> m Word32
getEventButtonButton s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 52) :: IO Word32
return val
setEventButtonButton :: MonadIO m => EventButton -> Word32 -> m ()
setEventButtonButton s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 52) (val :: Word32)
#if ENABLE_OVERLOADING
data EventButtonButtonFieldInfo
instance AttrInfo EventButtonButtonFieldInfo where
type AttrAllowedOps EventButtonButtonFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonButtonFieldInfo = (~) Word32
type AttrBaseTypeConstraint EventButtonButtonFieldInfo = (~) EventButton
type AttrGetType EventButtonButtonFieldInfo = Word32
type AttrLabel EventButtonButtonFieldInfo = "button"
type AttrOrigin EventButtonButtonFieldInfo = EventButton
attrGet _ = getEventButtonButton
attrSet _ = setEventButtonButton
attrConstruct = undefined
attrClear _ = undefined
eventButton_button :: AttrLabelProxy "button"
eventButton_button = AttrLabelProxy
#endif
getEventButtonDevice :: MonadIO m => EventButton -> m (Maybe Gdk.Device.Device)
getEventButtonDevice s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 56) :: IO (Ptr Gdk.Device.Device)
result <- SP.convertIfNonNull val $ \val' -> do
val'' <- (newObject Gdk.Device.Device) val'
return val''
return result
setEventButtonDevice :: MonadIO m => EventButton -> Ptr Gdk.Device.Device -> m ()
setEventButtonDevice s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 56) (val :: Ptr Gdk.Device.Device)
clearEventButtonDevice :: MonadIO m => EventButton -> m ()
clearEventButtonDevice s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 56) (FP.nullPtr :: Ptr Gdk.Device.Device)
#if ENABLE_OVERLOADING
data EventButtonDeviceFieldInfo
instance AttrInfo EventButtonDeviceFieldInfo where
type AttrAllowedOps EventButtonDeviceFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint EventButtonDeviceFieldInfo = (~) (Ptr Gdk.Device.Device)
type AttrBaseTypeConstraint EventButtonDeviceFieldInfo = (~) EventButton
type AttrGetType EventButtonDeviceFieldInfo = Maybe Gdk.Device.Device
type AttrLabel EventButtonDeviceFieldInfo = "device"
type AttrOrigin EventButtonDeviceFieldInfo = EventButton
attrGet _ = getEventButtonDevice
attrSet _ = setEventButtonDevice
attrConstruct = undefined
attrClear _ = clearEventButtonDevice
eventButton_device :: AttrLabelProxy "device"
eventButton_device = AttrLabelProxy
#endif
getEventButtonXRoot :: MonadIO m => EventButton -> m Double
getEventButtonXRoot s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 64) :: IO CDouble
let val' = realToFrac val
return val'
setEventButtonXRoot :: MonadIO m => EventButton -> Double -> m ()
setEventButtonXRoot s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 64) (val' :: CDouble)
#if ENABLE_OVERLOADING
data EventButtonXRootFieldInfo
instance AttrInfo EventButtonXRootFieldInfo where
type AttrAllowedOps EventButtonXRootFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonXRootFieldInfo = (~) Double
type AttrBaseTypeConstraint EventButtonXRootFieldInfo = (~) EventButton
type AttrGetType EventButtonXRootFieldInfo = Double
type AttrLabel EventButtonXRootFieldInfo = "x_root"
type AttrOrigin EventButtonXRootFieldInfo = EventButton
attrGet _ = getEventButtonXRoot
attrSet _ = setEventButtonXRoot
attrConstruct = undefined
attrClear _ = undefined
eventButton_xRoot :: AttrLabelProxy "xRoot"
eventButton_xRoot = AttrLabelProxy
#endif
getEventButtonYRoot :: MonadIO m => EventButton -> m Double
getEventButtonYRoot s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 72) :: IO CDouble
let val' = realToFrac val
return val'
setEventButtonYRoot :: MonadIO m => EventButton -> Double -> m ()
setEventButtonYRoot s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 72) (val' :: CDouble)
#if ENABLE_OVERLOADING
data EventButtonYRootFieldInfo
instance AttrInfo EventButtonYRootFieldInfo where
type AttrAllowedOps EventButtonYRootFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventButtonYRootFieldInfo = (~) Double
type AttrBaseTypeConstraint EventButtonYRootFieldInfo = (~) EventButton
type AttrGetType EventButtonYRootFieldInfo = Double
type AttrLabel EventButtonYRootFieldInfo = "y_root"
type AttrOrigin EventButtonYRootFieldInfo = EventButton
attrGet _ = getEventButtonYRoot
attrSet _ = setEventButtonYRoot
attrConstruct = undefined
attrClear _ = undefined
eventButton_yRoot :: AttrLabelProxy "yRoot"
eventButton_yRoot = AttrLabelProxy
#endif
#if 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 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) => O.IsLabelProxy t (EventButton -> p) where
fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveEventButtonMethod t EventButton, O.MethodInfo info EventButton p) => O.IsLabel t (EventButton -> 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
#endif