{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Gdk.Objects.Device.Device' object represents a single input device, such
-- as a keyboard, a mouse, a touchpad, etc.
-- 
-- See the t'GI.Gdk.Objects.DeviceManager.DeviceManager' documentation for more information
-- about the various kinds of master and slave devices, and their
-- relationships.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Gdk.Objects.Device
    ( 

-- * Exported types
    Device(..)                              ,
    IsDevice                                ,
    toDevice                                ,
    noDevice                                ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveDeviceMethod                     ,
#endif


-- ** getAssociatedDevice #method:getAssociatedDevice#

#if defined(ENABLE_OVERLOADING)
    DeviceGetAssociatedDeviceMethodInfo     ,
#endif
    deviceGetAssociatedDevice               ,


-- ** getAxes #method:getAxes#

#if defined(ENABLE_OVERLOADING)
    DeviceGetAxesMethodInfo                 ,
#endif
    deviceGetAxes                           ,


-- ** getAxisUse #method:getAxisUse#

#if defined(ENABLE_OVERLOADING)
    DeviceGetAxisUseMethodInfo              ,
#endif
    deviceGetAxisUse                        ,


-- ** getDeviceType #method:getDeviceType#

#if defined(ENABLE_OVERLOADING)
    DeviceGetDeviceTypeMethodInfo           ,
#endif
    deviceGetDeviceType                     ,


-- ** getDisplay #method:getDisplay#

#if defined(ENABLE_OVERLOADING)
    DeviceGetDisplayMethodInfo              ,
#endif
    deviceGetDisplay                        ,


-- ** getHasCursor #method:getHasCursor#

#if defined(ENABLE_OVERLOADING)
    DeviceGetHasCursorMethodInfo            ,
#endif
    deviceGetHasCursor                      ,


-- ** getKey #method:getKey#

#if defined(ENABLE_OVERLOADING)
    DeviceGetKeyMethodInfo                  ,
#endif
    deviceGetKey                            ,


-- ** getLastEventWindow #method:getLastEventWindow#

#if defined(ENABLE_OVERLOADING)
    DeviceGetLastEventWindowMethodInfo      ,
#endif
    deviceGetLastEventWindow                ,


-- ** getMode #method:getMode#

#if defined(ENABLE_OVERLOADING)
    DeviceGetModeMethodInfo                 ,
#endif
    deviceGetMode                           ,


-- ** getNAxes #method:getNAxes#

#if defined(ENABLE_OVERLOADING)
    DeviceGetNAxesMethodInfo                ,
#endif
    deviceGetNAxes                          ,


-- ** getNKeys #method:getNKeys#

#if defined(ENABLE_OVERLOADING)
    DeviceGetNKeysMethodInfo                ,
#endif
    deviceGetNKeys                          ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    DeviceGetNameMethodInfo                 ,
#endif
    deviceGetName                           ,


-- ** getPosition #method:getPosition#

#if defined(ENABLE_OVERLOADING)
    DeviceGetPositionMethodInfo             ,
#endif
    deviceGetPosition                       ,


-- ** getPositionDouble #method:getPositionDouble#

#if defined(ENABLE_OVERLOADING)
    DeviceGetPositionDoubleMethodInfo       ,
#endif
    deviceGetPositionDouble                 ,


-- ** getProductId #method:getProductId#

#if defined(ENABLE_OVERLOADING)
    DeviceGetProductIdMethodInfo            ,
#endif
    deviceGetProductId                      ,


-- ** getSeat #method:getSeat#

#if defined(ENABLE_OVERLOADING)
    DeviceGetSeatMethodInfo                 ,
#endif
    deviceGetSeat                           ,


-- ** getSource #method:getSource#

#if defined(ENABLE_OVERLOADING)
    DeviceGetSourceMethodInfo               ,
#endif
    deviceGetSource                         ,


-- ** getVendorId #method:getVendorId#

#if defined(ENABLE_OVERLOADING)
    DeviceGetVendorIdMethodInfo             ,
#endif
    deviceGetVendorId                       ,


-- ** getWindowAtPosition #method:getWindowAtPosition#

#if defined(ENABLE_OVERLOADING)
    DeviceGetWindowAtPositionMethodInfo     ,
#endif
    deviceGetWindowAtPosition               ,


-- ** getWindowAtPositionDouble #method:getWindowAtPositionDouble#

#if defined(ENABLE_OVERLOADING)
    DeviceGetWindowAtPositionDoubleMethodInfo,
#endif
    deviceGetWindowAtPositionDouble         ,


-- ** grab #method:grab#

#if defined(ENABLE_OVERLOADING)
    DeviceGrabMethodInfo                    ,
#endif
    deviceGrab                              ,


-- ** grabInfoLibgtkOnly #method:grabInfoLibgtkOnly#

    deviceGrabInfoLibgtkOnly                ,


-- ** listAxes #method:listAxes#

#if defined(ENABLE_OVERLOADING)
    DeviceListAxesMethodInfo                ,
#endif
    deviceListAxes                          ,


-- ** listSlaveDevices #method:listSlaveDevices#

#if defined(ENABLE_OVERLOADING)
    DeviceListSlaveDevicesMethodInfo        ,
#endif
    deviceListSlaveDevices                  ,


-- ** setAxisUse #method:setAxisUse#

#if defined(ENABLE_OVERLOADING)
    DeviceSetAxisUseMethodInfo              ,
#endif
    deviceSetAxisUse                        ,


-- ** setKey #method:setKey#

#if defined(ENABLE_OVERLOADING)
    DeviceSetKeyMethodInfo                  ,
#endif
    deviceSetKey                            ,


-- ** setMode #method:setMode#

#if defined(ENABLE_OVERLOADING)
    DeviceSetModeMethodInfo                 ,
#endif
    deviceSetMode                           ,


-- ** ungrab #method:ungrab#

#if defined(ENABLE_OVERLOADING)
    DeviceUngrabMethodInfo                  ,
#endif
    deviceUngrab                            ,


-- ** warp #method:warp#

#if defined(ENABLE_OVERLOADING)
    DeviceWarpMethodInfo                    ,
#endif
    deviceWarp                              ,




 -- * Properties
-- ** associatedDevice #attr:associatedDevice#
-- | Associated pointer or keyboard with this device, if any. Devices of type @/GDK_DEVICE_TYPE_MASTER/@
-- always come in keyboard\/pointer pairs. Other device types will have a 'P.Nothing' associated device.
-- 
-- /Since: 3.0/

#if defined(ENABLE_OVERLOADING)
    DeviceAssociatedDevicePropertyInfo      ,
#endif
#if defined(ENABLE_OVERLOADING)
    deviceAssociatedDevice                  ,
#endif
    getDeviceAssociatedDevice               ,


-- ** axes #attr:axes#
-- | The axes currently available for this device.
-- 
-- /Since: 3.22/

#if defined(ENABLE_OVERLOADING)
    DeviceAxesPropertyInfo                  ,
#endif
#if defined(ENABLE_OVERLOADING)
    deviceAxes                              ,
#endif
    getDeviceAxes                           ,


-- ** deviceManager #attr:deviceManager#
-- | The t'GI.Gdk.Objects.DeviceManager.DeviceManager' the t'GI.Gdk.Objects.Device.Device' pertains to.
-- 
-- /Since: 3.0/

#if defined(ENABLE_OVERLOADING)
    DeviceDeviceManagerPropertyInfo         ,
#endif
    constructDeviceDeviceManager            ,
#if defined(ENABLE_OVERLOADING)
    deviceDeviceManager                     ,
#endif
    getDeviceDeviceManager                  ,


-- ** display #attr:display#
-- | The t'GI.Gdk.Objects.Display.Display' the t'GI.Gdk.Objects.Device.Device' pertains to.
-- 
-- /Since: 3.0/

#if defined(ENABLE_OVERLOADING)
    DeviceDisplayPropertyInfo               ,
#endif
    constructDeviceDisplay                  ,
#if defined(ENABLE_OVERLOADING)
    deviceDisplay                           ,
#endif
    getDeviceDisplay                        ,


-- ** hasCursor #attr:hasCursor#
-- | Whether the device is represented by a cursor on the screen. Devices of type
-- 'GI.Gdk.Enums.DeviceTypeMaster' will have 'P.True' here.
-- 
-- /Since: 3.0/

#if defined(ENABLE_OVERLOADING)
    DeviceHasCursorPropertyInfo             ,
#endif
    constructDeviceHasCursor                ,
#if defined(ENABLE_OVERLOADING)
    deviceHasCursor                         ,
#endif
    getDeviceHasCursor                      ,


-- ** inputMode #attr:inputMode#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DeviceInputModePropertyInfo             ,
#endif
    constructDeviceInputMode                ,
#if defined(ENABLE_OVERLOADING)
    deviceInputMode                         ,
#endif
    getDeviceInputMode                      ,
    setDeviceInputMode                      ,


-- ** inputSource #attr:inputSource#
-- | Source type for the device.
-- 
-- /Since: 3.0/

#if defined(ENABLE_OVERLOADING)
    DeviceInputSourcePropertyInfo           ,
#endif
    constructDeviceInputSource              ,
#if defined(ENABLE_OVERLOADING)
    deviceInputSource                       ,
#endif
    getDeviceInputSource                    ,


-- ** nAxes #attr:nAxes#
-- | Number of axes in the device.
-- 
-- /Since: 3.0/

#if defined(ENABLE_OVERLOADING)
    DeviceNAxesPropertyInfo                 ,
#endif
#if defined(ENABLE_OVERLOADING)
    deviceNAxes                             ,
#endif
    getDeviceNAxes                          ,


-- ** name #attr:name#
-- | The device name.
-- 
-- /Since: 3.0/

#if defined(ENABLE_OVERLOADING)
    DeviceNamePropertyInfo                  ,
#endif
    constructDeviceName                     ,
#if defined(ENABLE_OVERLOADING)
    deviceName                              ,
#endif
    getDeviceName                           ,


-- ** numTouches #attr:numTouches#
-- | The maximal number of concurrent touches on a touch device.
-- Will be 0 if the device is not a touch device or if the number
-- of touches is unknown.
-- 
-- /Since: 3.20/

#if defined(ENABLE_OVERLOADING)
    DeviceNumTouchesPropertyInfo            ,
#endif
    constructDeviceNumTouches               ,
#if defined(ENABLE_OVERLOADING)
    deviceNumTouches                        ,
#endif
    getDeviceNumTouches                     ,


-- ** productId #attr:productId#
-- | Product ID of this device, see 'GI.Gdk.Objects.Device.deviceGetProductId'.
-- 
-- /Since: 3.16/

#if defined(ENABLE_OVERLOADING)
    DeviceProductIdPropertyInfo             ,
#endif
    constructDeviceProductId                ,
#if defined(ENABLE_OVERLOADING)
    deviceProductId                         ,
#endif
    getDeviceProductId                      ,


-- ** seat #attr:seat#
-- | t'GI.Gdk.Objects.Seat.Seat' of this device.
-- 
-- /Since: 3.20/

#if defined(ENABLE_OVERLOADING)
    DeviceSeatPropertyInfo                  ,
#endif
    clearDeviceSeat                         ,
    constructDeviceSeat                     ,
#if defined(ENABLE_OVERLOADING)
    deviceSeat                              ,
#endif
    getDeviceSeat                           ,
    setDeviceSeat                           ,


-- ** tool #attr:tool#
-- | /No description available in the introspection data./

#if defined(ENABLE_OVERLOADING)
    DeviceToolPropertyInfo                  ,
#endif
#if defined(ENABLE_OVERLOADING)
    deviceTool                              ,
#endif
    getDeviceTool                           ,


-- ** type #attr:type#
-- | Device role in the device manager.
-- 
-- /Since: 3.0/

#if defined(ENABLE_OVERLOADING)
    DeviceTypePropertyInfo                  ,
#endif
    constructDeviceType                     ,
#if defined(ENABLE_OVERLOADING)
    deviceType                              ,
#endif
    getDeviceType                           ,


-- ** vendorId #attr:vendorId#
-- | Vendor ID of this device, see 'GI.Gdk.Objects.Device.deviceGetVendorId'.
-- 
-- /Since: 3.16/

#if defined(ENABLE_OVERLOADING)
    DeviceVendorIdPropertyInfo              ,
#endif
    constructDeviceVendorId                 ,
#if defined(ENABLE_OVERLOADING)
    deviceVendorId                          ,
#endif
    getDeviceVendorId                       ,




 -- * Signals
-- ** changed #signal:changed#

    C_DeviceChangedCallback                 ,
    DeviceChangedCallback                   ,
#if defined(ENABLE_OVERLOADING)
    DeviceChangedSignalInfo                 ,
#endif
    afterDeviceChanged                      ,
    genClosure_DeviceChanged                ,
    mk_DeviceChangedCallback                ,
    noDeviceChangedCallback                 ,
    onDeviceChanged                         ,
    wrap_DeviceChangedCallback              ,


-- ** toolChanged #signal:toolChanged#

    C_DeviceToolChangedCallback             ,
    DeviceToolChangedCallback               ,
#if defined(ENABLE_OVERLOADING)
    DeviceToolChangedSignalInfo             ,
#endif
    afterDeviceToolChanged                  ,
    genClosure_DeviceToolChanged            ,
    mk_DeviceToolChangedCallback            ,
    noDeviceToolChangedCallback             ,
    onDeviceToolChanged                     ,
    wrap_DeviceToolChangedCallback          ,




    ) 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.GI.Base.Signals as B.Signals
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 qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Objects.Cursor as Gdk.Cursor
import {-# SOURCE #-} qualified GI.Gdk.Objects.DeviceManager as Gdk.DeviceManager
import {-# SOURCE #-} qualified GI.Gdk.Objects.DeviceTool as Gdk.DeviceTool
import {-# SOURCE #-} qualified GI.Gdk.Objects.Display as Gdk.Display
import {-# SOURCE #-} qualified GI.Gdk.Objects.Screen as Gdk.Screen
import {-# SOURCE #-} qualified GI.Gdk.Objects.Seat as Gdk.Seat
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window
import {-# SOURCE #-} qualified GI.Gdk.Structs.Atom as Gdk.Atom

-- | Memory-managed wrapper type.
newtype Device = Device (ManagedPtr Device)
    deriving (Device -> Device -> Bool
(Device -> Device -> Bool)
-> (Device -> Device -> Bool) -> Eq Device
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Device -> Device -> Bool
$c/= :: Device -> Device -> Bool
== :: Device -> Device -> Bool
$c== :: Device -> Device -> Bool
Eq)
foreign import ccall "gdk_device_get_type"
    c_gdk_device_get_type :: IO GType

instance GObject Device where
    gobjectType :: IO GType
gobjectType = IO GType
c_gdk_device_get_type
    

-- | Convert 'Device' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue Device where
    toGValue :: Device -> IO GValue
toGValue o :: Device
o = do
        GType
gtype <- IO GType
c_gdk_device_get_type
        Device -> (Ptr Device -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Device
o (GType -> (GValue -> Ptr Device -> IO ()) -> Ptr Device -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Device -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO Device
fromGValue gv :: GValue
gv = do
        Ptr Device
ptr <- GValue -> IO (Ptr Device)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Device)
        (ManagedPtr Device -> Device) -> Ptr Device -> IO Device
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Device -> Device
Device Ptr Device
ptr
        
    

-- | Type class for types which can be safely cast to `Device`, for instance with `toDevice`.
class (GObject o, O.IsDescendantOf Device o) => IsDevice o
instance (GObject o, O.IsDescendantOf Device o) => IsDevice o

instance O.HasParentTypes Device
type instance O.ParentTypes Device = '[GObject.Object.Object]

-- | Cast to `Device`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toDevice :: (MonadIO m, IsDevice o) => o -> m Device
toDevice :: o -> m Device
toDevice = IO Device -> m Device
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Device -> m Device) -> (o -> IO Device) -> o -> m Device
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Device -> Device) -> o -> IO Device
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Device -> Device
Device

-- | A convenience alias for `Nothing` :: `Maybe` `Device`.
noDevice :: Maybe Device
noDevice :: Maybe Device
noDevice = Maybe Device
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolveDeviceMethod (t :: Symbol) (o :: *) :: * where
    ResolveDeviceMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDeviceMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDeviceMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDeviceMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDeviceMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDeviceMethod "grab" o = DeviceGrabMethodInfo
    ResolveDeviceMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDeviceMethod "listAxes" o = DeviceListAxesMethodInfo
    ResolveDeviceMethod "listSlaveDevices" o = DeviceListSlaveDevicesMethodInfo
    ResolveDeviceMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDeviceMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDeviceMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDeviceMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDeviceMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDeviceMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDeviceMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDeviceMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDeviceMethod "ungrab" o = DeviceUngrabMethodInfo
    ResolveDeviceMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDeviceMethod "warp" o = DeviceWarpMethodInfo
    ResolveDeviceMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDeviceMethod "getAssociatedDevice" o = DeviceGetAssociatedDeviceMethodInfo
    ResolveDeviceMethod "getAxes" o = DeviceGetAxesMethodInfo
    ResolveDeviceMethod "getAxisUse" o = DeviceGetAxisUseMethodInfo
    ResolveDeviceMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDeviceMethod "getDeviceType" o = DeviceGetDeviceTypeMethodInfo
    ResolveDeviceMethod "getDisplay" o = DeviceGetDisplayMethodInfo
    ResolveDeviceMethod "getHasCursor" o = DeviceGetHasCursorMethodInfo
    ResolveDeviceMethod "getKey" o = DeviceGetKeyMethodInfo
    ResolveDeviceMethod "getLastEventWindow" o = DeviceGetLastEventWindowMethodInfo
    ResolveDeviceMethod "getMode" o = DeviceGetModeMethodInfo
    ResolveDeviceMethod "getNAxes" o = DeviceGetNAxesMethodInfo
    ResolveDeviceMethod "getNKeys" o = DeviceGetNKeysMethodInfo
    ResolveDeviceMethod "getName" o = DeviceGetNameMethodInfo
    ResolveDeviceMethod "getPosition" o = DeviceGetPositionMethodInfo
    ResolveDeviceMethod "getPositionDouble" o = DeviceGetPositionDoubleMethodInfo
    ResolveDeviceMethod "getProductId" o = DeviceGetProductIdMethodInfo
    ResolveDeviceMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDeviceMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDeviceMethod "getSeat" o = DeviceGetSeatMethodInfo
    ResolveDeviceMethod "getSource" o = DeviceGetSourceMethodInfo
    ResolveDeviceMethod "getVendorId" o = DeviceGetVendorIdMethodInfo
    ResolveDeviceMethod "getWindowAtPosition" o = DeviceGetWindowAtPositionMethodInfo
    ResolveDeviceMethod "getWindowAtPositionDouble" o = DeviceGetWindowAtPositionDoubleMethodInfo
    ResolveDeviceMethod "setAxisUse" o = DeviceSetAxisUseMethodInfo
    ResolveDeviceMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDeviceMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDeviceMethod "setKey" o = DeviceSetKeyMethodInfo
    ResolveDeviceMethod "setMode" o = DeviceSetModeMethodInfo
    ResolveDeviceMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDeviceMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveDeviceMethod t Device, O.MethodInfo info Device p) => OL.IsLabel t (Device -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif

-- signal Device::changed
-- | The [changed](#signal:changed) signal is emitted either when the t'GI.Gdk.Objects.Device.Device'
-- has changed the number of either axes or keys. For example
-- In X this will normally happen when the slave device routing
-- events through the master device changes (for example, user
-- switches from the USB mouse to a tablet), in that case the
-- master device will change to reflect the new slave device
-- axes and keys.
type DeviceChangedCallback =
    IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DeviceChangedCallback`@.
noDeviceChangedCallback :: Maybe DeviceChangedCallback
noDeviceChangedCallback :: Maybe (IO ())
noDeviceChangedCallback = Maybe (IO ())
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_DeviceChangedCallback =
    Ptr () ->                               -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_DeviceChangedCallback`.
foreign import ccall "wrapper"
    mk_DeviceChangedCallback :: C_DeviceChangedCallback -> IO (FunPtr C_DeviceChangedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_DeviceChanged :: MonadIO m => DeviceChangedCallback -> m (GClosure C_DeviceChangedCallback)
genClosure_DeviceChanged :: IO () -> m (GClosure C_DeviceChangedCallback)
genClosure_DeviceChanged cb :: IO ()
cb = IO (GClosure C_DeviceChangedCallback)
-> m (GClosure C_DeviceChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DeviceChangedCallback)
 -> m (GClosure C_DeviceChangedCallback))
-> IO (GClosure C_DeviceChangedCallback)
-> m (GClosure C_DeviceChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DeviceChangedCallback
cb' = IO () -> C_DeviceChangedCallback
wrap_DeviceChangedCallback IO ()
cb
    C_DeviceChangedCallback -> IO (FunPtr C_DeviceChangedCallback)
mk_DeviceChangedCallback C_DeviceChangedCallback
cb' IO (FunPtr C_DeviceChangedCallback)
-> (FunPtr C_DeviceChangedCallback
    -> IO (GClosure C_DeviceChangedCallback))
-> IO (GClosure C_DeviceChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DeviceChangedCallback
-> IO (GClosure C_DeviceChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DeviceChangedCallback` into a `C_DeviceChangedCallback`.
wrap_DeviceChangedCallback ::
    DeviceChangedCallback ->
    C_DeviceChangedCallback
wrap_DeviceChangedCallback :: IO () -> C_DeviceChangedCallback
wrap_DeviceChangedCallback _cb :: IO ()
_cb _ _ = do
    IO ()
_cb 


-- | Connect a signal handler for the [changed](#signal:changed) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' device #changed callback
-- @
-- 
-- 
onDeviceChanged :: (IsDevice a, MonadIO m) => a -> DeviceChangedCallback -> m SignalHandlerId
onDeviceChanged :: a -> IO () -> m SignalHandlerId
onDeviceChanged obj :: a
obj cb :: IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DeviceChangedCallback
cb' = IO () -> C_DeviceChangedCallback
wrap_DeviceChangedCallback IO ()
cb
    FunPtr C_DeviceChangedCallback
cb'' <- C_DeviceChangedCallback -> IO (FunPtr C_DeviceChangedCallback)
mk_DeviceChangedCallback C_DeviceChangedCallback
cb'
    a
-> Text
-> FunPtr C_DeviceChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "changed" FunPtr C_DeviceChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [changed](#signal:changed) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' device #changed callback
-- @
-- 
-- 
afterDeviceChanged :: (IsDevice a, MonadIO m) => a -> DeviceChangedCallback -> m SignalHandlerId
afterDeviceChanged :: a -> IO () -> m SignalHandlerId
afterDeviceChanged obj :: a
obj cb :: IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DeviceChangedCallback
cb' = IO () -> C_DeviceChangedCallback
wrap_DeviceChangedCallback IO ()
cb
    FunPtr C_DeviceChangedCallback
cb'' <- C_DeviceChangedCallback -> IO (FunPtr C_DeviceChangedCallback)
mk_DeviceChangedCallback C_DeviceChangedCallback
cb'
    a
-> Text
-> FunPtr C_DeviceChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "changed" FunPtr C_DeviceChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DeviceChangedSignalInfo
instance SignalInfo DeviceChangedSignalInfo where
    type HaskellCallbackType DeviceChangedSignalInfo = DeviceChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DeviceChangedCallback cb
        cb'' <- mk_DeviceChangedCallback cb'
        connectSignalFunPtr obj "changed" cb'' connectMode detail

#endif

-- signal Device::tool-changed
-- | The [toolChanged](#signal:toolChanged) signal is emitted on pen\/eraser
-- @/GdkDevices/@ whenever tools enter or leave proximity.
-- 
-- /Since: 3.22/
type DeviceToolChangedCallback =
    Gdk.DeviceTool.DeviceTool
    -- ^ /@tool@/: The new current tool
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DeviceToolChangedCallback`@.
noDeviceToolChangedCallback :: Maybe DeviceToolChangedCallback
noDeviceToolChangedCallback :: Maybe DeviceToolChangedCallback
noDeviceToolChangedCallback = Maybe DeviceToolChangedCallback
forall a. Maybe a
Nothing

-- | Type for the callback on the (unwrapped) C side.
type C_DeviceToolChangedCallback =
    Ptr () ->                               -- object
    Ptr Gdk.DeviceTool.DeviceTool ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_DeviceToolChangedCallback`.
foreign import ccall "wrapper"
    mk_DeviceToolChangedCallback :: C_DeviceToolChangedCallback -> IO (FunPtr C_DeviceToolChangedCallback)

-- | Wrap the callback into a `GClosure`.
genClosure_DeviceToolChanged :: MonadIO m => DeviceToolChangedCallback -> m (GClosure C_DeviceToolChangedCallback)
genClosure_DeviceToolChanged :: DeviceToolChangedCallback
-> m (GClosure C_DeviceToolChangedCallback)
genClosure_DeviceToolChanged cb :: DeviceToolChangedCallback
cb = IO (GClosure C_DeviceToolChangedCallback)
-> m (GClosure C_DeviceToolChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DeviceToolChangedCallback)
 -> m (GClosure C_DeviceToolChangedCallback))
-> IO (GClosure C_DeviceToolChangedCallback)
-> m (GClosure C_DeviceToolChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DeviceToolChangedCallback
cb' = DeviceToolChangedCallback -> C_DeviceToolChangedCallback
wrap_DeviceToolChangedCallback DeviceToolChangedCallback
cb
    C_DeviceToolChangedCallback
-> IO (FunPtr C_DeviceToolChangedCallback)
mk_DeviceToolChangedCallback C_DeviceToolChangedCallback
cb' IO (FunPtr C_DeviceToolChangedCallback)
-> (FunPtr C_DeviceToolChangedCallback
    -> IO (GClosure C_DeviceToolChangedCallback))
-> IO (GClosure C_DeviceToolChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DeviceToolChangedCallback
-> IO (GClosure C_DeviceToolChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DeviceToolChangedCallback` into a `C_DeviceToolChangedCallback`.
wrap_DeviceToolChangedCallback ::
    DeviceToolChangedCallback ->
    C_DeviceToolChangedCallback
wrap_DeviceToolChangedCallback :: DeviceToolChangedCallback -> C_DeviceToolChangedCallback
wrap_DeviceToolChangedCallback _cb :: DeviceToolChangedCallback
_cb _ tool :: Ptr DeviceTool
tool _ = do
    DeviceTool
tool' <- ((ManagedPtr DeviceTool -> DeviceTool)
-> Ptr DeviceTool -> IO DeviceTool
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DeviceTool -> DeviceTool
Gdk.DeviceTool.DeviceTool) Ptr DeviceTool
tool
    DeviceToolChangedCallback
_cb  DeviceTool
tool'


-- | Connect a signal handler for the [toolChanged](#signal:toolChanged) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' device #toolChanged callback
-- @
-- 
-- 
onDeviceToolChanged :: (IsDevice a, MonadIO m) => a -> DeviceToolChangedCallback -> m SignalHandlerId
onDeviceToolChanged :: a -> DeviceToolChangedCallback -> m SignalHandlerId
onDeviceToolChanged obj :: a
obj cb :: DeviceToolChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DeviceToolChangedCallback
cb' = DeviceToolChangedCallback -> C_DeviceToolChangedCallback
wrap_DeviceToolChangedCallback DeviceToolChangedCallback
cb
    FunPtr C_DeviceToolChangedCallback
cb'' <- C_DeviceToolChangedCallback
-> IO (FunPtr C_DeviceToolChangedCallback)
mk_DeviceToolChangedCallback C_DeviceToolChangedCallback
cb'
    a
-> Text
-> FunPtr C_DeviceToolChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "tool-changed" FunPtr C_DeviceToolChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [toolChanged](#signal:toolChanged) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' device #toolChanged callback
-- @
-- 
-- 
afterDeviceToolChanged :: (IsDevice a, MonadIO m) => a -> DeviceToolChangedCallback -> m SignalHandlerId
afterDeviceToolChanged :: a -> DeviceToolChangedCallback -> m SignalHandlerId
afterDeviceToolChanged obj :: a
obj cb :: DeviceToolChangedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DeviceToolChangedCallback
cb' = DeviceToolChangedCallback -> C_DeviceToolChangedCallback
wrap_DeviceToolChangedCallback DeviceToolChangedCallback
cb
    FunPtr C_DeviceToolChangedCallback
cb'' <- C_DeviceToolChangedCallback
-> IO (FunPtr C_DeviceToolChangedCallback)
mk_DeviceToolChangedCallback C_DeviceToolChangedCallback
cb'
    a
-> Text
-> FunPtr C_DeviceToolChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj "tool-changed" FunPtr C_DeviceToolChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DeviceToolChangedSignalInfo
instance SignalInfo DeviceToolChangedSignalInfo where
    type HaskellCallbackType DeviceToolChangedSignalInfo = DeviceToolChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DeviceToolChangedCallback cb
        cb'' <- mk_DeviceToolChangedCallback cb'
        connectSignalFunPtr obj "tool-changed" cb'' connectMode detail

#endif

-- VVV Prop "associated-device"
   -- Type: TInterface (Name {namespace = "Gdk", name = "Device"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just True,Nothing)

-- | Get the value of the “@associated-device@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #associatedDevice
-- @
getDeviceAssociatedDevice :: (MonadIO m, IsDevice o) => o -> m (Maybe Device)
getDeviceAssociatedDevice :: o -> m (Maybe Device)
getDeviceAssociatedDevice obj :: o
obj = IO (Maybe Device) -> m (Maybe Device)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Device) -> m (Maybe Device))
-> IO (Maybe Device) -> m (Maybe Device)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Device -> Device) -> IO (Maybe Device)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "associated-device" ManagedPtr Device -> Device
Device

#if defined(ENABLE_OVERLOADING)
data DeviceAssociatedDevicePropertyInfo
instance AttrInfo DeviceAssociatedDevicePropertyInfo where
    type AttrAllowedOps DeviceAssociatedDevicePropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DeviceAssociatedDevicePropertyInfo = IsDevice
    type AttrSetTypeConstraint DeviceAssociatedDevicePropertyInfo = (~) ()
    type AttrTransferTypeConstraint DeviceAssociatedDevicePropertyInfo = (~) ()
    type AttrTransferType DeviceAssociatedDevicePropertyInfo = ()
    type AttrGetType DeviceAssociatedDevicePropertyInfo = (Maybe Device)
    type AttrLabel DeviceAssociatedDevicePropertyInfo = "associated-device"
    type AttrOrigin DeviceAssociatedDevicePropertyInfo = Device
    attrGet = getDeviceAssociatedDevice
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "axes"
   -- Type: TInterface (Name {namespace = "Gdk", name = "AxisFlags"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@axes@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #axes
-- @
getDeviceAxes :: (MonadIO m, IsDevice o) => o -> m [Gdk.Flags.AxisFlags]
getDeviceAxes :: o -> m [AxisFlags]
getDeviceAxes obj :: o
obj = IO [AxisFlags] -> m [AxisFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [AxisFlags] -> m [AxisFlags])
-> IO [AxisFlags] -> m [AxisFlags]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [AxisFlags]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj "axes"

#if defined(ENABLE_OVERLOADING)
data DeviceAxesPropertyInfo
instance AttrInfo DeviceAxesPropertyInfo where
    type AttrAllowedOps DeviceAxesPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DeviceAxesPropertyInfo = IsDevice
    type AttrSetTypeConstraint DeviceAxesPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DeviceAxesPropertyInfo = (~) ()
    type AttrTransferType DeviceAxesPropertyInfo = ()
    type AttrGetType DeviceAxesPropertyInfo = [Gdk.Flags.AxisFlags]
    type AttrLabel DeviceAxesPropertyInfo = "axes"
    type AttrOrigin DeviceAxesPropertyInfo = Device
    attrGet = getDeviceAxes
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "device-manager"
   -- Type: TInterface (Name {namespace = "Gdk", name = "DeviceManager"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@device-manager@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #deviceManager
-- @
getDeviceDeviceManager :: (MonadIO m, IsDevice o) => o -> m (Maybe Gdk.DeviceManager.DeviceManager)
getDeviceDeviceManager :: o -> m (Maybe DeviceManager)
getDeviceDeviceManager obj :: o
obj = IO (Maybe DeviceManager) -> m (Maybe DeviceManager)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DeviceManager) -> m (Maybe DeviceManager))
-> IO (Maybe DeviceManager) -> m (Maybe DeviceManager)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr DeviceManager -> DeviceManager)
-> IO (Maybe DeviceManager)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "device-manager" ManagedPtr DeviceManager -> DeviceManager
Gdk.DeviceManager.DeviceManager

-- | Construct a `GValueConstruct` with valid value for the “@device-manager@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceDeviceManager :: (IsDevice o, Gdk.DeviceManager.IsDeviceManager a) => a -> IO (GValueConstruct o)
constructDeviceDeviceManager :: a -> IO (GValueConstruct o)
constructDeviceDeviceManager val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "device-manager" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

#if defined(ENABLE_OVERLOADING)
data DeviceDeviceManagerPropertyInfo
instance AttrInfo DeviceDeviceManagerPropertyInfo where
    type AttrAllowedOps DeviceDeviceManagerPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DeviceDeviceManagerPropertyInfo = IsDevice
    type AttrSetTypeConstraint DeviceDeviceManagerPropertyInfo = Gdk.DeviceManager.IsDeviceManager
    type AttrTransferTypeConstraint DeviceDeviceManagerPropertyInfo = Gdk.DeviceManager.IsDeviceManager
    type AttrTransferType DeviceDeviceManagerPropertyInfo = Gdk.DeviceManager.DeviceManager
    type AttrGetType DeviceDeviceManagerPropertyInfo = (Maybe Gdk.DeviceManager.DeviceManager)
    type AttrLabel DeviceDeviceManagerPropertyInfo = "device-manager"
    type AttrOrigin DeviceDeviceManagerPropertyInfo = Device
    attrGet = getDeviceDeviceManager
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gdk.DeviceManager.DeviceManager v
    attrConstruct = constructDeviceDeviceManager
    attrClear = undefined
#endif

-- VVV Prop "display"
   -- Type: TInterface (Name {namespace = "Gdk", name = "Display"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@display@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #display
-- @
getDeviceDisplay :: (MonadIO m, IsDevice o) => o -> m Gdk.Display.Display
getDeviceDisplay :: o -> m Display
getDeviceDisplay obj :: o
obj = IO Display -> m Display
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Display -> m Display) -> IO Display -> m Display
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Display) -> IO Display
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "getDeviceDisplay" (IO (Maybe Display) -> IO Display)
-> IO (Maybe Display) -> IO Display
forall a b. (a -> b) -> a -> b
$ o
-> String -> (ManagedPtr Display -> Display) -> IO (Maybe Display)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "display" ManagedPtr Display -> Display
Gdk.Display.Display

-- | Construct a `GValueConstruct` with valid value for the “@display@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceDisplay :: (IsDevice o, Gdk.Display.IsDisplay a) => a -> IO (GValueConstruct o)
constructDeviceDisplay :: a -> IO (GValueConstruct o)
constructDeviceDisplay val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "display" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

#if defined(ENABLE_OVERLOADING)
data DeviceDisplayPropertyInfo
instance AttrInfo DeviceDisplayPropertyInfo where
    type AttrAllowedOps DeviceDisplayPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DeviceDisplayPropertyInfo = IsDevice
    type AttrSetTypeConstraint DeviceDisplayPropertyInfo = Gdk.Display.IsDisplay
    type AttrTransferTypeConstraint DeviceDisplayPropertyInfo = Gdk.Display.IsDisplay
    type AttrTransferType DeviceDisplayPropertyInfo = Gdk.Display.Display
    type AttrGetType DeviceDisplayPropertyInfo = Gdk.Display.Display
    type AttrLabel DeviceDisplayPropertyInfo = "display"
    type AttrOrigin DeviceDisplayPropertyInfo = Device
    attrGet = getDeviceDisplay
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gdk.Display.Display v
    attrConstruct = constructDeviceDisplay
    attrClear = undefined
#endif

-- VVV Prop "has-cursor"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@has-cursor@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #hasCursor
-- @
getDeviceHasCursor :: (MonadIO m, IsDevice o) => o -> m Bool
getDeviceHasCursor :: o -> m Bool
getDeviceHasCursor obj :: o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj "has-cursor"

-- | Construct a `GValueConstruct` with valid value for the “@has-cursor@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceHasCursor :: (IsDevice o) => Bool -> IO (GValueConstruct o)
constructDeviceHasCursor :: Bool -> IO (GValueConstruct o)
constructDeviceHasCursor val :: Bool
val = String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool "has-cursor" Bool
val

#if defined(ENABLE_OVERLOADING)
data DeviceHasCursorPropertyInfo
instance AttrInfo DeviceHasCursorPropertyInfo where
    type AttrAllowedOps DeviceHasCursorPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DeviceHasCursorPropertyInfo = IsDevice
    type AttrSetTypeConstraint DeviceHasCursorPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint DeviceHasCursorPropertyInfo = (~) Bool
    type AttrTransferType DeviceHasCursorPropertyInfo = Bool
    type AttrGetType DeviceHasCursorPropertyInfo = Bool
    type AttrLabel DeviceHasCursorPropertyInfo = "has-cursor"
    type AttrOrigin DeviceHasCursorPropertyInfo = Device
    attrGet = getDeviceHasCursor
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDeviceHasCursor
    attrClear = undefined
#endif

-- VVV Prop "input-mode"
   -- Type: TInterface (Name {namespace = "Gdk", name = "InputMode"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@input-mode@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #inputMode
-- @
getDeviceInputMode :: (MonadIO m, IsDevice o) => o -> m Gdk.Enums.InputMode
getDeviceInputMode :: o -> m InputMode
getDeviceInputMode obj :: o
obj = IO InputMode -> m InputMode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputMode -> m InputMode) -> IO InputMode -> m InputMode
forall a b. (a -> b) -> a -> b
$ o -> String -> IO InputMode
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj "input-mode"

-- | Set the value of the “@input-mode@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' device [ #inputMode 'Data.GI.Base.Attributes.:=' value ]
-- @
setDeviceInputMode :: (MonadIO m, IsDevice o) => o -> Gdk.Enums.InputMode -> m ()
setDeviceInputMode :: o -> InputMode -> m ()
setDeviceInputMode obj :: o
obj val :: InputMode
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> InputMode -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj "input-mode" InputMode
val

-- | Construct a `GValueConstruct` with valid value for the “@input-mode@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceInputMode :: (IsDevice o) => Gdk.Enums.InputMode -> IO (GValueConstruct o)
constructDeviceInputMode :: InputMode -> IO (GValueConstruct o)
constructDeviceInputMode val :: InputMode
val = String -> InputMode -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum "input-mode" InputMode
val

#if defined(ENABLE_OVERLOADING)
data DeviceInputModePropertyInfo
instance AttrInfo DeviceInputModePropertyInfo where
    type AttrAllowedOps DeviceInputModePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DeviceInputModePropertyInfo = IsDevice
    type AttrSetTypeConstraint DeviceInputModePropertyInfo = (~) Gdk.Enums.InputMode
    type AttrTransferTypeConstraint DeviceInputModePropertyInfo = (~) Gdk.Enums.InputMode
    type AttrTransferType DeviceInputModePropertyInfo = Gdk.Enums.InputMode
    type AttrGetType DeviceInputModePropertyInfo = Gdk.Enums.InputMode
    type AttrLabel DeviceInputModePropertyInfo = "input-mode"
    type AttrOrigin DeviceInputModePropertyInfo = Device
    attrGet = getDeviceInputMode
    attrSet = setDeviceInputMode
    attrTransfer _ v = do
        return v
    attrConstruct = constructDeviceInputMode
    attrClear = undefined
#endif

-- VVV Prop "input-source"
   -- Type: TInterface (Name {namespace = "Gdk", name = "InputSource"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@input-source@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #inputSource
-- @
getDeviceInputSource :: (MonadIO m, IsDevice o) => o -> m Gdk.Enums.InputSource
getDeviceInputSource :: o -> m InputSource
getDeviceInputSource obj :: o
obj = IO InputSource -> m InputSource
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputSource -> m InputSource)
-> IO InputSource -> m InputSource
forall a b. (a -> b) -> a -> b
$ o -> String -> IO InputSource
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj "input-source"

-- | Construct a `GValueConstruct` with valid value for the “@input-source@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceInputSource :: (IsDevice o) => Gdk.Enums.InputSource -> IO (GValueConstruct o)
constructDeviceInputSource :: InputSource -> IO (GValueConstruct o)
constructDeviceInputSource val :: InputSource
val = String -> InputSource -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum "input-source" InputSource
val

#if defined(ENABLE_OVERLOADING)
data DeviceInputSourcePropertyInfo
instance AttrInfo DeviceInputSourcePropertyInfo where
    type AttrAllowedOps DeviceInputSourcePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DeviceInputSourcePropertyInfo = IsDevice
    type AttrSetTypeConstraint DeviceInputSourcePropertyInfo = (~) Gdk.Enums.InputSource
    type AttrTransferTypeConstraint DeviceInputSourcePropertyInfo = (~) Gdk.Enums.InputSource
    type AttrTransferType DeviceInputSourcePropertyInfo = Gdk.Enums.InputSource
    type AttrGetType DeviceInputSourcePropertyInfo = Gdk.Enums.InputSource
    type AttrLabel DeviceInputSourcePropertyInfo = "input-source"
    type AttrOrigin DeviceInputSourcePropertyInfo = Device
    attrGet = getDeviceInputSource
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDeviceInputSource
    attrClear = undefined
#endif

-- VVV Prop "n-axes"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@n-axes@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #nAxes
-- @
getDeviceNAxes :: (MonadIO m, IsDevice o) => o -> m Word32
getDeviceNAxes :: o -> m Word32
getDeviceNAxes obj :: o
obj = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj "n-axes"

#if defined(ENABLE_OVERLOADING)
data DeviceNAxesPropertyInfo
instance AttrInfo DeviceNAxesPropertyInfo where
    type AttrAllowedOps DeviceNAxesPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint DeviceNAxesPropertyInfo = IsDevice
    type AttrSetTypeConstraint DeviceNAxesPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DeviceNAxesPropertyInfo = (~) ()
    type AttrTransferType DeviceNAxesPropertyInfo = ()
    type AttrGetType DeviceNAxesPropertyInfo = Word32
    type AttrLabel DeviceNAxesPropertyInfo = "n-axes"
    type AttrOrigin DeviceNAxesPropertyInfo = Device
    attrGet = getDeviceNAxes
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "name"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@name@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #name
-- @
getDeviceName :: (MonadIO m, IsDevice o) => o -> m T.Text
getDeviceName :: o -> m Text
getDeviceName obj :: o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "getDeviceName" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "name"

-- | Construct a `GValueConstruct` with valid value for the “@name@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceName :: (IsDevice o) => T.Text -> IO (GValueConstruct o)
constructDeviceName :: Text -> IO (GValueConstruct o)
constructDeviceName val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

#if defined(ENABLE_OVERLOADING)
data DeviceNamePropertyInfo
instance AttrInfo DeviceNamePropertyInfo where
    type AttrAllowedOps DeviceNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DeviceNamePropertyInfo = IsDevice
    type AttrSetTypeConstraint DeviceNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DeviceNamePropertyInfo = (~) T.Text
    type AttrTransferType DeviceNamePropertyInfo = T.Text
    type AttrGetType DeviceNamePropertyInfo = T.Text
    type AttrLabel DeviceNamePropertyInfo = "name"
    type AttrOrigin DeviceNamePropertyInfo = Device
    attrGet = getDeviceName
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDeviceName
    attrClear = undefined
#endif

-- VVV Prop "num-touches"
   -- Type: TBasicType TUInt
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@num-touches@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #numTouches
-- @
getDeviceNumTouches :: (MonadIO m, IsDevice o) => o -> m Word32
getDeviceNumTouches :: o -> m Word32
getDeviceNumTouches obj :: o
obj = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word32
forall a. GObject a => a -> String -> IO Word32
B.Properties.getObjectPropertyUInt32 o
obj "num-touches"

-- | Construct a `GValueConstruct` with valid value for the “@num-touches@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceNumTouches :: (IsDevice o) => Word32 -> IO (GValueConstruct o)
constructDeviceNumTouches :: Word32 -> IO (GValueConstruct o)
constructDeviceNumTouches val :: Word32
val = String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 "num-touches" Word32
val

#if defined(ENABLE_OVERLOADING)
data DeviceNumTouchesPropertyInfo
instance AttrInfo DeviceNumTouchesPropertyInfo where
    type AttrAllowedOps DeviceNumTouchesPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DeviceNumTouchesPropertyInfo = IsDevice
    type AttrSetTypeConstraint DeviceNumTouchesPropertyInfo = (~) Word32
    type AttrTransferTypeConstraint DeviceNumTouchesPropertyInfo = (~) Word32
    type AttrTransferType DeviceNumTouchesPropertyInfo = Word32
    type AttrGetType DeviceNumTouchesPropertyInfo = Word32
    type AttrLabel DeviceNumTouchesPropertyInfo = "num-touches"
    type AttrOrigin DeviceNumTouchesPropertyInfo = Device
    attrGet = getDeviceNumTouches
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDeviceNumTouches
    attrClear = undefined
#endif

-- VVV Prop "product-id"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just True,Nothing)

-- | Get the value of the “@product-id@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #productId
-- @
getDeviceProductId :: (MonadIO m, IsDevice o) => o -> m (Maybe T.Text)
getDeviceProductId :: o -> m (Maybe Text)
getDeviceProductId obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "product-id"

-- | Construct a `GValueConstruct` with valid value for the “@product-id@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceProductId :: (IsDevice o) => T.Text -> IO (GValueConstruct o)
constructDeviceProductId :: Text -> IO (GValueConstruct o)
constructDeviceProductId val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "product-id" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

#if defined(ENABLE_OVERLOADING)
data DeviceProductIdPropertyInfo
instance AttrInfo DeviceProductIdPropertyInfo where
    type AttrAllowedOps DeviceProductIdPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DeviceProductIdPropertyInfo = IsDevice
    type AttrSetTypeConstraint DeviceProductIdPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DeviceProductIdPropertyInfo = (~) T.Text
    type AttrTransferType DeviceProductIdPropertyInfo = T.Text
    type AttrGetType DeviceProductIdPropertyInfo = (Maybe T.Text)
    type AttrLabel DeviceProductIdPropertyInfo = "product-id"
    type AttrOrigin DeviceProductIdPropertyInfo = Device
    attrGet = getDeviceProductId
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDeviceProductId
    attrClear = undefined
#endif

-- VVV Prop "seat"
   -- Type: TInterface (Name {namespace = "Gdk", name = "Seat"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@seat@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #seat
-- @
getDeviceSeat :: (MonadIO m, IsDevice o) => o -> m Gdk.Seat.Seat
getDeviceSeat :: o -> m Seat
getDeviceSeat obj :: o
obj = IO Seat -> m Seat
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Seat -> m Seat) -> IO Seat -> m Seat
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Seat) -> IO Seat
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "getDeviceSeat" (IO (Maybe Seat) -> IO Seat) -> IO (Maybe Seat) -> IO Seat
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Seat -> Seat) -> IO (Maybe Seat)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "seat" ManagedPtr Seat -> Seat
Gdk.Seat.Seat

-- | Set the value of the “@seat@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' device [ #seat 'Data.GI.Base.Attributes.:=' value ]
-- @
setDeviceSeat :: (MonadIO m, IsDevice o, Gdk.Seat.IsSeat a) => o -> a -> m ()
setDeviceSeat :: o -> a -> m ()
setDeviceSeat obj :: o
obj val :: a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "seat" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@seat@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceSeat :: (IsDevice o, Gdk.Seat.IsSeat a) => a -> IO (GValueConstruct o)
constructDeviceSeat :: a -> IO (GValueConstruct o)
constructDeviceSeat val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "seat" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Set the value of the “@seat@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #seat
-- @
clearDeviceSeat :: (MonadIO m, IsDevice o) => o -> m ()
clearDeviceSeat :: o -> m ()
clearDeviceSeat obj :: o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Seat -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj "seat" (Maybe Seat
forall a. Maybe a
Nothing :: Maybe Gdk.Seat.Seat)

#if defined(ENABLE_OVERLOADING)
data DeviceSeatPropertyInfo
instance AttrInfo DeviceSeatPropertyInfo where
    type AttrAllowedOps DeviceSeatPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DeviceSeatPropertyInfo = IsDevice
    type AttrSetTypeConstraint DeviceSeatPropertyInfo = Gdk.Seat.IsSeat
    type AttrTransferTypeConstraint DeviceSeatPropertyInfo = Gdk.Seat.IsSeat
    type AttrTransferType DeviceSeatPropertyInfo = Gdk.Seat.Seat
    type AttrGetType DeviceSeatPropertyInfo = Gdk.Seat.Seat
    type AttrLabel DeviceSeatPropertyInfo = "seat"
    type AttrOrigin DeviceSeatPropertyInfo = Device
    attrGet = getDeviceSeat
    attrSet = setDeviceSeat
    attrTransfer _ v = do
        unsafeCastTo Gdk.Seat.Seat v
    attrConstruct = constructDeviceSeat
    attrClear = clearDeviceSeat
#endif

-- VVV Prop "tool"
   -- Type: TInterface (Name {namespace = "Gdk", name = "DeviceTool"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@tool@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #tool
-- @
getDeviceTool :: (MonadIO m, IsDevice o) => o -> m (Maybe Gdk.DeviceTool.DeviceTool)
getDeviceTool :: o -> m (Maybe DeviceTool)
getDeviceTool obj :: o
obj = IO (Maybe DeviceTool) -> m (Maybe DeviceTool)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DeviceTool) -> m (Maybe DeviceTool))
-> IO (Maybe DeviceTool) -> m (Maybe DeviceTool)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr DeviceTool -> DeviceTool)
-> IO (Maybe DeviceTool)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "tool" ManagedPtr DeviceTool -> DeviceTool
Gdk.DeviceTool.DeviceTool

#if defined(ENABLE_OVERLOADING)
data DeviceToolPropertyInfo
instance AttrInfo DeviceToolPropertyInfo where
    type AttrAllowedOps DeviceToolPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DeviceToolPropertyInfo = IsDevice
    type AttrSetTypeConstraint DeviceToolPropertyInfo = (~) ()
    type AttrTransferTypeConstraint DeviceToolPropertyInfo = (~) ()
    type AttrTransferType DeviceToolPropertyInfo = ()
    type AttrGetType DeviceToolPropertyInfo = (Maybe Gdk.DeviceTool.DeviceTool)
    type AttrLabel DeviceToolPropertyInfo = "tool"
    type AttrOrigin DeviceToolPropertyInfo = Device
    attrGet = getDeviceTool
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif

-- VVV Prop "type"
   -- Type: TInterface (Name {namespace = "Gdk", name = "DeviceType"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@type@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #type
-- @
getDeviceType :: (MonadIO m, IsDevice o) => o -> m Gdk.Enums.DeviceType
getDeviceType :: o -> m DeviceType
getDeviceType obj :: o
obj = IO DeviceType -> m DeviceType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DeviceType -> m DeviceType) -> IO DeviceType -> m DeviceType
forall a b. (a -> b) -> a -> b
$ o -> String -> IO DeviceType
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj "type"

-- | Construct a `GValueConstruct` with valid value for the “@type@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceType :: (IsDevice o) => Gdk.Enums.DeviceType -> IO (GValueConstruct o)
constructDeviceType :: DeviceType -> IO (GValueConstruct o)
constructDeviceType val :: DeviceType
val = String -> DeviceType -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum "type" DeviceType
val

#if defined(ENABLE_OVERLOADING)
data DeviceTypePropertyInfo
instance AttrInfo DeviceTypePropertyInfo where
    type AttrAllowedOps DeviceTypePropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DeviceTypePropertyInfo = IsDevice
    type AttrSetTypeConstraint DeviceTypePropertyInfo = (~) Gdk.Enums.DeviceType
    type AttrTransferTypeConstraint DeviceTypePropertyInfo = (~) Gdk.Enums.DeviceType
    type AttrTransferType DeviceTypePropertyInfo = Gdk.Enums.DeviceType
    type AttrGetType DeviceTypePropertyInfo = Gdk.Enums.DeviceType
    type AttrLabel DeviceTypePropertyInfo = "type"
    type AttrOrigin DeviceTypePropertyInfo = Device
    attrGet = getDeviceType
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDeviceType
    attrClear = undefined
#endif

-- VVV Prop "vendor-id"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just True,Nothing)

-- | Get the value of the “@vendor-id@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' device #vendorId
-- @
getDeviceVendorId :: (MonadIO m, IsDevice o) => o -> m (Maybe T.Text)
getDeviceVendorId :: o -> m (Maybe Text)
getDeviceVendorId obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "vendor-id"

-- | Construct a `GValueConstruct` with valid value for the “@vendor-id@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDeviceVendorId :: (IsDevice o) => T.Text -> IO (GValueConstruct o)
constructDeviceVendorId :: Text -> IO (GValueConstruct o)
constructDeviceVendorId val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "vendor-id" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

#if defined(ENABLE_OVERLOADING)
data DeviceVendorIdPropertyInfo
instance AttrInfo DeviceVendorIdPropertyInfo where
    type AttrAllowedOps DeviceVendorIdPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DeviceVendorIdPropertyInfo = IsDevice
    type AttrSetTypeConstraint DeviceVendorIdPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DeviceVendorIdPropertyInfo = (~) T.Text
    type AttrTransferType DeviceVendorIdPropertyInfo = T.Text
    type AttrGetType DeviceVendorIdPropertyInfo = (Maybe T.Text)
    type AttrLabel DeviceVendorIdPropertyInfo = "vendor-id"
    type AttrOrigin DeviceVendorIdPropertyInfo = Device
    attrGet = getDeviceVendorId
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDeviceVendorId
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Device
type instance O.AttributeList Device = DeviceAttributeList
type DeviceAttributeList = ('[ '("associatedDevice", DeviceAssociatedDevicePropertyInfo), '("axes", DeviceAxesPropertyInfo), '("deviceManager", DeviceDeviceManagerPropertyInfo), '("display", DeviceDisplayPropertyInfo), '("hasCursor", DeviceHasCursorPropertyInfo), '("inputMode", DeviceInputModePropertyInfo), '("inputSource", DeviceInputSourcePropertyInfo), '("nAxes", DeviceNAxesPropertyInfo), '("name", DeviceNamePropertyInfo), '("numTouches", DeviceNumTouchesPropertyInfo), '("productId", DeviceProductIdPropertyInfo), '("seat", DeviceSeatPropertyInfo), '("tool", DeviceToolPropertyInfo), '("type", DeviceTypePropertyInfo), '("vendorId", DeviceVendorIdPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
deviceAssociatedDevice :: AttrLabelProxy "associatedDevice"
deviceAssociatedDevice = AttrLabelProxy

deviceAxes :: AttrLabelProxy "axes"
deviceAxes = AttrLabelProxy

deviceDeviceManager :: AttrLabelProxy "deviceManager"
deviceDeviceManager = AttrLabelProxy

deviceDisplay :: AttrLabelProxy "display"
deviceDisplay = AttrLabelProxy

deviceHasCursor :: AttrLabelProxy "hasCursor"
deviceHasCursor = AttrLabelProxy

deviceInputMode :: AttrLabelProxy "inputMode"
deviceInputMode = AttrLabelProxy

deviceInputSource :: AttrLabelProxy "inputSource"
deviceInputSource = AttrLabelProxy

deviceNAxes :: AttrLabelProxy "nAxes"
deviceNAxes = AttrLabelProxy

deviceName :: AttrLabelProxy "name"
deviceName = AttrLabelProxy

deviceNumTouches :: AttrLabelProxy "numTouches"
deviceNumTouches = AttrLabelProxy

deviceProductId :: AttrLabelProxy "productId"
deviceProductId = AttrLabelProxy

deviceSeat :: AttrLabelProxy "seat"
deviceSeat = AttrLabelProxy

deviceTool :: AttrLabelProxy "tool"
deviceTool = AttrLabelProxy

deviceType :: AttrLabelProxy "type"
deviceType = AttrLabelProxy

deviceVendorId :: AttrLabelProxy "vendorId"
deviceVendorId = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Device = DeviceSignalList
type DeviceSignalList = ('[ '("changed", DeviceChangedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("toolChanged", DeviceToolChangedSignalInfo)] :: [(Symbol, *)])

#endif

-- method Device::get_associated_device
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Device" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_associated_device" gdk_device_get_associated_device :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    IO (Ptr Device)

-- | Returns the associated device to /@device@/, if /@device@/ is of type
-- 'GI.Gdk.Enums.DeviceTypeMaster', it will return the paired pointer or
-- keyboard.
-- 
-- If /@device@/ is of type 'GI.Gdk.Enums.DeviceTypeSlave', it will return
-- the master device to which /@device@/ is attached to.
-- 
-- If /@device@/ is of type 'GI.Gdk.Enums.DeviceTypeFloating', 'P.Nothing' will be
-- returned, as there is no associated device.
-- 
-- /Since: 3.0/
deviceGetAssociatedDevice ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gdk.Objects.Device.Device'
    -> m (Maybe Device)
    -- ^ __Returns:__ The associated device, or
    --   'P.Nothing'
deviceGetAssociatedDevice :: a -> m (Maybe Device)
deviceGetAssociatedDevice device :: a
device = IO (Maybe Device) -> m (Maybe Device)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Device) -> m (Maybe Device))
-> IO (Maybe Device) -> m (Maybe Device)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr Device
result <- Ptr Device -> IO (Ptr Device)
gdk_device_get_associated_device Ptr Device
device'
    Maybe Device
maybeResult <- Ptr Device -> (Ptr Device -> IO Device) -> IO (Maybe Device)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Device
result ((Ptr Device -> IO Device) -> IO (Maybe Device))
-> (Ptr Device -> IO Device) -> IO (Maybe Device)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Device
result' -> do
        Device
result'' <- ((ManagedPtr Device -> Device) -> Ptr Device -> IO Device
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Device -> Device
Device) Ptr Device
result'
        Device -> IO Device
forall (m :: * -> *) a. Monad m => a -> m a
return Device
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Maybe Device -> IO (Maybe Device)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Device
maybeResult

#if defined(ENABLE_OVERLOADING)
data DeviceGetAssociatedDeviceMethodInfo
instance (signature ~ (m (Maybe Device)), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetAssociatedDeviceMethodInfo a signature where
    overloadedMethod = deviceGetAssociatedDevice

#endif

-- method Device::get_axes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "AxisFlags" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_axes" gdk_device_get_axes :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    IO CUInt

-- | Returns the axes currently available on the device.
-- 
-- /Since: 3.22/
deviceGetAxes ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gdk.Objects.Device.Device'
    -> m [Gdk.Flags.AxisFlags]
deviceGetAxes :: a -> m [AxisFlags]
deviceGetAxes device :: a
device = IO [AxisFlags] -> m [AxisFlags]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [AxisFlags] -> m [AxisFlags])
-> IO [AxisFlags] -> m [AxisFlags]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    CUInt
result <- Ptr Device -> IO CUInt
gdk_device_get_axes Ptr Device
device'
    let result' :: [AxisFlags]
result' = CUInt -> [AxisFlags]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    [AxisFlags] -> IO [AxisFlags]
forall (m :: * -> *) a. Monad m => a -> m a
return [AxisFlags]
result'

#if defined(ENABLE_OVERLOADING)
data DeviceGetAxesMethodInfo
instance (signature ~ (m [Gdk.Flags.AxisFlags]), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetAxesMethodInfo a signature where
    overloadedMethod = deviceGetAxes

#endif

-- method Device::get_axis_use
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer #GdkDevice."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "index_"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the index of the axis."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "AxisUse" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_axis_use" gdk_device_get_axis_use :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    Word32 ->                               -- index_ : TBasicType TUInt
    IO CUInt

-- | Returns the axis use for /@index_@/.
-- 
-- /Since: 2.20/
deviceGetAxisUse ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a pointer t'GI.Gdk.Objects.Device.Device'.
    -> Word32
    -- ^ /@index_@/: the index of the axis.
    -> m Gdk.Enums.AxisUse
    -- ^ __Returns:__ a t'GI.Gdk.Enums.AxisUse' specifying how the axis is used.
deviceGetAxisUse :: a -> Word32 -> m AxisUse
deviceGetAxisUse device :: a
device index_ :: Word32
index_ = IO AxisUse -> m AxisUse
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AxisUse -> m AxisUse) -> IO AxisUse -> m AxisUse
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    CUInt
result <- Ptr Device -> Word32 -> IO CUInt
gdk_device_get_axis_use Ptr Device
device' Word32
index_
    let result' :: AxisUse
result' = (Int -> AxisUse
forall a. Enum a => Int -> a
toEnum (Int -> AxisUse) -> (CUInt -> Int) -> CUInt -> AxisUse
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    AxisUse -> IO AxisUse
forall (m :: * -> *) a. Monad m => a -> m a
return AxisUse
result'

#if defined(ENABLE_OVERLOADING)
data DeviceGetAxisUseMethodInfo
instance (signature ~ (Word32 -> m Gdk.Enums.AxisUse), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetAxisUseMethodInfo a signature where
    overloadedMethod = deviceGetAxisUse

#endif

-- method Device::get_device_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "DeviceType" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_device_type" gdk_device_get_device_type :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    IO CUInt

-- | Returns the device type for /@device@/.
-- 
-- /Since: 3.0/
deviceGetDeviceType ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gdk.Objects.Device.Device'
    -> m Gdk.Enums.DeviceType
    -- ^ __Returns:__ the t'GI.Gdk.Enums.DeviceType' for /@device@/.
deviceGetDeviceType :: a -> m DeviceType
deviceGetDeviceType device :: a
device = IO DeviceType -> m DeviceType
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DeviceType -> m DeviceType) -> IO DeviceType -> m DeviceType
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    CUInt
result <- Ptr Device -> IO CUInt
gdk_device_get_device_type Ptr Device
device'
    let result' :: DeviceType
result' = (Int -> DeviceType
forall a. Enum a => Int -> a
toEnum (Int -> DeviceType) -> (CUInt -> Int) -> CUInt -> DeviceType
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    DeviceType -> IO DeviceType
forall (m :: * -> *) a. Monad m => a -> m a
return DeviceType
result'

#if defined(ENABLE_OVERLOADING)
data DeviceGetDeviceTypeMethodInfo
instance (signature ~ (m Gdk.Enums.DeviceType), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetDeviceTypeMethodInfo a signature where
    overloadedMethod = deviceGetDeviceType

#endif

-- method Device::get_display
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Display" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_display" gdk_device_get_display :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    IO (Ptr Gdk.Display.Display)

-- | Returns the t'GI.Gdk.Objects.Display.Display' to which /@device@/ pertains.
-- 
-- /Since: 3.0/
deviceGetDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gdk.Objects.Device.Device'
    -> m Gdk.Display.Display
    -- ^ __Returns:__ a t'GI.Gdk.Objects.Display.Display'. This memory is owned
    --          by GTK+, and must not be freed or unreffed.
deviceGetDisplay :: a -> m Display
deviceGetDisplay device :: a
device = IO Display -> m Display
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Display -> m Display) -> IO Display -> m Display
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr Display
result <- Ptr Device -> IO (Ptr Display)
gdk_device_get_display Ptr Device
device'
    Text -> Ptr Display -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "deviceGetDisplay" Ptr Display
result
    Display
result' <- ((ManagedPtr Display -> Display) -> Ptr Display -> IO Display
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Display -> Display
Gdk.Display.Display) Ptr Display
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Display -> IO Display
forall (m :: * -> *) a. Monad m => a -> m a
return Display
result'

#if defined(ENABLE_OVERLOADING)
data DeviceGetDisplayMethodInfo
instance (signature ~ (m Gdk.Display.Display), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetDisplayMethodInfo a signature where
    overloadedMethod = deviceGetDisplay

#endif

-- method Device::get_has_cursor
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_has_cursor" gdk_device_get_has_cursor :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    IO CInt

-- | Determines whether the pointer follows device motion.
-- This is not meaningful for keyboard devices, which don\'t have a pointer.
-- 
-- /Since: 2.20/
deviceGetHasCursor ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gdk.Objects.Device.Device'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the pointer follows device motion
deviceGetHasCursor :: a -> m Bool
deviceGetHasCursor device :: a
device = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    CInt
result <- Ptr Device -> IO CInt
gdk_device_get_has_cursor Ptr Device
device'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DeviceGetHasCursorMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetHasCursorMethodInfo a signature where
    overloadedMethod = deviceGetHasCursor

#endif

-- method Device::get_key
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevice." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "index_"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the index of the macro button to get."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "keyval"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return value for the keyval."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "modifiers"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ModifierType" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return value for modifiers."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_key" gdk_device_get_key :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    Word32 ->                               -- index_ : TBasicType TUInt
    Ptr Word32 ->                           -- keyval : TBasicType TUInt
    Ptr CUInt ->                            -- modifiers : TInterface (Name {namespace = "Gdk", name = "ModifierType"})
    IO CInt

-- | If /@index_@/ has a valid keyval, this function will return 'P.True'
-- and fill in /@keyval@/ and /@modifiers@/ with the keyval settings.
-- 
-- /Since: 2.20/
deviceGetKey ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gdk.Objects.Device.Device'.
    -> Word32
    -- ^ /@index_@/: the index of the macro button to get.
    -> m ((Bool, Word32, [Gdk.Flags.ModifierType]))
    -- ^ __Returns:__ 'P.True' if keyval is set for /@index@/.
deviceGetKey :: a -> Word32 -> m (Bool, Word32, [ModifierType])
deviceGetKey device :: a
device index_ :: Word32
index_ = IO (Bool, Word32, [ModifierType])
-> m (Bool, Word32, [ModifierType])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Word32, [ModifierType])
 -> m (Bool, Word32, [ModifierType]))
-> IO (Bool, Word32, [ModifierType])
-> m (Bool, Word32, [ModifierType])
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr Word32
keyval <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
    Ptr CUInt
modifiers <- IO (Ptr CUInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CUInt)
    CInt
result <- Ptr Device -> Word32 -> Ptr Word32 -> Ptr CUInt -> IO CInt
gdk_device_get_key Ptr Device
device' Word32
index_ Ptr Word32
keyval Ptr CUInt
modifiers
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Word32
keyval' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
keyval
    CUInt
modifiers' <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CUInt
modifiers
    let modifiers'' :: [ModifierType]
modifiers'' = CUInt -> [ModifierType]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
modifiers'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
keyval
    Ptr CUInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CUInt
modifiers
    (Bool, Word32, [ModifierType]) -> IO (Bool, Word32, [ModifierType])
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Word32
keyval', [ModifierType]
modifiers'')

#if defined(ENABLE_OVERLOADING)
data DeviceGetKeyMethodInfo
instance (signature ~ (Word32 -> m ((Bool, Word32, [Gdk.Flags.ModifierType]))), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetKeyMethodInfo a signature where
    overloadedMethod = deviceGetKey

#endif

-- method Device::get_last_event_window
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GdkDevice, with a source other than %GDK_SOURCE_KEYBOARD"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Window" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_last_event_window" gdk_device_get_last_event_window :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    IO (Ptr Gdk.Window.Window)

-- | Gets information about which window the given pointer device is in, based on events
-- that have been received so far from the display server. If another application
-- has a pointer grab, or this application has a grab with owner_events = 'P.False',
-- 'P.Nothing' may be returned even if the pointer is physically over one of this
-- application\'s windows.
-- 
-- /Since: 3.12/
deviceGetLastEventWindow ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gdk.Objects.Device.Device', with a source other than 'GI.Gdk.Enums.InputSourceKeyboard'
    -> m (Maybe Gdk.Window.Window)
    -- ^ __Returns:__ the last window the device
deviceGetLastEventWindow :: a -> m (Maybe Window)
deviceGetLastEventWindow device :: a
device = IO (Maybe Window) -> m (Maybe Window)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Window) -> m (Maybe Window))
-> IO (Maybe Window) -> m (Maybe Window)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr Window
result <- Ptr Device -> IO (Ptr Window)
gdk_device_get_last_event_window Ptr Device
device'
    Maybe Window
maybeResult <- Ptr Window -> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Window
result ((Ptr Window -> IO Window) -> IO (Maybe Window))
-> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Window
result' -> do
        Window
result'' <- ((ManagedPtr Window -> Window) -> Ptr Window -> IO Window
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Window -> Window
Gdk.Window.Window) Ptr Window
result'
        Window -> IO Window
forall (m :: * -> *) a. Monad m => a -> m a
return Window
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Maybe Window -> IO (Maybe Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Window
maybeResult

#if defined(ENABLE_OVERLOADING)
data DeviceGetLastEventWindowMethodInfo
instance (signature ~ (m (Maybe Gdk.Window.Window)), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetLastEventWindowMethodInfo a signature where
    overloadedMethod = deviceGetLastEventWindow

#endif

-- method Device::get_mode
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "InputMode" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_mode" gdk_device_get_mode :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    IO CUInt

-- | Determines the mode of the device.
-- 
-- /Since: 2.20/
deviceGetMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gdk.Objects.Device.Device'
    -> m Gdk.Enums.InputMode
    -- ^ __Returns:__ a t'GI.Gdk.Enums.InputSource'
deviceGetMode :: a -> m InputMode
deviceGetMode device :: a
device = IO InputMode -> m InputMode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputMode -> m InputMode) -> IO InputMode -> m InputMode
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    CUInt
result <- Ptr Device -> IO CUInt
gdk_device_get_mode Ptr Device
device'
    let result' :: InputMode
result' = (Int -> InputMode
forall a. Enum a => Int -> a
toEnum (Int -> InputMode) -> (CUInt -> Int) -> CUInt -> InputMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    InputMode -> IO InputMode
forall (m :: * -> *) a. Monad m => a -> m a
return InputMode
result'

#if defined(ENABLE_OVERLOADING)
data DeviceGetModeMethodInfo
instance (signature ~ (m Gdk.Enums.InputMode), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetModeMethodInfo a signature where
    overloadedMethod = deviceGetMode

#endif

-- method Device::get_n_axes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer #GdkDevice"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_n_axes" gdk_device_get_n_axes :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    IO Int32

-- | Returns the number of axes the device currently has.
-- 
-- /Since: 3.0/
deviceGetNAxes ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a pointer t'GI.Gdk.Objects.Device.Device'
    -> m Int32
    -- ^ __Returns:__ the number of axes.
deviceGetNAxes :: a -> m Int32
deviceGetNAxes device :: a
device = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Int32
result <- Ptr Device -> IO Int32
gdk_device_get_n_axes Ptr Device
device'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data DeviceGetNAxesMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetNAxesMethodInfo a signature where
    overloadedMethod = deviceGetNAxes

#endif

-- method Device::get_n_keys
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_n_keys" gdk_device_get_n_keys :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    IO Int32

-- | Returns the number of keys the device currently has.
-- 
-- /Since: 2.24/
deviceGetNKeys ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gdk.Objects.Device.Device'
    -> m Int32
    -- ^ __Returns:__ the number of keys.
deviceGetNKeys :: a -> m Int32
deviceGetNKeys device :: a
device = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Int32
result <- Ptr Device -> IO Int32
gdk_device_get_n_keys Ptr Device
device'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data DeviceGetNKeysMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetNKeysMethodInfo a signature where
    overloadedMethod = deviceGetNKeys

#endif

-- method Device::get_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_name" gdk_device_get_name :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    IO CString

-- | Determines the name of the device.
-- 
-- /Since: 2.20/
deviceGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gdk.Objects.Device.Device'
    -> m T.Text
    -- ^ __Returns:__ a name
deviceGetName :: a -> m Text
deviceGetName device :: a
device = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    CString
result <- Ptr Device -> IO CString
gdk_device_get_name Ptr Device
device'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "deviceGetName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DeviceGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetNameMethodInfo a signature where
    overloadedMethod = deviceGetName

#endif

-- method Device::get_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "pointer device to query status about."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "screen"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Screen" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store the #GdkScreen\n         the @device is on, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store root window X coordinate of @device, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store root window Y coordinate of @device, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_position" gdk_device_get_position :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    Ptr (Ptr Gdk.Screen.Screen) ->          -- screen : TInterface (Name {namespace = "Gdk", name = "Screen"})
    Ptr Int32 ->                            -- x : TBasicType TInt
    Ptr Int32 ->                            -- y : TBasicType TInt
    IO ()

-- | Gets the current location of /@device@/. As a slave device
-- coordinates are those of its master pointer, This function
-- may not be called on devices of type 'GI.Gdk.Enums.DeviceTypeSlave',
-- unless there is an ongoing grab on them, see 'GI.Gdk.Objects.Device.deviceGrab'.
-- 
-- /Since: 3.0/
deviceGetPosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: pointer device to query status about.
    -> m ((Gdk.Screen.Screen, Int32, Int32))
deviceGetPosition :: a -> m (Screen, Int32, Int32)
deviceGetPosition device :: a
device = IO (Screen, Int32, Int32) -> m (Screen, Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Screen, Int32, Int32) -> m (Screen, Int32, Int32))
-> IO (Screen, Int32, Int32) -> m (Screen, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr (Ptr Screen)
screen <- IO (Ptr (Ptr Screen))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr Gdk.Screen.Screen))
    Ptr Int32
x <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
y <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Device -> Ptr (Ptr Screen) -> Ptr Int32 -> Ptr Int32 -> IO ()
gdk_device_get_position Ptr Device
device' Ptr (Ptr Screen)
screen Ptr Int32
x Ptr Int32
y
    Ptr Screen
screen' <- Ptr (Ptr Screen) -> IO (Ptr Screen)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Screen)
screen
    Screen
screen'' <- ((ManagedPtr Screen -> Screen) -> Ptr Screen -> IO Screen
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Screen -> Screen
Gdk.Screen.Screen) Ptr Screen
screen'
    Int32
x' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
x
    Int32
y' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
y
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Ptr (Ptr Screen) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Screen)
screen
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
x
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
y
    (Screen, Int32, Int32) -> IO (Screen, Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Screen
screen'', Int32
x', Int32
y')

#if defined(ENABLE_OVERLOADING)
data DeviceGetPositionMethodInfo
instance (signature ~ (m ((Gdk.Screen.Screen, Int32, Int32))), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetPositionMethodInfo a signature where
    overloadedMethod = deviceGetPosition

#endif

-- method Device::get_position_double
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "pointer device to query status about."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "screen"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Screen" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store the #GdkScreen\n         the @device is on, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TDouble
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store root window X coordinate of @device, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TDouble
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store root window Y coordinate of @device, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_position_double" gdk_device_get_position_double :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    Ptr (Ptr Gdk.Screen.Screen) ->          -- screen : TInterface (Name {namespace = "Gdk", name = "Screen"})
    Ptr CDouble ->                          -- x : TBasicType TDouble
    Ptr CDouble ->                          -- y : TBasicType TDouble
    IO ()

-- | Gets the current location of /@device@/ in double precision. As a slave device\'s
-- coordinates are those of its master pointer, this function
-- may not be called on devices of type 'GI.Gdk.Enums.DeviceTypeSlave',
-- unless there is an ongoing grab on them. See 'GI.Gdk.Objects.Device.deviceGrab'.
-- 
-- /Since: 3.10/
deviceGetPositionDouble ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: pointer device to query status about.
    -> m ((Gdk.Screen.Screen, Double, Double))
deviceGetPositionDouble :: a -> m (Screen, Double, Double)
deviceGetPositionDouble device :: a
device = IO (Screen, Double, Double) -> m (Screen, Double, Double)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Screen, Double, Double) -> m (Screen, Double, Double))
-> IO (Screen, Double, Double) -> m (Screen, Double, Double)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr (Ptr Screen)
screen <- IO (Ptr (Ptr Screen))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr Gdk.Screen.Screen))
    Ptr CDouble
x <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble
y <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr Device
-> Ptr (Ptr Screen) -> Ptr CDouble -> Ptr CDouble -> IO ()
gdk_device_get_position_double Ptr Device
device' Ptr (Ptr Screen)
screen Ptr CDouble
x Ptr CDouble
y
    Ptr Screen
screen' <- Ptr (Ptr Screen) -> IO (Ptr Screen)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Screen)
screen
    Screen
screen'' <- ((ManagedPtr Screen -> Screen) -> Ptr Screen -> IO Screen
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Screen -> Screen
Gdk.Screen.Screen) Ptr Screen
screen'
    CDouble
x' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
x
    let x'' :: Double
x'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
x'
    CDouble
y' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
y
    let y'' :: Double
y'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
y'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Ptr (Ptr Screen) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Screen)
screen
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
x
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
y
    (Screen, Double, Double) -> IO (Screen, Double, Double)
forall (m :: * -> *) a. Monad m => a -> m a
return (Screen
screen'', Double
x'', Double
y'')

#if defined(ENABLE_OVERLOADING)
data DeviceGetPositionDoubleMethodInfo
instance (signature ~ (m ((Gdk.Screen.Screen, Double, Double))), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetPositionDoubleMethodInfo a signature where
    overloadedMethod = deviceGetPositionDouble

#endif

-- method Device::get_product_id
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a slave #GdkDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_product_id" gdk_device_get_product_id :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    IO CString

-- | Returns the product ID of this device, or 'P.Nothing' if this information couldn\'t
-- be obtained. This ID is retrieved from the device, and is thus constant for
-- it. See 'GI.Gdk.Objects.Device.deviceGetVendorId' for more information.
-- 
-- /Since: 3.16/
deviceGetProductId ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a slave t'GI.Gdk.Objects.Device.Device'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the product ID, or 'P.Nothing'
deviceGetProductId :: a -> m (Maybe Text)
deviceGetProductId device :: a
device = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    CString
result <- Ptr Device -> IO CString
gdk_device_get_product_id Ptr Device
device'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \result' :: CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data DeviceGetProductIdMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetProductIdMethodInfo a signature where
    overloadedMethod = deviceGetProductId

#endif

-- method Device::get_seat
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "A #GdkDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Seat" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_seat" gdk_device_get_seat :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    IO (Ptr Gdk.Seat.Seat)

-- | Returns the t'GI.Gdk.Objects.Seat.Seat' the device belongs to.
-- 
-- /Since: 3.20/
deviceGetSeat ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: A t'GI.Gdk.Objects.Device.Device'
    -> m Gdk.Seat.Seat
    -- ^ __Returns:__ A t'GI.Gdk.Objects.Seat.Seat'. This memory is owned by GTK+ and
    --          must not be freed.
deviceGetSeat :: a -> m Seat
deviceGetSeat device :: a
device = IO Seat -> m Seat
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Seat -> m Seat) -> IO Seat -> m Seat
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr Seat
result <- Ptr Device -> IO (Ptr Seat)
gdk_device_get_seat Ptr Device
device'
    Text -> Ptr Seat -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "deviceGetSeat" Ptr Seat
result
    Seat
result' <- ((ManagedPtr Seat -> Seat) -> Ptr Seat -> IO Seat
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Seat -> Seat
Gdk.Seat.Seat) Ptr Seat
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Seat -> IO Seat
forall (m :: * -> *) a. Monad m => a -> m a
return Seat
result'

#if defined(ENABLE_OVERLOADING)
data DeviceGetSeatMethodInfo
instance (signature ~ (m Gdk.Seat.Seat), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetSeatMethodInfo a signature where
    overloadedMethod = deviceGetSeat

#endif

-- method Device::get_source
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "InputSource" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_source" gdk_device_get_source :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    IO CUInt

-- | Determines the type of the device.
-- 
-- /Since: 2.20/
deviceGetSource ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gdk.Objects.Device.Device'
    -> m Gdk.Enums.InputSource
    -- ^ __Returns:__ a t'GI.Gdk.Enums.InputSource'
deviceGetSource :: a -> m InputSource
deviceGetSource device :: a
device = IO InputSource -> m InputSource
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO InputSource -> m InputSource)
-> IO InputSource -> m InputSource
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    CUInt
result <- Ptr Device -> IO CUInt
gdk_device_get_source Ptr Device
device'
    let result' :: InputSource
result' = (Int -> InputSource
forall a. Enum a => Int -> a
toEnum (Int -> InputSource) -> (CUInt -> Int) -> CUInt -> InputSource
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    InputSource -> IO InputSource
forall (m :: * -> *) a. Monad m => a -> m a
return InputSource
result'

#if defined(ENABLE_OVERLOADING)
data DeviceGetSourceMethodInfo
instance (signature ~ (m Gdk.Enums.InputSource), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetSourceMethodInfo a signature where
    overloadedMethod = deviceGetSource

#endif

-- method Device::get_vendor_id
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a slave #GdkDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_vendor_id" gdk_device_get_vendor_id :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    IO CString

-- | Returns the vendor ID of this device, or 'P.Nothing' if this information couldn\'t
-- be obtained. This ID is retrieved from the device, and is thus constant for
-- it.
-- 
-- This function, together with 'GI.Gdk.Objects.Device.deviceGetProductId', can be used to eg.
-- compose t'GI.Gio.Objects.Settings.Settings' paths to store settings for this device.
-- 
-- 
-- === /C code/
-- >
-- > static GSettings *
-- > get_device_settings (GdkDevice *device)
-- > {
-- >   const gchar *vendor, *product;
-- >   GSettings *settings;
-- >   GdkDevice *device;
-- >   gchar *path;
-- >
-- >   vendor = gdk_device_get_vendor_id (device);
-- >   product = gdk_device_get_product_id (device);
-- >
-- >   path = g_strdup_printf ("/org/example/app/devices/%s:%s/", vendor, product);
-- >   settings = g_settings_new_with_path (DEVICE_SCHEMA, path);
-- >   g_free (path);
-- >
-- >   return settings;
-- > }
-- 
-- 
-- /Since: 3.16/
deviceGetVendorId ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a slave t'GI.Gdk.Objects.Device.Device'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the vendor ID, or 'P.Nothing'
deviceGetVendorId :: a -> m (Maybe Text)
deviceGetVendorId device :: a
device = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    CString
result <- Ptr Device -> IO CString
gdk_device_get_vendor_id Ptr Device
device'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \result' :: CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data DeviceGetVendorIdMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetVendorIdMethodInfo a signature where
    overloadedMethod = deviceGetVendorId

#endif

-- method Device::get_window_at_position
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "pointer #GdkDevice to query info to."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "win_x"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the X coordinate of the device location,\n        relative to the window origin, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "win_y"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the Y coordinate of the device location,\n        relative to the window origin, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Window" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_window_at_position" gdk_device_get_window_at_position :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    Ptr Int32 ->                            -- win_x : TBasicType TInt
    Ptr Int32 ->                            -- win_y : TBasicType TInt
    IO (Ptr Gdk.Window.Window)

-- | Obtains the window underneath /@device@/, returning the location of the device in /@winX@/ and /@winY@/. Returns
-- 'P.Nothing' if the window tree under /@device@/ is not known to GDK (for example, belongs to another application).
-- 
-- As a slave device coordinates are those of its master pointer, This
-- function may not be called on devices of type 'GI.Gdk.Enums.DeviceTypeSlave',
-- unless there is an ongoing grab on them, see 'GI.Gdk.Objects.Device.deviceGrab'.
-- 
-- /Since: 3.0/
deviceGetWindowAtPosition ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: pointer t'GI.Gdk.Objects.Device.Device' to query info to.
    -> m ((Maybe Gdk.Window.Window, Int32, Int32))
    -- ^ __Returns:__ the t'GI.Gdk.Objects.Window.Window' under the
    -- device position, or 'P.Nothing'.
deviceGetWindowAtPosition :: a -> m (Maybe Window, Int32, Int32)
deviceGetWindowAtPosition device :: a
device = IO (Maybe Window, Int32, Int32) -> m (Maybe Window, Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Window, Int32, Int32) -> m (Maybe Window, Int32, Int32))
-> IO (Maybe Window, Int32, Int32)
-> m (Maybe Window, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr Int32
winX <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
winY <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Window
result <- Ptr Device -> Ptr Int32 -> Ptr Int32 -> IO (Ptr Window)
gdk_device_get_window_at_position Ptr Device
device' Ptr Int32
winX Ptr Int32
winY
    Maybe Window
maybeResult <- Ptr Window -> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Window
result ((Ptr Window -> IO Window) -> IO (Maybe Window))
-> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Window
result' -> do
        Window
result'' <- ((ManagedPtr Window -> Window) -> Ptr Window -> IO Window
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Window -> Window
Gdk.Window.Window) Ptr Window
result'
        Window -> IO Window
forall (m :: * -> *) a. Monad m => a -> m a
return Window
result''
    Int32
winX' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
winX
    Int32
winY' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
winY
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
winX
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
winY
    (Maybe Window, Int32, Int32) -> IO (Maybe Window, Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Window
maybeResult, Int32
winX', Int32
winY')

#if defined(ENABLE_OVERLOADING)
data DeviceGetWindowAtPositionMethodInfo
instance (signature ~ (m ((Maybe Gdk.Window.Window, Int32, Int32))), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetWindowAtPositionMethodInfo a signature where
    overloadedMethod = deviceGetWindowAtPosition

#endif

-- method Device::get_window_at_position_double
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "pointer #GdkDevice to query info to."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "win_x"
--           , argType = TBasicType TDouble
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the X coordinate of the device location,\n        relative to the window origin, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "win_y"
--           , argType = TBasicType TDouble
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the Y coordinate of the device location,\n        relative to the window origin, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Window" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_get_window_at_position_double" gdk_device_get_window_at_position_double :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    Ptr CDouble ->                          -- win_x : TBasicType TDouble
    Ptr CDouble ->                          -- win_y : TBasicType TDouble
    IO (Ptr Gdk.Window.Window)

-- | Obtains the window underneath /@device@/, returning the location of the device in /@winX@/ and /@winY@/ in
-- double precision. Returns 'P.Nothing' if the window tree under /@device@/ is not known to GDK (for example,
-- belongs to another application).
-- 
-- As a slave device coordinates are those of its master pointer, This
-- function may not be called on devices of type 'GI.Gdk.Enums.DeviceTypeSlave',
-- unless there is an ongoing grab on them, see 'GI.Gdk.Objects.Device.deviceGrab'.
-- 
-- /Since: 3.0/
deviceGetWindowAtPositionDouble ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: pointer t'GI.Gdk.Objects.Device.Device' to query info to.
    -> m ((Maybe Gdk.Window.Window, Double, Double))
    -- ^ __Returns:__ the t'GI.Gdk.Objects.Window.Window' under the
    --   device position, or 'P.Nothing'.
deviceGetWindowAtPositionDouble :: a -> m (Maybe Window, Double, Double)
deviceGetWindowAtPositionDouble device :: a
device = IO (Maybe Window, Double, Double)
-> m (Maybe Window, Double, Double)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Window, Double, Double)
 -> m (Maybe Window, Double, Double))
-> IO (Maybe Window, Double, Double)
-> m (Maybe Window, Double, Double)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr CDouble
winX <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble
winY <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr Window
result <- Ptr Device -> Ptr CDouble -> Ptr CDouble -> IO (Ptr Window)
gdk_device_get_window_at_position_double Ptr Device
device' Ptr CDouble
winX Ptr CDouble
winY
    Maybe Window
maybeResult <- Ptr Window -> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Window
result ((Ptr Window -> IO Window) -> IO (Maybe Window))
-> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Window
result' -> do
        Window
result'' <- ((ManagedPtr Window -> Window) -> Ptr Window -> IO Window
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Window -> Window
Gdk.Window.Window) Ptr Window
result'
        Window -> IO Window
forall (m :: * -> *) a. Monad m => a -> m a
return Window
result''
    CDouble
winX' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
winX
    let winX'' :: Double
winX'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
winX'
    CDouble
winY' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
winY
    let winY'' :: Double
winY'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
winY'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
winX
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
winY
    (Maybe Window, Double, Double) -> IO (Maybe Window, Double, Double)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Window
maybeResult, Double
winX'', Double
winY'')

#if defined(ENABLE_OVERLOADING)
data DeviceGetWindowAtPositionDoubleMethodInfo
instance (signature ~ (m ((Maybe Gdk.Window.Window, Double, Double))), MonadIO m, IsDevice a) => O.MethodInfo DeviceGetWindowAtPositionDoubleMethodInfo a signature where
    overloadedMethod = deviceGetWindowAtPositionDouble

#endif

-- method Device::grab
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #GdkDevice. To get the device you can use gtk_get_current_event_device()\n  or gdk_event_get_device() if the grab is in reaction to an event. Also, you can use\n  gdk_device_manager_get_client_pointer() but only in code that isn\8217t triggered by a\n  #GdkEvent and there aren\8217t other means to get a meaningful #GdkDevice to operate on."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "window"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the #GdkWindow which will own the grab (the grab window)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "grab_ownership"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "GrabOwnership" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "specifies the grab ownership."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "owner_events"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "if %FALSE then all device events are reported with respect to\n               @window and are only reported if selected by @event_mask. If\n               %TRUE then pointer events for this application are reported\n               as normal, but pointer events outside this application are\n               reported with respect to @window and only if selected by\n               @event_mask. In either mode, unreported events are discarded."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "event_mask"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "EventMask" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "specifies the event mask, which is used in accordance with\n             @owner_events."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cursor"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Cursor" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the cursor to display while the grab is active if the device is\n         a pointer. If this is %NULL then the normal cursors are used for\n         @window and its descendants, and the cursor for @window is used\n         elsewhere."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "time_"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the timestamp of the event which led to this pointer grab. This\n        usually comes from the #GdkEvent struct, though %GDK_CURRENT_TIME\n        can be used if the time isn\8217t known."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "GrabStatus" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_grab" gdk_device_grab :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    Ptr Gdk.Window.Window ->                -- window : TInterface (Name {namespace = "Gdk", name = "Window"})
    CUInt ->                                -- grab_ownership : TInterface (Name {namespace = "Gdk", name = "GrabOwnership"})
    CInt ->                                 -- owner_events : TBasicType TBoolean
    CUInt ->                                -- event_mask : TInterface (Name {namespace = "Gdk", name = "EventMask"})
    Ptr Gdk.Cursor.Cursor ->                -- cursor : TInterface (Name {namespace = "Gdk", name = "Cursor"})
    Word32 ->                               -- time_ : TBasicType TUInt32
    IO CUInt

{-# DEPRECATED deviceGrab ["(Since version 3.20.)","Use 'GI.Gdk.Objects.Seat.seatGrab' instead."] #-}
-- | Grabs the device so that all events coming from this device are passed to
-- this application until the device is ungrabbed with 'GI.Gdk.Objects.Device.deviceUngrab',
-- or the window becomes unviewable. This overrides any previous grab on the device
-- by this client.
-- 
-- Note that /@device@/ and /@window@/ need to be on the same display.
-- 
-- Device grabs are used for operations which need complete control over the
-- given device events (either pointer or keyboard). For example in GTK+ this
-- is used for Drag and Drop operations, popup menus and such.
-- 
-- Note that if the event mask of an X window has selected both button press
-- and button release events, then a button press event will cause an automatic
-- pointer grab until the button is released. X does this automatically since
-- most applications expect to receive button press and release events in pairs.
-- It is equivalent to a pointer grab on the window with /@ownerEvents@/ set to
-- 'P.True'.
-- 
-- If you set up anything at the time you take the grab that needs to be
-- cleaned up when the grab ends, you should handle the t'GI.Gdk.Structs.EventGrabBroken.EventGrabBroken'
-- events that are emitted when the grab ends unvoluntarily.
-- 
-- /Since: 3.0/
deviceGrab ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a, Gdk.Window.IsWindow b, Gdk.Cursor.IsCursor c) =>
    a
    -- ^ /@device@/: a t'GI.Gdk.Objects.Device.Device'. To get the device you can use @/gtk_get_current_event_device()/@
    --   or 'GI.Gdk.Unions.Event.eventGetDevice' if the grab is in reaction to an event. Also, you can use
    --   'GI.Gdk.Objects.DeviceManager.deviceManagerGetClientPointer' but only in code that isn’t triggered by a
    --   t'GI.Gdk.Unions.Event.Event' and there aren’t other means to get a meaningful t'GI.Gdk.Objects.Device.Device' to operate on.
    -> b
    -- ^ /@window@/: the t'GI.Gdk.Objects.Window.Window' which will own the grab (the grab window)
    -> Gdk.Enums.GrabOwnership
    -- ^ /@grabOwnership@/: specifies the grab ownership.
    -> Bool
    -- ^ /@ownerEvents@/: if 'P.False' then all device events are reported with respect to
    --                /@window@/ and are only reported if selected by /@eventMask@/. If
    --                'P.True' then pointer events for this application are reported
    --                as normal, but pointer events outside this application are
    --                reported with respect to /@window@/ and only if selected by
    --                /@eventMask@/. In either mode, unreported events are discarded.
    -> [Gdk.Flags.EventMask]
    -- ^ /@eventMask@/: specifies the event mask, which is used in accordance with
    --              /@ownerEvents@/.
    -> Maybe (c)
    -- ^ /@cursor@/: the cursor to display while the grab is active if the device is
    --          a pointer. If this is 'P.Nothing' then the normal cursors are used for
    --          /@window@/ and its descendants, and the cursor for /@window@/ is used
    --          elsewhere.
    -> Word32
    -- ^ /@time_@/: the timestamp of the event which led to this pointer grab. This
    --         usually comes from the t'GI.Gdk.Unions.Event.Event' struct, though 'GI.Gdk.Constants.CURRENT_TIME'
    --         can be used if the time isn’t known.
    -> m Gdk.Enums.GrabStatus
    -- ^ __Returns:__ 'GI.Gdk.Enums.GrabStatusSuccess' if the grab was successful.
deviceGrab :: a
-> b
-> GrabOwnership
-> Bool
-> [EventMask]
-> Maybe c
-> Word32
-> m GrabStatus
deviceGrab device :: a
device window :: b
window grabOwnership :: GrabOwnership
grabOwnership ownerEvents :: Bool
ownerEvents eventMask :: [EventMask]
eventMask cursor :: Maybe c
cursor time_ :: Word32
time_ = IO GrabStatus -> m GrabStatus
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GrabStatus -> m GrabStatus) -> IO GrabStatus -> m GrabStatus
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr Window
window' <- b -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
window
    let grabOwnership' :: CUInt
grabOwnership' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (GrabOwnership -> Int) -> GrabOwnership -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GrabOwnership -> Int
forall a. Enum a => a -> Int
fromEnum) GrabOwnership
grabOwnership
    let ownerEvents' :: CInt
ownerEvents' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
ownerEvents
    let eventMask' :: CUInt
eventMask' = [EventMask] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [EventMask]
eventMask
    Ptr Cursor
maybeCursor <- case Maybe c
cursor of
        Nothing -> Ptr Cursor -> IO (Ptr Cursor)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cursor
forall a. Ptr a
nullPtr
        Just jCursor :: c
jCursor -> do
            Ptr Cursor
jCursor' <- c -> IO (Ptr Cursor)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCursor
            Ptr Cursor -> IO (Ptr Cursor)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cursor
jCursor'
    CUInt
result <- Ptr Device
-> Ptr Window
-> CUInt
-> CInt
-> CUInt
-> Ptr Cursor
-> Word32
-> IO CUInt
gdk_device_grab Ptr Device
device' Ptr Window
window' CUInt
grabOwnership' CInt
ownerEvents' CUInt
eventMask' Ptr Cursor
maybeCursor Word32
time_
    let result' :: GrabStatus
result' = (Int -> GrabStatus
forall a. Enum a => Int -> a
toEnum (Int -> GrabStatus) -> (CUInt -> Int) -> CUInt -> GrabStatus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
window
    Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cursor c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    GrabStatus -> IO GrabStatus
forall (m :: * -> *) a. Monad m => a -> m a
return GrabStatus
result'

#if defined(ENABLE_OVERLOADING)
data DeviceGrabMethodInfo
instance (signature ~ (b -> Gdk.Enums.GrabOwnership -> Bool -> [Gdk.Flags.EventMask] -> Maybe (c) -> Word32 -> m Gdk.Enums.GrabStatus), MonadIO m, IsDevice a, Gdk.Window.IsWindow b, Gdk.Cursor.IsCursor c) => O.MethodInfo DeviceGrabMethodInfo a signature where
    overloadedMethod = deviceGrab

#endif

-- method Device::list_axes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer #GdkDevice"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList (TInterface Name { namespace = "Gdk" , name = "Atom" }))
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_list_axes" gdk_device_list_axes :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    IO (Ptr (GList (Ptr Gdk.Atom.Atom)))

-- | Returns a t'GI.GLib.Structs.List.List' of @/GdkAtoms/@, containing the labels for
-- the axes that /@device@/ currently has.
-- 
-- /Since: 3.0/
deviceListAxes ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a pointer t'GI.Gdk.Objects.Device.Device'
    -> m [Gdk.Atom.Atom]
    -- ^ __Returns:__ 
    --     A t'GI.GLib.Structs.List.List' of @/GdkAtoms/@, free with @/g_list_free()/@.
deviceListAxes :: a -> m [Atom]
deviceListAxes device :: a
device = IO [Atom] -> m [Atom]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Atom] -> m [Atom]) -> IO [Atom] -> m [Atom]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr (GList (Ptr Atom))
result <- Ptr Device -> IO (Ptr (GList (Ptr Atom)))
gdk_device_list_axes Ptr Device
device'
    [Ptr Atom]
result' <- Ptr (GList (Ptr Atom)) -> IO [Ptr Atom]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr Atom))
result
    [Atom]
result'' <- (Ptr Atom -> IO Atom) -> [Ptr Atom] -> IO [Atom]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Atom -> Atom) -> Ptr Atom -> IO Atom
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr Atom -> Atom
Gdk.Atom.Atom) [Ptr Atom]
result'
    Ptr (GList (Ptr Atom)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr Atom))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    [Atom] -> IO [Atom]
forall (m :: * -> *) a. Monad m => a -> m a
return [Atom]
result''

#if defined(ENABLE_OVERLOADING)
data DeviceListAxesMethodInfo
instance (signature ~ (m [Gdk.Atom.Atom]), MonadIO m, IsDevice a) => O.MethodInfo DeviceListAxesMethodInfo a signature where
    overloadedMethod = deviceListAxes

#endif

-- method Device::list_slave_devices
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TGList (TInterface Name { namespace = "Gdk" , name = "Device" }))
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_list_slave_devices" gdk_device_list_slave_devices :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    IO (Ptr (GList (Ptr Device)))

-- | If the device if of type 'GI.Gdk.Enums.DeviceTypeMaster', it will return
-- the list of slave devices attached to it, otherwise it will return
-- 'P.Nothing'
deviceListSlaveDevices ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gdk.Objects.Device.Device'
    -> m [Device]
    -- ^ __Returns:__ 
    --          the list of slave devices, or 'P.Nothing'. The list must be
    --          freed with @/g_list_free()/@, the contents of the list are
    --          owned by GTK+ and should not be freed.
deviceListSlaveDevices :: a -> m [Device]
deviceListSlaveDevices device :: a
device = IO [Device] -> m [Device]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Device] -> m [Device]) -> IO [Device] -> m [Device]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr (GList (Ptr Device))
result <- Ptr Device -> IO (Ptr (GList (Ptr Device)))
gdk_device_list_slave_devices Ptr Device
device'
    [Ptr Device]
result' <- Ptr (GList (Ptr Device)) -> IO [Ptr Device]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr Device))
result
    [Device]
result'' <- (Ptr Device -> IO Device) -> [Ptr Device] -> IO [Device]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Device -> Device) -> Ptr Device -> IO Device
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Device -> Device
Device) [Ptr Device]
result'
    Ptr (GList (Ptr Device)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr Device))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    [Device] -> IO [Device]
forall (m :: * -> *) a. Monad m => a -> m a
return [Device]
result''

#if defined(ENABLE_OVERLOADING)
data DeviceListSlaveDevicesMethodInfo
instance (signature ~ (m [Device]), MonadIO m, IsDevice a) => O.MethodInfo DeviceListSlaveDevicesMethodInfo a signature where
    overloadedMethod = deviceListSlaveDevices

#endif

-- method Device::set_axis_use
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a pointer #GdkDevice"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "index_"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the index of the axis"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "use"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "AxisUse" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "specifies how the axis is used"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_set_axis_use" gdk_device_set_axis_use :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    Word32 ->                               -- index_ : TBasicType TUInt
    CUInt ->                                -- use : TInterface (Name {namespace = "Gdk", name = "AxisUse"})
    IO ()

-- | Specifies how an axis of a device is used.
deviceSetAxisUse ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a pointer t'GI.Gdk.Objects.Device.Device'
    -> Word32
    -- ^ /@index_@/: the index of the axis
    -> Gdk.Enums.AxisUse
    -- ^ /@use@/: specifies how the axis is used
    -> m ()
deviceSetAxisUse :: a -> Word32 -> AxisUse -> m ()
deviceSetAxisUse device :: a
device index_ :: Word32
index_ use :: AxisUse
use = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    let use' :: CUInt
use' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (AxisUse -> Int) -> AxisUse -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AxisUse -> Int
forall a. Enum a => a -> Int
fromEnum) AxisUse
use
    Ptr Device -> Word32 -> CUInt -> IO ()
gdk_device_set_axis_use Ptr Device
device' Word32
index_ CUInt
use'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DeviceSetAxisUseMethodInfo
instance (signature ~ (Word32 -> Gdk.Enums.AxisUse -> m ()), MonadIO m, IsDevice a) => O.MethodInfo DeviceSetAxisUseMethodInfo a signature where
    overloadedMethod = deviceSetAxisUse

#endif

-- method Device::set_key
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "index_"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the index of the macro button to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "keyval"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the keyval to generate"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "modifiers"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ModifierType" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the modifiers to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_set_key" gdk_device_set_key :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    Word32 ->                               -- index_ : TBasicType TUInt
    Word32 ->                               -- keyval : TBasicType TUInt
    CUInt ->                                -- modifiers : TInterface (Name {namespace = "Gdk", name = "ModifierType"})
    IO ()

-- | Specifies the X key event to generate when a macro button of a device
-- is pressed.
deviceSetKey ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gdk.Objects.Device.Device'
    -> Word32
    -- ^ /@index_@/: the index of the macro button to set
    -> Word32
    -- ^ /@keyval@/: the keyval to generate
    -> [Gdk.Flags.ModifierType]
    -- ^ /@modifiers@/: the modifiers to set
    -> m ()
deviceSetKey :: a -> Word32 -> Word32 -> [ModifierType] -> m ()
deviceSetKey device :: a
device index_ :: Word32
index_ keyval :: Word32
keyval modifiers :: [ModifierType]
modifiers = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    let modifiers' :: CUInt
modifiers' = [ModifierType] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [ModifierType]
modifiers
    Ptr Device -> Word32 -> Word32 -> CUInt -> IO ()
gdk_device_set_key Ptr Device
device' Word32
index_ Word32
keyval CUInt
modifiers'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DeviceSetKeyMethodInfo
instance (signature ~ (Word32 -> Word32 -> [Gdk.Flags.ModifierType] -> m ()), MonadIO m, IsDevice a) => O.MethodInfo DeviceSetKeyMethodInfo a signature where
    overloadedMethod = deviceSetKey

#endif

-- method Device::set_mode
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevice." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "mode"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "InputMode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the input mode." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_set_mode" gdk_device_set_mode :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    CUInt ->                                -- mode : TInterface (Name {namespace = "Gdk", name = "InputMode"})
    IO CInt

-- | Sets a the mode of an input device. The mode controls if the
-- device is active and whether the device’s range is mapped to the
-- entire screen or to a single window.
-- 
-- Note: This is only meaningful for floating devices, master devices (and
-- slaves connected to these) drive the pointer cursor, which is not limited
-- by the input mode.
deviceSetMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gdk.Objects.Device.Device'.
    -> Gdk.Enums.InputMode
    -- ^ /@mode@/: the input mode.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the mode was successfully changed.
deviceSetMode :: a -> InputMode -> m Bool
deviceSetMode device :: a
device mode :: InputMode
mode = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    let mode' :: CUInt
mode' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (InputMode -> Int) -> InputMode -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InputMode -> Int
forall a. Enum a => a -> Int
fromEnum) InputMode
mode
    CInt
result <- Ptr Device -> CUInt -> IO CInt
gdk_device_set_mode Ptr Device
device' CUInt
mode'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DeviceSetModeMethodInfo
instance (signature ~ (Gdk.Enums.InputMode -> m Bool), MonadIO m, IsDevice a) => O.MethodInfo DeviceSetModeMethodInfo a signature where
    overloadedMethod = deviceSetMode

#endif

-- method Device::ungrab
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDevice" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "time_"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a timestap (e.g. %GDK_CURRENT_TIME)."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_ungrab" gdk_device_ungrab :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    Word32 ->                               -- time_ : TBasicType TUInt32
    IO ()

{-# DEPRECATED deviceUngrab ["(Since version 3.20.)","Use 'GI.Gdk.Objects.Seat.seatUngrab' instead."] #-}
-- | Release any grab on /@device@/.
-- 
-- /Since: 3.0/
deviceUngrab ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
    a
    -- ^ /@device@/: a t'GI.Gdk.Objects.Device.Device'
    -> Word32
    -- ^ /@time_@/: a timestap (e.g. 'GI.Gdk.Constants.CURRENT_TIME').
    -> m ()
deviceUngrab :: a -> Word32 -> m ()
deviceUngrab device :: a
device time_ :: Word32
time_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr Device -> Word32 -> IO ()
gdk_device_ungrab Ptr Device
device' Word32
time_
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DeviceUngrabMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDevice a) => O.MethodInfo DeviceUngrabMethodInfo a signature where
    overloadedMethod = deviceUngrab

#endif

-- method Device::warp
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the device to warp."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "screen"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Screen" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the screen to warp @device to."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the X coordinate of the destination."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the Y coordinate of the destination."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_warp" gdk_device_warp :: 
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    Ptr Gdk.Screen.Screen ->                -- screen : TInterface (Name {namespace = "Gdk", name = "Screen"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    IO ()

-- | Warps /@device@/ in /@display@/ to the point /@x@/,/@y@/ on
-- the screen /@screen@/, unless the device is confined
-- to a window by a grab, in which case it will be moved
-- as far as allowed by the grab. Warping the pointer
-- creates events as if the user had moved the mouse
-- instantaneously to the destination.
-- 
-- Note that the pointer should normally be under the
-- control of the user. This function was added to cover
-- some rare use cases like keyboard navigation support
-- for the color picker in the @/GtkColorSelectionDialog/@.
-- 
-- /Since: 3.0/
deviceWarp ::
    (B.CallStack.HasCallStack, MonadIO m, IsDevice a, Gdk.Screen.IsScreen b) =>
    a
    -- ^ /@device@/: the device to warp.
    -> b
    -- ^ /@screen@/: the screen to warp /@device@/ to.
    -> Int32
    -- ^ /@x@/: the X coordinate of the destination.
    -> Int32
    -- ^ /@y@/: the Y coordinate of the destination.
    -> m ()
deviceWarp :: a -> b -> Int32 -> Int32 -> m ()
deviceWarp device :: a
device screen :: b
screen x :: Int32
x y :: Int32
y = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Device
device' <- a -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
device
    Ptr Screen
screen' <- b -> IO (Ptr Screen)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
screen
    Ptr Device -> Ptr Screen -> Int32 -> Int32 -> IO ()
gdk_device_warp Ptr Device
device' Ptr Screen
screen' Int32
x Int32
y
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
device
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
screen
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DeviceWarpMethodInfo
instance (signature ~ (b -> Int32 -> Int32 -> m ()), MonadIO m, IsDevice a, Gdk.Screen.IsScreen b) => O.MethodInfo DeviceWarpMethodInfo a signature where
    overloadedMethod = deviceWarp

#endif

-- method Device::grab_info_libgtk_only
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the display for which to get the grab information"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "device"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Device" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "device to get the grab information from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "grab_window"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Window" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "location to store current grab window"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "owner_events"
--           , argType = TBasicType TBoolean
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store boolean indicating whether\n  the @owner_events flag to gdk_keyboard_grab() or\n  gdk_pointer_grab() was %TRUE."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_device_grab_info_libgtk_only" gdk_device_grab_info_libgtk_only :: 
    Ptr Gdk.Display.Display ->              -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    Ptr Device ->                           -- device : TInterface (Name {namespace = "Gdk", name = "Device"})
    Ptr (Ptr Gdk.Window.Window) ->          -- grab_window : TInterface (Name {namespace = "Gdk", name = "Window"})
    Ptr CInt ->                             -- owner_events : TBasicType TBoolean
    IO CInt

{-# DEPRECATED deviceGrabInfoLibgtkOnly ["(Since version 3.16)","The symbol was never meant to be used outside","  of GTK+"] #-}
-- | Determines information about the current keyboard grab.
-- This is not public API and must not be used by applications.
deviceGrabInfoLibgtkOnly ::
    (B.CallStack.HasCallStack, MonadIO m, Gdk.Display.IsDisplay a, IsDevice b) =>
    a
    -- ^ /@display@/: the display for which to get the grab information
    -> b
    -- ^ /@device@/: device to get the grab information from
    -> m ((Bool, Gdk.Window.Window, Bool))
    -- ^ __Returns:__ 'P.True' if this application currently has the
    --  keyboard grabbed.
deviceGrabInfoLibgtkOnly :: a -> b -> m (Bool, Window, Bool)
deviceGrabInfoLibgtkOnly display :: a
display device :: b
device = IO (Bool, Window, Bool) -> m (Bool, Window, Bool)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Window, Bool) -> m (Bool, Window, Bool))
-> IO (Bool, Window, Bool) -> m (Bool, Window, Bool)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
    Ptr Device
device' <- b -> IO (Ptr Device)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
device
    Ptr (Ptr Window)
grabWindow <- IO (Ptr (Ptr Window))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr Gdk.Window.Window))
    Ptr CInt
ownerEvents <- IO (Ptr CInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CInt)
    CInt
result <- Ptr Display
-> Ptr Device -> Ptr (Ptr Window) -> Ptr CInt -> IO CInt
gdk_device_grab_info_libgtk_only Ptr Display
display' Ptr Device
device' Ptr (Ptr Window)
grabWindow Ptr CInt
ownerEvents
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    Ptr Window
grabWindow' <- Ptr (Ptr Window) -> IO (Ptr Window)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Window)
grabWindow
    Window
grabWindow'' <- ((ManagedPtr Window -> Window) -> Ptr Window -> IO Window
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Window -> Window
Gdk.Window.Window) Ptr Window
grabWindow'
    CInt
ownerEvents' <- Ptr CInt -> IO CInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CInt
ownerEvents
    let ownerEvents'' :: Bool
ownerEvents'' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
ownerEvents'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
device
    Ptr (Ptr Window) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Window)
grabWindow
    Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
ownerEvents
    (Bool, Window, Bool) -> IO (Bool, Window, Bool)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Window
grabWindow'', Bool
ownerEvents'')

#if defined(ENABLE_OVERLOADING)
#endif