gi-gdk-3.0.10: Gdk bindings

CopyrightWill Thompson, Iñaki García Etxebarria and Jonas Platte
LicenseLGPL-2.1
MaintainerIñaki García Etxebarria (garetxe@gmail.com)
Safe HaskellNone
LanguageHaskell2010

GI.Gdk.Objects.Device

Contents

Description

 

Synopsis

Exported types

newtype Device Source #

Constructors

Device (ManagedPtr Device) 

Instances

GObject Device Source # 
IsObject Device Source # 
IsDevice Device Source # 
((~) * info (ResolveDeviceMethod t Device), MethodInfo * info Device p) => IsLabel t (Device -> p) Source # 

Methods

fromLabel :: Proxy# Symbol t -> Device -> p #

((~) * info (ResolveDeviceMethod t Device), MethodInfo * info Device p) => IsLabelProxy t (Device -> p) Source # 

Methods

fromLabelProxy :: Proxy Symbol t -> Device -> p

HasAttributeList * Device Source # 
type SignalList Device Source # 
type SignalList Device
type AttributeList Device Source # 
type AttributeList Device

class GObject o => IsDevice o Source #

Instances

(GObject a, UnknownAncestorError Constraint Device a) => IsDevice a Source # 
IsDevice Device Source # 

Methods

getAssociatedDevice

data DeviceGetAssociatedDeviceMethodInfo Source #

Instances

((~) * signature (m (Maybe Device)), MonadIO m, IsDevice a) => MethodInfo * DeviceGetAssociatedDeviceMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGetAssociatedDeviceMethodInfo a -> signature -> s

getAxisUse

data DeviceGetAxisUseMethodInfo Source #

Instances

((~) * signature (Word32 -> m AxisUse), MonadIO m, IsDevice a) => MethodInfo * DeviceGetAxisUseMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGetAxisUseMethodInfo a -> signature -> s

getDeviceType

data DeviceGetDeviceTypeMethodInfo Source #

Instances

((~) * signature (m DeviceType), MonadIO m, IsDevice a) => MethodInfo * DeviceGetDeviceTypeMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGetDeviceTypeMethodInfo a -> signature -> s

getDisplay

data DeviceGetDisplayMethodInfo Source #

Instances

((~) * signature (m Display), MonadIO m, IsDevice a) => MethodInfo * DeviceGetDisplayMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGetDisplayMethodInfo a -> signature -> s

getHasCursor

data DeviceGetHasCursorMethodInfo Source #

Instances

((~) * signature (m Bool), MonadIO m, IsDevice a) => MethodInfo * DeviceGetHasCursorMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGetHasCursorMethodInfo a -> signature -> s

getKey

data DeviceGetKeyMethodInfo Source #

Instances

((~) * signature (Word32 -> m (Bool, Word32, [ModifierType])), MonadIO m, IsDevice a) => MethodInfo * DeviceGetKeyMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGetKeyMethodInfo a -> signature -> s

getLastEventWindow

data DeviceGetLastEventWindowMethodInfo Source #

Instances

((~) * signature (m (Maybe Window)), MonadIO m, IsDevice a) => MethodInfo * DeviceGetLastEventWindowMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGetLastEventWindowMethodInfo a -> signature -> s

getMode

data DeviceGetModeMethodInfo Source #

Instances

((~) * signature (m InputMode), MonadIO m, IsDevice a) => MethodInfo * DeviceGetModeMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGetModeMethodInfo a -> signature -> s

getNAxes

data DeviceGetNAxesMethodInfo Source #

Instances

((~) * signature (m Int32), MonadIO m, IsDevice a) => MethodInfo * DeviceGetNAxesMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGetNAxesMethodInfo a -> signature -> s

getNKeys

data DeviceGetNKeysMethodInfo Source #

Instances

((~) * signature (m Int32), MonadIO m, IsDevice a) => MethodInfo * DeviceGetNKeysMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGetNKeysMethodInfo a -> signature -> s

getName

data DeviceGetNameMethodInfo Source #

Instances

((~) * signature (m Text), MonadIO m, IsDevice a) => MethodInfo * DeviceGetNameMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGetNameMethodInfo a -> signature -> s

deviceGetName :: (MonadIO m, IsDevice a) => a -> m Text Source #

getPosition

data DeviceGetPositionMethodInfo Source #

Instances

((~) * signature (m (Screen, Int32, Int32)), MonadIO m, IsDevice a) => MethodInfo * DeviceGetPositionMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGetPositionMethodInfo a -> signature -> s

getPositionDouble

data DeviceGetPositionDoubleMethodInfo Source #

Instances

((~) * signature (m (Screen, Double, Double)), MonadIO m, IsDevice a) => MethodInfo * DeviceGetPositionDoubleMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGetPositionDoubleMethodInfo a -> signature -> s

getProductId

data DeviceGetProductIdMethodInfo Source #

Instances

((~) * signature (m (Maybe Text)), MonadIO m, IsDevice a) => MethodInfo * DeviceGetProductIdMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGetProductIdMethodInfo a -> signature -> s

deviceGetProductId :: (MonadIO m, IsDevice a) => a -> m (Maybe Text) Source #

getSeat

data DeviceGetSeatMethodInfo Source #

Instances

((~) * signature (m Seat), MonadIO m, IsDevice a) => MethodInfo * DeviceGetSeatMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGetSeatMethodInfo a -> signature -> s

getSource

data DeviceGetSourceMethodInfo Source #

Instances

((~) * signature (m InputSource), MonadIO m, IsDevice a) => MethodInfo * DeviceGetSourceMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGetSourceMethodInfo a -> signature -> s

getVendorId

data DeviceGetVendorIdMethodInfo Source #

Instances

((~) * signature (m (Maybe Text)), MonadIO m, IsDevice a) => MethodInfo * DeviceGetVendorIdMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGetVendorIdMethodInfo a -> signature -> s

deviceGetVendorId :: (MonadIO m, IsDevice a) => a -> m (Maybe Text) Source #

getWindowAtPosition

data DeviceGetWindowAtPositionMethodInfo Source #

Instances

((~) * signature (m (Maybe Window, Int32, Int32)), MonadIO m, IsDevice a) => MethodInfo * DeviceGetWindowAtPositionMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGetWindowAtPositionMethodInfo a -> signature -> s

getWindowAtPositionDouble

grab

data DeviceGrabMethodInfo Source #

Instances

((~) * signature (b -> GrabOwnership -> Bool -> [EventMask] -> Maybe c -> Word32 -> m GrabStatus), MonadIO m, IsDevice a, IsWindow b, IsCursor c) => MethodInfo * DeviceGrabMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceGrabMethodInfo a -> signature -> s

deviceGrab :: (MonadIO m, IsDevice a, IsWindow b, IsCursor c) => a -> b -> GrabOwnership -> Bool -> [EventMask] -> Maybe c -> Word32 -> m GrabStatus Source #

Deprecated: (Since version 3.20.)Use gdk_seat_grab() instead.

grabInfoLibgtkOnly

deviceGrabInfoLibgtkOnly :: (MonadIO m, IsDisplay a, IsDevice b) => a -> b -> m (Bool, Window, Bool) Source #

Deprecated: (Since version 3.16)The symbol was never meant to be used outside of GTK+

listAxes

data DeviceListAxesMethodInfo Source #

Instances

((~) * signature (m [Atom]), MonadIO m, IsDevice a) => MethodInfo * DeviceListAxesMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceListAxesMethodInfo a -> signature -> s

deviceListAxes :: (MonadIO m, IsDevice a) => a -> m [Atom] Source #

listSlaveDevices

data DeviceListSlaveDevicesMethodInfo Source #

Instances

((~) * signature (m [Device]), MonadIO m, IsDevice a) => MethodInfo * DeviceListSlaveDevicesMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceListSlaveDevicesMethodInfo a -> signature -> s

setAxisUse

data DeviceSetAxisUseMethodInfo Source #

Instances

((~) * signature (Word32 -> AxisUse -> m ()), MonadIO m, IsDevice a) => MethodInfo * DeviceSetAxisUseMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceSetAxisUseMethodInfo a -> signature -> s

deviceSetAxisUse :: (MonadIO m, IsDevice a) => a -> Word32 -> AxisUse -> m () Source #

setKey

data DeviceSetKeyMethodInfo Source #

Instances

((~) * signature (Word32 -> Word32 -> [ModifierType] -> m ()), MonadIO m, IsDevice a) => MethodInfo * DeviceSetKeyMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceSetKeyMethodInfo a -> signature -> s

deviceSetKey :: (MonadIO m, IsDevice a) => a -> Word32 -> Word32 -> [ModifierType] -> m () Source #

setMode

data DeviceSetModeMethodInfo Source #

Instances

((~) * signature (InputMode -> m Bool), MonadIO m, IsDevice a) => MethodInfo * DeviceSetModeMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceSetModeMethodInfo a -> signature -> s

ungrab

data DeviceUngrabMethodInfo Source #

Instances

((~) * signature (Word32 -> m ()), MonadIO m, IsDevice a) => MethodInfo * DeviceUngrabMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceUngrabMethodInfo a -> signature -> s

deviceUngrab :: (MonadIO m, IsDevice a) => a -> Word32 -> m () Source #

Deprecated: (Since version 3.20.)Use gdk_seat_ungrab() instead.

warp

data DeviceWarpMethodInfo Source #

Instances

((~) * signature (b -> Int32 -> Int32 -> m ()), MonadIO m, IsDevice a, IsScreen b) => MethodInfo * DeviceWarpMethodInfo a signature Source # 

Methods

overloadedMethod :: MethodProxy DeviceWarpMethodInfo a -> signature -> s

deviceWarp :: (MonadIO m, IsDevice a, IsScreen b) => a -> b -> Int32 -> Int32 -> m () Source #

Properties

associatedDevice

data DeviceAssociatedDevicePropertyInfo Source #

Instances

AttrInfo DeviceAssociatedDevicePropertyInfo Source # 

Associated Types

type AttrAllowedOps DeviceAssociatedDevicePropertyInfo :: [AttrOpTag]

type AttrSetTypeConstraint DeviceAssociatedDevicePropertyInfo :: * -> Constraint

type AttrBaseTypeConstraint DeviceAssociatedDevicePropertyInfo :: * -> Constraint

type AttrGetType DeviceAssociatedDevicePropertyInfo :: *

type AttrLabel DeviceAssociatedDevicePropertyInfo :: Symbol

type AttrOrigin DeviceAssociatedDevicePropertyInfo :: *

type AttrSetTypeConstraint DeviceAssociatedDevicePropertyInfo Source # 
type AttrSetTypeConstraint DeviceAssociatedDevicePropertyInfo = * ~ ()
type AttrOrigin DeviceAssociatedDevicePropertyInfo Source # 
type AttrLabel DeviceAssociatedDevicePropertyInfo Source # 
type AttrLabel DeviceAssociatedDevicePropertyInfo = "associated-device"
type AttrGetType DeviceAssociatedDevicePropertyInfo Source # 
type AttrBaseTypeConstraint DeviceAssociatedDevicePropertyInfo Source # 
type AttrBaseTypeConstraint DeviceAssociatedDevicePropertyInfo = IsDevice
type AttrAllowedOps DeviceAssociatedDevicePropertyInfo Source # 
type AttrAllowedOps DeviceAssociatedDevicePropertyInfo = (:) AttrOpTag AttrGet ((:) AttrOpTag AttrClear ([] AttrOpTag))

deviceAssociatedDevice :: AttrLabelProxy "associatedDevice" Source #

deviceManager

data DeviceDeviceManagerPropertyInfo Source #

Instances

AttrInfo DeviceDeviceManagerPropertyInfo Source # 

Associated Types

type AttrAllowedOps DeviceDeviceManagerPropertyInfo :: [AttrOpTag]

type AttrSetTypeConstraint DeviceDeviceManagerPropertyInfo :: * -> Constraint

type AttrBaseTypeConstraint DeviceDeviceManagerPropertyInfo :: * -> Constraint

type AttrGetType DeviceDeviceManagerPropertyInfo :: *

type AttrLabel DeviceDeviceManagerPropertyInfo :: Symbol

type AttrOrigin DeviceDeviceManagerPropertyInfo :: *

Methods

attrGet :: AttrBaseTypeConstraint DeviceDeviceManagerPropertyInfo o => Proxy * DeviceDeviceManagerPropertyInfo -> o -> IO (AttrGetType DeviceDeviceManagerPropertyInfo)

attrSet :: (AttrBaseTypeConstraint DeviceDeviceManagerPropertyInfo o, AttrSetTypeConstraint DeviceDeviceManagerPropertyInfo b) => Proxy * DeviceDeviceManagerPropertyInfo -> o -> b -> IO ()

attrClear :: AttrBaseTypeConstraint DeviceDeviceManagerPropertyInfo o => Proxy * DeviceDeviceManagerPropertyInfo -> o -> IO ()

attrConstruct :: (AttrBaseTypeConstraint DeviceDeviceManagerPropertyInfo o, AttrSetTypeConstraint DeviceDeviceManagerPropertyInfo b) => Proxy * DeviceDeviceManagerPropertyInfo -> b -> IO (GValueConstruct o)

type AttrSetTypeConstraint DeviceDeviceManagerPropertyInfo Source # 
type AttrOrigin DeviceDeviceManagerPropertyInfo Source # 
type AttrLabel DeviceDeviceManagerPropertyInfo Source # 
type AttrLabel DeviceDeviceManagerPropertyInfo = "device-manager"
type AttrGetType DeviceDeviceManagerPropertyInfo Source # 
type AttrBaseTypeConstraint DeviceDeviceManagerPropertyInfo Source # 
type AttrBaseTypeConstraint DeviceDeviceManagerPropertyInfo = IsDevice
type AttrAllowedOps DeviceDeviceManagerPropertyInfo Source # 
type AttrAllowedOps DeviceDeviceManagerPropertyInfo = (:) AttrOpTag AttrConstruct ((:) AttrOpTag AttrGet ((:) AttrOpTag AttrClear ([] AttrOpTag)))

constructDeviceDeviceManager :: (IsDevice o, IsDeviceManager a) => a -> IO (GValueConstruct o) Source #

deviceDeviceManager :: AttrLabelProxy "deviceManager" Source #

display

data DeviceDisplayPropertyInfo Source #

Instances

AttrInfo DeviceDisplayPropertyInfo Source # 

Associated Types

type AttrAllowedOps DeviceDisplayPropertyInfo :: [AttrOpTag]

type AttrSetTypeConstraint DeviceDisplayPropertyInfo :: * -> Constraint

type AttrBaseTypeConstraint DeviceDisplayPropertyInfo :: * -> Constraint

type AttrGetType DeviceDisplayPropertyInfo :: *

type AttrLabel DeviceDisplayPropertyInfo :: Symbol

type AttrOrigin DeviceDisplayPropertyInfo :: *

Methods

attrGet :: AttrBaseTypeConstraint DeviceDisplayPropertyInfo o => Proxy * DeviceDisplayPropertyInfo -> o -> IO (AttrGetType DeviceDisplayPropertyInfo)

attrSet :: (AttrBaseTypeConstraint DeviceDisplayPropertyInfo o, AttrSetTypeConstraint DeviceDisplayPropertyInfo b) => Proxy * DeviceDisplayPropertyInfo -> o -> b -> IO ()

attrClear :: AttrBaseTypeConstraint DeviceDisplayPropertyInfo o => Proxy * DeviceDisplayPropertyInfo -> o -> IO ()

attrConstruct :: (AttrBaseTypeConstraint DeviceDisplayPropertyInfo o, AttrSetTypeConstraint DeviceDisplayPropertyInfo b) => Proxy * DeviceDisplayPropertyInfo -> b -> IO (GValueConstruct o)

type AttrSetTypeConstraint DeviceDisplayPropertyInfo Source # 
type AttrSetTypeConstraint DeviceDisplayPropertyInfo = IsDisplay
type AttrOrigin DeviceDisplayPropertyInfo Source # 
type AttrLabel DeviceDisplayPropertyInfo Source # 
type AttrLabel DeviceDisplayPropertyInfo = "display"
type AttrGetType DeviceDisplayPropertyInfo Source # 
type AttrBaseTypeConstraint DeviceDisplayPropertyInfo Source # 
type AttrBaseTypeConstraint DeviceDisplayPropertyInfo = IsDevice
type AttrAllowedOps DeviceDisplayPropertyInfo Source # 
type AttrAllowedOps DeviceDisplayPropertyInfo = (:) AttrOpTag AttrConstruct ((:) AttrOpTag AttrGet ((:) AttrOpTag AttrClear ([] AttrOpTag)))

constructDeviceDisplay :: (IsDevice o, IsDisplay a) => a -> IO (GValueConstruct o) Source #

deviceDisplay :: AttrLabelProxy "display" Source #

hasCursor

data DeviceHasCursorPropertyInfo Source #

Instances

AttrInfo DeviceHasCursorPropertyInfo Source # 

Associated Types

type AttrAllowedOps DeviceHasCursorPropertyInfo :: [AttrOpTag]

type AttrSetTypeConstraint DeviceHasCursorPropertyInfo :: * -> Constraint

type AttrBaseTypeConstraint DeviceHasCursorPropertyInfo :: * -> Constraint

type AttrGetType DeviceHasCursorPropertyInfo :: *

type AttrLabel DeviceHasCursorPropertyInfo :: Symbol

type AttrOrigin DeviceHasCursorPropertyInfo :: *

Methods

attrGet :: AttrBaseTypeConstraint DeviceHasCursorPropertyInfo o => Proxy * DeviceHasCursorPropertyInfo -> o -> IO (AttrGetType DeviceHasCursorPropertyInfo)

attrSet :: (AttrBaseTypeConstraint DeviceHasCursorPropertyInfo o, AttrSetTypeConstraint DeviceHasCursorPropertyInfo b) => Proxy * DeviceHasCursorPropertyInfo -> o -> b -> IO ()

attrClear :: AttrBaseTypeConstraint DeviceHasCursorPropertyInfo o => Proxy * DeviceHasCursorPropertyInfo -> o -> IO ()

attrConstruct :: (AttrBaseTypeConstraint DeviceHasCursorPropertyInfo o, AttrSetTypeConstraint DeviceHasCursorPropertyInfo b) => Proxy * DeviceHasCursorPropertyInfo -> b -> IO (GValueConstruct o)

type AttrSetTypeConstraint DeviceHasCursorPropertyInfo Source # 
type AttrSetTypeConstraint DeviceHasCursorPropertyInfo = * ~ Bool
type AttrOrigin DeviceHasCursorPropertyInfo Source # 
type AttrLabel DeviceHasCursorPropertyInfo Source # 
type AttrLabel DeviceHasCursorPropertyInfo = "has-cursor"
type AttrGetType DeviceHasCursorPropertyInfo Source # 
type AttrBaseTypeConstraint DeviceHasCursorPropertyInfo Source # 
type AttrBaseTypeConstraint DeviceHasCursorPropertyInfo = IsDevice
type AttrAllowedOps DeviceHasCursorPropertyInfo Source # 
type AttrAllowedOps DeviceHasCursorPropertyInfo = (:) AttrOpTag AttrConstruct ((:) AttrOpTag AttrGet ([] AttrOpTag))

constructDeviceHasCursor :: IsDevice o => Bool -> IO (GValueConstruct o) Source #

deviceHasCursor :: AttrLabelProxy "hasCursor" Source #

inputMode

data DeviceInputModePropertyInfo Source #

Instances

AttrInfo DeviceInputModePropertyInfo Source # 

Associated Types

type AttrAllowedOps DeviceInputModePropertyInfo :: [AttrOpTag]

type AttrSetTypeConstraint DeviceInputModePropertyInfo :: * -> Constraint

type AttrBaseTypeConstraint DeviceInputModePropertyInfo :: * -> Constraint

type AttrGetType DeviceInputModePropertyInfo :: *

type AttrLabel DeviceInputModePropertyInfo :: Symbol

type AttrOrigin DeviceInputModePropertyInfo :: *

Methods

attrGet :: AttrBaseTypeConstraint DeviceInputModePropertyInfo o => Proxy * DeviceInputModePropertyInfo -> o -> IO (AttrGetType DeviceInputModePropertyInfo)

attrSet :: (AttrBaseTypeConstraint DeviceInputModePropertyInfo o, AttrSetTypeConstraint DeviceInputModePropertyInfo b) => Proxy * DeviceInputModePropertyInfo -> o -> b -> IO ()

attrClear :: AttrBaseTypeConstraint DeviceInputModePropertyInfo o => Proxy * DeviceInputModePropertyInfo -> o -> IO ()

attrConstruct :: (AttrBaseTypeConstraint DeviceInputModePropertyInfo o, AttrSetTypeConstraint DeviceInputModePropertyInfo b) => Proxy * DeviceInputModePropertyInfo -> b -> IO (GValueConstruct o)

type AttrSetTypeConstraint DeviceInputModePropertyInfo Source # 
type AttrSetTypeConstraint DeviceInputModePropertyInfo = * ~ InputMode
type AttrOrigin DeviceInputModePropertyInfo Source # 
type AttrLabel DeviceInputModePropertyInfo Source # 
type AttrLabel DeviceInputModePropertyInfo = "input-mode"
type AttrGetType DeviceInputModePropertyInfo Source # 
type AttrBaseTypeConstraint DeviceInputModePropertyInfo Source # 
type AttrBaseTypeConstraint DeviceInputModePropertyInfo = IsDevice
type AttrAllowedOps DeviceInputModePropertyInfo Source # 
type AttrAllowedOps DeviceInputModePropertyInfo = (:) AttrOpTag AttrSet ((:) AttrOpTag AttrConstruct ((:) AttrOpTag AttrGet ([] AttrOpTag)))

constructDeviceInputMode :: IsDevice o => InputMode -> IO (GValueConstruct o) Source #

deviceInputMode :: AttrLabelProxy "inputMode" Source #

inputSource

data DeviceInputSourcePropertyInfo Source #

Instances

AttrInfo DeviceInputSourcePropertyInfo Source # 

Associated Types

type AttrAllowedOps DeviceInputSourcePropertyInfo :: [AttrOpTag]

type AttrSetTypeConstraint DeviceInputSourcePropertyInfo :: * -> Constraint

type AttrBaseTypeConstraint DeviceInputSourcePropertyInfo :: * -> Constraint

type AttrGetType DeviceInputSourcePropertyInfo :: *

type AttrLabel DeviceInputSourcePropertyInfo :: Symbol

type AttrOrigin DeviceInputSourcePropertyInfo :: *

Methods

attrGet :: AttrBaseTypeConstraint DeviceInputSourcePropertyInfo o => Proxy * DeviceInputSourcePropertyInfo -> o -> IO (AttrGetType DeviceInputSourcePropertyInfo)

attrSet :: (AttrBaseTypeConstraint DeviceInputSourcePropertyInfo o, AttrSetTypeConstraint DeviceInputSourcePropertyInfo b) => Proxy * DeviceInputSourcePropertyInfo -> o -> b -> IO ()

attrClear :: AttrBaseTypeConstraint DeviceInputSourcePropertyInfo o => Proxy * DeviceInputSourcePropertyInfo -> o -> IO ()

attrConstruct :: (AttrBaseTypeConstraint DeviceInputSourcePropertyInfo o, AttrSetTypeConstraint DeviceInputSourcePropertyInfo b) => Proxy * DeviceInputSourcePropertyInfo -> b -> IO (GValueConstruct o)

type AttrSetTypeConstraint DeviceInputSourcePropertyInfo Source # 
type AttrSetTypeConstraint DeviceInputSourcePropertyInfo = * ~ InputSource
type AttrOrigin DeviceInputSourcePropertyInfo Source # 
type AttrLabel DeviceInputSourcePropertyInfo Source # 
type AttrLabel DeviceInputSourcePropertyInfo = "input-source"
type AttrGetType DeviceInputSourcePropertyInfo Source # 
type AttrBaseTypeConstraint DeviceInputSourcePropertyInfo Source # 
type AttrBaseTypeConstraint DeviceInputSourcePropertyInfo = IsDevice
type AttrAllowedOps DeviceInputSourcePropertyInfo Source # 
type AttrAllowedOps DeviceInputSourcePropertyInfo = (:) AttrOpTag AttrConstruct ((:) AttrOpTag AttrGet ([] AttrOpTag))

constructDeviceInputSource :: IsDevice o => InputSource -> IO (GValueConstruct o) Source #

deviceInputSource :: AttrLabelProxy "inputSource" Source #

nAxes

data DeviceNAxesPropertyInfo Source #

Instances

AttrInfo DeviceNAxesPropertyInfo Source # 

Associated Types

type AttrAllowedOps DeviceNAxesPropertyInfo :: [AttrOpTag]

type AttrSetTypeConstraint DeviceNAxesPropertyInfo :: * -> Constraint

type AttrBaseTypeConstraint DeviceNAxesPropertyInfo :: * -> Constraint

type AttrGetType DeviceNAxesPropertyInfo :: *

type AttrLabel DeviceNAxesPropertyInfo :: Symbol

type AttrOrigin DeviceNAxesPropertyInfo :: *

Methods

attrGet :: AttrBaseTypeConstraint DeviceNAxesPropertyInfo o => Proxy * DeviceNAxesPropertyInfo -> o -> IO (AttrGetType DeviceNAxesPropertyInfo)

attrSet :: (AttrBaseTypeConstraint DeviceNAxesPropertyInfo o, AttrSetTypeConstraint DeviceNAxesPropertyInfo b) => Proxy * DeviceNAxesPropertyInfo -> o -> b -> IO ()

attrClear :: AttrBaseTypeConstraint DeviceNAxesPropertyInfo o => Proxy * DeviceNAxesPropertyInfo -> o -> IO ()

attrConstruct :: (AttrBaseTypeConstraint DeviceNAxesPropertyInfo o, AttrSetTypeConstraint DeviceNAxesPropertyInfo b) => Proxy * DeviceNAxesPropertyInfo -> b -> IO (GValueConstruct o)

type AttrSetTypeConstraint DeviceNAxesPropertyInfo Source # 
type AttrSetTypeConstraint DeviceNAxesPropertyInfo = * ~ ()
type AttrOrigin DeviceNAxesPropertyInfo Source # 
type AttrLabel DeviceNAxesPropertyInfo Source # 
type AttrLabel DeviceNAxesPropertyInfo = "n-axes"
type AttrGetType DeviceNAxesPropertyInfo Source # 
type AttrGetType DeviceNAxesPropertyInfo = Word32
type AttrBaseTypeConstraint DeviceNAxesPropertyInfo Source # 
type AttrBaseTypeConstraint DeviceNAxesPropertyInfo = IsDevice
type AttrAllowedOps DeviceNAxesPropertyInfo Source # 
type AttrAllowedOps DeviceNAxesPropertyInfo = (:) AttrOpTag AttrGet ([] AttrOpTag)

deviceNAxes :: AttrLabelProxy "nAxes" Source #

name

data DeviceNamePropertyInfo Source #

Instances

AttrInfo DeviceNamePropertyInfo Source # 

Associated Types

type AttrAllowedOps DeviceNamePropertyInfo :: [AttrOpTag]

type AttrSetTypeConstraint DeviceNamePropertyInfo :: * -> Constraint

type AttrBaseTypeConstraint DeviceNamePropertyInfo :: * -> Constraint

type AttrGetType DeviceNamePropertyInfo :: *

type AttrLabel DeviceNamePropertyInfo :: Symbol

type AttrOrigin DeviceNamePropertyInfo :: *

Methods

attrGet :: AttrBaseTypeConstraint DeviceNamePropertyInfo o => Proxy * DeviceNamePropertyInfo -> o -> IO (AttrGetType DeviceNamePropertyInfo)

attrSet :: (AttrBaseTypeConstraint DeviceNamePropertyInfo o, AttrSetTypeConstraint DeviceNamePropertyInfo b) => Proxy * DeviceNamePropertyInfo -> o -> b -> IO ()

attrClear :: AttrBaseTypeConstraint DeviceNamePropertyInfo o => Proxy * DeviceNamePropertyInfo -> o -> IO ()

attrConstruct :: (AttrBaseTypeConstraint DeviceNamePropertyInfo o, AttrSetTypeConstraint DeviceNamePropertyInfo b) => Proxy * DeviceNamePropertyInfo -> b -> IO (GValueConstruct o)

type AttrSetTypeConstraint DeviceNamePropertyInfo Source # 
type AttrSetTypeConstraint DeviceNamePropertyInfo = * ~ Text
type AttrOrigin DeviceNamePropertyInfo Source # 
type AttrOrigin DeviceNamePropertyInfo = Device
type AttrLabel DeviceNamePropertyInfo Source # 
type AttrLabel DeviceNamePropertyInfo = "name"
type AttrGetType DeviceNamePropertyInfo Source # 
type AttrGetType DeviceNamePropertyInfo = Text
type AttrBaseTypeConstraint DeviceNamePropertyInfo Source # 
type AttrBaseTypeConstraint DeviceNamePropertyInfo = IsDevice
type AttrAllowedOps DeviceNamePropertyInfo Source # 
type AttrAllowedOps DeviceNamePropertyInfo = (:) AttrOpTag AttrConstruct ((:) AttrOpTag AttrGet ((:) AttrOpTag AttrClear ([] AttrOpTag)))

constructDeviceName :: IsDevice o => Text -> IO (GValueConstruct o) Source #

deviceName :: AttrLabelProxy "name" Source #

getDeviceName :: (MonadIO m, IsDevice o) => o -> m Text Source #

numTouches

data DeviceNumTouchesPropertyInfo Source #

Instances

AttrInfo DeviceNumTouchesPropertyInfo Source # 

Associated Types

type AttrAllowedOps DeviceNumTouchesPropertyInfo :: [AttrOpTag]

type AttrSetTypeConstraint DeviceNumTouchesPropertyInfo :: * -> Constraint

type AttrBaseTypeConstraint DeviceNumTouchesPropertyInfo :: * -> Constraint

type AttrGetType DeviceNumTouchesPropertyInfo :: *

type AttrLabel DeviceNumTouchesPropertyInfo :: Symbol

type AttrOrigin DeviceNumTouchesPropertyInfo :: *

Methods

attrGet :: AttrBaseTypeConstraint DeviceNumTouchesPropertyInfo o => Proxy * DeviceNumTouchesPropertyInfo -> o -> IO (AttrGetType DeviceNumTouchesPropertyInfo)

attrSet :: (AttrBaseTypeConstraint DeviceNumTouchesPropertyInfo o, AttrSetTypeConstraint DeviceNumTouchesPropertyInfo b) => Proxy * DeviceNumTouchesPropertyInfo -> o -> b -> IO ()

attrClear :: AttrBaseTypeConstraint DeviceNumTouchesPropertyInfo o => Proxy * DeviceNumTouchesPropertyInfo -> o -> IO ()

attrConstruct :: (AttrBaseTypeConstraint DeviceNumTouchesPropertyInfo o, AttrSetTypeConstraint DeviceNumTouchesPropertyInfo b) => Proxy * DeviceNumTouchesPropertyInfo -> b -> IO (GValueConstruct o)

type AttrSetTypeConstraint DeviceNumTouchesPropertyInfo Source # 
type AttrSetTypeConstraint DeviceNumTouchesPropertyInfo = * ~ Word32
type AttrOrigin DeviceNumTouchesPropertyInfo Source # 
type AttrLabel DeviceNumTouchesPropertyInfo Source # 
type AttrLabel DeviceNumTouchesPropertyInfo = "num-touches"
type AttrGetType DeviceNumTouchesPropertyInfo Source # 
type AttrBaseTypeConstraint DeviceNumTouchesPropertyInfo Source # 
type AttrBaseTypeConstraint DeviceNumTouchesPropertyInfo = IsDevice
type AttrAllowedOps DeviceNumTouchesPropertyInfo Source # 
type AttrAllowedOps DeviceNumTouchesPropertyInfo = (:) AttrOpTag AttrConstruct ((:) AttrOpTag AttrGet ([] AttrOpTag))

constructDeviceNumTouches :: IsDevice o => Word32 -> IO (GValueConstruct o) Source #

deviceNumTouches :: AttrLabelProxy "numTouches" Source #

productId

data DeviceProductIdPropertyInfo Source #

Instances

AttrInfo DeviceProductIdPropertyInfo Source # 

Associated Types

type AttrAllowedOps DeviceProductIdPropertyInfo :: [AttrOpTag]

type AttrSetTypeConstraint DeviceProductIdPropertyInfo :: * -> Constraint

type AttrBaseTypeConstraint DeviceProductIdPropertyInfo :: * -> Constraint

type AttrGetType DeviceProductIdPropertyInfo :: *

type AttrLabel DeviceProductIdPropertyInfo :: Symbol

type AttrOrigin DeviceProductIdPropertyInfo :: *

Methods

attrGet :: AttrBaseTypeConstraint DeviceProductIdPropertyInfo o => Proxy * DeviceProductIdPropertyInfo -> o -> IO (AttrGetType DeviceProductIdPropertyInfo)

attrSet :: (AttrBaseTypeConstraint DeviceProductIdPropertyInfo o, AttrSetTypeConstraint DeviceProductIdPropertyInfo b) => Proxy * DeviceProductIdPropertyInfo -> o -> b -> IO ()

attrClear :: AttrBaseTypeConstraint DeviceProductIdPropertyInfo o => Proxy * DeviceProductIdPropertyInfo -> o -> IO ()

attrConstruct :: (AttrBaseTypeConstraint DeviceProductIdPropertyInfo o, AttrSetTypeConstraint DeviceProductIdPropertyInfo b) => Proxy * DeviceProductIdPropertyInfo -> b -> IO (GValueConstruct o)

type AttrSetTypeConstraint DeviceProductIdPropertyInfo Source # 
type AttrSetTypeConstraint DeviceProductIdPropertyInfo = * ~ Text
type AttrOrigin DeviceProductIdPropertyInfo Source # 
type AttrLabel DeviceProductIdPropertyInfo Source # 
type AttrLabel DeviceProductIdPropertyInfo = "product-id"
type AttrGetType DeviceProductIdPropertyInfo Source # 
type AttrGetType DeviceProductIdPropertyInfo = Maybe Text
type AttrBaseTypeConstraint DeviceProductIdPropertyInfo Source # 
type AttrBaseTypeConstraint DeviceProductIdPropertyInfo = IsDevice
type AttrAllowedOps DeviceProductIdPropertyInfo Source # 
type AttrAllowedOps DeviceProductIdPropertyInfo = (:) AttrOpTag AttrConstruct ((:) AttrOpTag AttrGet ((:) AttrOpTag AttrClear ([] AttrOpTag)))

constructDeviceProductId :: IsDevice o => Text -> IO (GValueConstruct o) Source #

deviceProductId :: AttrLabelProxy "productId" Source #

getDeviceProductId :: (MonadIO m, IsDevice o) => o -> m (Maybe Text) Source #

seat

data DeviceSeatPropertyInfo Source #

Instances

AttrInfo DeviceSeatPropertyInfo Source # 

Associated Types

type AttrAllowedOps DeviceSeatPropertyInfo :: [AttrOpTag]

type AttrSetTypeConstraint DeviceSeatPropertyInfo :: * -> Constraint

type AttrBaseTypeConstraint DeviceSeatPropertyInfo :: * -> Constraint

type AttrGetType DeviceSeatPropertyInfo :: *

type AttrLabel DeviceSeatPropertyInfo :: Symbol

type AttrOrigin DeviceSeatPropertyInfo :: *

Methods

attrGet :: AttrBaseTypeConstraint DeviceSeatPropertyInfo o => Proxy * DeviceSeatPropertyInfo -> o -> IO (AttrGetType DeviceSeatPropertyInfo)

attrSet :: (AttrBaseTypeConstraint DeviceSeatPropertyInfo o, AttrSetTypeConstraint DeviceSeatPropertyInfo b) => Proxy * DeviceSeatPropertyInfo -> o -> b -> IO ()

attrClear :: AttrBaseTypeConstraint DeviceSeatPropertyInfo o => Proxy * DeviceSeatPropertyInfo -> o -> IO ()

attrConstruct :: (AttrBaseTypeConstraint DeviceSeatPropertyInfo o, AttrSetTypeConstraint DeviceSeatPropertyInfo b) => Proxy * DeviceSeatPropertyInfo -> b -> IO (GValueConstruct o)

type AttrSetTypeConstraint DeviceSeatPropertyInfo Source # 
type AttrSetTypeConstraint DeviceSeatPropertyInfo = IsSeat
type AttrOrigin DeviceSeatPropertyInfo Source # 
type AttrOrigin DeviceSeatPropertyInfo = Device
type AttrLabel DeviceSeatPropertyInfo Source # 
type AttrLabel DeviceSeatPropertyInfo = "seat"
type AttrGetType DeviceSeatPropertyInfo Source # 
type AttrGetType DeviceSeatPropertyInfo = Seat
type AttrBaseTypeConstraint DeviceSeatPropertyInfo Source # 
type AttrBaseTypeConstraint DeviceSeatPropertyInfo = IsDevice
type AttrAllowedOps DeviceSeatPropertyInfo Source # 
type AttrAllowedOps DeviceSeatPropertyInfo = (:) AttrOpTag AttrSet ((:) AttrOpTag AttrConstruct ((:) AttrOpTag AttrGet ((:) AttrOpTag AttrClear ([] AttrOpTag))))

clearDeviceSeat :: (MonadIO m, IsDevice o) => o -> m () Source #

constructDeviceSeat :: (IsDevice o, IsSeat a) => a -> IO (GValueConstruct o) Source #

deviceSeat :: AttrLabelProxy "seat" Source #

setDeviceSeat :: (MonadIO m, IsDevice o, IsSeat a) => o -> a -> m () Source #

type

data DeviceTypePropertyInfo Source #

Instances

AttrInfo DeviceTypePropertyInfo Source # 

Associated Types

type AttrAllowedOps DeviceTypePropertyInfo :: [AttrOpTag]

type AttrSetTypeConstraint DeviceTypePropertyInfo :: * -> Constraint

type AttrBaseTypeConstraint DeviceTypePropertyInfo :: * -> Constraint

type AttrGetType DeviceTypePropertyInfo :: *

type AttrLabel DeviceTypePropertyInfo :: Symbol

type AttrOrigin DeviceTypePropertyInfo :: *

Methods

attrGet :: AttrBaseTypeConstraint DeviceTypePropertyInfo o => Proxy * DeviceTypePropertyInfo -> o -> IO (AttrGetType DeviceTypePropertyInfo)

attrSet :: (AttrBaseTypeConstraint DeviceTypePropertyInfo o, AttrSetTypeConstraint DeviceTypePropertyInfo b) => Proxy * DeviceTypePropertyInfo -> o -> b -> IO ()

attrClear :: AttrBaseTypeConstraint DeviceTypePropertyInfo o => Proxy * DeviceTypePropertyInfo -> o -> IO ()

attrConstruct :: (AttrBaseTypeConstraint DeviceTypePropertyInfo o, AttrSetTypeConstraint DeviceTypePropertyInfo b) => Proxy * DeviceTypePropertyInfo -> b -> IO (GValueConstruct o)

type AttrSetTypeConstraint DeviceTypePropertyInfo Source # 
type AttrSetTypeConstraint DeviceTypePropertyInfo = * ~ DeviceType
type AttrOrigin DeviceTypePropertyInfo Source # 
type AttrOrigin DeviceTypePropertyInfo = Device
type AttrLabel DeviceTypePropertyInfo Source # 
type AttrLabel DeviceTypePropertyInfo = "type"
type AttrGetType DeviceTypePropertyInfo Source # 
type AttrBaseTypeConstraint DeviceTypePropertyInfo Source # 
type AttrBaseTypeConstraint DeviceTypePropertyInfo = IsDevice
type AttrAllowedOps DeviceTypePropertyInfo Source # 
type AttrAllowedOps DeviceTypePropertyInfo = (:) AttrOpTag AttrConstruct ((:) AttrOpTag AttrGet ([] AttrOpTag))

constructDeviceType :: IsDevice o => DeviceType -> IO (GValueConstruct o) Source #

deviceType :: AttrLabelProxy "type" Source #

vendorId

data DeviceVendorIdPropertyInfo Source #

Instances

AttrInfo DeviceVendorIdPropertyInfo Source # 

Associated Types

type AttrAllowedOps DeviceVendorIdPropertyInfo :: [AttrOpTag]

type AttrSetTypeConstraint DeviceVendorIdPropertyInfo :: * -> Constraint

type AttrBaseTypeConstraint DeviceVendorIdPropertyInfo :: * -> Constraint

type AttrGetType DeviceVendorIdPropertyInfo :: *

type AttrLabel DeviceVendorIdPropertyInfo :: Symbol

type AttrOrigin DeviceVendorIdPropertyInfo :: *

Methods

attrGet :: AttrBaseTypeConstraint DeviceVendorIdPropertyInfo o => Proxy * DeviceVendorIdPropertyInfo -> o -> IO (AttrGetType DeviceVendorIdPropertyInfo)

attrSet :: (AttrBaseTypeConstraint DeviceVendorIdPropertyInfo o, AttrSetTypeConstraint DeviceVendorIdPropertyInfo b) => Proxy * DeviceVendorIdPropertyInfo -> o -> b -> IO ()

attrClear :: AttrBaseTypeConstraint DeviceVendorIdPropertyInfo o => Proxy * DeviceVendorIdPropertyInfo -> o -> IO ()

attrConstruct :: (AttrBaseTypeConstraint DeviceVendorIdPropertyInfo o, AttrSetTypeConstraint DeviceVendorIdPropertyInfo b) => Proxy * DeviceVendorIdPropertyInfo -> b -> IO (GValueConstruct o)

type AttrSetTypeConstraint DeviceVendorIdPropertyInfo Source # 
type AttrSetTypeConstraint DeviceVendorIdPropertyInfo = * ~ Text
type AttrOrigin DeviceVendorIdPropertyInfo Source # 
type AttrLabel DeviceVendorIdPropertyInfo Source # 
type AttrLabel DeviceVendorIdPropertyInfo = "vendor-id"
type AttrGetType DeviceVendorIdPropertyInfo Source # 
type AttrGetType DeviceVendorIdPropertyInfo = Maybe Text
type AttrBaseTypeConstraint DeviceVendorIdPropertyInfo Source # 
type AttrBaseTypeConstraint DeviceVendorIdPropertyInfo = IsDevice
type AttrAllowedOps DeviceVendorIdPropertyInfo Source # 
type AttrAllowedOps DeviceVendorIdPropertyInfo = (:) AttrOpTag AttrConstruct ((:) AttrOpTag AttrGet ((:) AttrOpTag AttrClear ([] AttrOpTag)))

constructDeviceVendorId :: IsDevice o => Text -> IO (GValueConstruct o) Source #

deviceVendorId :: AttrLabelProxy "vendorId" Source #

getDeviceVendorId :: (MonadIO m, IsDevice o) => o -> m (Maybe Text) Source #

Signals

changed

type C_DeviceChangedCallback = Ptr () -> Ptr () -> IO () Source #

data DeviceChangedSignalInfo Source #

Instances

SignalInfo DeviceChangedSignalInfo Source # 

Associated Types

type HaskellCallbackType DeviceChangedSignalInfo :: *

Methods

connectSignal :: GObject o => SignalProxy o DeviceChangedSignalInfo -> o -> HaskellCallbackType DeviceChangedSignalInfo -> SignalConnectMode -> IO SignalHandlerId

type HaskellCallbackType DeviceChangedSignalInfo Source # 

afterDeviceChanged :: (GObject a, MonadIO m) => a -> DeviceChangedCallback -> m SignalHandlerId Source #

onDeviceChanged :: (GObject a, MonadIO m) => a -> DeviceChangedCallback -> m SignalHandlerId Source #