module GI.Gdk.Structs.EventTouchpadPinch
(
EventTouchpadPinch(..) ,
newZeroEventTouchpadPinch ,
noEventTouchpadPinch ,
eventTouchpadPinch_angleDelta ,
getEventTouchpadPinchAngleDelta ,
setEventTouchpadPinchAngleDelta ,
eventTouchpadPinch_dx ,
getEventTouchpadPinchDx ,
setEventTouchpadPinchDx ,
eventTouchpadPinch_dy ,
getEventTouchpadPinchDy ,
setEventTouchpadPinchDy ,
eventTouchpadPinch_nFingers ,
getEventTouchpadPinchNFingers ,
setEventTouchpadPinchNFingers ,
eventTouchpadPinch_phase ,
getEventTouchpadPinchPhase ,
setEventTouchpadPinchPhase ,
eventTouchpadPinch_scale ,
getEventTouchpadPinchScale ,
setEventTouchpadPinchScale ,
eventTouchpadPinch_sendEvent ,
getEventTouchpadPinchSendEvent ,
setEventTouchpadPinchSendEvent ,
eventTouchpadPinch_state ,
getEventTouchpadPinchState ,
setEventTouchpadPinchState ,
eventTouchpadPinch_time ,
getEventTouchpadPinchTime ,
setEventTouchpadPinchTime ,
eventTouchpadPinch_type ,
getEventTouchpadPinchType ,
setEventTouchpadPinchType ,
clearEventTouchpadPinchWindow ,
eventTouchpadPinch_window ,
getEventTouchpadPinchWindow ,
setEventTouchpadPinchWindow ,
eventTouchpadPinch_x ,
getEventTouchpadPinchX ,
setEventTouchpadPinchX ,
eventTouchpadPinch_xRoot ,
getEventTouchpadPinchXRoot ,
setEventTouchpadPinchXRoot ,
eventTouchpadPinch_y ,
getEventTouchpadPinchY ,
setEventTouchpadPinchY ,
eventTouchpadPinch_yRoot ,
getEventTouchpadPinchYRoot ,
setEventTouchpadPinchYRoot ,
) 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.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 qualified GI.Gdk.Enums as Gdk.Enums
import qualified GI.Gdk.Flags as Gdk.Flags
import qualified GI.Gdk.Objects.Window as Gdk.Window
newtype EventTouchpadPinch = EventTouchpadPinch (ManagedPtr EventTouchpadPinch)
instance WrappedPtr EventTouchpadPinch where
wrappedPtrCalloc = callocBytes 104
wrappedPtrCopy = \p -> withManagedPtr p (copyBytes 104 >=> wrapPtr EventTouchpadPinch)
wrappedPtrFree = Just ptr_to_g_free
newZeroEventTouchpadPinch :: MonadIO m => m EventTouchpadPinch
newZeroEventTouchpadPinch = liftIO $ wrappedPtrCalloc >>= wrapPtr EventTouchpadPinch
instance tag ~ 'AttrSet => Constructible EventTouchpadPinch tag where
new _ attrs = do
o <- newZeroEventTouchpadPinch
GI.Attributes.set o attrs
return o
noEventTouchpadPinch :: Maybe EventTouchpadPinch
noEventTouchpadPinch = Nothing
getEventTouchpadPinchType :: MonadIO m => EventTouchpadPinch -> m Gdk.Enums.EventType
getEventTouchpadPinchType s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 0) :: IO CUInt
let val' = (toEnum . fromIntegral) val
return val'
setEventTouchpadPinchType :: MonadIO m => EventTouchpadPinch -> Gdk.Enums.EventType -> m ()
setEventTouchpadPinchType s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = (fromIntegral . fromEnum) val
poke (ptr `plusPtr` 0) (val' :: CUInt)
data EventTouchpadPinchTypeFieldInfo
instance AttrInfo EventTouchpadPinchTypeFieldInfo where
type AttrAllowedOps EventTouchpadPinchTypeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventTouchpadPinchTypeFieldInfo = (~) Gdk.Enums.EventType
type AttrBaseTypeConstraint EventTouchpadPinchTypeFieldInfo = (~) EventTouchpadPinch
type AttrGetType EventTouchpadPinchTypeFieldInfo = Gdk.Enums.EventType
type AttrLabel EventTouchpadPinchTypeFieldInfo = "type"
type AttrOrigin EventTouchpadPinchTypeFieldInfo = EventTouchpadPinch
attrGet _ = getEventTouchpadPinchType
attrSet _ = setEventTouchpadPinchType
attrConstruct = undefined
attrClear _ = undefined
eventTouchpadPinch_type :: AttrLabelProxy "type"
eventTouchpadPinch_type = AttrLabelProxy
getEventTouchpadPinchWindow :: MonadIO m => EventTouchpadPinch -> m (Maybe Gdk.Window.Window)
getEventTouchpadPinchWindow 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
setEventTouchpadPinchWindow :: MonadIO m => EventTouchpadPinch -> Ptr Gdk.Window.Window -> m ()
setEventTouchpadPinchWindow s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (val :: Ptr Gdk.Window.Window)
clearEventTouchpadPinchWindow :: MonadIO m => EventTouchpadPinch -> m ()
clearEventTouchpadPinchWindow s = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 8) (FP.nullPtr :: Ptr Gdk.Window.Window)
data EventTouchpadPinchWindowFieldInfo
instance AttrInfo EventTouchpadPinchWindowFieldInfo where
type AttrAllowedOps EventTouchpadPinchWindowFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint EventTouchpadPinchWindowFieldInfo = (~) (Ptr Gdk.Window.Window)
type AttrBaseTypeConstraint EventTouchpadPinchWindowFieldInfo = (~) EventTouchpadPinch
type AttrGetType EventTouchpadPinchWindowFieldInfo = Maybe Gdk.Window.Window
type AttrLabel EventTouchpadPinchWindowFieldInfo = "window"
type AttrOrigin EventTouchpadPinchWindowFieldInfo = EventTouchpadPinch
attrGet _ = getEventTouchpadPinchWindow
attrSet _ = setEventTouchpadPinchWindow
attrConstruct = undefined
attrClear _ = clearEventTouchpadPinchWindow
eventTouchpadPinch_window :: AttrLabelProxy "window"
eventTouchpadPinch_window = AttrLabelProxy
getEventTouchpadPinchSendEvent :: MonadIO m => EventTouchpadPinch -> m Int8
getEventTouchpadPinchSendEvent s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 16) :: IO Int8
return val
setEventTouchpadPinchSendEvent :: MonadIO m => EventTouchpadPinch -> Int8 -> m ()
setEventTouchpadPinchSendEvent s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 16) (val :: Int8)
data EventTouchpadPinchSendEventFieldInfo
instance AttrInfo EventTouchpadPinchSendEventFieldInfo where
type AttrAllowedOps EventTouchpadPinchSendEventFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventTouchpadPinchSendEventFieldInfo = (~) Int8
type AttrBaseTypeConstraint EventTouchpadPinchSendEventFieldInfo = (~) EventTouchpadPinch
type AttrGetType EventTouchpadPinchSendEventFieldInfo = Int8
type AttrLabel EventTouchpadPinchSendEventFieldInfo = "send_event"
type AttrOrigin EventTouchpadPinchSendEventFieldInfo = EventTouchpadPinch
attrGet _ = getEventTouchpadPinchSendEvent
attrSet _ = setEventTouchpadPinchSendEvent
attrConstruct = undefined
attrClear _ = undefined
eventTouchpadPinch_sendEvent :: AttrLabelProxy "sendEvent"
eventTouchpadPinch_sendEvent = AttrLabelProxy
getEventTouchpadPinchPhase :: MonadIO m => EventTouchpadPinch -> m Gdk.Enums.TouchpadGesturePhase
getEventTouchpadPinchPhase s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 20) :: IO CUInt
let val' = (toEnum . fromIntegral) val
return val'
setEventTouchpadPinchPhase :: MonadIO m => EventTouchpadPinch -> Gdk.Enums.TouchpadGesturePhase -> m ()
setEventTouchpadPinchPhase s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = (fromIntegral . fromEnum) val
poke (ptr `plusPtr` 20) (val' :: CUInt)
data EventTouchpadPinchPhaseFieldInfo
instance AttrInfo EventTouchpadPinchPhaseFieldInfo where
type AttrAllowedOps EventTouchpadPinchPhaseFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventTouchpadPinchPhaseFieldInfo = (~) Gdk.Enums.TouchpadGesturePhase
type AttrBaseTypeConstraint EventTouchpadPinchPhaseFieldInfo = (~) EventTouchpadPinch
type AttrGetType EventTouchpadPinchPhaseFieldInfo = Gdk.Enums.TouchpadGesturePhase
type AttrLabel EventTouchpadPinchPhaseFieldInfo = "phase"
type AttrOrigin EventTouchpadPinchPhaseFieldInfo = EventTouchpadPinch
attrGet _ = getEventTouchpadPinchPhase
attrSet _ = setEventTouchpadPinchPhase
attrConstruct = undefined
attrClear _ = undefined
eventTouchpadPinch_phase :: AttrLabelProxy "phase"
eventTouchpadPinch_phase = AttrLabelProxy
getEventTouchpadPinchNFingers :: MonadIO m => EventTouchpadPinch -> m Int8
getEventTouchpadPinchNFingers s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 24) :: IO Int8
return val
setEventTouchpadPinchNFingers :: MonadIO m => EventTouchpadPinch -> Int8 -> m ()
setEventTouchpadPinchNFingers s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 24) (val :: Int8)
data EventTouchpadPinchNFingersFieldInfo
instance AttrInfo EventTouchpadPinchNFingersFieldInfo where
type AttrAllowedOps EventTouchpadPinchNFingersFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventTouchpadPinchNFingersFieldInfo = (~) Int8
type AttrBaseTypeConstraint EventTouchpadPinchNFingersFieldInfo = (~) EventTouchpadPinch
type AttrGetType EventTouchpadPinchNFingersFieldInfo = Int8
type AttrLabel EventTouchpadPinchNFingersFieldInfo = "n_fingers"
type AttrOrigin EventTouchpadPinchNFingersFieldInfo = EventTouchpadPinch
attrGet _ = getEventTouchpadPinchNFingers
attrSet _ = setEventTouchpadPinchNFingers
attrConstruct = undefined
attrClear _ = undefined
eventTouchpadPinch_nFingers :: AttrLabelProxy "nFingers"
eventTouchpadPinch_nFingers = AttrLabelProxy
getEventTouchpadPinchTime :: MonadIO m => EventTouchpadPinch -> m Word32
getEventTouchpadPinchTime s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 28) :: IO Word32
return val
setEventTouchpadPinchTime :: MonadIO m => EventTouchpadPinch -> Word32 -> m ()
setEventTouchpadPinchTime s val = liftIO $ withManagedPtr s $ \ptr -> do
poke (ptr `plusPtr` 28) (val :: Word32)
data EventTouchpadPinchTimeFieldInfo
instance AttrInfo EventTouchpadPinchTimeFieldInfo where
type AttrAllowedOps EventTouchpadPinchTimeFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventTouchpadPinchTimeFieldInfo = (~) Word32
type AttrBaseTypeConstraint EventTouchpadPinchTimeFieldInfo = (~) EventTouchpadPinch
type AttrGetType EventTouchpadPinchTimeFieldInfo = Word32
type AttrLabel EventTouchpadPinchTimeFieldInfo = "time"
type AttrOrigin EventTouchpadPinchTimeFieldInfo = EventTouchpadPinch
attrGet _ = getEventTouchpadPinchTime
attrSet _ = setEventTouchpadPinchTime
attrConstruct = undefined
attrClear _ = undefined
eventTouchpadPinch_time :: AttrLabelProxy "time"
eventTouchpadPinch_time = AttrLabelProxy
getEventTouchpadPinchX :: MonadIO m => EventTouchpadPinch -> m Double
getEventTouchpadPinchX s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 32) :: IO CDouble
let val' = realToFrac val
return val'
setEventTouchpadPinchX :: MonadIO m => EventTouchpadPinch -> Double -> m ()
setEventTouchpadPinchX s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 32) (val' :: CDouble)
data EventTouchpadPinchXFieldInfo
instance AttrInfo EventTouchpadPinchXFieldInfo where
type AttrAllowedOps EventTouchpadPinchXFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventTouchpadPinchXFieldInfo = (~) Double
type AttrBaseTypeConstraint EventTouchpadPinchXFieldInfo = (~) EventTouchpadPinch
type AttrGetType EventTouchpadPinchXFieldInfo = Double
type AttrLabel EventTouchpadPinchXFieldInfo = "x"
type AttrOrigin EventTouchpadPinchXFieldInfo = EventTouchpadPinch
attrGet _ = getEventTouchpadPinchX
attrSet _ = setEventTouchpadPinchX
attrConstruct = undefined
attrClear _ = undefined
eventTouchpadPinch_x :: AttrLabelProxy "x"
eventTouchpadPinch_x = AttrLabelProxy
getEventTouchpadPinchY :: MonadIO m => EventTouchpadPinch -> m Double
getEventTouchpadPinchY s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 40) :: IO CDouble
let val' = realToFrac val
return val'
setEventTouchpadPinchY :: MonadIO m => EventTouchpadPinch -> Double -> m ()
setEventTouchpadPinchY s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 40) (val' :: CDouble)
data EventTouchpadPinchYFieldInfo
instance AttrInfo EventTouchpadPinchYFieldInfo where
type AttrAllowedOps EventTouchpadPinchYFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventTouchpadPinchYFieldInfo = (~) Double
type AttrBaseTypeConstraint EventTouchpadPinchYFieldInfo = (~) EventTouchpadPinch
type AttrGetType EventTouchpadPinchYFieldInfo = Double
type AttrLabel EventTouchpadPinchYFieldInfo = "y"
type AttrOrigin EventTouchpadPinchYFieldInfo = EventTouchpadPinch
attrGet _ = getEventTouchpadPinchY
attrSet _ = setEventTouchpadPinchY
attrConstruct = undefined
attrClear _ = undefined
eventTouchpadPinch_y :: AttrLabelProxy "y"
eventTouchpadPinch_y = AttrLabelProxy
getEventTouchpadPinchDx :: MonadIO m => EventTouchpadPinch -> m Double
getEventTouchpadPinchDx s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 48) :: IO CDouble
let val' = realToFrac val
return val'
setEventTouchpadPinchDx :: MonadIO m => EventTouchpadPinch -> Double -> m ()
setEventTouchpadPinchDx s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 48) (val' :: CDouble)
data EventTouchpadPinchDxFieldInfo
instance AttrInfo EventTouchpadPinchDxFieldInfo where
type AttrAllowedOps EventTouchpadPinchDxFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventTouchpadPinchDxFieldInfo = (~) Double
type AttrBaseTypeConstraint EventTouchpadPinchDxFieldInfo = (~) EventTouchpadPinch
type AttrGetType EventTouchpadPinchDxFieldInfo = Double
type AttrLabel EventTouchpadPinchDxFieldInfo = "dx"
type AttrOrigin EventTouchpadPinchDxFieldInfo = EventTouchpadPinch
attrGet _ = getEventTouchpadPinchDx
attrSet _ = setEventTouchpadPinchDx
attrConstruct = undefined
attrClear _ = undefined
eventTouchpadPinch_dx :: AttrLabelProxy "dx"
eventTouchpadPinch_dx = AttrLabelProxy
getEventTouchpadPinchDy :: MonadIO m => EventTouchpadPinch -> m Double
getEventTouchpadPinchDy s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 56) :: IO CDouble
let val' = realToFrac val
return val'
setEventTouchpadPinchDy :: MonadIO m => EventTouchpadPinch -> Double -> m ()
setEventTouchpadPinchDy s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 56) (val' :: CDouble)
data EventTouchpadPinchDyFieldInfo
instance AttrInfo EventTouchpadPinchDyFieldInfo where
type AttrAllowedOps EventTouchpadPinchDyFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventTouchpadPinchDyFieldInfo = (~) Double
type AttrBaseTypeConstraint EventTouchpadPinchDyFieldInfo = (~) EventTouchpadPinch
type AttrGetType EventTouchpadPinchDyFieldInfo = Double
type AttrLabel EventTouchpadPinchDyFieldInfo = "dy"
type AttrOrigin EventTouchpadPinchDyFieldInfo = EventTouchpadPinch
attrGet _ = getEventTouchpadPinchDy
attrSet _ = setEventTouchpadPinchDy
attrConstruct = undefined
attrClear _ = undefined
eventTouchpadPinch_dy :: AttrLabelProxy "dy"
eventTouchpadPinch_dy = AttrLabelProxy
getEventTouchpadPinchAngleDelta :: MonadIO m => EventTouchpadPinch -> m Double
getEventTouchpadPinchAngleDelta s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 64) :: IO CDouble
let val' = realToFrac val
return val'
setEventTouchpadPinchAngleDelta :: MonadIO m => EventTouchpadPinch -> Double -> m ()
setEventTouchpadPinchAngleDelta s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 64) (val' :: CDouble)
data EventTouchpadPinchAngleDeltaFieldInfo
instance AttrInfo EventTouchpadPinchAngleDeltaFieldInfo where
type AttrAllowedOps EventTouchpadPinchAngleDeltaFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventTouchpadPinchAngleDeltaFieldInfo = (~) Double
type AttrBaseTypeConstraint EventTouchpadPinchAngleDeltaFieldInfo = (~) EventTouchpadPinch
type AttrGetType EventTouchpadPinchAngleDeltaFieldInfo = Double
type AttrLabel EventTouchpadPinchAngleDeltaFieldInfo = "angle_delta"
type AttrOrigin EventTouchpadPinchAngleDeltaFieldInfo = EventTouchpadPinch
attrGet _ = getEventTouchpadPinchAngleDelta
attrSet _ = setEventTouchpadPinchAngleDelta
attrConstruct = undefined
attrClear _ = undefined
eventTouchpadPinch_angleDelta :: AttrLabelProxy "angleDelta"
eventTouchpadPinch_angleDelta = AttrLabelProxy
getEventTouchpadPinchScale :: MonadIO m => EventTouchpadPinch -> m Double
getEventTouchpadPinchScale s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 72) :: IO CDouble
let val' = realToFrac val
return val'
setEventTouchpadPinchScale :: MonadIO m => EventTouchpadPinch -> Double -> m ()
setEventTouchpadPinchScale s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 72) (val' :: CDouble)
data EventTouchpadPinchScaleFieldInfo
instance AttrInfo EventTouchpadPinchScaleFieldInfo where
type AttrAllowedOps EventTouchpadPinchScaleFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventTouchpadPinchScaleFieldInfo = (~) Double
type AttrBaseTypeConstraint EventTouchpadPinchScaleFieldInfo = (~) EventTouchpadPinch
type AttrGetType EventTouchpadPinchScaleFieldInfo = Double
type AttrLabel EventTouchpadPinchScaleFieldInfo = "scale"
type AttrOrigin EventTouchpadPinchScaleFieldInfo = EventTouchpadPinch
attrGet _ = getEventTouchpadPinchScale
attrSet _ = setEventTouchpadPinchScale
attrConstruct = undefined
attrClear _ = undefined
eventTouchpadPinch_scale :: AttrLabelProxy "scale"
eventTouchpadPinch_scale = AttrLabelProxy
getEventTouchpadPinchXRoot :: MonadIO m => EventTouchpadPinch -> m Double
getEventTouchpadPinchXRoot s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 80) :: IO CDouble
let val' = realToFrac val
return val'
setEventTouchpadPinchXRoot :: MonadIO m => EventTouchpadPinch -> Double -> m ()
setEventTouchpadPinchXRoot s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 80) (val' :: CDouble)
data EventTouchpadPinchXRootFieldInfo
instance AttrInfo EventTouchpadPinchXRootFieldInfo where
type AttrAllowedOps EventTouchpadPinchXRootFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventTouchpadPinchXRootFieldInfo = (~) Double
type AttrBaseTypeConstraint EventTouchpadPinchXRootFieldInfo = (~) EventTouchpadPinch
type AttrGetType EventTouchpadPinchXRootFieldInfo = Double
type AttrLabel EventTouchpadPinchXRootFieldInfo = "x_root"
type AttrOrigin EventTouchpadPinchXRootFieldInfo = EventTouchpadPinch
attrGet _ = getEventTouchpadPinchXRoot
attrSet _ = setEventTouchpadPinchXRoot
attrConstruct = undefined
attrClear _ = undefined
eventTouchpadPinch_xRoot :: AttrLabelProxy "xRoot"
eventTouchpadPinch_xRoot = AttrLabelProxy
getEventTouchpadPinchYRoot :: MonadIO m => EventTouchpadPinch -> m Double
getEventTouchpadPinchYRoot s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 88) :: IO CDouble
let val' = realToFrac val
return val'
setEventTouchpadPinchYRoot :: MonadIO m => EventTouchpadPinch -> Double -> m ()
setEventTouchpadPinchYRoot s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = realToFrac val
poke (ptr `plusPtr` 88) (val' :: CDouble)
data EventTouchpadPinchYRootFieldInfo
instance AttrInfo EventTouchpadPinchYRootFieldInfo where
type AttrAllowedOps EventTouchpadPinchYRootFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventTouchpadPinchYRootFieldInfo = (~) Double
type AttrBaseTypeConstraint EventTouchpadPinchYRootFieldInfo = (~) EventTouchpadPinch
type AttrGetType EventTouchpadPinchYRootFieldInfo = Double
type AttrLabel EventTouchpadPinchYRootFieldInfo = "y_root"
type AttrOrigin EventTouchpadPinchYRootFieldInfo = EventTouchpadPinch
attrGet _ = getEventTouchpadPinchYRoot
attrSet _ = setEventTouchpadPinchYRoot
attrConstruct = undefined
attrClear _ = undefined
eventTouchpadPinch_yRoot :: AttrLabelProxy "yRoot"
eventTouchpadPinch_yRoot = AttrLabelProxy
getEventTouchpadPinchState :: MonadIO m => EventTouchpadPinch -> m [Gdk.Flags.ModifierType]
getEventTouchpadPinchState s = liftIO $ withManagedPtr s $ \ptr -> do
val <- peek (ptr `plusPtr` 96) :: IO CUInt
let val' = wordToGFlags val
return val'
setEventTouchpadPinchState :: MonadIO m => EventTouchpadPinch -> [Gdk.Flags.ModifierType] -> m ()
setEventTouchpadPinchState s val = liftIO $ withManagedPtr s $ \ptr -> do
let val' = gflagsToWord val
poke (ptr `plusPtr` 96) (val' :: CUInt)
data EventTouchpadPinchStateFieldInfo
instance AttrInfo EventTouchpadPinchStateFieldInfo where
type AttrAllowedOps EventTouchpadPinchStateFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint EventTouchpadPinchStateFieldInfo = (~) [Gdk.Flags.ModifierType]
type AttrBaseTypeConstraint EventTouchpadPinchStateFieldInfo = (~) EventTouchpadPinch
type AttrGetType EventTouchpadPinchStateFieldInfo = [Gdk.Flags.ModifierType]
type AttrLabel EventTouchpadPinchStateFieldInfo = "state"
type AttrOrigin EventTouchpadPinchStateFieldInfo = EventTouchpadPinch
attrGet _ = getEventTouchpadPinchState
attrSet _ = setEventTouchpadPinchState
attrConstruct = undefined
attrClear _ = undefined
eventTouchpadPinch_state :: AttrLabelProxy "state"
eventTouchpadPinch_state = AttrLabelProxy
instance O.HasAttributeList EventTouchpadPinch
type instance O.AttributeList EventTouchpadPinch = EventTouchpadPinchAttributeList
type EventTouchpadPinchAttributeList = ('[ '("type", EventTouchpadPinchTypeFieldInfo), '("window", EventTouchpadPinchWindowFieldInfo), '("sendEvent", EventTouchpadPinchSendEventFieldInfo), '("phase", EventTouchpadPinchPhaseFieldInfo), '("nFingers", EventTouchpadPinchNFingersFieldInfo), '("time", EventTouchpadPinchTimeFieldInfo), '("x", EventTouchpadPinchXFieldInfo), '("y", EventTouchpadPinchYFieldInfo), '("dx", EventTouchpadPinchDxFieldInfo), '("dy", EventTouchpadPinchDyFieldInfo), '("angleDelta", EventTouchpadPinchAngleDeltaFieldInfo), '("scale", EventTouchpadPinchScaleFieldInfo), '("xRoot", EventTouchpadPinchXRootFieldInfo), '("yRoot", EventTouchpadPinchYRootFieldInfo), '("state", EventTouchpadPinchStateFieldInfo)] :: [(Symbol, *)])
type family ResolveEventTouchpadPinchMethod (t :: Symbol) (o :: *) :: * where
ResolveEventTouchpadPinchMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveEventTouchpadPinchMethod t EventTouchpadPinch, O.MethodInfo info EventTouchpadPinch p) => O.IsLabelProxy t (EventTouchpadPinch -> p) where
fromLabelProxy _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#if MIN_VERSION_base(4,9,0)
instance (info ~ ResolveEventTouchpadPinchMethod t EventTouchpadPinch, O.MethodInfo info EventTouchpadPinch p) => O.IsLabel t (EventTouchpadPinch -> p) where
fromLabel _ = O.overloadedMethod (O.MethodProxy :: O.MethodProxy info)
#endif