{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Objects.Device
(
Device(..) ,
IsDevice ,
toDevice ,
#if defined(ENABLE_OVERLOADING)
ResolveDeviceMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DeviceGetAssociatedDeviceMethodInfo ,
#endif
deviceGetAssociatedDevice ,
#if defined(ENABLE_OVERLOADING)
DeviceGetAxesMethodInfo ,
#endif
deviceGetAxes ,
#if defined(ENABLE_OVERLOADING)
DeviceGetAxisUseMethodInfo ,
#endif
deviceGetAxisUse ,
#if defined(ENABLE_OVERLOADING)
DeviceGetDeviceTypeMethodInfo ,
#endif
deviceGetDeviceType ,
#if defined(ENABLE_OVERLOADING)
DeviceGetDisplayMethodInfo ,
#endif
deviceGetDisplay ,
#if defined(ENABLE_OVERLOADING)
DeviceGetHasCursorMethodInfo ,
#endif
deviceGetHasCursor ,
#if defined(ENABLE_OVERLOADING)
DeviceGetKeyMethodInfo ,
#endif
deviceGetKey ,
#if defined(ENABLE_OVERLOADING)
DeviceGetLastEventWindowMethodInfo ,
#endif
deviceGetLastEventWindow ,
#if defined(ENABLE_OVERLOADING)
DeviceGetModeMethodInfo ,
#endif
deviceGetMode ,
#if defined(ENABLE_OVERLOADING)
DeviceGetNAxesMethodInfo ,
#endif
deviceGetNAxes ,
#if defined(ENABLE_OVERLOADING)
DeviceGetNKeysMethodInfo ,
#endif
deviceGetNKeys ,
#if defined(ENABLE_OVERLOADING)
DeviceGetNameMethodInfo ,
#endif
deviceGetName ,
#if defined(ENABLE_OVERLOADING)
DeviceGetPositionMethodInfo ,
#endif
deviceGetPosition ,
#if defined(ENABLE_OVERLOADING)
DeviceGetPositionDoubleMethodInfo ,
#endif
deviceGetPositionDouble ,
#if defined(ENABLE_OVERLOADING)
DeviceGetProductIdMethodInfo ,
#endif
deviceGetProductId ,
#if defined(ENABLE_OVERLOADING)
DeviceGetSeatMethodInfo ,
#endif
deviceGetSeat ,
#if defined(ENABLE_OVERLOADING)
DeviceGetSourceMethodInfo ,
#endif
deviceGetSource ,
#if defined(ENABLE_OVERLOADING)
DeviceGetVendorIdMethodInfo ,
#endif
deviceGetVendorId ,
#if defined(ENABLE_OVERLOADING)
DeviceGetWindowAtPositionMethodInfo ,
#endif
deviceGetWindowAtPosition ,
#if defined(ENABLE_OVERLOADING)
DeviceGetWindowAtPositionDoubleMethodInfo,
#endif
deviceGetWindowAtPositionDouble ,
#if defined(ENABLE_OVERLOADING)
DeviceGrabMethodInfo ,
#endif
deviceGrab ,
deviceGrabInfoLibgtkOnly ,
#if defined(ENABLE_OVERLOADING)
DeviceListAxesMethodInfo ,
#endif
deviceListAxes ,
#if defined(ENABLE_OVERLOADING)
DeviceListSlaveDevicesMethodInfo ,
#endif
deviceListSlaveDevices ,
#if defined(ENABLE_OVERLOADING)
DeviceSetAxisUseMethodInfo ,
#endif
deviceSetAxisUse ,
#if defined(ENABLE_OVERLOADING)
DeviceSetKeyMethodInfo ,
#endif
deviceSetKey ,
#if defined(ENABLE_OVERLOADING)
DeviceSetModeMethodInfo ,
#endif
deviceSetMode ,
#if defined(ENABLE_OVERLOADING)
DeviceUngrabMethodInfo ,
#endif
deviceUngrab ,
#if defined(ENABLE_OVERLOADING)
DeviceWarpMethodInfo ,
#endif
deviceWarp ,
#if defined(ENABLE_OVERLOADING)
DeviceAssociatedDevicePropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceAssociatedDevice ,
#endif
getDeviceAssociatedDevice ,
#if defined(ENABLE_OVERLOADING)
DeviceAxesPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceAxes ,
#endif
getDeviceAxes ,
#if defined(ENABLE_OVERLOADING)
DeviceDeviceManagerPropertyInfo ,
#endif
constructDeviceDeviceManager ,
#if defined(ENABLE_OVERLOADING)
deviceDeviceManager ,
#endif
getDeviceDeviceManager ,
#if defined(ENABLE_OVERLOADING)
DeviceDisplayPropertyInfo ,
#endif
constructDeviceDisplay ,
#if defined(ENABLE_OVERLOADING)
deviceDisplay ,
#endif
getDeviceDisplay ,
#if defined(ENABLE_OVERLOADING)
DeviceHasCursorPropertyInfo ,
#endif
constructDeviceHasCursor ,
#if defined(ENABLE_OVERLOADING)
deviceHasCursor ,
#endif
getDeviceHasCursor ,
#if defined(ENABLE_OVERLOADING)
DeviceInputModePropertyInfo ,
#endif
constructDeviceInputMode ,
#if defined(ENABLE_OVERLOADING)
deviceInputMode ,
#endif
getDeviceInputMode ,
setDeviceInputMode ,
#if defined(ENABLE_OVERLOADING)
DeviceInputSourcePropertyInfo ,
#endif
constructDeviceInputSource ,
#if defined(ENABLE_OVERLOADING)
deviceInputSource ,
#endif
getDeviceInputSource ,
#if defined(ENABLE_OVERLOADING)
DeviceNAxesPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceNAxes ,
#endif
getDeviceNAxes ,
#if defined(ENABLE_OVERLOADING)
DeviceNamePropertyInfo ,
#endif
constructDeviceName ,
#if defined(ENABLE_OVERLOADING)
deviceName ,
#endif
getDeviceName ,
#if defined(ENABLE_OVERLOADING)
DeviceNumTouchesPropertyInfo ,
#endif
constructDeviceNumTouches ,
#if defined(ENABLE_OVERLOADING)
deviceNumTouches ,
#endif
getDeviceNumTouches ,
#if defined(ENABLE_OVERLOADING)
DeviceProductIdPropertyInfo ,
#endif
constructDeviceProductId ,
#if defined(ENABLE_OVERLOADING)
deviceProductId ,
#endif
getDeviceProductId ,
#if defined(ENABLE_OVERLOADING)
DeviceSeatPropertyInfo ,
#endif
clearDeviceSeat ,
constructDeviceSeat ,
#if defined(ENABLE_OVERLOADING)
deviceSeat ,
#endif
getDeviceSeat ,
setDeviceSeat ,
#if defined(ENABLE_OVERLOADING)
DeviceToolPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
deviceTool ,
#endif
getDeviceTool ,
#if defined(ENABLE_OVERLOADING)
DeviceTypePropertyInfo ,
#endif
constructDeviceType ,
#if defined(ENABLE_OVERLOADING)
deviceType ,
#endif
getDeviceType ,
#if defined(ENABLE_OVERLOADING)
DeviceVendorIdPropertyInfo ,
#endif
constructDeviceVendorId ,
#if defined(ENABLE_OVERLOADING)
deviceVendorId ,
#endif
getDeviceVendorId ,
C_DeviceChangedCallback ,
DeviceChangedCallback ,
#if defined(ENABLE_OVERLOADING)
DeviceChangedSignalInfo ,
#endif
afterDeviceChanged ,
genClosure_DeviceChanged ,
mk_DeviceChangedCallback ,
noDeviceChangedCallback ,
onDeviceChanged ,
wrap_DeviceChangedCallback ,
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.BasicTypes as B.Types
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 Control.Monad.IO.Class as MIO
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
newtype Device = Device (SP.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)
instance SP.ManagedPtrNewtype Device where
toManagedPtr :: Device -> ManagedPtr Device
toManagedPtr (Device ManagedPtr Device
p) = ManagedPtr Device
p
foreign import ccall "gdk_device_get_type"
c_gdk_device_get_type :: IO B.Types.GType
instance B.Types.TypedObject Device where
glibType :: IO GType
glibType = IO GType
c_gdk_device_get_type
instance B.Types.GObject Device
instance B.GValue.IsGValue Device where
toGValue :: Device -> IO GValue
toGValue 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 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
class (SP.GObject o, O.IsDescendantOf Device o) => IsDevice o
instance (SP.GObject o, O.IsDescendantOf Device o) => IsDevice o
instance O.HasParentTypes Device
type instance O.ParentTypes Device = '[GObject.Object.Object]
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, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr Device -> Device
Device
#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
type DeviceChangedCallback =
IO ()
noDeviceChangedCallback :: Maybe DeviceChangedCallback
noDeviceChangedCallback :: Maybe (IO ())
noDeviceChangedCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_DeviceChangedCallback =
Ptr () ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DeviceChangedCallback :: C_DeviceChangedCallback -> IO (FunPtr C_DeviceChangedCallback)
genClosure_DeviceChanged :: MonadIO m => DeviceChangedCallback -> m (GClosure C_DeviceChangedCallback)
genClosure_DeviceChanged :: IO () -> m (GClosure C_DeviceChangedCallback)
genClosure_DeviceChanged 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_DeviceChangedCallback ::
DeviceChangedCallback ->
C_DeviceChangedCallback
wrap_DeviceChangedCallback :: IO () -> C_DeviceChangedCallback
wrap_DeviceChangedCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
IO ()
_cb
onDeviceChanged :: (IsDevice a, MonadIO m) => a -> DeviceChangedCallback -> m SignalHandlerId
onDeviceChanged :: a -> IO () -> m SignalHandlerId
onDeviceChanged a
obj 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 Text
"changed" FunPtr C_DeviceChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDeviceChanged :: (IsDevice a, MonadIO m) => a -> DeviceChangedCallback -> m SignalHandlerId
afterDeviceChanged :: a -> IO () -> m SignalHandlerId
afterDeviceChanged a
obj 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 Text
"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
type DeviceToolChangedCallback =
Gdk.DeviceTool.DeviceTool
-> IO ()
noDeviceToolChangedCallback :: Maybe DeviceToolChangedCallback
noDeviceToolChangedCallback :: Maybe DeviceToolChangedCallback
noDeviceToolChangedCallback = Maybe DeviceToolChangedCallback
forall a. Maybe a
Nothing
type C_DeviceToolChangedCallback =
Ptr () ->
Ptr Gdk.DeviceTool.DeviceTool ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DeviceToolChangedCallback :: C_DeviceToolChangedCallback -> IO (FunPtr C_DeviceToolChangedCallback)
genClosure_DeviceToolChanged :: MonadIO m => DeviceToolChangedCallback -> m (GClosure C_DeviceToolChangedCallback)
genClosure_DeviceToolChanged :: DeviceToolChangedCallback
-> m (GClosure C_DeviceToolChangedCallback)
genClosure_DeviceToolChanged 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_DeviceToolChangedCallback ::
DeviceToolChangedCallback ->
C_DeviceToolChangedCallback
wrap_DeviceToolChangedCallback :: DeviceToolChangedCallback -> C_DeviceToolChangedCallback
wrap_DeviceToolChangedCallback DeviceToolChangedCallback
_cb Ptr ()
_ Ptr DeviceTool
tool Ptr ()
_ = 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'
onDeviceToolChanged :: (IsDevice a, MonadIO m) => a -> DeviceToolChangedCallback -> m SignalHandlerId
onDeviceToolChanged :: a -> DeviceToolChangedCallback -> m SignalHandlerId
onDeviceToolChanged a
obj 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 Text
"tool-changed" FunPtr C_DeviceToolChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDeviceToolChanged :: (IsDevice a, MonadIO m) => a -> DeviceToolChangedCallback -> m SignalHandlerId
afterDeviceToolChanged :: a -> DeviceToolChangedCallback -> m SignalHandlerId
afterDeviceToolChanged a
obj 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 Text
"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
getDeviceAssociatedDevice :: (MonadIO m, IsDevice o) => o -> m (Maybe Device)
getDeviceAssociatedDevice :: o -> m (Maybe Device)
getDeviceAssociatedDevice 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 String
"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
getDeviceAxes :: (MonadIO m, IsDevice o) => o -> m [Gdk.Flags.AxisFlags]
getDeviceAxes :: o -> m [AxisFlags]
getDeviceAxes 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 String
"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
getDeviceDeviceManager :: (MonadIO m, IsDevice o) => o -> m (Maybe Gdk.DeviceManager.DeviceManager)
getDeviceDeviceManager :: o -> m (Maybe DeviceManager)
getDeviceDeviceManager 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 String
"device-manager" ManagedPtr DeviceManager -> DeviceManager
Gdk.DeviceManager.DeviceManager
constructDeviceDeviceManager :: (IsDevice o, MIO.MonadIO m, Gdk.DeviceManager.IsDeviceManager a) => a -> m (GValueConstruct o)
constructDeviceDeviceManager :: a -> m (GValueConstruct o)
constructDeviceDeviceManager a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"device-manager" (a -> Maybe a
forall a. a -> Maybe a
P.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
getDeviceDisplay :: (MonadIO m, IsDevice o) => o -> m Gdk.Display.Display
getDeviceDisplay :: o -> m Display
getDeviceDisplay 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 Text
"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 String
"display" ManagedPtr Display -> Display
Gdk.Display.Display
constructDeviceDisplay :: (IsDevice o, MIO.MonadIO m, Gdk.Display.IsDisplay a) => a -> m (GValueConstruct o)
constructDeviceDisplay :: a -> m (GValueConstruct o)
constructDeviceDisplay a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"display" (a -> Maybe a
forall a. a -> Maybe a
P.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
getDeviceHasCursor :: (MonadIO m, IsDevice o) => o -> m Bool
getDeviceHasCursor :: o -> m Bool
getDeviceHasCursor 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 String
"has-cursor"
constructDeviceHasCursor :: (IsDevice o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructDeviceHasCursor :: Bool -> m (GValueConstruct o)
constructDeviceHasCursor Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"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
getDeviceInputMode :: (MonadIO m, IsDevice o) => o -> m Gdk.Enums.InputMode
getDeviceInputMode :: o -> m InputMode
getDeviceInputMode 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 String
"input-mode"
setDeviceInputMode :: (MonadIO m, IsDevice o) => o -> Gdk.Enums.InputMode -> m ()
setDeviceInputMode :: o -> InputMode -> m ()
setDeviceInputMode o
obj 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 String
"input-mode" InputMode
val
constructDeviceInputMode :: (IsDevice o, MIO.MonadIO m) => Gdk.Enums.InputMode -> m (GValueConstruct o)
constructDeviceInputMode :: InputMode -> m (GValueConstruct o)
constructDeviceInputMode InputMode
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> InputMode -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"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
getDeviceInputSource :: (MonadIO m, IsDevice o) => o -> m Gdk.Enums.InputSource
getDeviceInputSource :: o -> m InputSource
getDeviceInputSource 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 String
"input-source"
constructDeviceInputSource :: (IsDevice o, MIO.MonadIO m) => Gdk.Enums.InputSource -> m (GValueConstruct o)
constructDeviceInputSource :: InputSource -> m (GValueConstruct o)
constructDeviceInputSource InputSource
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> InputSource -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"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
getDeviceNAxes :: (MonadIO m, IsDevice o) => o -> m Word32
getDeviceNAxes :: o -> m Word32
getDeviceNAxes 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 String
"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
getDeviceName :: (MonadIO m, IsDevice o) => o -> m T.Text
getDeviceName :: o -> m Text
getDeviceName 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 Text
"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 String
"name"
constructDeviceName :: (IsDevice o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructDeviceName :: Text -> m (GValueConstruct o)
constructDeviceName Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"name" (Text -> Maybe Text
forall a. a -> Maybe a
P.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
getDeviceNumTouches :: (MonadIO m, IsDevice o) => o -> m Word32
getDeviceNumTouches :: o -> m Word32
getDeviceNumTouches 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 String
"num-touches"
constructDeviceNumTouches :: (IsDevice o, MIO.MonadIO m) => Word32 -> m (GValueConstruct o)
constructDeviceNumTouches :: Word32 -> m (GValueConstruct o)
constructDeviceNumTouches Word32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word32 -> IO (GValueConstruct o)
forall o. String -> Word32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt32 String
"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
getDeviceProductId :: (MonadIO m, IsDevice o) => o -> m (Maybe T.Text)
getDeviceProductId :: o -> m (Maybe Text)
getDeviceProductId 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 String
"product-id"
constructDeviceProductId :: (IsDevice o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructDeviceProductId :: Text -> m (GValueConstruct o)
constructDeviceProductId Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"product-id" (Text -> Maybe Text
forall a. a -> Maybe a
P.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
getDeviceSeat :: (MonadIO m, IsDevice o) => o -> m Gdk.Seat.Seat
getDeviceSeat :: o -> m Seat
getDeviceSeat 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 Text
"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 String
"seat" ManagedPtr Seat -> Seat
Gdk.Seat.Seat
setDeviceSeat :: (MonadIO m, IsDevice o, Gdk.Seat.IsSeat a) => o -> a -> m ()
setDeviceSeat :: o -> a -> m ()
setDeviceSeat o
obj 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 String
"seat" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructDeviceSeat :: (IsDevice o, MIO.MonadIO m, Gdk.Seat.IsSeat a) => a -> m (GValueConstruct o)
constructDeviceSeat :: a -> m (GValueConstruct o)
constructDeviceSeat a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"seat" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearDeviceSeat :: (MonadIO m, IsDevice o) => o -> m ()
clearDeviceSeat :: o -> m ()
clearDeviceSeat 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 String
"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
getDeviceTool :: (MonadIO m, IsDevice o) => o -> m (Maybe Gdk.DeviceTool.DeviceTool)
getDeviceTool :: o -> m (Maybe DeviceTool)
getDeviceTool 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 String
"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
getDeviceType :: (MonadIO m, IsDevice o) => o -> m Gdk.Enums.DeviceType
getDeviceType :: o -> m DeviceType
getDeviceType 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 String
"type"
constructDeviceType :: (IsDevice o, MIO.MonadIO m) => Gdk.Enums.DeviceType -> m (GValueConstruct o)
constructDeviceType :: DeviceType -> m (GValueConstruct o)
constructDeviceType DeviceType
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> DeviceType -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"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
getDeviceVendorId :: (MonadIO m, IsDevice o) => o -> m (Maybe T.Text)
getDeviceVendorId :: o -> m (Maybe Text)
getDeviceVendorId 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 String
"vendor-id"
constructDeviceVendorId :: (IsDevice o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructDeviceVendorId :: Text -> m (GValueConstruct o)
constructDeviceVendorId Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"vendor-id" (Text -> Maybe Text
forall a. a -> Maybe a
P.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
foreign import ccall "gdk_device_get_associated_device" gdk_device_get_associated_device ::
Ptr Device ->
IO (Ptr Device)
deviceGetAssociatedDevice ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m (Maybe Device)
deviceGetAssociatedDevice :: a -> m (Maybe Device)
deviceGetAssociatedDevice 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
$ \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
foreign import ccall "gdk_device_get_axes" gdk_device_get_axes ::
Ptr Device ->
IO CUInt
deviceGetAxes ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m [Gdk.Flags.AxisFlags]
deviceGetAxes :: a -> m [AxisFlags]
deviceGetAxes 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
foreign import ccall "gdk_device_get_axis_use" gdk_device_get_axis_use ::
Ptr Device ->
Word32 ->
IO CUInt
deviceGetAxisUse ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> Word32
-> m Gdk.Enums.AxisUse
deviceGetAxisUse :: a -> Word32 -> m AxisUse
deviceGetAxisUse a
device 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
foreign import ccall "gdk_device_get_device_type" gdk_device_get_device_type ::
Ptr Device ->
IO CUInt
deviceGetDeviceType ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m Gdk.Enums.DeviceType
deviceGetDeviceType :: a -> m DeviceType
deviceGetDeviceType 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
foreign import ccall "gdk_device_get_display" gdk_device_get_display ::
Ptr Device ->
IO (Ptr Gdk.Display.Display)
deviceGetDisplay ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m Gdk.Display.Display
deviceGetDisplay :: a -> m Display
deviceGetDisplay 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 Text
"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
foreign import ccall "gdk_device_get_has_cursor" gdk_device_get_has_cursor ::
Ptr Device ->
IO CInt
deviceGetHasCursor ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m Bool
deviceGetHasCursor :: a -> m Bool
deviceGetHasCursor 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
/= CInt
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
foreign import ccall "gdk_device_get_key" gdk_device_get_key ::
Ptr Device ->
Word32 ->
Ptr Word32 ->
Ptr CUInt ->
IO CInt
deviceGetKey ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> Word32
-> m ((Bool, Word32, [Gdk.Flags.ModifierType]))
deviceGetKey :: a -> Word32 -> m (Bool, Word32, [ModifierType])
deviceGetKey a
device 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
/= CInt
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
foreign import ccall "gdk_device_get_last_event_window" gdk_device_get_last_event_window ::
Ptr Device ->
IO (Ptr Gdk.Window.Window)
deviceGetLastEventWindow ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m (Maybe Gdk.Window.Window)
deviceGetLastEventWindow :: a -> m (Maybe Window)
deviceGetLastEventWindow 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
$ \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
foreign import ccall "gdk_device_get_mode" gdk_device_get_mode ::
Ptr Device ->
IO CUInt
deviceGetMode ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m Gdk.Enums.InputMode
deviceGetMode :: a -> m InputMode
deviceGetMode 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
foreign import ccall "gdk_device_get_n_axes" gdk_device_get_n_axes ::
Ptr Device ->
IO Int32
deviceGetNAxes ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m Int32
deviceGetNAxes :: a -> m Int32
deviceGetNAxes 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
foreign import ccall "gdk_device_get_n_keys" gdk_device_get_n_keys ::
Ptr Device ->
IO Int32
deviceGetNKeys ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m Int32
deviceGetNKeys :: a -> m Int32
deviceGetNKeys 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
foreign import ccall "gdk_device_get_name" gdk_device_get_name ::
Ptr Device ->
IO CString
deviceGetName ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m T.Text
deviceGetName :: a -> m Text
deviceGetName 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 Text
"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
foreign import ccall "gdk_device_get_position" gdk_device_get_position ::
Ptr Device ->
Ptr (Ptr Gdk.Screen.Screen) ->
Ptr Int32 ->
Ptr Int32 ->
IO ()
deviceGetPosition ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m ((Gdk.Screen.Screen, Int32, Int32))
deviceGetPosition :: a -> m (Screen, Int32, Int32)
deviceGetPosition 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)
callocMem :: 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
foreign import ccall "gdk_device_get_position_double" gdk_device_get_position_double ::
Ptr Device ->
Ptr (Ptr Gdk.Screen.Screen) ->
Ptr CDouble ->
Ptr CDouble ->
IO ()
deviceGetPositionDouble ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m ((Gdk.Screen.Screen, Double, Double))
deviceGetPositionDouble :: a -> m (Screen, Double, Double)
deviceGetPositionDouble 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)
callocMem :: 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
foreign import ccall "gdk_device_get_product_id" gdk_device_get_product_id ::
Ptr Device ->
IO CString
deviceGetProductId ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m (Maybe T.Text)
deviceGetProductId :: a -> m (Maybe Text)
deviceGetProductId 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
$ \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
foreign import ccall "gdk_device_get_seat" gdk_device_get_seat ::
Ptr Device ->
IO (Ptr Gdk.Seat.Seat)
deviceGetSeat ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m Gdk.Seat.Seat
deviceGetSeat :: a -> m Seat
deviceGetSeat 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 Text
"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
foreign import ccall "gdk_device_get_source" gdk_device_get_source ::
Ptr Device ->
IO CUInt
deviceGetSource ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m Gdk.Enums.InputSource
deviceGetSource :: a -> m InputSource
deviceGetSource 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
foreign import ccall "gdk_device_get_vendor_id" gdk_device_get_vendor_id ::
Ptr Device ->
IO CString
deviceGetVendorId ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m (Maybe T.Text)
deviceGetVendorId :: a -> m (Maybe Text)
deviceGetVendorId 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
$ \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
foreign import ccall "gdk_device_get_window_at_position" gdk_device_get_window_at_position ::
Ptr Device ->
Ptr Int32 ->
Ptr Int32 ->
IO (Ptr Gdk.Window.Window)
deviceGetWindowAtPosition ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m ((Maybe Gdk.Window.Window, Int32, Int32))
deviceGetWindowAtPosition :: a -> m (Maybe Window, Int32, Int32)
deviceGetWindowAtPosition 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
$ \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
foreign import ccall "gdk_device_get_window_at_position_double" gdk_device_get_window_at_position_double ::
Ptr Device ->
Ptr CDouble ->
Ptr CDouble ->
IO (Ptr Gdk.Window.Window)
deviceGetWindowAtPositionDouble ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m ((Maybe Gdk.Window.Window, Double, Double))
deviceGetWindowAtPositionDouble :: a -> m (Maybe Window, Double, Double)
deviceGetWindowAtPositionDouble 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
$ \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
foreign import ccall "gdk_device_grab" gdk_device_grab ::
Ptr Device ->
Ptr Gdk.Window.Window ->
CUInt ->
CInt ->
CUInt ->
Ptr Gdk.Cursor.Cursor ->
Word32 ->
IO CUInt
{-# DEPRECATED deviceGrab ["(Since version 3.20.)","Use 'GI.Gdk.Objects.Seat.seatGrab' instead."] #-}
deviceGrab ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a, Gdk.Window.IsWindow b, Gdk.Cursor.IsCursor c) =>
a
-> b
-> Gdk.Enums.GrabOwnership
-> Bool
-> [Gdk.Flags.EventMask]
-> Maybe (c)
-> Word32
-> m Gdk.Enums.GrabStatus
deviceGrab :: a
-> b
-> GrabOwnership
-> Bool
-> [EventMask]
-> Maybe c
-> Word32
-> m GrabStatus
deviceGrab a
device b
window GrabOwnership
grabOwnership Bool
ownerEvents [EventMask]
eventMask Maybe c
cursor 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
Maybe c
Nothing -> Ptr Cursor -> IO (Ptr Cursor)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cursor
forall a. Ptr a
nullPtr
Just 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
foreign import ccall "gdk_device_list_axes" gdk_device_list_axes ::
Ptr Device ->
IO (Ptr (GList (Ptr Gdk.Atom.Atom)))
deviceListAxes ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m [Gdk.Atom.Atom]
deviceListAxes :: a -> m [Atom]
deviceListAxes 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, BoxedPtr 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
foreign import ccall "gdk_device_list_slave_devices" gdk_device_list_slave_devices ::
Ptr Device ->
IO (Ptr (GList (Ptr Device)))
deviceListSlaveDevices ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> m [Device]
deviceListSlaveDevices :: a -> m [Device]
deviceListSlaveDevices 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
foreign import ccall "gdk_device_set_axis_use" gdk_device_set_axis_use ::
Ptr Device ->
Word32 ->
CUInt ->
IO ()
deviceSetAxisUse ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> Word32
-> Gdk.Enums.AxisUse
-> m ()
deviceSetAxisUse :: a -> Word32 -> AxisUse -> m ()
deviceSetAxisUse a
device Word32
index_ 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
foreign import ccall "gdk_device_set_key" gdk_device_set_key ::
Ptr Device ->
Word32 ->
Word32 ->
CUInt ->
IO ()
deviceSetKey ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> Word32
-> Word32
-> [Gdk.Flags.ModifierType]
-> m ()
deviceSetKey :: a -> Word32 -> Word32 -> [ModifierType] -> m ()
deviceSetKey a
device Word32
index_ Word32
keyval [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
foreign import ccall "gdk_device_set_mode" gdk_device_set_mode ::
Ptr Device ->
CUInt ->
IO CInt
deviceSetMode ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> Gdk.Enums.InputMode
-> m Bool
deviceSetMode :: a -> InputMode -> m Bool
deviceSetMode a
device 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
/= CInt
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
foreign import ccall "gdk_device_ungrab" gdk_device_ungrab ::
Ptr Device ->
Word32 ->
IO ()
{-# DEPRECATED deviceUngrab ["(Since version 3.20.)","Use 'GI.Gdk.Objects.Seat.seatUngrab' instead."] #-}
deviceUngrab ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a) =>
a
-> Word32
-> m ()
deviceUngrab :: a -> Word32 -> m ()
deviceUngrab a
device 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
foreign import ccall "gdk_device_warp" gdk_device_warp ::
Ptr Device ->
Ptr Gdk.Screen.Screen ->
Int32 ->
Int32 ->
IO ()
deviceWarp ::
(B.CallStack.HasCallStack, MonadIO m, IsDevice a, Gdk.Screen.IsScreen b) =>
a
-> b
-> Int32
-> Int32
-> m ()
deviceWarp :: a -> b -> Int32 -> Int32 -> m ()
deviceWarp a
device b
screen Int32
x 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
foreign import ccall "gdk_device_grab_info_libgtk_only" gdk_device_grab_info_libgtk_only ::
Ptr Gdk.Display.Display ->
Ptr Device ->
Ptr (Ptr Gdk.Window.Window) ->
Ptr CInt ->
IO CInt
{-# DEPRECATED deviceGrabInfoLibgtkOnly ["(Since version 3.16)","The symbol was never meant to be used outside"," of GTK+"] #-}
deviceGrabInfoLibgtkOnly ::
(B.CallStack.HasCallStack, MonadIO m, Gdk.Display.IsDisplay a, IsDevice b) =>
a
-> b
-> m ((Bool, Gdk.Window.Window, Bool))
deviceGrabInfoLibgtkOnly :: a -> b -> m (Bool, Window, Bool)
deviceGrabInfoLibgtkOnly a
display 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)
callocMem :: 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
/= CInt
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
/= CInt
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