{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Objects.DeviceManager
(
DeviceManager(..) ,
IsDeviceManager ,
toDeviceManager ,
#if defined(ENABLE_OVERLOADING)
ResolveDeviceManagerMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DeviceManagerGetClientPointerMethodInfo ,
#endif
deviceManagerGetClientPointer ,
#if defined(ENABLE_OVERLOADING)
DeviceManagerGetDisplayMethodInfo ,
#endif
deviceManagerGetDisplay ,
#if defined(ENABLE_OVERLOADING)
DeviceManagerListDevicesMethodInfo ,
#endif
deviceManagerListDevices ,
#if defined(ENABLE_OVERLOADING)
DeviceManagerDisplayPropertyInfo ,
#endif
constructDeviceManagerDisplay ,
#if defined(ENABLE_OVERLOADING)
deviceManagerDisplay ,
#endif
getDeviceManagerDisplay ,
DeviceManagerDeviceAddedCallback ,
#if defined(ENABLE_OVERLOADING)
DeviceManagerDeviceAddedSignalInfo ,
#endif
afterDeviceManagerDeviceAdded ,
onDeviceManagerDeviceAdded ,
DeviceManagerDeviceChangedCallback ,
#if defined(ENABLE_OVERLOADING)
DeviceManagerDeviceChangedSignalInfo ,
#endif
afterDeviceManagerDeviceChanged ,
onDeviceManagerDeviceChanged ,
DeviceManagerDeviceRemovedCallback ,
#if defined(ENABLE_OVERLOADING)
DeviceManagerDeviceRemovedSignalInfo ,
#endif
afterDeviceManagerDeviceRemoved ,
onDeviceManagerDeviceRemoved ,
) 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.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
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.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
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 GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.Cairo.Enums as Cairo.Enums
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.Cairo.Structs.Pattern as Cairo.Pattern
import qualified GI.Cairo.Structs.Region as Cairo.Region
import qualified GI.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Callbacks as Gdk.Callbacks
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Objects.AppLaunchContext as Gdk.AppLaunchContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Cursor as Gdk.Cursor
import {-# SOURCE #-} qualified GI.Gdk.Objects.Device as Gdk.Device
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.DragContext as Gdk.DragContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.DrawingContext as Gdk.DrawingContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import {-# SOURCE #-} qualified GI.Gdk.Objects.GLContext as Gdk.GLContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Monitor as Gdk.Monitor
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.Visual as Gdk.Visual
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window
import {-# SOURCE #-} qualified GI.Gdk.Structs.Atom as Gdk.Atom
import {-# SOURCE #-} qualified GI.Gdk.Structs.Color as Gdk.Color
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventAny as Gdk.EventAny
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventButton as Gdk.EventButton
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventConfigure as Gdk.EventConfigure
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventCrossing as Gdk.EventCrossing
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventDND as Gdk.EventDND
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventExpose as Gdk.EventExpose
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventFocus as Gdk.EventFocus
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventGrabBroken as Gdk.EventGrabBroken
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventKey as Gdk.EventKey
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventMotion as Gdk.EventMotion
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventOwnerChange as Gdk.EventOwnerChange
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadAxis as Gdk.EventPadAxis
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadButton as Gdk.EventPadButton
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadGroupMode as Gdk.EventPadGroupMode
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventProperty as Gdk.EventProperty
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventProximity as Gdk.EventProximity
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventScroll as Gdk.EventScroll
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSelection as Gdk.EventSelection
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSequence as Gdk.EventSequence
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSetting as Gdk.EventSetting
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouch as Gdk.EventTouch
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouchpadPinch as Gdk.EventTouchpadPinch
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouchpadSwipe as Gdk.EventTouchpadSwipe
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventVisibility as Gdk.EventVisibility
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventWindowState as Gdk.EventWindowState
import {-# SOURCE #-} qualified GI.Gdk.Structs.FrameTimings as Gdk.FrameTimings
import {-# SOURCE #-} qualified GI.Gdk.Structs.Geometry as Gdk.Geometry
import {-# SOURCE #-} qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import {-# SOURCE #-} qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import {-# SOURCE #-} qualified GI.Gdk.Structs.WindowAttr as Gdk.WindowAttr
import {-# SOURCE #-} qualified GI.Gdk.Unions.Event as Gdk.Event
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Objects.AppLaunchContext as Gio.AppLaunchContext
#else
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Objects.Device as Gdk.Device
import {-# SOURCE #-} qualified GI.Gdk.Objects.Display as Gdk.Display
#endif
newtype DeviceManager = DeviceManager (SP.ManagedPtr DeviceManager)
deriving (DeviceManager -> DeviceManager -> Bool
(DeviceManager -> DeviceManager -> Bool)
-> (DeviceManager -> DeviceManager -> Bool) -> Eq DeviceManager
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeviceManager -> DeviceManager -> Bool
== :: DeviceManager -> DeviceManager -> Bool
$c/= :: DeviceManager -> DeviceManager -> Bool
/= :: DeviceManager -> DeviceManager -> Bool
Eq)
instance SP.ManagedPtrNewtype DeviceManager where
toManagedPtr :: DeviceManager -> ManagedPtr DeviceManager
toManagedPtr (DeviceManager ManagedPtr DeviceManager
p) = ManagedPtr DeviceManager
p
foreign import ccall "gdk_device_manager_get_type"
c_gdk_device_manager_get_type :: IO B.Types.GType
instance B.Types.TypedObject DeviceManager where
glibType :: IO GType
glibType = IO GType
c_gdk_device_manager_get_type
instance B.Types.GObject DeviceManager
class (SP.GObject o, O.IsDescendantOf DeviceManager o) => IsDeviceManager o
instance (SP.GObject o, O.IsDescendantOf DeviceManager o) => IsDeviceManager o
instance O.HasParentTypes DeviceManager
type instance O.ParentTypes DeviceManager = '[GObject.Object.Object]
toDeviceManager :: (MIO.MonadIO m, IsDeviceManager o) => o -> m DeviceManager
toDeviceManager :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceManager o) =>
o -> m DeviceManager
toDeviceManager = IO DeviceManager -> m DeviceManager
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DeviceManager -> m DeviceManager)
-> (o -> IO DeviceManager) -> o -> m DeviceManager
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DeviceManager -> DeviceManager)
-> o -> IO DeviceManager
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DeviceManager -> DeviceManager
DeviceManager
instance B.GValue.IsGValue (Maybe DeviceManager) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_device_manager_get_type
gvalueSet_ :: Ptr GValue -> Maybe DeviceManager -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DeviceManager
P.Nothing = Ptr GValue -> Ptr DeviceManager -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DeviceManager
forall a. Ptr a
FP.nullPtr :: FP.Ptr DeviceManager)
gvalueSet_ Ptr GValue
gv (P.Just DeviceManager
obj) = DeviceManager -> (Ptr DeviceManager -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DeviceManager
obj (Ptr GValue -> Ptr DeviceManager -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe DeviceManager)
gvalueGet_ Ptr GValue
gv = do
Ptr DeviceManager
ptr <- Ptr GValue -> IO (Ptr DeviceManager)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DeviceManager)
if Ptr DeviceManager
ptr Ptr DeviceManager -> Ptr DeviceManager -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DeviceManager
forall a. Ptr a
FP.nullPtr
then DeviceManager -> Maybe DeviceManager
forall a. a -> Maybe a
P.Just (DeviceManager -> Maybe DeviceManager)
-> IO DeviceManager -> IO (Maybe DeviceManager)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DeviceManager -> DeviceManager)
-> Ptr DeviceManager -> IO DeviceManager
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DeviceManager -> DeviceManager
DeviceManager Ptr DeviceManager
ptr
else Maybe DeviceManager -> IO (Maybe DeviceManager)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DeviceManager
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveDeviceManagerMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveDeviceManagerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveDeviceManagerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveDeviceManagerMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveDeviceManagerMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveDeviceManagerMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveDeviceManagerMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveDeviceManagerMethod "listDevices" o = DeviceManagerListDevicesMethodInfo
ResolveDeviceManagerMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveDeviceManagerMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveDeviceManagerMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveDeviceManagerMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveDeviceManagerMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveDeviceManagerMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveDeviceManagerMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveDeviceManagerMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveDeviceManagerMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveDeviceManagerMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveDeviceManagerMethod "getClientPointer" o = DeviceManagerGetClientPointerMethodInfo
ResolveDeviceManagerMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveDeviceManagerMethod "getDisplay" o = DeviceManagerGetDisplayMethodInfo
ResolveDeviceManagerMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveDeviceManagerMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveDeviceManagerMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveDeviceManagerMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveDeviceManagerMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveDeviceManagerMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDeviceManagerMethod t DeviceManager, O.OverloadedMethod info DeviceManager p) => OL.IsLabel t (DeviceManager -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveDeviceManagerMethod t DeviceManager, O.OverloadedMethod info DeviceManager p, R.HasField t DeviceManager p) => R.HasField t DeviceManager p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveDeviceManagerMethod t DeviceManager, O.OverloadedMethodInfo info DeviceManager) => OL.IsLabel t (O.MethodProxy info DeviceManager) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
type DeviceManagerDeviceAddedCallback =
Gdk.Device.Device
-> IO ()
type C_DeviceManagerDeviceAddedCallback =
Ptr DeviceManager ->
Ptr Gdk.Device.Device ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DeviceManagerDeviceAddedCallback :: C_DeviceManagerDeviceAddedCallback -> IO (FunPtr C_DeviceManagerDeviceAddedCallback)
wrap_DeviceManagerDeviceAddedCallback ::
GObject a => (a -> DeviceManagerDeviceAddedCallback) ->
C_DeviceManagerDeviceAddedCallback
wrap_DeviceManagerDeviceAddedCallback :: forall a.
GObject a =>
(a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
wrap_DeviceManagerDeviceAddedCallback a -> DeviceManagerDeviceAddedCallback
gi'cb Ptr DeviceManager
gi'selfPtr Ptr Device
device Ptr ()
_ = do
Device
device' <- ((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
Gdk.Device.Device) Ptr Device
device
Ptr DeviceManager -> (DeviceManager -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr DeviceManager
gi'selfPtr ((DeviceManager -> IO ()) -> IO ())
-> (DeviceManager -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \DeviceManager
gi'self -> a -> DeviceManagerDeviceAddedCallback
gi'cb (DeviceManager -> a
forall a b. Coercible a b => a -> b
Coerce.coerce DeviceManager
gi'self) Device
device'
onDeviceManagerDeviceAdded :: (IsDeviceManager a, MonadIO m) => a -> ((?self :: a) => DeviceManagerDeviceAddedCallback) -> m SignalHandlerId
onDeviceManagerDeviceAdded :: forall a (m :: * -> *).
(IsDeviceManager a, MonadIO m) =>
a
-> ((?self::a) => DeviceManagerDeviceAddedCallback)
-> m SignalHandlerId
onDeviceManagerDeviceAdded a
obj (?self::a) => DeviceManagerDeviceAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> DeviceManagerDeviceAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DeviceManagerDeviceAddedCallback
DeviceManagerDeviceAddedCallback
cb
let wrapped' :: C_DeviceManagerDeviceAddedCallback
wrapped' = (a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
forall a.
GObject a =>
(a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
wrap_DeviceManagerDeviceAddedCallback a -> DeviceManagerDeviceAddedCallback
wrapped
FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' <- C_DeviceManagerDeviceAddedCallback
-> IO (FunPtr C_DeviceManagerDeviceAddedCallback)
mk_DeviceManagerDeviceAddedCallback C_DeviceManagerDeviceAddedCallback
wrapped'
a
-> Text
-> FunPtr C_DeviceManagerDeviceAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"device-added" FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDeviceManagerDeviceAdded :: (IsDeviceManager a, MonadIO m) => a -> ((?self :: a) => DeviceManagerDeviceAddedCallback) -> m SignalHandlerId
afterDeviceManagerDeviceAdded :: forall a (m :: * -> *).
(IsDeviceManager a, MonadIO m) =>
a
-> ((?self::a) => DeviceManagerDeviceAddedCallback)
-> m SignalHandlerId
afterDeviceManagerDeviceAdded a
obj (?self::a) => DeviceManagerDeviceAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> DeviceManagerDeviceAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DeviceManagerDeviceAddedCallback
DeviceManagerDeviceAddedCallback
cb
let wrapped' :: C_DeviceManagerDeviceAddedCallback
wrapped' = (a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
forall a.
GObject a =>
(a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
wrap_DeviceManagerDeviceAddedCallback a -> DeviceManagerDeviceAddedCallback
wrapped
FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' <- C_DeviceManagerDeviceAddedCallback
-> IO (FunPtr C_DeviceManagerDeviceAddedCallback)
mk_DeviceManagerDeviceAddedCallback C_DeviceManagerDeviceAddedCallback
wrapped'
a
-> Text
-> FunPtr C_DeviceManagerDeviceAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"device-added" FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data DeviceManagerDeviceAddedSignalInfo
instance SignalInfo DeviceManagerDeviceAddedSignalInfo where
type HaskellCallbackType DeviceManagerDeviceAddedSignalInfo = DeviceManagerDeviceAddedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_DeviceManagerDeviceAddedCallback cb
cb'' <- mk_DeviceManagerDeviceAddedCallback cb'
connectSignalFunPtr obj "device-added" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DeviceManager::device-added"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-DeviceManager.html#g:signal:deviceAdded"})
#endif
type DeviceManagerDeviceChangedCallback =
Gdk.Device.Device
-> IO ()
type C_DeviceManagerDeviceChangedCallback =
Ptr DeviceManager ->
Ptr Gdk.Device.Device ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DeviceManagerDeviceChangedCallback :: C_DeviceManagerDeviceChangedCallback -> IO (FunPtr C_DeviceManagerDeviceChangedCallback)
wrap_DeviceManagerDeviceChangedCallback ::
GObject a => (a -> DeviceManagerDeviceChangedCallback) ->
C_DeviceManagerDeviceChangedCallback
wrap_DeviceManagerDeviceChangedCallback :: forall a.
GObject a =>
(a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
wrap_DeviceManagerDeviceChangedCallback a -> DeviceManagerDeviceAddedCallback
gi'cb Ptr DeviceManager
gi'selfPtr Ptr Device
device Ptr ()
_ = do
Device
device' <- ((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
Gdk.Device.Device) Ptr Device
device
Ptr DeviceManager -> (DeviceManager -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr DeviceManager
gi'selfPtr ((DeviceManager -> IO ()) -> IO ())
-> (DeviceManager -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \DeviceManager
gi'self -> a -> DeviceManagerDeviceAddedCallback
gi'cb (DeviceManager -> a
forall a b. Coercible a b => a -> b
Coerce.coerce DeviceManager
gi'self) Device
device'
onDeviceManagerDeviceChanged :: (IsDeviceManager a, MonadIO m) => a -> ((?self :: a) => DeviceManagerDeviceChangedCallback) -> m SignalHandlerId
onDeviceManagerDeviceChanged :: forall a (m :: * -> *).
(IsDeviceManager a, MonadIO m) =>
a
-> ((?self::a) => DeviceManagerDeviceAddedCallback)
-> m SignalHandlerId
onDeviceManagerDeviceChanged a
obj (?self::a) => DeviceManagerDeviceAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> DeviceManagerDeviceAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DeviceManagerDeviceAddedCallback
DeviceManagerDeviceAddedCallback
cb
let wrapped' :: C_DeviceManagerDeviceAddedCallback
wrapped' = (a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
forall a.
GObject a =>
(a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
wrap_DeviceManagerDeviceChangedCallback a -> DeviceManagerDeviceAddedCallback
wrapped
FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' <- C_DeviceManagerDeviceAddedCallback
-> IO (FunPtr C_DeviceManagerDeviceAddedCallback)
mk_DeviceManagerDeviceChangedCallback C_DeviceManagerDeviceAddedCallback
wrapped'
a
-> Text
-> FunPtr C_DeviceManagerDeviceAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"device-changed" FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDeviceManagerDeviceChanged :: (IsDeviceManager a, MonadIO m) => a -> ((?self :: a) => DeviceManagerDeviceChangedCallback) -> m SignalHandlerId
afterDeviceManagerDeviceChanged :: forall a (m :: * -> *).
(IsDeviceManager a, MonadIO m) =>
a
-> ((?self::a) => DeviceManagerDeviceAddedCallback)
-> m SignalHandlerId
afterDeviceManagerDeviceChanged a
obj (?self::a) => DeviceManagerDeviceAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> DeviceManagerDeviceAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DeviceManagerDeviceAddedCallback
DeviceManagerDeviceAddedCallback
cb
let wrapped' :: C_DeviceManagerDeviceAddedCallback
wrapped' = (a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
forall a.
GObject a =>
(a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
wrap_DeviceManagerDeviceChangedCallback a -> DeviceManagerDeviceAddedCallback
wrapped
FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' <- C_DeviceManagerDeviceAddedCallback
-> IO (FunPtr C_DeviceManagerDeviceAddedCallback)
mk_DeviceManagerDeviceChangedCallback C_DeviceManagerDeviceAddedCallback
wrapped'
a
-> Text
-> FunPtr C_DeviceManagerDeviceAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"device-changed" FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data DeviceManagerDeviceChangedSignalInfo
instance SignalInfo DeviceManagerDeviceChangedSignalInfo where
type HaskellCallbackType DeviceManagerDeviceChangedSignalInfo = DeviceManagerDeviceChangedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_DeviceManagerDeviceChangedCallback cb
cb'' <- mk_DeviceManagerDeviceChangedCallback cb'
connectSignalFunPtr obj "device-changed" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DeviceManager::device-changed"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-DeviceManager.html#g:signal:deviceChanged"})
#endif
type DeviceManagerDeviceRemovedCallback =
Gdk.Device.Device
-> IO ()
type C_DeviceManagerDeviceRemovedCallback =
Ptr DeviceManager ->
Ptr Gdk.Device.Device ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DeviceManagerDeviceRemovedCallback :: C_DeviceManagerDeviceRemovedCallback -> IO (FunPtr C_DeviceManagerDeviceRemovedCallback)
wrap_DeviceManagerDeviceRemovedCallback ::
GObject a => (a -> DeviceManagerDeviceRemovedCallback) ->
C_DeviceManagerDeviceRemovedCallback
wrap_DeviceManagerDeviceRemovedCallback :: forall a.
GObject a =>
(a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
wrap_DeviceManagerDeviceRemovedCallback a -> DeviceManagerDeviceAddedCallback
gi'cb Ptr DeviceManager
gi'selfPtr Ptr Device
device Ptr ()
_ = do
Device
device' <- ((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
Gdk.Device.Device) Ptr Device
device
Ptr DeviceManager -> (DeviceManager -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr DeviceManager
gi'selfPtr ((DeviceManager -> IO ()) -> IO ())
-> (DeviceManager -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \DeviceManager
gi'self -> a -> DeviceManagerDeviceAddedCallback
gi'cb (DeviceManager -> a
forall a b. Coercible a b => a -> b
Coerce.coerce DeviceManager
gi'self) Device
device'
onDeviceManagerDeviceRemoved :: (IsDeviceManager a, MonadIO m) => a -> ((?self :: a) => DeviceManagerDeviceRemovedCallback) -> m SignalHandlerId
onDeviceManagerDeviceRemoved :: forall a (m :: * -> *).
(IsDeviceManager a, MonadIO m) =>
a
-> ((?self::a) => DeviceManagerDeviceAddedCallback)
-> m SignalHandlerId
onDeviceManagerDeviceRemoved a
obj (?self::a) => DeviceManagerDeviceAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> DeviceManagerDeviceAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DeviceManagerDeviceAddedCallback
DeviceManagerDeviceAddedCallback
cb
let wrapped' :: C_DeviceManagerDeviceAddedCallback
wrapped' = (a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
forall a.
GObject a =>
(a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
wrap_DeviceManagerDeviceRemovedCallback a -> DeviceManagerDeviceAddedCallback
wrapped
FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' <- C_DeviceManagerDeviceAddedCallback
-> IO (FunPtr C_DeviceManagerDeviceAddedCallback)
mk_DeviceManagerDeviceRemovedCallback C_DeviceManagerDeviceAddedCallback
wrapped'
a
-> Text
-> FunPtr C_DeviceManagerDeviceAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"device-removed" FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDeviceManagerDeviceRemoved :: (IsDeviceManager a, MonadIO m) => a -> ((?self :: a) => DeviceManagerDeviceRemovedCallback) -> m SignalHandlerId
afterDeviceManagerDeviceRemoved :: forall a (m :: * -> *).
(IsDeviceManager a, MonadIO m) =>
a
-> ((?self::a) => DeviceManagerDeviceAddedCallback)
-> m SignalHandlerId
afterDeviceManagerDeviceRemoved a
obj (?self::a) => DeviceManagerDeviceAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
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 wrapped :: a -> DeviceManagerDeviceAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DeviceManagerDeviceAddedCallback
DeviceManagerDeviceAddedCallback
cb
let wrapped' :: C_DeviceManagerDeviceAddedCallback
wrapped' = (a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
forall a.
GObject a =>
(a -> DeviceManagerDeviceAddedCallback)
-> C_DeviceManagerDeviceAddedCallback
wrap_DeviceManagerDeviceRemovedCallback a -> DeviceManagerDeviceAddedCallback
wrapped
FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' <- C_DeviceManagerDeviceAddedCallback
-> IO (FunPtr C_DeviceManagerDeviceAddedCallback)
mk_DeviceManagerDeviceRemovedCallback C_DeviceManagerDeviceAddedCallback
wrapped'
a
-> Text
-> FunPtr C_DeviceManagerDeviceAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"device-removed" FunPtr C_DeviceManagerDeviceAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data DeviceManagerDeviceRemovedSignalInfo
instance SignalInfo DeviceManagerDeviceRemovedSignalInfo where
type HaskellCallbackType DeviceManagerDeviceRemovedSignalInfo = DeviceManagerDeviceRemovedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_DeviceManagerDeviceRemovedCallback cb
cb'' <- mk_DeviceManagerDeviceRemovedCallback cb'
connectSignalFunPtr obj "device-removed" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DeviceManager::device-removed"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-DeviceManager.html#g:signal:deviceRemoved"})
#endif
getDeviceManagerDisplay :: (MonadIO m, IsDeviceManager o) => o -> m (Maybe Gdk.Display.Display)
getDeviceManagerDisplay :: forall (m :: * -> *) o.
(MonadIO m, IsDeviceManager o) =>
o -> m (Maybe Display)
getDeviceManagerDisplay o
obj = IO (Maybe Display) -> m (Maybe Display)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Display) -> m (Maybe Display))
-> IO (Maybe Display) -> m (Maybe 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
constructDeviceManagerDisplay :: (IsDeviceManager o, MIO.MonadIO m, Gdk.Display.IsDisplay a) => a -> m (GValueConstruct o)
constructDeviceManagerDisplay :: forall o (m :: * -> *) a.
(IsDeviceManager o, MonadIO m, IsDisplay a) =>
a -> m (GValueConstruct o)
constructDeviceManagerDisplay a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (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 DeviceManagerDisplayPropertyInfo
instance AttrInfo DeviceManagerDisplayPropertyInfo where
type AttrAllowedOps DeviceManagerDisplayPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DeviceManagerDisplayPropertyInfo = IsDeviceManager
type AttrSetTypeConstraint DeviceManagerDisplayPropertyInfo = Gdk.Display.IsDisplay
type AttrTransferTypeConstraint DeviceManagerDisplayPropertyInfo = Gdk.Display.IsDisplay
type AttrTransferType DeviceManagerDisplayPropertyInfo = Gdk.Display.Display
type AttrGetType DeviceManagerDisplayPropertyInfo = (Maybe Gdk.Display.Display)
type AttrLabel DeviceManagerDisplayPropertyInfo = "display"
type AttrOrigin DeviceManagerDisplayPropertyInfo = DeviceManager
attrGet = getDeviceManagerDisplay
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo Gdk.Display.Display v
attrConstruct = constructDeviceManagerDisplay
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DeviceManager.display"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-DeviceManager.html#g:attr:display"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DeviceManager
type instance O.AttributeList DeviceManager = DeviceManagerAttributeList
type DeviceManagerAttributeList = ('[ '("display", DeviceManagerDisplayPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
deviceManagerDisplay :: AttrLabelProxy "display"
deviceManagerDisplay = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DeviceManager = DeviceManagerSignalList
type DeviceManagerSignalList = ('[ '("deviceAdded", DeviceManagerDeviceAddedSignalInfo), '("deviceChanged", DeviceManagerDeviceChangedSignalInfo), '("deviceRemoved", DeviceManagerDeviceRemovedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gdk_device_manager_get_client_pointer" gdk_device_manager_get_client_pointer ::
Ptr DeviceManager ->
IO (Ptr Gdk.Device.Device)
{-# DEPRECATED deviceManagerGetClientPointer ["(Since version 3.20)","Use 'GI.Gdk.Objects.Seat.seatGetPointer' instead."] #-}
deviceManagerGetClientPointer ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceManager a) =>
a
-> m Gdk.Device.Device
deviceManagerGetClientPointer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceManager a) =>
a -> m Device
deviceManagerGetClientPointer a
deviceManager = IO Device -> m Device
forall a. IO a -> m a
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 DeviceManager
deviceManager' <- a -> IO (Ptr DeviceManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
deviceManager
Ptr Device
result <- Ptr DeviceManager -> IO (Ptr Device)
gdk_device_manager_get_client_pointer Ptr DeviceManager
deviceManager'
Text -> Ptr Device -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"deviceManagerGetClientPointer" Ptr Device
result
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
Gdk.Device.Device) Ptr Device
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
deviceManager
Device -> IO Device
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Device
result'
#if defined(ENABLE_OVERLOADING)
data DeviceManagerGetClientPointerMethodInfo
instance (signature ~ (m Gdk.Device.Device), MonadIO m, IsDeviceManager a) => O.OverloadedMethod DeviceManagerGetClientPointerMethodInfo a signature where
overloadedMethod = deviceManagerGetClientPointer
instance O.OverloadedMethodInfo DeviceManagerGetClientPointerMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DeviceManager.deviceManagerGetClientPointer",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-DeviceManager.html#v:deviceManagerGetClientPointer"
})
#endif
foreign import ccall "gdk_device_manager_get_display" gdk_device_manager_get_display ::
Ptr DeviceManager ->
IO (Ptr Gdk.Display.Display)
deviceManagerGetDisplay ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceManager a) =>
a
-> m (Maybe Gdk.Display.Display)
deviceManagerGetDisplay :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceManager a) =>
a -> m (Maybe Display)
deviceManagerGetDisplay a
deviceManager = IO (Maybe Display) -> m (Maybe Display)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Display) -> m (Maybe Display))
-> IO (Maybe Display) -> m (Maybe Display)
forall a b. (a -> b) -> a -> b
$ do
Ptr DeviceManager
deviceManager' <- a -> IO (Ptr DeviceManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
deviceManager
Ptr Display
result <- Ptr DeviceManager -> IO (Ptr Display)
gdk_device_manager_get_display Ptr DeviceManager
deviceManager'
Maybe Display
maybeResult <- Ptr Display -> (Ptr Display -> IO Display) -> IO (Maybe Display)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Display
result ((Ptr Display -> IO Display) -> IO (Maybe Display))
-> (Ptr Display -> IO Display) -> IO (Maybe Display)
forall a b. (a -> b) -> a -> b
$ \Ptr Display
result' -> do
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'
Display -> IO Display
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Display
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
deviceManager
Maybe Display -> IO (Maybe Display)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Display
maybeResult
#if defined(ENABLE_OVERLOADING)
data DeviceManagerGetDisplayMethodInfo
instance (signature ~ (m (Maybe Gdk.Display.Display)), MonadIO m, IsDeviceManager a) => O.OverloadedMethod DeviceManagerGetDisplayMethodInfo a signature where
overloadedMethod = deviceManagerGetDisplay
instance O.OverloadedMethodInfo DeviceManagerGetDisplayMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DeviceManager.deviceManagerGetDisplay",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-DeviceManager.html#v:deviceManagerGetDisplay"
})
#endif
foreign import ccall "gdk_device_manager_list_devices" gdk_device_manager_list_devices ::
Ptr DeviceManager ->
CUInt ->
IO (Ptr (GList (Ptr Gdk.Device.Device)))
{-# DEPRECATED deviceManagerListDevices ["(Since version 3.20)",", use 'GI.Gdk.Objects.Seat.seatGetPointer', 'GI.Gdk.Objects.Seat.seatGetKeyboard'"," and 'GI.Gdk.Objects.Seat.seatGetSlaves' instead."] #-}
deviceManagerListDevices ::
(B.CallStack.HasCallStack, MonadIO m, IsDeviceManager a) =>
a
-> Gdk.Enums.DeviceType
-> m [Gdk.Device.Device]
deviceManagerListDevices :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDeviceManager a) =>
a -> DeviceType -> m [Device]
deviceManagerListDevices a
deviceManager DeviceType
type_ = IO [Device] -> m [Device]
forall a. IO a -> m a
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 DeviceManager
deviceManager' <- a -> IO (Ptr DeviceManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
deviceManager
let type_' :: CUInt
type_' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (DeviceType -> Int) -> DeviceType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DeviceType -> Int
forall a. Enum a => a -> Int
fromEnum) DeviceType
type_
Ptr (GList (Ptr Device))
result <- Ptr DeviceManager -> CUInt -> IO (Ptr (GList (Ptr Device)))
gdk_device_manager_list_devices Ptr DeviceManager
deviceManager' CUInt
type_'
[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)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [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
Gdk.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
deviceManager
[Device] -> IO [Device]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Device]
result''
#if defined(ENABLE_OVERLOADING)
data DeviceManagerListDevicesMethodInfo
instance (signature ~ (Gdk.Enums.DeviceType -> m [Gdk.Device.Device]), MonadIO m, IsDeviceManager a) => O.OverloadedMethod DeviceManagerListDevicesMethodInfo a signature where
overloadedMethod = deviceManagerListDevices
instance O.OverloadedMethodInfo DeviceManagerListDevicesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DeviceManager.deviceManagerListDevices",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-DeviceManager.html#v:deviceManagerListDevices"
})
#endif