#define ENABLE_OVERLOADING (MIN_VERSION_haskell_gi_overloading(1,0,0) \
&& !defined(__HADDOCK_VERSION__))
module GI.Gdk.Structs.EventMotion
(
EventMotion(..) ,
newZeroEventMotion ,
noEventMotion ,
#if ENABLE_OVERLOADING
eventMotion_axes ,
#endif
getEventMotionAxes ,
setEventMotionAxes ,
clearEventMotionDevice ,
#if ENABLE_OVERLOADING
eventMotion_device ,
#endif
getEventMotionDevice ,
setEventMotionDevice ,
#if ENABLE_OVERLOADING
eventMotion_isHint ,
#endif
getEventMotionIsHint ,
setEventMotionIsHint ,
#if ENABLE_OVERLOADING
eventMotion_sendEvent ,
#endif
getEventMotionSendEvent ,
setEventMotionSendEvent ,
#if ENABLE_OVERLOADING
eventMotion_state ,
#endif
getEventMotionState ,
setEventMotionState ,
#if ENABLE_OVERLOADING
eventMotion_time ,
#endif
getEventMotionTime ,
setEventMotionTime ,
#if ENABLE_OVERLOADING
eventMotion_type ,
#endif
getEventMotionType ,
setEventMotionType ,
clearEventMotionWindow ,
#if ENABLE_OVERLOADING
eventMotion_window ,
#endif
getEventMotionWindow ,
setEventMotionWindow ,
#if ENABLE_OVERLOADING
eventMotion_x ,
#endif
getEventMotionX ,
setEventMotionX ,
#if ENABLE_OVERLOADING
eventMotion_xRoot ,
#endif
getEventMotionXRoot ,
setEventMotionXRoot ,
#if ENABLE_OVERLOADING
eventMotion_y ,
#endif
getEventMotionY ,
setEventMotionY ,
#if ENABLE_OVERLOADING
eventMotion_yRoot ,
#endif
getEventMotionYRoot ,
setEventMotionYRoot ,
) 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.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 EventMotion = EventMotion (ManagedPtr EventMotion)
instance WrappedPtr EventMotion where
wrappedPtrCalloc = callocBytes 80
wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 80 >=> wrapPtr EventMotion)
wrappedPtrFree = Just ptr_to_g_free
newZeroEventMotion :: MonadIO m => m EventMotion
newZeroEventMotion = liftIO $ wrappedPtrCalloc >>= wrapPtr EventMotion
instance tag ~ 'AttrSet => Constructible EventMotion tag where
new _ attrs = do
o <- newZeroEventMotion
GI.Attributes.set o attrs
return o
noEventMotion :: Maybe EventMotion
noEventMotion = Nothing
getEventMotionType :: MonadIO m => EventMotion -> m Gdk.Enums.EventType
getEventMotionType s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 0) :: IO CInt
let val' = (toEnum . fromIntegral) val
return val'
setEventMotionType :: MonadIO m => EventMotion -> Gdk.Enums.EventType -> m ()
setEventMotionType s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = (fromIntegral . fromEnum) val
poke (ptr `plusPtr` 0) (val' :: CInt)
#if ENABLE_OVERLOADING
data EventMotionTypeFieldInfo
instance AttrInfo EventMotionTypeFieldInfo where
type AttrAllowedOps EventMotionTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventMotionTypeFieldInfo = (~) Gdk.Enums.EventType
type AttrBaseTypeConstraint EventMotionTypeFieldInfo = (~) EventMotion
type AttrGetType EventMotionTypeFieldInfo = Gdk.Enums.EventType
type AttrLabel EventMotionTypeFieldInfo = "type"
type AttrOrigin EventMotionTypeFieldInfo = EventMotion
attrGet _ = getEventMotionType
attrSet _ = setEventMotionType
attrConstruct = undefined
attrClear _ = undefined
eventMotion_type :: AttrLabelProxy "type"
eventMotion_type = AttrLabelProxy
#endif
getEventMotionWindow :: MonadIO m => EventMotion -> m (Maybe Gdk.Window.Window)
getEventMotionWindow 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
setEventMotionWindow :: MonadIO m => EventMotion -> Ptr Gdk.Window.Window -> m ()
setEventMotionWindow s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (val :: Ptr Gdk.Window.Window)
clearEventMotionWindow :: MonadIO m => EventMotion -> m ()
clearEventMotionWindow s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gdk.Window.Window)
#if ENABLE_OVERLOADING
data EventMotionWindowFieldInfo
instance AttrInfo EventMotionWindowFieldInfo where
type AttrAllowedOps EventMotionWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint EventMotionWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
type AttrBaseTypeConstraint EventMotionWindowFieldInfo = (~) EventMotion
type AttrGetType EventMotionWindowFieldInfo = Maybe Gdk.Window.Window
type AttrLabel EventMotionWindowFieldInfo = "window"
type AttrOrigin EventMotionWindowFieldInfo = EventMotion
attrGet _ = getEventMotionWindow
attrSet _ = setEventMotionWindow
attrConstruct = undefined
attrClear _ = clearEventMotionWindow
eventMotion_window :: AttrLabelProxy "window"
eventMotion_window = AttrLabelProxy
#endif
getEventMotionSendEvent :: MonadIO m => EventMotion -> m Int8
getEventMotionSendEvent s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 16) :: IO Int8
return val
setEventMotionSendEvent :: MonadIO m => EventMotion -> Int8 -> m ()
setEventMotionSendEvent s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 16) (val :: Int8)
#if ENABLE_OVERLOADING
data EventMotionSendEventFieldInfo
instance AttrInfo EventMotionSendEventFieldInfo where
type AttrAllowedOps EventMotionSendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventMotionSendEventFieldInfo = (~) Int8
type AttrBaseTypeConstraint EventMotionSendEventFieldInfo = (~) EventMotion
type AttrGetType EventMotionSendEventFieldInfo = Int8
type AttrLabel EventMotionSendEventFieldInfo = "send_event"
type AttrOrigin EventMotionSendEventFieldInfo = EventMotion
attrGet _ = getEventMotionSendEvent
attrSet _ = setEventMotionSendEvent
attrConstruct = undefined
attrClear _ = undefined
eventMotion_sendEvent :: AttrLabelProxy "sendEvent"
eventMotion_sendEvent = AttrLabelProxy
#endif
getEventMotionTime :: MonadIO m => EventMotion -> m Word32
getEventMotionTime s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 20) :: IO Word32
return val
setEventMotionTime :: MonadIO m => EventMotion -> Word32 -> m ()
setEventMotionTime s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 20) (val :: Word32)
#if ENABLE_OVERLOADING
data EventMotionTimeFieldInfo
instance AttrInfo EventMotionTimeFieldInfo where
type AttrAllowedOps EventMotionTimeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventMotionTimeFieldInfo = (~) Word32
type AttrBaseTypeConstraint EventMotionTimeFieldInfo = (~) EventMotion
type AttrGetType EventMotionTimeFieldInfo = Word32
type AttrLabel EventMotionTimeFieldInfo = "time"
type AttrOrigin EventMotionTimeFieldInfo = EventMotion
attrGet _ = getEventMotionTime
attrSet _ = setEventMotionTime
attrConstruct = undefined
attrClear _ = undefined
eventMotion_time :: AttrLabelProxy "time"
eventMotion_time = AttrLabelProxy
#endif
getEventMotionX :: MonadIO m => EventMotion -> m Double
getEventMotionX s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 24) :: IO CDouble
let val' = realToFrac val
return val'
setEventMotionX :: MonadIO m => EventMotion -> Double -> m ()
setEventMotionX s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 24) (val' :: CDouble)
#if ENABLE_OVERLOADING
data EventMotionXFieldInfo
instance AttrInfo EventMotionXFieldInfo where
type AttrAllowedOps EventMotionXFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventMotionXFieldInfo = (~) Double
type AttrBaseTypeConstraint EventMotionXFieldInfo = (~) EventMotion
type AttrGetType EventMotionXFieldInfo = Double
type AttrLabel EventMotionXFieldInfo = "x"
type AttrOrigin EventMotionXFieldInfo = EventMotion
attrGet _ = getEventMotionX
attrSet _ = setEventMotionX
attrConstruct = undefined
attrClear _ = undefined
eventMotion_x :: AttrLabelProxy "x"
eventMotion_x = AttrLabelProxy
#endif
getEventMotionY :: MonadIO m => EventMotion -> m Double
getEventMotionY s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 32) :: IO CDouble
let val' = realToFrac val
return val'
setEventMotionY :: MonadIO m => EventMotion -> Double -> m ()
setEventMotionY s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 32) (val' :: CDouble)
#if ENABLE_OVERLOADING
data EventMotionYFieldInfo
instance AttrInfo EventMotionYFieldInfo where
type AttrAllowedOps EventMotionYFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventMotionYFieldInfo = (~) Double
type AttrBaseTypeConstraint EventMotionYFieldInfo = (~) EventMotion
type AttrGetType EventMotionYFieldInfo = Double
type AttrLabel EventMotionYFieldInfo = "y"
type AttrOrigin EventMotionYFieldInfo = EventMotion
attrGet _ = getEventMotionY
attrSet _ = setEventMotionY
attrConstruct = undefined
attrClear _ = undefined
eventMotion_y :: AttrLabelProxy "y"
eventMotion_y = AttrLabelProxy
#endif
getEventMotionAxes :: MonadIO m => EventMotion -> m Double
getEventMotionAxes s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 40) :: IO CDouble
let val' = realToFrac val
return val'
setEventMotionAxes :: MonadIO m => EventMotion -> Double -> m ()
setEventMotionAxes s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 40) (val' :: CDouble)
#if ENABLE_OVERLOADING
data EventMotionAxesFieldInfo
instance AttrInfo EventMotionAxesFieldInfo where
type AttrAllowedOps EventMotionAxesFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventMotionAxesFieldInfo = (~) Double
type AttrBaseTypeConstraint EventMotionAxesFieldInfo = (~) EventMotion
type AttrGetType EventMotionAxesFieldInfo = Double
type AttrLabel EventMotionAxesFieldInfo = "axes"
type AttrOrigin EventMotionAxesFieldInfo = EventMotion
attrGet _ = getEventMotionAxes
attrSet _ = setEventMotionAxes
attrConstruct = undefined
attrClear _ = undefined
eventMotion_axes :: AttrLabelProxy "axes"
eventMotion_axes = AttrLabelProxy
#endif
getEventMotionState :: MonadIO m => EventMotion -> m [Gdk.Flags.ModifierType]
getEventMotionState s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 48) :: IO CUInt
let val' = wordToGFlags val
return val'
setEventMotionState :: MonadIO m => EventMotion -> [Gdk.Flags.ModifierType] -> m ()
setEventMotionState s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = gflagsToWord val
poke (ptr `plusPtr` 48) (val' :: CUInt)
#if ENABLE_OVERLOADING
data EventMotionStateFieldInfo
instance AttrInfo EventMotionStateFieldInfo where
type AttrAllowedOps EventMotionStateFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventMotionStateFieldInfo = (~) [Gdk.Flags.ModifierType]
type AttrBaseTypeConstraint EventMotionStateFieldInfo = (~) EventMotion
type AttrGetType EventMotionStateFieldInfo = [Gdk.Flags.ModifierType]
type AttrLabel EventMotionStateFieldInfo = "state"
type AttrOrigin EventMotionStateFieldInfo = EventMotion
attrGet _ = getEventMotionState
attrSet _ = setEventMotionState
attrConstruct = undefined
attrClear _ = undefined
eventMotion_state :: AttrLabelProxy "state"
eventMotion_state = AttrLabelProxy
#endif
getEventMotionIsHint :: MonadIO m => EventMotion -> m Int16
getEventMotionIsHint s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 52) :: IO Int16
return val
setEventMotionIsHint :: MonadIO m => EventMotion -> Int16 -> m ()
setEventMotionIsHint s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 52) (val :: Int16)
#if ENABLE_OVERLOADING
data EventMotionIsHintFieldInfo
instance AttrInfo EventMotionIsHintFieldInfo where
type AttrAllowedOps EventMotionIsHintFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventMotionIsHintFieldInfo = (~) Int16
type AttrBaseTypeConstraint EventMotionIsHintFieldInfo = (~) EventMotion
type AttrGetType EventMotionIsHintFieldInfo = Int16
type AttrLabel EventMotionIsHintFieldInfo = "is_hint"
type AttrOrigin EventMotionIsHintFieldInfo = EventMotion
attrGet _ = getEventMotionIsHint
attrSet _ = setEventMotionIsHint
attrConstruct = undefined
attrClear _ = undefined
eventMotion_isHint :: AttrLabelProxy "isHint"
eventMotion_isHint = AttrLabelProxy
#endif
getEventMotionDevice :: MonadIO m => EventMotion -> m (Maybe Gdk.Device.Device)
getEventMotionDevice 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
setEventMotionDevice :: MonadIO m => EventMotion -> Ptr Gdk.Device.Device -> m ()
setEventMotionDevice s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 56) (val :: Ptr Gdk.Device.Device)
clearEventMotionDevice :: MonadIO m => EventMotion -> m ()
clearEventMotionDevice s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 56) (FP.nullPtr :: Ptr Gdk.Device.Device)
#if ENABLE_OVERLOADING
data EventMotionDeviceFieldInfo
instance AttrInfo EventMotionDeviceFieldInfo where
type AttrAllowedOps EventMotionDeviceFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint EventMotionDeviceFieldInfo = (~) (Ptr Gdk.Device.Device)
type AttrBaseTypeConstraint EventMotionDeviceFieldInfo = (~) EventMotion
type AttrGetType EventMotionDeviceFieldInfo = Maybe Gdk.Device.Device
type AttrLabel EventMotionDeviceFieldInfo = "device"
type AttrOrigin EventMotionDeviceFieldInfo = EventMotion
attrGet _ = getEventMotionDevice
attrSet _ = setEventMotionDevice
attrConstruct = undefined
attrClear _ = clearEventMotionDevice
eventMotion_device :: AttrLabelProxy "device"
eventMotion_device = AttrLabelProxy
#endif
getEventMotionXRoot :: MonadIO m => EventMotion -> m Double
getEventMotionXRoot s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 64) :: IO CDouble
let val' = realToFrac val
return val'
setEventMotionXRoot :: MonadIO m => EventMotion -> Double -> m ()
setEventMotionXRoot s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 64) (val' :: CDouble)
#if ENABLE_OVERLOADING
data EventMotionXRootFieldInfo
instance AttrInfo EventMotionXRootFieldInfo where
type AttrAllowedOps EventMotionXRootFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventMotionXRootFieldInfo = (~) Double
type AttrBaseTypeConstraint EventMotionXRootFieldInfo = (~) EventMotion
type AttrGetType EventMotionXRootFieldInfo = Double
type AttrLabel EventMotionXRootFieldInfo = "x_root"
type AttrOrigin EventMotionXRootFieldInfo = EventMotion
attrGet _ = getEventMotionXRoot
attrSet _ = setEventMotionXRoot
attrConstruct = undefined
attrClear _ = undefined
eventMotion_xRoot :: AttrLabelProxy "xRoot"
eventMotion_xRoot = AttrLabelProxy
#endif
getEventMotionYRoot :: MonadIO m => EventMotion -> m Double
getEventMotionYRoot s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 72) :: IO CDouble
let val' = realToFrac val
return val'
setEventMotionYRoot :: MonadIO m => EventMotion -> Double -> m ()
setEventMotionYRoot s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 72) (val' :: CDouble)
#if ENABLE_OVERLOADING
data EventMotionYRootFieldInfo
instance AttrInfo EventMotionYRootFieldInfo where
type AttrAllowedOps EventMotionYRootFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventMotionYRootFieldInfo = (~) Double
type AttrBaseTypeConstraint EventMotionYRootFieldInfo = (~) EventMotion
type AttrGetType EventMotionYRootFieldInfo = Double
type AttrLabel EventMotionYRootFieldInfo = "y_root"
type AttrOrigin EventMotionYRootFieldInfo = EventMotion
attrGet _ = getEventMotionYRoot
attrSet _ = setEventMotionYRoot
attrConstruct = undefined
attrClear _ = undefined
eventMotion_yRoot :: AttrLabelProxy "yRoot"
eventMotion_yRoot = AttrLabelProxy
#endif
#if ENABLE_OVERLOADING
instance O.HasAttributeList EventMotion
type instance O.AttributeList EventMotion = EventMotionAttributeList
type EventMotionAttributeList = ('[ '("type", EventMotionTypeFieldInfo), '("window", EventMotionWindowFieldInfo), '("sendEvent", EventMotionSendEventFieldInfo), '("time", EventMotionTimeFieldInfo), '("x", EventMotionXFieldInfo), '("y", EventMotionYFieldInfo), '("axes", EventMotionAxesFieldInfo), '("state", EventMotionStateFieldInfo), '("isHint", EventMotionIsHintFieldInfo), '("device", EventMotionDeviceFieldInfo), '("xRoot", EventMotionXRootFieldInfo), '("yRoot", EventMotionYRootFieldInfo)] :: [(Symbol, *)])
#endif
#if ENABLE_OVERLOADING
type family ResolveEventMotionMethod (t :: Symbol) (o :: *) :: * where
ResolveEventMotionMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveEventMotionMethod t EventMotion, O.MethodInfo info EventMotion p) => OL.IsLabel t (EventMotion -> 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