{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Objects.Display
(
Display(..) ,
IsDisplay ,
toDisplay ,
#if defined(ENABLE_OVERLOADING)
ResolveDisplayMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DisplayBeepMethodInfo ,
#endif
displayBeep ,
#if defined(ENABLE_OVERLOADING)
DisplayCloseMethodInfo ,
#endif
displayClose ,
#if defined(ENABLE_OVERLOADING)
DisplayDeviceIsGrabbedMethodInfo ,
#endif
displayDeviceIsGrabbed ,
#if defined(ENABLE_OVERLOADING)
DisplayFlushMethodInfo ,
#endif
displayFlush ,
#if defined(ENABLE_OVERLOADING)
DisplayGetAppLaunchContextMethodInfo ,
#endif
displayGetAppLaunchContext ,
displayGetDefault ,
#if defined(ENABLE_OVERLOADING)
DisplayGetDefaultCursorSizeMethodInfo ,
#endif
displayGetDefaultCursorSize ,
#if defined(ENABLE_OVERLOADING)
DisplayGetDefaultGroupMethodInfo ,
#endif
displayGetDefaultGroup ,
#if defined(ENABLE_OVERLOADING)
DisplayGetDefaultScreenMethodInfo ,
#endif
displayGetDefaultScreen ,
#if defined(ENABLE_OVERLOADING)
DisplayGetDefaultSeatMethodInfo ,
#endif
displayGetDefaultSeat ,
#if defined(ENABLE_OVERLOADING)
DisplayGetDeviceManagerMethodInfo ,
#endif
displayGetDeviceManager ,
#if defined(ENABLE_OVERLOADING)
DisplayGetEventMethodInfo ,
#endif
displayGetEvent ,
#if defined(ENABLE_OVERLOADING)
DisplayGetMaximalCursorSizeMethodInfo ,
#endif
displayGetMaximalCursorSize ,
#if defined(ENABLE_OVERLOADING)
DisplayGetMonitorMethodInfo ,
#endif
displayGetMonitor ,
#if defined(ENABLE_OVERLOADING)
DisplayGetMonitorAtPointMethodInfo ,
#endif
displayGetMonitorAtPoint ,
#if defined(ENABLE_OVERLOADING)
DisplayGetMonitorAtWindowMethodInfo ,
#endif
displayGetMonitorAtWindow ,
#if defined(ENABLE_OVERLOADING)
DisplayGetNMonitorsMethodInfo ,
#endif
displayGetNMonitors ,
#if defined(ENABLE_OVERLOADING)
DisplayGetNScreensMethodInfo ,
#endif
displayGetNScreens ,
#if defined(ENABLE_OVERLOADING)
DisplayGetNameMethodInfo ,
#endif
displayGetName ,
#if defined(ENABLE_OVERLOADING)
DisplayGetPointerMethodInfo ,
#endif
displayGetPointer ,
#if defined(ENABLE_OVERLOADING)
DisplayGetPrimaryMonitorMethodInfo ,
#endif
displayGetPrimaryMonitor ,
#if defined(ENABLE_OVERLOADING)
DisplayGetScreenMethodInfo ,
#endif
displayGetScreen ,
#if defined(ENABLE_OVERLOADING)
DisplayGetWindowAtPointerMethodInfo ,
#endif
displayGetWindowAtPointer ,
#if defined(ENABLE_OVERLOADING)
DisplayHasPendingMethodInfo ,
#endif
displayHasPending ,
#if defined(ENABLE_OVERLOADING)
DisplayIsClosedMethodInfo ,
#endif
displayIsClosed ,
#if defined(ENABLE_OVERLOADING)
DisplayKeyboardUngrabMethodInfo ,
#endif
displayKeyboardUngrab ,
#if defined(ENABLE_OVERLOADING)
DisplayListDevicesMethodInfo ,
#endif
displayListDevices ,
#if defined(ENABLE_OVERLOADING)
DisplayListSeatsMethodInfo ,
#endif
displayListSeats ,
#if defined(ENABLE_OVERLOADING)
DisplayNotifyStartupCompleteMethodInfo ,
#endif
displayNotifyStartupComplete ,
displayOpen ,
displayOpenDefaultLibgtkOnly ,
#if defined(ENABLE_OVERLOADING)
DisplayPeekEventMethodInfo ,
#endif
displayPeekEvent ,
#if defined(ENABLE_OVERLOADING)
DisplayPointerIsGrabbedMethodInfo ,
#endif
displayPointerIsGrabbed ,
#if defined(ENABLE_OVERLOADING)
DisplayPointerUngrabMethodInfo ,
#endif
displayPointerUngrab ,
#if defined(ENABLE_OVERLOADING)
DisplayPutEventMethodInfo ,
#endif
displayPutEvent ,
#if defined(ENABLE_OVERLOADING)
DisplayRequestSelectionNotificationMethodInfo,
#endif
displayRequestSelectionNotification ,
#if defined(ENABLE_OVERLOADING)
DisplaySetDoubleClickDistanceMethodInfo ,
#endif
displaySetDoubleClickDistance ,
#if defined(ENABLE_OVERLOADING)
DisplaySetDoubleClickTimeMethodInfo ,
#endif
displaySetDoubleClickTime ,
#if defined(ENABLE_OVERLOADING)
DisplayStoreClipboardMethodInfo ,
#endif
displayStoreClipboard ,
#if defined(ENABLE_OVERLOADING)
DisplaySupportsClipboardPersistenceMethodInfo,
#endif
displaySupportsClipboardPersistence ,
#if defined(ENABLE_OVERLOADING)
DisplaySupportsCompositeMethodInfo ,
#endif
displaySupportsComposite ,
#if defined(ENABLE_OVERLOADING)
DisplaySupportsCursorAlphaMethodInfo ,
#endif
displaySupportsCursorAlpha ,
#if defined(ENABLE_OVERLOADING)
DisplaySupportsCursorColorMethodInfo ,
#endif
displaySupportsCursorColor ,
#if defined(ENABLE_OVERLOADING)
DisplaySupportsInputShapesMethodInfo ,
#endif
displaySupportsInputShapes ,
#if defined(ENABLE_OVERLOADING)
DisplaySupportsSelectionNotificationMethodInfo,
#endif
displaySupportsSelectionNotification ,
#if defined(ENABLE_OVERLOADING)
DisplaySupportsShapesMethodInfo ,
#endif
displaySupportsShapes ,
#if defined(ENABLE_OVERLOADING)
DisplaySyncMethodInfo ,
#endif
displaySync ,
#if defined(ENABLE_OVERLOADING)
DisplayWarpPointerMethodInfo ,
#endif
displayWarpPointer ,
DisplayClosedCallback ,
#if defined(ENABLE_OVERLOADING)
DisplayClosedSignalInfo ,
#endif
afterDisplayClosed ,
onDisplayClosed ,
DisplayMonitorAddedCallback ,
#if defined(ENABLE_OVERLOADING)
DisplayMonitorAddedSignalInfo ,
#endif
afterDisplayMonitorAdded ,
onDisplayMonitorAdded ,
DisplayMonitorRemovedCallback ,
#if defined(ENABLE_OVERLOADING)
DisplayMonitorRemovedSignalInfo ,
#endif
afterDisplayMonitorRemoved ,
onDisplayMonitorRemoved ,
DisplayOpenedCallback ,
#if defined(ENABLE_OVERLOADING)
DisplayOpenedSignalInfo ,
#endif
afterDisplayOpened ,
onDisplayOpened ,
DisplaySeatAddedCallback ,
#if defined(ENABLE_OVERLOADING)
DisplaySeatAddedSignalInfo ,
#endif
afterDisplaySeatAdded ,
onDisplaySeatAdded ,
DisplaySeatRemovedCallback ,
#if defined(ENABLE_OVERLOADING)
DisplaySeatRemovedSignalInfo ,
#endif
afterDisplaySeatRemoved ,
onDisplaySeatRemoved ,
) 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.DeviceManager as Gdk.DeviceManager
import {-# SOURCE #-} qualified GI.Gdk.Objects.DeviceTool as Gdk.DeviceTool
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.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Objects.AppLaunchContext as Gdk.AppLaunchContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Device as Gdk.Device
import {-# SOURCE #-} qualified GI.Gdk.Objects.DeviceManager as Gdk.DeviceManager
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.Window as Gdk.Window
import {-# SOURCE #-} qualified GI.Gdk.Structs.Atom as Gdk.Atom
import {-# SOURCE #-} qualified GI.Gdk.Unions.Event as Gdk.Event
#endif
newtype Display = Display (SP.ManagedPtr Display)
deriving (Display -> Display -> Bool
(Display -> Display -> Bool)
-> (Display -> Display -> Bool) -> Eq Display
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Display -> Display -> Bool
== :: Display -> Display -> Bool
$c/= :: Display -> Display -> Bool
/= :: Display -> Display -> Bool
Eq)
instance SP.ManagedPtrNewtype Display where
toManagedPtr :: Display -> ManagedPtr Display
toManagedPtr (Display ManagedPtr Display
p) = ManagedPtr Display
p
foreign import ccall "gdk_display_get_type"
c_gdk_display_get_type :: IO B.Types.GType
instance B.Types.TypedObject Display where
glibType :: IO GType
glibType = IO GType
c_gdk_display_get_type
instance B.Types.GObject Display
class (SP.GObject o, O.IsDescendantOf Display o) => IsDisplay o
instance (SP.GObject o, O.IsDescendantOf Display o) => IsDisplay o
instance O.HasParentTypes Display
type instance O.ParentTypes Display = '[GObject.Object.Object]
toDisplay :: (MIO.MonadIO m, IsDisplay o) => o -> m Display
toDisplay :: forall (m :: * -> *) o. (MonadIO m, IsDisplay o) => o -> m Display
toDisplay = IO Display -> m Display
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Display -> m Display) -> (o -> IO Display) -> o -> m Display
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Display -> Display) -> o -> IO Display
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Display -> Display
Display
instance B.GValue.IsGValue (Maybe Display) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_display_get_type
gvalueSet_ :: Ptr GValue -> Maybe Display -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Display
P.Nothing = Ptr GValue -> Ptr Display -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Display
forall a. Ptr a
FP.nullPtr :: FP.Ptr Display)
gvalueSet_ Ptr GValue
gv (P.Just Display
obj) = Display -> (Ptr Display -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Display
obj (Ptr GValue -> Ptr Display -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Display)
gvalueGet_ Ptr GValue
gv = do
Ptr Display
ptr <- Ptr GValue -> IO (Ptr Display)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Display)
if Ptr Display
ptr Ptr Display -> Ptr Display -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Display
forall a. Ptr a
FP.nullPtr
then Display -> Maybe Display
forall a. a -> Maybe a
P.Just (Display -> Maybe Display) -> IO Display -> IO (Maybe Display)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Display -> Display) -> Ptr Display -> IO Display
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Display -> Display
Display Ptr Display
ptr
else Maybe Display -> IO (Maybe Display)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Display
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveDisplayMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveDisplayMethod "beep" o = DisplayBeepMethodInfo
ResolveDisplayMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveDisplayMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveDisplayMethod "close" o = DisplayCloseMethodInfo
ResolveDisplayMethod "deviceIsGrabbed" o = DisplayDeviceIsGrabbedMethodInfo
ResolveDisplayMethod "flush" o = DisplayFlushMethodInfo
ResolveDisplayMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveDisplayMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveDisplayMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveDisplayMethod "hasPending" o = DisplayHasPendingMethodInfo
ResolveDisplayMethod "isClosed" o = DisplayIsClosedMethodInfo
ResolveDisplayMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveDisplayMethod "keyboardUngrab" o = DisplayKeyboardUngrabMethodInfo
ResolveDisplayMethod "listDevices" o = DisplayListDevicesMethodInfo
ResolveDisplayMethod "listSeats" o = DisplayListSeatsMethodInfo
ResolveDisplayMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveDisplayMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveDisplayMethod "notifyStartupComplete" o = DisplayNotifyStartupCompleteMethodInfo
ResolveDisplayMethod "peekEvent" o = DisplayPeekEventMethodInfo
ResolveDisplayMethod "pointerIsGrabbed" o = DisplayPointerIsGrabbedMethodInfo
ResolveDisplayMethod "pointerUngrab" o = DisplayPointerUngrabMethodInfo
ResolveDisplayMethod "putEvent" o = DisplayPutEventMethodInfo
ResolveDisplayMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveDisplayMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveDisplayMethod "requestSelectionNotification" o = DisplayRequestSelectionNotificationMethodInfo
ResolveDisplayMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveDisplayMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveDisplayMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveDisplayMethod "storeClipboard" o = DisplayStoreClipboardMethodInfo
ResolveDisplayMethod "supportsClipboardPersistence" o = DisplaySupportsClipboardPersistenceMethodInfo
ResolveDisplayMethod "supportsComposite" o = DisplaySupportsCompositeMethodInfo
ResolveDisplayMethod "supportsCursorAlpha" o = DisplaySupportsCursorAlphaMethodInfo
ResolveDisplayMethod "supportsCursorColor" o = DisplaySupportsCursorColorMethodInfo
ResolveDisplayMethod "supportsInputShapes" o = DisplaySupportsInputShapesMethodInfo
ResolveDisplayMethod "supportsSelectionNotification" o = DisplaySupportsSelectionNotificationMethodInfo
ResolveDisplayMethod "supportsShapes" o = DisplaySupportsShapesMethodInfo
ResolveDisplayMethod "sync" o = DisplaySyncMethodInfo
ResolveDisplayMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveDisplayMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveDisplayMethod "warpPointer" o = DisplayWarpPointerMethodInfo
ResolveDisplayMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveDisplayMethod "getAppLaunchContext" o = DisplayGetAppLaunchContextMethodInfo
ResolveDisplayMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveDisplayMethod "getDefaultCursorSize" o = DisplayGetDefaultCursorSizeMethodInfo
ResolveDisplayMethod "getDefaultGroup" o = DisplayGetDefaultGroupMethodInfo
ResolveDisplayMethod "getDefaultScreen" o = DisplayGetDefaultScreenMethodInfo
ResolveDisplayMethod "getDefaultSeat" o = DisplayGetDefaultSeatMethodInfo
ResolveDisplayMethod "getDeviceManager" o = DisplayGetDeviceManagerMethodInfo
ResolveDisplayMethod "getEvent" o = DisplayGetEventMethodInfo
ResolveDisplayMethod "getMaximalCursorSize" o = DisplayGetMaximalCursorSizeMethodInfo
ResolveDisplayMethod "getMonitor" o = DisplayGetMonitorMethodInfo
ResolveDisplayMethod "getMonitorAtPoint" o = DisplayGetMonitorAtPointMethodInfo
ResolveDisplayMethod "getMonitorAtWindow" o = DisplayGetMonitorAtWindowMethodInfo
ResolveDisplayMethod "getNMonitors" o = DisplayGetNMonitorsMethodInfo
ResolveDisplayMethod "getNScreens" o = DisplayGetNScreensMethodInfo
ResolveDisplayMethod "getName" o = DisplayGetNameMethodInfo
ResolveDisplayMethod "getPointer" o = DisplayGetPointerMethodInfo
ResolveDisplayMethod "getPrimaryMonitor" o = DisplayGetPrimaryMonitorMethodInfo
ResolveDisplayMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveDisplayMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveDisplayMethod "getScreen" o = DisplayGetScreenMethodInfo
ResolveDisplayMethod "getWindowAtPointer" o = DisplayGetWindowAtPointerMethodInfo
ResolveDisplayMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveDisplayMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveDisplayMethod "setDoubleClickDistance" o = DisplaySetDoubleClickDistanceMethodInfo
ResolveDisplayMethod "setDoubleClickTime" o = DisplaySetDoubleClickTimeMethodInfo
ResolveDisplayMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveDisplayMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDisplayMethod t Display, O.OverloadedMethod info Display p) => OL.IsLabel t (Display -> 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 ~ ResolveDisplayMethod t Display, O.OverloadedMethod info Display p, R.HasField t Display p) => R.HasField t Display p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveDisplayMethod t Display, O.OverloadedMethodInfo info Display) => OL.IsLabel t (O.MethodProxy info Display) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
type DisplayClosedCallback =
Bool
-> IO ()
type C_DisplayClosedCallback =
Ptr Display ->
CInt ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DisplayClosedCallback :: C_DisplayClosedCallback -> IO (FunPtr C_DisplayClosedCallback)
wrap_DisplayClosedCallback ::
GObject a => (a -> DisplayClosedCallback) ->
C_DisplayClosedCallback
wrap_DisplayClosedCallback :: forall a.
GObject a =>
(a -> DisplayClosedCallback) -> C_DisplayClosedCallback
wrap_DisplayClosedCallback a -> DisplayClosedCallback
gi'cb Ptr Display
gi'selfPtr CInt
isError Ptr ()
_ = do
let isError' :: Bool
isError' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
isError
Ptr Display -> (Display -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr Display
gi'selfPtr ((Display -> IO ()) -> IO ()) -> (Display -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Display
gi'self -> a -> DisplayClosedCallback
gi'cb (Display -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Display
gi'self) Bool
isError'
onDisplayClosed :: (IsDisplay a, MonadIO m) => a -> ((?self :: a) => DisplayClosedCallback) -> m SignalHandlerId
onDisplayClosed :: forall a (m :: * -> *).
(IsDisplay a, MonadIO m) =>
a -> ((?self::a) => DisplayClosedCallback) -> m SignalHandlerId
onDisplayClosed a
obj (?self::a) => DisplayClosedCallback
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 -> DisplayClosedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DisplayClosedCallback
DisplayClosedCallback
cb
let wrapped' :: C_DisplayClosedCallback
wrapped' = (a -> DisplayClosedCallback) -> C_DisplayClosedCallback
forall a.
GObject a =>
(a -> DisplayClosedCallback) -> C_DisplayClosedCallback
wrap_DisplayClosedCallback a -> DisplayClosedCallback
wrapped
FunPtr C_DisplayClosedCallback
wrapped'' <- C_DisplayClosedCallback -> IO (FunPtr C_DisplayClosedCallback)
mk_DisplayClosedCallback C_DisplayClosedCallback
wrapped'
a
-> Text
-> FunPtr C_DisplayClosedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"closed" FunPtr C_DisplayClosedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDisplayClosed :: (IsDisplay a, MonadIO m) => a -> ((?self :: a) => DisplayClosedCallback) -> m SignalHandlerId
afterDisplayClosed :: forall a (m :: * -> *).
(IsDisplay a, MonadIO m) =>
a -> ((?self::a) => DisplayClosedCallback) -> m SignalHandlerId
afterDisplayClosed a
obj (?self::a) => DisplayClosedCallback
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 -> DisplayClosedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DisplayClosedCallback
DisplayClosedCallback
cb
let wrapped' :: C_DisplayClosedCallback
wrapped' = (a -> DisplayClosedCallback) -> C_DisplayClosedCallback
forall a.
GObject a =>
(a -> DisplayClosedCallback) -> C_DisplayClosedCallback
wrap_DisplayClosedCallback a -> DisplayClosedCallback
wrapped
FunPtr C_DisplayClosedCallback
wrapped'' <- C_DisplayClosedCallback -> IO (FunPtr C_DisplayClosedCallback)
mk_DisplayClosedCallback C_DisplayClosedCallback
wrapped'
a
-> Text
-> FunPtr C_DisplayClosedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"closed" FunPtr C_DisplayClosedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data DisplayClosedSignalInfo
instance SignalInfo DisplayClosedSignalInfo where
type HaskellCallbackType DisplayClosedSignalInfo = DisplayClosedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_DisplayClosedCallback cb
cb'' <- mk_DisplayClosedCallback cb'
connectSignalFunPtr obj "closed" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display::closed"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#g:signal:closed"})
#endif
type DisplayMonitorAddedCallback =
Gdk.Monitor.Monitor
-> IO ()
type C_DisplayMonitorAddedCallback =
Ptr Display ->
Ptr Gdk.Monitor.Monitor ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DisplayMonitorAddedCallback :: C_DisplayMonitorAddedCallback -> IO (FunPtr C_DisplayMonitorAddedCallback)
wrap_DisplayMonitorAddedCallback ::
GObject a => (a -> DisplayMonitorAddedCallback) ->
C_DisplayMonitorAddedCallback
wrap_DisplayMonitorAddedCallback :: forall a.
GObject a =>
(a -> DisplayMonitorAddedCallback) -> C_DisplayMonitorAddedCallback
wrap_DisplayMonitorAddedCallback a -> DisplayMonitorAddedCallback
gi'cb Ptr Display
gi'selfPtr Ptr Monitor
monitor Ptr ()
_ = do
Monitor
monitor' <- ((ManagedPtr Monitor -> Monitor) -> Ptr Monitor -> IO Monitor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Monitor -> Monitor
Gdk.Monitor.Monitor) Ptr Monitor
monitor
Ptr Display -> (Display -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr Display
gi'selfPtr ((Display -> IO ()) -> IO ()) -> (Display -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Display
gi'self -> a -> DisplayMonitorAddedCallback
gi'cb (Display -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Display
gi'self) Monitor
monitor'
onDisplayMonitorAdded :: (IsDisplay a, MonadIO m) => a -> ((?self :: a) => DisplayMonitorAddedCallback) -> m SignalHandlerId
onDisplayMonitorAdded :: forall a (m :: * -> *).
(IsDisplay a, MonadIO m) =>
a
-> ((?self::a) => DisplayMonitorAddedCallback) -> m SignalHandlerId
onDisplayMonitorAdded a
obj (?self::a) => DisplayMonitorAddedCallback
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 -> DisplayMonitorAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DisplayMonitorAddedCallback
DisplayMonitorAddedCallback
cb
let wrapped' :: C_DisplayMonitorAddedCallback
wrapped' = (a -> DisplayMonitorAddedCallback) -> C_DisplayMonitorAddedCallback
forall a.
GObject a =>
(a -> DisplayMonitorAddedCallback) -> C_DisplayMonitorAddedCallback
wrap_DisplayMonitorAddedCallback a -> DisplayMonitorAddedCallback
wrapped
FunPtr C_DisplayMonitorAddedCallback
wrapped'' <- C_DisplayMonitorAddedCallback
-> IO (FunPtr C_DisplayMonitorAddedCallback)
mk_DisplayMonitorAddedCallback C_DisplayMonitorAddedCallback
wrapped'
a
-> Text
-> FunPtr C_DisplayMonitorAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"monitor-added" FunPtr C_DisplayMonitorAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDisplayMonitorAdded :: (IsDisplay a, MonadIO m) => a -> ((?self :: a) => DisplayMonitorAddedCallback) -> m SignalHandlerId
afterDisplayMonitorAdded :: forall a (m :: * -> *).
(IsDisplay a, MonadIO m) =>
a
-> ((?self::a) => DisplayMonitorAddedCallback) -> m SignalHandlerId
afterDisplayMonitorAdded a
obj (?self::a) => DisplayMonitorAddedCallback
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 -> DisplayMonitorAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DisplayMonitorAddedCallback
DisplayMonitorAddedCallback
cb
let wrapped' :: C_DisplayMonitorAddedCallback
wrapped' = (a -> DisplayMonitorAddedCallback) -> C_DisplayMonitorAddedCallback
forall a.
GObject a =>
(a -> DisplayMonitorAddedCallback) -> C_DisplayMonitorAddedCallback
wrap_DisplayMonitorAddedCallback a -> DisplayMonitorAddedCallback
wrapped
FunPtr C_DisplayMonitorAddedCallback
wrapped'' <- C_DisplayMonitorAddedCallback
-> IO (FunPtr C_DisplayMonitorAddedCallback)
mk_DisplayMonitorAddedCallback C_DisplayMonitorAddedCallback
wrapped'
a
-> Text
-> FunPtr C_DisplayMonitorAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"monitor-added" FunPtr C_DisplayMonitorAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data DisplayMonitorAddedSignalInfo
instance SignalInfo DisplayMonitorAddedSignalInfo where
type HaskellCallbackType DisplayMonitorAddedSignalInfo = DisplayMonitorAddedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_DisplayMonitorAddedCallback cb
cb'' <- mk_DisplayMonitorAddedCallback cb'
connectSignalFunPtr obj "monitor-added" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display::monitor-added"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#g:signal:monitorAdded"})
#endif
type DisplayMonitorRemovedCallback =
Gdk.Monitor.Monitor
-> IO ()
type C_DisplayMonitorRemovedCallback =
Ptr Display ->
Ptr Gdk.Monitor.Monitor ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DisplayMonitorRemovedCallback :: C_DisplayMonitorRemovedCallback -> IO (FunPtr C_DisplayMonitorRemovedCallback)
wrap_DisplayMonitorRemovedCallback ::
GObject a => (a -> DisplayMonitorRemovedCallback) ->
C_DisplayMonitorRemovedCallback
wrap_DisplayMonitorRemovedCallback :: forall a.
GObject a =>
(a -> DisplayMonitorAddedCallback) -> C_DisplayMonitorAddedCallback
wrap_DisplayMonitorRemovedCallback a -> DisplayMonitorAddedCallback
gi'cb Ptr Display
gi'selfPtr Ptr Monitor
monitor Ptr ()
_ = do
Monitor
monitor' <- ((ManagedPtr Monitor -> Monitor) -> Ptr Monitor -> IO Monitor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Monitor -> Monitor
Gdk.Monitor.Monitor) Ptr Monitor
monitor
Ptr Display -> (Display -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr Display
gi'selfPtr ((Display -> IO ()) -> IO ()) -> (Display -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Display
gi'self -> a -> DisplayMonitorAddedCallback
gi'cb (Display -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Display
gi'self) Monitor
monitor'
onDisplayMonitorRemoved :: (IsDisplay a, MonadIO m) => a -> ((?self :: a) => DisplayMonitorRemovedCallback) -> m SignalHandlerId
onDisplayMonitorRemoved :: forall a (m :: * -> *).
(IsDisplay a, MonadIO m) =>
a
-> ((?self::a) => DisplayMonitorAddedCallback) -> m SignalHandlerId
onDisplayMonitorRemoved a
obj (?self::a) => DisplayMonitorAddedCallback
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 -> DisplayMonitorAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DisplayMonitorAddedCallback
DisplayMonitorAddedCallback
cb
let wrapped' :: C_DisplayMonitorAddedCallback
wrapped' = (a -> DisplayMonitorAddedCallback) -> C_DisplayMonitorAddedCallback
forall a.
GObject a =>
(a -> DisplayMonitorAddedCallback) -> C_DisplayMonitorAddedCallback
wrap_DisplayMonitorRemovedCallback a -> DisplayMonitorAddedCallback
wrapped
FunPtr C_DisplayMonitorAddedCallback
wrapped'' <- C_DisplayMonitorAddedCallback
-> IO (FunPtr C_DisplayMonitorAddedCallback)
mk_DisplayMonitorRemovedCallback C_DisplayMonitorAddedCallback
wrapped'
a
-> Text
-> FunPtr C_DisplayMonitorAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"monitor-removed" FunPtr C_DisplayMonitorAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDisplayMonitorRemoved :: (IsDisplay a, MonadIO m) => a -> ((?self :: a) => DisplayMonitorRemovedCallback) -> m SignalHandlerId
afterDisplayMonitorRemoved :: forall a (m :: * -> *).
(IsDisplay a, MonadIO m) =>
a
-> ((?self::a) => DisplayMonitorAddedCallback) -> m SignalHandlerId
afterDisplayMonitorRemoved a
obj (?self::a) => DisplayMonitorAddedCallback
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 -> DisplayMonitorAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DisplayMonitorAddedCallback
DisplayMonitorAddedCallback
cb
let wrapped' :: C_DisplayMonitorAddedCallback
wrapped' = (a -> DisplayMonitorAddedCallback) -> C_DisplayMonitorAddedCallback
forall a.
GObject a =>
(a -> DisplayMonitorAddedCallback) -> C_DisplayMonitorAddedCallback
wrap_DisplayMonitorRemovedCallback a -> DisplayMonitorAddedCallback
wrapped
FunPtr C_DisplayMonitorAddedCallback
wrapped'' <- C_DisplayMonitorAddedCallback
-> IO (FunPtr C_DisplayMonitorAddedCallback)
mk_DisplayMonitorRemovedCallback C_DisplayMonitorAddedCallback
wrapped'
a
-> Text
-> FunPtr C_DisplayMonitorAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"monitor-removed" FunPtr C_DisplayMonitorAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data DisplayMonitorRemovedSignalInfo
instance SignalInfo DisplayMonitorRemovedSignalInfo where
type HaskellCallbackType DisplayMonitorRemovedSignalInfo = DisplayMonitorRemovedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_DisplayMonitorRemovedCallback cb
cb'' <- mk_DisplayMonitorRemovedCallback cb'
connectSignalFunPtr obj "monitor-removed" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display::monitor-removed"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#g:signal:monitorRemoved"})
#endif
type DisplayOpenedCallback =
IO ()
type C_DisplayOpenedCallback =
Ptr Display ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DisplayOpenedCallback :: C_DisplayOpenedCallback -> IO (FunPtr C_DisplayOpenedCallback)
wrap_DisplayOpenedCallback ::
GObject a => (a -> DisplayOpenedCallback) ->
C_DisplayOpenedCallback
wrap_DisplayOpenedCallback :: forall a. GObject a => (a -> IO ()) -> C_DisplayOpenedCallback
wrap_DisplayOpenedCallback a -> IO ()
gi'cb Ptr Display
gi'selfPtr Ptr ()
_ = do
Ptr Display -> (Display -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr Display
gi'selfPtr ((Display -> IO ()) -> IO ()) -> (Display -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Display
gi'self -> a -> IO ()
gi'cb (Display -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Display
gi'self)
onDisplayOpened :: (IsDisplay a, MonadIO m) => a -> ((?self :: a) => DisplayOpenedCallback) -> m SignalHandlerId
onDisplayOpened :: forall a (m :: * -> *).
(IsDisplay a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onDisplayOpened a
obj (?self::a) => IO ()
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 -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_DisplayOpenedCallback
wrapped' = (a -> IO ()) -> C_DisplayOpenedCallback
forall a. GObject a => (a -> IO ()) -> C_DisplayOpenedCallback
wrap_DisplayOpenedCallback a -> IO ()
wrapped
FunPtr C_DisplayOpenedCallback
wrapped'' <- C_DisplayOpenedCallback -> IO (FunPtr C_DisplayOpenedCallback)
mk_DisplayOpenedCallback C_DisplayOpenedCallback
wrapped'
a
-> Text
-> FunPtr C_DisplayOpenedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"opened" FunPtr C_DisplayOpenedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDisplayOpened :: (IsDisplay a, MonadIO m) => a -> ((?self :: a) => DisplayOpenedCallback) -> m SignalHandlerId
afterDisplayOpened :: forall a (m :: * -> *).
(IsDisplay a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterDisplayOpened a
obj (?self::a) => IO ()
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 -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
let wrapped' :: C_DisplayOpenedCallback
wrapped' = (a -> IO ()) -> C_DisplayOpenedCallback
forall a. GObject a => (a -> IO ()) -> C_DisplayOpenedCallback
wrap_DisplayOpenedCallback a -> IO ()
wrapped
FunPtr C_DisplayOpenedCallback
wrapped'' <- C_DisplayOpenedCallback -> IO (FunPtr C_DisplayOpenedCallback)
mk_DisplayOpenedCallback C_DisplayOpenedCallback
wrapped'
a
-> Text
-> FunPtr C_DisplayOpenedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"opened" FunPtr C_DisplayOpenedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data DisplayOpenedSignalInfo
instance SignalInfo DisplayOpenedSignalInfo where
type HaskellCallbackType DisplayOpenedSignalInfo = DisplayOpenedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_DisplayOpenedCallback cb
cb'' <- mk_DisplayOpenedCallback cb'
connectSignalFunPtr obj "opened" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display::opened"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#g:signal:opened"})
#endif
type DisplaySeatAddedCallback =
Gdk.Seat.Seat
-> IO ()
type C_DisplaySeatAddedCallback =
Ptr Display ->
Ptr Gdk.Seat.Seat ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DisplaySeatAddedCallback :: C_DisplaySeatAddedCallback -> IO (FunPtr C_DisplaySeatAddedCallback)
wrap_DisplaySeatAddedCallback ::
GObject a => (a -> DisplaySeatAddedCallback) ->
C_DisplaySeatAddedCallback
wrap_DisplaySeatAddedCallback :: forall a.
GObject a =>
(a -> DisplaySeatAddedCallback) -> C_DisplaySeatAddedCallback
wrap_DisplaySeatAddedCallback a -> DisplaySeatAddedCallback
gi'cb Ptr Display
gi'selfPtr Ptr Seat
seat Ptr ()
_ = do
Seat
seat' <- ((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
seat
Ptr Display -> (Display -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr Display
gi'selfPtr ((Display -> IO ()) -> IO ()) -> (Display -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Display
gi'self -> a -> DisplaySeatAddedCallback
gi'cb (Display -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Display
gi'self) Seat
seat'
onDisplaySeatAdded :: (IsDisplay a, MonadIO m) => a -> ((?self :: a) => DisplaySeatAddedCallback) -> m SignalHandlerId
onDisplaySeatAdded :: forall a (m :: * -> *).
(IsDisplay a, MonadIO m) =>
a -> ((?self::a) => DisplaySeatAddedCallback) -> m SignalHandlerId
onDisplaySeatAdded a
obj (?self::a) => DisplaySeatAddedCallback
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 -> DisplaySeatAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DisplaySeatAddedCallback
DisplaySeatAddedCallback
cb
let wrapped' :: C_DisplaySeatAddedCallback
wrapped' = (a -> DisplaySeatAddedCallback) -> C_DisplaySeatAddedCallback
forall a.
GObject a =>
(a -> DisplaySeatAddedCallback) -> C_DisplaySeatAddedCallback
wrap_DisplaySeatAddedCallback a -> DisplaySeatAddedCallback
wrapped
FunPtr C_DisplaySeatAddedCallback
wrapped'' <- C_DisplaySeatAddedCallback
-> IO (FunPtr C_DisplaySeatAddedCallback)
mk_DisplaySeatAddedCallback C_DisplaySeatAddedCallback
wrapped'
a
-> Text
-> FunPtr C_DisplaySeatAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"seat-added" FunPtr C_DisplaySeatAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDisplaySeatAdded :: (IsDisplay a, MonadIO m) => a -> ((?self :: a) => DisplaySeatAddedCallback) -> m SignalHandlerId
afterDisplaySeatAdded :: forall a (m :: * -> *).
(IsDisplay a, MonadIO m) =>
a -> ((?self::a) => DisplaySeatAddedCallback) -> m SignalHandlerId
afterDisplaySeatAdded a
obj (?self::a) => DisplaySeatAddedCallback
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 -> DisplaySeatAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DisplaySeatAddedCallback
DisplaySeatAddedCallback
cb
let wrapped' :: C_DisplaySeatAddedCallback
wrapped' = (a -> DisplaySeatAddedCallback) -> C_DisplaySeatAddedCallback
forall a.
GObject a =>
(a -> DisplaySeatAddedCallback) -> C_DisplaySeatAddedCallback
wrap_DisplaySeatAddedCallback a -> DisplaySeatAddedCallback
wrapped
FunPtr C_DisplaySeatAddedCallback
wrapped'' <- C_DisplaySeatAddedCallback
-> IO (FunPtr C_DisplaySeatAddedCallback)
mk_DisplaySeatAddedCallback C_DisplaySeatAddedCallback
wrapped'
a
-> Text
-> FunPtr C_DisplaySeatAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"seat-added" FunPtr C_DisplaySeatAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data DisplaySeatAddedSignalInfo
instance SignalInfo DisplaySeatAddedSignalInfo where
type HaskellCallbackType DisplaySeatAddedSignalInfo = DisplaySeatAddedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_DisplaySeatAddedCallback cb
cb'' <- mk_DisplaySeatAddedCallback cb'
connectSignalFunPtr obj "seat-added" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display::seat-added"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#g:signal:seatAdded"})
#endif
type DisplaySeatRemovedCallback =
Gdk.Seat.Seat
-> IO ()
type C_DisplaySeatRemovedCallback =
Ptr Display ->
Ptr Gdk.Seat.Seat ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_DisplaySeatRemovedCallback :: C_DisplaySeatRemovedCallback -> IO (FunPtr C_DisplaySeatRemovedCallback)
wrap_DisplaySeatRemovedCallback ::
GObject a => (a -> DisplaySeatRemovedCallback) ->
C_DisplaySeatRemovedCallback
wrap_DisplaySeatRemovedCallback :: forall a.
GObject a =>
(a -> DisplaySeatAddedCallback) -> C_DisplaySeatAddedCallback
wrap_DisplaySeatRemovedCallback a -> DisplaySeatAddedCallback
gi'cb Ptr Display
gi'selfPtr Ptr Seat
seat Ptr ()
_ = do
Seat
seat' <- ((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
seat
Ptr Display -> (Display -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr Display
gi'selfPtr ((Display -> IO ()) -> IO ()) -> (Display -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Display
gi'self -> a -> DisplaySeatAddedCallback
gi'cb (Display -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Display
gi'self) Seat
seat'
onDisplaySeatRemoved :: (IsDisplay a, MonadIO m) => a -> ((?self :: a) => DisplaySeatRemovedCallback) -> m SignalHandlerId
onDisplaySeatRemoved :: forall a (m :: * -> *).
(IsDisplay a, MonadIO m) =>
a -> ((?self::a) => DisplaySeatAddedCallback) -> m SignalHandlerId
onDisplaySeatRemoved a
obj (?self::a) => DisplaySeatAddedCallback
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 -> DisplaySeatAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DisplaySeatAddedCallback
DisplaySeatAddedCallback
cb
let wrapped' :: C_DisplaySeatAddedCallback
wrapped' = (a -> DisplaySeatAddedCallback) -> C_DisplaySeatAddedCallback
forall a.
GObject a =>
(a -> DisplaySeatAddedCallback) -> C_DisplaySeatAddedCallback
wrap_DisplaySeatRemovedCallback a -> DisplaySeatAddedCallback
wrapped
FunPtr C_DisplaySeatAddedCallback
wrapped'' <- C_DisplaySeatAddedCallback
-> IO (FunPtr C_DisplaySeatAddedCallback)
mk_DisplaySeatRemovedCallback C_DisplaySeatAddedCallback
wrapped'
a
-> Text
-> FunPtr C_DisplaySeatAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"seat-removed" FunPtr C_DisplaySeatAddedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterDisplaySeatRemoved :: (IsDisplay a, MonadIO m) => a -> ((?self :: a) => DisplaySeatRemovedCallback) -> m SignalHandlerId
afterDisplaySeatRemoved :: forall a (m :: * -> *).
(IsDisplay a, MonadIO m) =>
a -> ((?self::a) => DisplaySeatAddedCallback) -> m SignalHandlerId
afterDisplaySeatRemoved a
obj (?self::a) => DisplaySeatAddedCallback
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 -> DisplaySeatAddedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => DisplaySeatAddedCallback
DisplaySeatAddedCallback
cb
let wrapped' :: C_DisplaySeatAddedCallback
wrapped' = (a -> DisplaySeatAddedCallback) -> C_DisplaySeatAddedCallback
forall a.
GObject a =>
(a -> DisplaySeatAddedCallback) -> C_DisplaySeatAddedCallback
wrap_DisplaySeatRemovedCallback a -> DisplaySeatAddedCallback
wrapped
FunPtr C_DisplaySeatAddedCallback
wrapped'' <- C_DisplaySeatAddedCallback
-> IO (FunPtr C_DisplaySeatAddedCallback)
mk_DisplaySeatRemovedCallback C_DisplaySeatAddedCallback
wrapped'
a
-> Text
-> FunPtr C_DisplaySeatAddedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"seat-removed" FunPtr C_DisplaySeatAddedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data DisplaySeatRemovedSignalInfo
instance SignalInfo DisplaySeatRemovedSignalInfo where
type HaskellCallbackType DisplaySeatRemovedSignalInfo = DisplaySeatRemovedCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_DisplaySeatRemovedCallback cb
cb'' <- mk_DisplaySeatRemovedCallback cb'
connectSignalFunPtr obj "seat-removed" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display::seat-removed"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#g:signal:seatRemoved"})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Display
type instance O.AttributeList Display = DisplayAttributeList
type DisplayAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Display = DisplaySignalList
type DisplaySignalList = ('[ '("closed", DisplayClosedSignalInfo), '("monitorAdded", DisplayMonitorAddedSignalInfo), '("monitorRemoved", DisplayMonitorRemovedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("opened", DisplayOpenedSignalInfo), '("seatAdded", DisplaySeatAddedSignalInfo), '("seatRemoved", DisplaySeatRemovedSignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gdk_display_beep" gdk_display_beep ::
Ptr Display ->
IO ()
displayBeep ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m ()
displayBeep :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m ()
displayBeep a
display = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
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 Display -> IO ()
gdk_display_beep Ptr Display
display'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DisplayBeepMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayBeepMethodInfo a signature where
overloadedMethod = displayBeep
instance O.OverloadedMethodInfo DisplayBeepMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayBeep",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayBeep"
})
#endif
foreign import ccall "gdk_display_close" gdk_display_close ::
Ptr Display ->
IO ()
displayClose ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m ()
displayClose :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m ()
displayClose a
display = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
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 Display -> IO ()
gdk_display_close Ptr Display
display'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DisplayCloseMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayCloseMethodInfo a signature where
overloadedMethod = displayClose
instance O.OverloadedMethodInfo DisplayCloseMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayClose",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayClose"
})
#endif
foreign import ccall "gdk_display_device_is_grabbed" gdk_display_device_is_grabbed ::
Ptr Display ->
Ptr Gdk.Device.Device ->
IO CInt
displayDeviceIsGrabbed ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a, Gdk.Device.IsDevice b) =>
a
-> b
-> m Bool
displayDeviceIsGrabbed :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDisplay a, IsDevice b) =>
a -> b -> m Bool
displayDeviceIsGrabbed a
display b
device = IO Bool -> m Bool
forall a. IO a -> m a
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 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
CInt
result <- Ptr Display -> Ptr Device -> IO CInt
gdk_display_device_is_grabbed Ptr Display
display' 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
display
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
device
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DisplayDeviceIsGrabbedMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsDisplay a, Gdk.Device.IsDevice b) => O.OverloadedMethod DisplayDeviceIsGrabbedMethodInfo a signature where
overloadedMethod = displayDeviceIsGrabbed
instance O.OverloadedMethodInfo DisplayDeviceIsGrabbedMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayDeviceIsGrabbed",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayDeviceIsGrabbed"
})
#endif
foreign import ccall "gdk_display_flush" gdk_display_flush ::
Ptr Display ->
IO ()
displayFlush ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m ()
displayFlush :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m ()
displayFlush a
display = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
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 Display -> IO ()
gdk_display_flush Ptr Display
display'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DisplayFlushMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayFlushMethodInfo a signature where
overloadedMethod = displayFlush
instance O.OverloadedMethodInfo DisplayFlushMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayFlush",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayFlush"
})
#endif
foreign import ccall "gdk_display_get_app_launch_context" gdk_display_get_app_launch_context ::
Ptr Display ->
IO (Ptr Gdk.AppLaunchContext.AppLaunchContext)
displayGetAppLaunchContext ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m Gdk.AppLaunchContext.AppLaunchContext
displayGetAppLaunchContext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m AppLaunchContext
displayGetAppLaunchContext a
display = IO AppLaunchContext -> m AppLaunchContext
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AppLaunchContext -> m AppLaunchContext)
-> IO AppLaunchContext -> m AppLaunchContext
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 AppLaunchContext
result <- Ptr Display -> IO (Ptr AppLaunchContext)
gdk_display_get_app_launch_context Ptr Display
display'
Text -> Ptr AppLaunchContext -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"displayGetAppLaunchContext" Ptr AppLaunchContext
result
AppLaunchContext
result' <- ((ManagedPtr AppLaunchContext -> AppLaunchContext)
-> Ptr AppLaunchContext -> IO AppLaunchContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr AppLaunchContext -> AppLaunchContext
Gdk.AppLaunchContext.AppLaunchContext) Ptr AppLaunchContext
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
AppLaunchContext -> IO AppLaunchContext
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return AppLaunchContext
result'
#if defined(ENABLE_OVERLOADING)
data DisplayGetAppLaunchContextMethodInfo
instance (signature ~ (m Gdk.AppLaunchContext.AppLaunchContext), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayGetAppLaunchContextMethodInfo a signature where
overloadedMethod = displayGetAppLaunchContext
instance O.OverloadedMethodInfo DisplayGetAppLaunchContextMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayGetAppLaunchContext",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayGetAppLaunchContext"
})
#endif
foreign import ccall "gdk_display_get_default_cursor_size" gdk_display_get_default_cursor_size ::
Ptr Display ->
IO Word32
displayGetDefaultCursorSize ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m Word32
displayGetDefaultCursorSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Word32
displayGetDefaultCursorSize a
display = IO Word32 -> m Word32
forall a. IO a -> m a
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
$ do
Ptr Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
Word32
result <- Ptr Display -> IO Word32
gdk_display_get_default_cursor_size Ptr Display
display'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data DisplayGetDefaultCursorSizeMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayGetDefaultCursorSizeMethodInfo a signature where
overloadedMethod = displayGetDefaultCursorSize
instance O.OverloadedMethodInfo DisplayGetDefaultCursorSizeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayGetDefaultCursorSize",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayGetDefaultCursorSize"
})
#endif
foreign import ccall "gdk_display_get_default_group" gdk_display_get_default_group ::
Ptr Display ->
IO (Ptr Gdk.Window.Window)
displayGetDefaultGroup ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m Gdk.Window.Window
displayGetDefaultGroup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Window
displayGetDefaultGroup a
display = IO Window -> m Window
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Window -> m Window) -> IO Window -> m Window
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 Window
result <- Ptr Display -> IO (Ptr Window)
gdk_display_get_default_group Ptr Display
display'
Text -> Ptr Window -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"displayGetDefaultGroup" Ptr Window
result
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
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
Window -> IO Window
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Window
result'
#if defined(ENABLE_OVERLOADING)
data DisplayGetDefaultGroupMethodInfo
instance (signature ~ (m Gdk.Window.Window), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayGetDefaultGroupMethodInfo a signature where
overloadedMethod = displayGetDefaultGroup
instance O.OverloadedMethodInfo DisplayGetDefaultGroupMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayGetDefaultGroup",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayGetDefaultGroup"
})
#endif
foreign import ccall "gdk_display_get_default_screen" gdk_display_get_default_screen ::
Ptr Display ->
IO (Ptr Gdk.Screen.Screen)
displayGetDefaultScreen ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m Gdk.Screen.Screen
displayGetDefaultScreen :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Screen
displayGetDefaultScreen a
display = IO Screen -> m Screen
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Screen -> m Screen) -> IO Screen -> m Screen
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 Screen
result <- Ptr Display -> IO (Ptr Screen)
gdk_display_get_default_screen Ptr Display
display'
Text -> Ptr Screen -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"displayGetDefaultScreen" Ptr Screen
result
Screen
result' <- ((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
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
Screen -> IO Screen
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Screen
result'
#if defined(ENABLE_OVERLOADING)
data DisplayGetDefaultScreenMethodInfo
instance (signature ~ (m Gdk.Screen.Screen), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayGetDefaultScreenMethodInfo a signature where
overloadedMethod = displayGetDefaultScreen
instance O.OverloadedMethodInfo DisplayGetDefaultScreenMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayGetDefaultScreen",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayGetDefaultScreen"
})
#endif
foreign import ccall "gdk_display_get_default_seat" gdk_display_get_default_seat ::
Ptr Display ->
IO (Ptr Gdk.Seat.Seat)
displayGetDefaultSeat ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m Gdk.Seat.Seat
displayGetDefaultSeat :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Seat
displayGetDefaultSeat a
display = IO Seat -> m Seat
forall a. IO a -> m a
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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
Ptr Seat
result <- Ptr Display -> IO (Ptr Seat)
gdk_display_get_default_seat Ptr Display
display'
Text -> Ptr Seat -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"displayGetDefaultSeat" 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
display
Seat -> IO Seat
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Seat
result'
#if defined(ENABLE_OVERLOADING)
data DisplayGetDefaultSeatMethodInfo
instance (signature ~ (m Gdk.Seat.Seat), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayGetDefaultSeatMethodInfo a signature where
overloadedMethod = displayGetDefaultSeat
instance O.OverloadedMethodInfo DisplayGetDefaultSeatMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayGetDefaultSeat",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayGetDefaultSeat"
})
#endif
foreign import ccall "gdk_display_get_device_manager" gdk_display_get_device_manager ::
Ptr Display ->
IO (Ptr Gdk.DeviceManager.DeviceManager)
{-# DEPRECATED displayGetDeviceManager ["(Since version 3.20.)","Use 'GI.Gdk.Objects.Display.displayGetDefaultSeat' and t'GI.Gdk.Objects.Seat.Seat' operations."] #-}
displayGetDeviceManager ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m (Maybe Gdk.DeviceManager.DeviceManager)
displayGetDeviceManager :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m (Maybe DeviceManager)
displayGetDeviceManager a
display = IO (Maybe DeviceManager) -> m (Maybe DeviceManager)
forall a. IO a -> m a
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
$ do
Ptr Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
Ptr DeviceManager
result <- Ptr Display -> IO (Ptr DeviceManager)
gdk_display_get_device_manager Ptr Display
display'
Maybe DeviceManager
maybeResult <- Ptr DeviceManager
-> (Ptr DeviceManager -> IO DeviceManager)
-> IO (Maybe DeviceManager)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr DeviceManager
result ((Ptr DeviceManager -> IO DeviceManager)
-> IO (Maybe DeviceManager))
-> (Ptr DeviceManager -> IO DeviceManager)
-> IO (Maybe DeviceManager)
forall a b. (a -> b) -> a -> b
$ \Ptr DeviceManager
result' -> do
DeviceManager
result'' <- ((ManagedPtr DeviceManager -> DeviceManager)
-> Ptr DeviceManager -> IO DeviceManager
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DeviceManager -> DeviceManager
Gdk.DeviceManager.DeviceManager) Ptr DeviceManager
result'
DeviceManager -> IO DeviceManager
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return DeviceManager
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
Maybe DeviceManager -> IO (Maybe DeviceManager)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DeviceManager
maybeResult
#if defined(ENABLE_OVERLOADING)
data DisplayGetDeviceManagerMethodInfo
instance (signature ~ (m (Maybe Gdk.DeviceManager.DeviceManager)), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayGetDeviceManagerMethodInfo a signature where
overloadedMethod = displayGetDeviceManager
instance O.OverloadedMethodInfo DisplayGetDeviceManagerMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayGetDeviceManager",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayGetDeviceManager"
})
#endif
foreign import ccall "gdk_display_get_event" gdk_display_get_event ::
Ptr Display ->
IO (Ptr Gdk.Event.Event)
displayGetEvent ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m (Maybe Gdk.Event.Event)
displayGetEvent :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m (Maybe Event)
displayGetEvent a
display = IO (Maybe Event) -> m (Maybe Event)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Event) -> m (Maybe Event))
-> IO (Maybe Event) -> m (Maybe Event)
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 Event
result <- Ptr Display -> IO (Ptr Event)
gdk_display_get_event Ptr Display
display'
Maybe Event
maybeResult <- Ptr Event -> (Ptr Event -> IO Event) -> IO (Maybe Event)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Event
result ((Ptr Event -> IO Event) -> IO (Maybe Event))
-> (Ptr Event -> IO Event) -> IO (Maybe Event)
forall a b. (a -> b) -> a -> b
$ \Ptr Event
result' -> do
Event
result'' <- ((ManagedPtr Event -> Event) -> Ptr Event -> IO Event
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Event -> Event
Gdk.Event.Event) Ptr Event
result'
Event -> IO Event
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Event
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
Maybe Event -> IO (Maybe Event)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Event
maybeResult
#if defined(ENABLE_OVERLOADING)
data DisplayGetEventMethodInfo
instance (signature ~ (m (Maybe Gdk.Event.Event)), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayGetEventMethodInfo a signature where
overloadedMethod = displayGetEvent
instance O.OverloadedMethodInfo DisplayGetEventMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayGetEvent",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayGetEvent"
})
#endif
foreign import ccall "gdk_display_get_maximal_cursor_size" gdk_display_get_maximal_cursor_size ::
Ptr Display ->
Ptr Word32 ->
Ptr Word32 ->
IO ()
displayGetMaximalCursorSize ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m ((Word32, Word32))
displayGetMaximalCursorSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m (Word32, Word32)
displayGetMaximalCursorSize a
display = IO (Word32, Word32) -> m (Word32, Word32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Word32, Word32) -> m (Word32, Word32))
-> IO (Word32, Word32) -> m (Word32, Word32)
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 Word32
width <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
Ptr Word32
height <- IO (Ptr Word32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word32)
Ptr Display -> Ptr Word32 -> Ptr Word32 -> IO ()
gdk_display_get_maximal_cursor_size Ptr Display
display' Ptr Word32
width Ptr Word32
height
Word32
width' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
width
Word32
height' <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek Ptr Word32
height
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
width
Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word32
height
(Word32, Word32) -> IO (Word32, Word32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Word32
width', Word32
height')
#if defined(ENABLE_OVERLOADING)
data DisplayGetMaximalCursorSizeMethodInfo
instance (signature ~ (m ((Word32, Word32))), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayGetMaximalCursorSizeMethodInfo a signature where
overloadedMethod = displayGetMaximalCursorSize
instance O.OverloadedMethodInfo DisplayGetMaximalCursorSizeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayGetMaximalCursorSize",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayGetMaximalCursorSize"
})
#endif
foreign import ccall "gdk_display_get_monitor" gdk_display_get_monitor ::
Ptr Display ->
Int32 ->
IO (Ptr Gdk.Monitor.Monitor)
displayGetMonitor ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> Int32
-> m (Maybe Gdk.Monitor.Monitor)
displayGetMonitor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> Int32 -> m (Maybe Monitor)
displayGetMonitor a
display Int32
monitorNum = IO (Maybe Monitor) -> m (Maybe Monitor)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Monitor) -> m (Maybe Monitor))
-> IO (Maybe Monitor) -> m (Maybe Monitor)
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 Monitor
result <- Ptr Display -> Int32 -> IO (Ptr Monitor)
gdk_display_get_monitor Ptr Display
display' Int32
monitorNum
Maybe Monitor
maybeResult <- Ptr Monitor -> (Ptr Monitor -> IO Monitor) -> IO (Maybe Monitor)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Monitor
result ((Ptr Monitor -> IO Monitor) -> IO (Maybe Monitor))
-> (Ptr Monitor -> IO Monitor) -> IO (Maybe Monitor)
forall a b. (a -> b) -> a -> b
$ \Ptr Monitor
result' -> do
Monitor
result'' <- ((ManagedPtr Monitor -> Monitor) -> Ptr Monitor -> IO Monitor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Monitor -> Monitor
Gdk.Monitor.Monitor) Ptr Monitor
result'
Monitor -> IO Monitor
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Monitor
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
Maybe Monitor -> IO (Maybe Monitor)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Monitor
maybeResult
#if defined(ENABLE_OVERLOADING)
data DisplayGetMonitorMethodInfo
instance (signature ~ (Int32 -> m (Maybe Gdk.Monitor.Monitor)), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayGetMonitorMethodInfo a signature where
overloadedMethod = displayGetMonitor
instance O.OverloadedMethodInfo DisplayGetMonitorMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayGetMonitor",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayGetMonitor"
})
#endif
foreign import ccall "gdk_display_get_monitor_at_point" gdk_display_get_monitor_at_point ::
Ptr Display ->
Int32 ->
Int32 ->
IO (Ptr Gdk.Monitor.Monitor)
displayGetMonitorAtPoint ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> Int32
-> Int32
-> m Gdk.Monitor.Monitor
displayGetMonitorAtPoint :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> Int32 -> Int32 -> m Monitor
displayGetMonitorAtPoint a
display Int32
x Int32
y = IO Monitor -> m Monitor
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Monitor -> m Monitor) -> IO Monitor -> m Monitor
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 Monitor
result <- Ptr Display -> Int32 -> Int32 -> IO (Ptr Monitor)
gdk_display_get_monitor_at_point Ptr Display
display' Int32
x Int32
y
Text -> Ptr Monitor -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"displayGetMonitorAtPoint" Ptr Monitor
result
Monitor
result' <- ((ManagedPtr Monitor -> Monitor) -> Ptr Monitor -> IO Monitor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Monitor -> Monitor
Gdk.Monitor.Monitor) Ptr Monitor
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
Monitor -> IO Monitor
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Monitor
result'
#if defined(ENABLE_OVERLOADING)
data DisplayGetMonitorAtPointMethodInfo
instance (signature ~ (Int32 -> Int32 -> m Gdk.Monitor.Monitor), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayGetMonitorAtPointMethodInfo a signature where
overloadedMethod = displayGetMonitorAtPoint
instance O.OverloadedMethodInfo DisplayGetMonitorAtPointMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayGetMonitorAtPoint",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayGetMonitorAtPoint"
})
#endif
foreign import ccall "gdk_display_get_monitor_at_window" gdk_display_get_monitor_at_window ::
Ptr Display ->
Ptr Gdk.Window.Window ->
IO (Ptr Gdk.Monitor.Monitor)
displayGetMonitorAtWindow ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a, Gdk.Window.IsWindow b) =>
a
-> b
-> m Gdk.Monitor.Monitor
displayGetMonitorAtWindow :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDisplay a, IsWindow b) =>
a -> b -> m Monitor
displayGetMonitorAtWindow a
display b
window = IO Monitor -> m Monitor
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Monitor -> m Monitor) -> IO Monitor -> m Monitor
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 Window
window' <- b -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
window
Ptr Monitor
result <- Ptr Display -> Ptr Window -> IO (Ptr Monitor)
gdk_display_get_monitor_at_window Ptr Display
display' Ptr Window
window'
Text -> Ptr Monitor -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"displayGetMonitorAtWindow" Ptr Monitor
result
Monitor
result' <- ((ManagedPtr Monitor -> Monitor) -> Ptr Monitor -> IO Monitor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Monitor -> Monitor
Gdk.Monitor.Monitor) Ptr Monitor
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
window
Monitor -> IO Monitor
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Monitor
result'
#if defined(ENABLE_OVERLOADING)
data DisplayGetMonitorAtWindowMethodInfo
instance (signature ~ (b -> m Gdk.Monitor.Monitor), MonadIO m, IsDisplay a, Gdk.Window.IsWindow b) => O.OverloadedMethod DisplayGetMonitorAtWindowMethodInfo a signature where
overloadedMethod = displayGetMonitorAtWindow
instance O.OverloadedMethodInfo DisplayGetMonitorAtWindowMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayGetMonitorAtWindow",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayGetMonitorAtWindow"
})
#endif
foreign import ccall "gdk_display_get_n_monitors" gdk_display_get_n_monitors ::
Ptr Display ->
IO Int32
displayGetNMonitors ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m Int32
displayGetNMonitors :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Int32
displayGetNMonitors a
display = IO Int32 -> m Int32
forall a. IO a -> m a
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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
Int32
result <- Ptr Display -> IO Int32
gdk_display_get_n_monitors Ptr Display
display'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data DisplayGetNMonitorsMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayGetNMonitorsMethodInfo a signature where
overloadedMethod = displayGetNMonitors
instance O.OverloadedMethodInfo DisplayGetNMonitorsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayGetNMonitors",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayGetNMonitors"
})
#endif
foreign import ccall "gdk_display_get_n_screens" gdk_display_get_n_screens ::
Ptr Display ->
IO Int32
{-# DEPRECATED displayGetNScreens ["(Since version 3.10)","The number of screens is always 1."] #-}
displayGetNScreens ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m Int32
displayGetNScreens :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Int32
displayGetNScreens a
display = IO Int32 -> m Int32
forall a. IO a -> m a
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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
Int32
result <- Ptr Display -> IO Int32
gdk_display_get_n_screens Ptr Display
display'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data DisplayGetNScreensMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayGetNScreensMethodInfo a signature where
overloadedMethod = displayGetNScreens
instance O.OverloadedMethodInfo DisplayGetNScreensMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayGetNScreens",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayGetNScreens"
})
#endif
foreign import ccall "gdk_display_get_name" gdk_display_get_name ::
Ptr Display ->
IO CString
displayGetName ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m T.Text
displayGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Text
displayGetName a
display = IO Text -> m Text
forall a. IO a -> m a
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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
CString
result <- Ptr Display -> IO CString
gdk_display_get_name Ptr Display
display'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"displayGetName" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data DisplayGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayGetNameMethodInfo a signature where
overloadedMethod = displayGetName
instance O.OverloadedMethodInfo DisplayGetNameMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayGetName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayGetName"
})
#endif
foreign import ccall "gdk_display_get_pointer" gdk_display_get_pointer ::
Ptr Display ->
Ptr (Ptr Gdk.Screen.Screen) ->
Ptr Int32 ->
Ptr Int32 ->
Ptr CUInt ->
IO ()
{-# DEPRECATED displayGetPointer ["(Since version 3.0)","Use 'GI.Gdk.Objects.Device.deviceGetPosition' instead."] #-}
displayGetPointer ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m ((Gdk.Screen.Screen, Int32, Int32, [Gdk.Flags.ModifierType]))
displayGetPointer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m (Screen, Int32, Int32, [ModifierType])
displayGetPointer a
display = IO (Screen, Int32, Int32, [ModifierType])
-> m (Screen, Int32, Int32, [ModifierType])
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Screen, Int32, Int32, [ModifierType])
-> m (Screen, Int32, Int32, [ModifierType]))
-> IO (Screen, Int32, Int32, [ModifierType])
-> m (Screen, Int32, Int32, [ModifierType])
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 (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 CUInt
mask <- IO (Ptr CUInt)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CUInt)
Ptr Display
-> Ptr (Ptr Screen) -> Ptr Int32 -> Ptr Int32 -> Ptr CUInt -> IO ()
gdk_display_get_pointer Ptr Display
display' Ptr (Ptr Screen)
screen Ptr Int32
x Ptr Int32
y Ptr CUInt
mask
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
CUInt
mask' <- Ptr CUInt -> IO CUInt
forall a. Storable a => Ptr a -> IO a
peek Ptr CUInt
mask
let mask'' :: [ModifierType]
mask'' = CUInt -> [ModifierType]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
mask'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
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
Ptr CUInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CUInt
mask
(Screen, Int32, Int32, [ModifierType])
-> IO (Screen, Int32, Int32, [ModifierType])
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Screen
screen'', Int32
x', Int32
y', [ModifierType]
mask'')
#if defined(ENABLE_OVERLOADING)
data DisplayGetPointerMethodInfo
instance (signature ~ (m ((Gdk.Screen.Screen, Int32, Int32, [Gdk.Flags.ModifierType]))), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayGetPointerMethodInfo a signature where
overloadedMethod = displayGetPointer
instance O.OverloadedMethodInfo DisplayGetPointerMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayGetPointer",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayGetPointer"
})
#endif
foreign import ccall "gdk_display_get_primary_monitor" gdk_display_get_primary_monitor ::
Ptr Display ->
IO (Ptr Gdk.Monitor.Monitor)
displayGetPrimaryMonitor ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m (Maybe Gdk.Monitor.Monitor)
displayGetPrimaryMonitor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m (Maybe Monitor)
displayGetPrimaryMonitor a
display = IO (Maybe Monitor) -> m (Maybe Monitor)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Monitor) -> m (Maybe Monitor))
-> IO (Maybe Monitor) -> m (Maybe Monitor)
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 Monitor
result <- Ptr Display -> IO (Ptr Monitor)
gdk_display_get_primary_monitor Ptr Display
display'
Maybe Monitor
maybeResult <- Ptr Monitor -> (Ptr Monitor -> IO Monitor) -> IO (Maybe Monitor)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Monitor
result ((Ptr Monitor -> IO Monitor) -> IO (Maybe Monitor))
-> (Ptr Monitor -> IO Monitor) -> IO (Maybe Monitor)
forall a b. (a -> b) -> a -> b
$ \Ptr Monitor
result' -> do
Monitor
result'' <- ((ManagedPtr Monitor -> Monitor) -> Ptr Monitor -> IO Monitor
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Monitor -> Monitor
Gdk.Monitor.Monitor) Ptr Monitor
result'
Monitor -> IO Monitor
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Monitor
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
Maybe Monitor -> IO (Maybe Monitor)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Monitor
maybeResult
#if defined(ENABLE_OVERLOADING)
data DisplayGetPrimaryMonitorMethodInfo
instance (signature ~ (m (Maybe Gdk.Monitor.Monitor)), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayGetPrimaryMonitorMethodInfo a signature where
overloadedMethod = displayGetPrimaryMonitor
instance O.OverloadedMethodInfo DisplayGetPrimaryMonitorMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayGetPrimaryMonitor",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayGetPrimaryMonitor"
})
#endif
foreign import ccall "gdk_display_get_screen" gdk_display_get_screen ::
Ptr Display ->
Int32 ->
IO (Ptr Gdk.Screen.Screen)
{-# DEPRECATED displayGetScreen ["(Since version 3.20)","There is only one screen; use 'GI.Gdk.Objects.Display.displayGetDefaultScreen' to get it."] #-}
displayGetScreen ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> Int32
-> m Gdk.Screen.Screen
displayGetScreen :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> Int32 -> m Screen
displayGetScreen a
display Int32
screenNum = IO Screen -> m Screen
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Screen -> m Screen) -> IO Screen -> m Screen
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 Screen
result <- Ptr Display -> Int32 -> IO (Ptr Screen)
gdk_display_get_screen Ptr Display
display' Int32
screenNum
Text -> Ptr Screen -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"displayGetScreen" Ptr Screen
result
Screen
result' <- ((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
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
Screen -> IO Screen
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Screen
result'
#if defined(ENABLE_OVERLOADING)
data DisplayGetScreenMethodInfo
instance (signature ~ (Int32 -> m Gdk.Screen.Screen), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayGetScreenMethodInfo a signature where
overloadedMethod = displayGetScreen
instance O.OverloadedMethodInfo DisplayGetScreenMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayGetScreen",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayGetScreen"
})
#endif
foreign import ccall "gdk_display_get_window_at_pointer" gdk_display_get_window_at_pointer ::
Ptr Display ->
Ptr Int32 ->
Ptr Int32 ->
IO (Ptr Gdk.Window.Window)
{-# DEPRECATED displayGetWindowAtPointer ["(Since version 3.0)","Use 'GI.Gdk.Objects.Device.deviceGetWindowAtPosition' instead."] #-}
displayGetWindowAtPointer ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m ((Maybe Gdk.Window.Window, Int32, Int32))
displayGetWindowAtPointer :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m (Maybe Window, Int32, Int32)
displayGetWindowAtPointer a
display = IO (Maybe Window, Int32, Int32) -> m (Maybe Window, Int32, Int32)
forall a. IO a -> m a
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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
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 Display -> Ptr Int32 -> Ptr Int32 -> IO (Ptr Window)
gdk_display_get_window_at_pointer Ptr Display
display' 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 a. a -> IO a
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
display
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Window
maybeResult, Int32
winX', Int32
winY')
#if defined(ENABLE_OVERLOADING)
data DisplayGetWindowAtPointerMethodInfo
instance (signature ~ (m ((Maybe Gdk.Window.Window, Int32, Int32))), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayGetWindowAtPointerMethodInfo a signature where
overloadedMethod = displayGetWindowAtPointer
instance O.OverloadedMethodInfo DisplayGetWindowAtPointerMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayGetWindowAtPointer",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayGetWindowAtPointer"
})
#endif
foreign import ccall "gdk_display_has_pending" gdk_display_has_pending ::
Ptr Display ->
IO CInt
displayHasPending ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m Bool
displayHasPending :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Bool
displayHasPending a
display = IO Bool -> m Bool
forall a. IO a -> m a
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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
CInt
result <- Ptr Display -> IO CInt
gdk_display_has_pending Ptr Display
display'
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
display
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DisplayHasPendingMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayHasPendingMethodInfo a signature where
overloadedMethod = displayHasPending
instance O.OverloadedMethodInfo DisplayHasPendingMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayHasPending",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayHasPending"
})
#endif
foreign import ccall "gdk_display_is_closed" gdk_display_is_closed ::
Ptr Display ->
IO CInt
displayIsClosed ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m Bool
displayIsClosed :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Bool
displayIsClosed a
display = IO Bool -> m Bool
forall a. IO a -> m a
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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
CInt
result <- Ptr Display -> IO CInt
gdk_display_is_closed Ptr Display
display'
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
display
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DisplayIsClosedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayIsClosedMethodInfo a signature where
overloadedMethod = displayIsClosed
instance O.OverloadedMethodInfo DisplayIsClosedMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayIsClosed",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayIsClosed"
})
#endif
foreign import ccall "gdk_display_keyboard_ungrab" gdk_display_keyboard_ungrab ::
Ptr Display ->
Word32 ->
IO ()
{-# DEPRECATED displayKeyboardUngrab ["(Since version 3.0)","Use 'GI.Gdk.Objects.Device.deviceUngrab', together with 'GI.Gdk.Objects.Device.deviceGrab'"," instead."] #-}
displayKeyboardUngrab ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> Word32
-> m ()
displayKeyboardUngrab :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> Word32 -> m ()
displayKeyboardUngrab a
display Word32
time_ = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
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 Display -> Word32 -> IO ()
gdk_display_keyboard_ungrab Ptr Display
display' Word32
time_
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DisplayKeyboardUngrabMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayKeyboardUngrabMethodInfo a signature where
overloadedMethod = displayKeyboardUngrab
instance O.OverloadedMethodInfo DisplayKeyboardUngrabMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayKeyboardUngrab",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayKeyboardUngrab"
})
#endif
foreign import ccall "gdk_display_list_devices" gdk_display_list_devices ::
Ptr Display ->
IO (Ptr (GList (Ptr Gdk.Device.Device)))
{-# DEPRECATED displayListDevices ["(Since version 3.0)","Use 'GI.Gdk.Objects.DeviceManager.deviceManagerListDevices' instead."] #-}
displayListDevices ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m [Gdk.Device.Device]
displayListDevices :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m [Device]
displayListDevices a
display = 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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
Ptr (GList (Ptr Device))
result <- Ptr Display -> IO (Ptr (GList (Ptr Device)))
gdk_display_list_devices Ptr Display
display'
[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'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
[Device] -> IO [Device]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Device]
result''
#if defined(ENABLE_OVERLOADING)
data DisplayListDevicesMethodInfo
instance (signature ~ (m [Gdk.Device.Device]), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayListDevicesMethodInfo a signature where
overloadedMethod = displayListDevices
instance O.OverloadedMethodInfo DisplayListDevicesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayListDevices",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayListDevices"
})
#endif
foreign import ccall "gdk_display_list_seats" gdk_display_list_seats ::
Ptr Display ->
IO (Ptr (GList (Ptr Gdk.Seat.Seat)))
displayListSeats ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m [Gdk.Seat.Seat]
displayListSeats :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m [Seat]
displayListSeats a
display = IO [Seat] -> m [Seat]
forall a. IO a -> m a
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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
Ptr (GList (Ptr Seat))
result <- Ptr Display -> IO (Ptr (GList (Ptr Seat)))
gdk_display_list_seats Ptr Display
display'
[Ptr Seat]
result' <- Ptr (GList (Ptr Seat)) -> IO [Ptr Seat]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr Seat))
result
[Seat]
result'' <- (Ptr Seat -> IO Seat) -> [Ptr Seat] -> IO [Seat]
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 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'
Ptr (GList (Ptr Seat)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr Seat))
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
[Seat] -> IO [Seat]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Seat]
result''
#if defined(ENABLE_OVERLOADING)
data DisplayListSeatsMethodInfo
instance (signature ~ (m [Gdk.Seat.Seat]), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayListSeatsMethodInfo a signature where
overloadedMethod = displayListSeats
instance O.OverloadedMethodInfo DisplayListSeatsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayListSeats",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayListSeats"
})
#endif
foreign import ccall "gdk_display_notify_startup_complete" gdk_display_notify_startup_complete ::
Ptr Display ->
CString ->
IO ()
displayNotifyStartupComplete ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> T.Text
-> m ()
displayNotifyStartupComplete :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> Text -> m ()
displayNotifyStartupComplete a
display Text
startupId = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
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
CString
startupId' <- Text -> IO CString
textToCString Text
startupId
Ptr Display -> CString -> IO ()
gdk_display_notify_startup_complete Ptr Display
display' CString
startupId'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
startupId'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DisplayNotifyStartupCompleteMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayNotifyStartupCompleteMethodInfo a signature where
overloadedMethod = displayNotifyStartupComplete
instance O.OverloadedMethodInfo DisplayNotifyStartupCompleteMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayNotifyStartupComplete",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayNotifyStartupComplete"
})
#endif
foreign import ccall "gdk_display_peek_event" gdk_display_peek_event ::
Ptr Display ->
IO (Ptr Gdk.Event.Event)
displayPeekEvent ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m (Maybe Gdk.Event.Event)
displayPeekEvent :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m (Maybe Event)
displayPeekEvent a
display = IO (Maybe Event) -> m (Maybe Event)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Event) -> m (Maybe Event))
-> IO (Maybe Event) -> m (Maybe Event)
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 Event
result <- Ptr Display -> IO (Ptr Event)
gdk_display_peek_event Ptr Display
display'
Maybe Event
maybeResult <- Ptr Event -> (Ptr Event -> IO Event) -> IO (Maybe Event)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Event
result ((Ptr Event -> IO Event) -> IO (Maybe Event))
-> (Ptr Event -> IO Event) -> IO (Maybe Event)
forall a b. (a -> b) -> a -> b
$ \Ptr Event
result' -> do
Event
result'' <- ((ManagedPtr Event -> Event) -> Ptr Event -> IO Event
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Event -> Event
Gdk.Event.Event) Ptr Event
result'
Event -> IO Event
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Event
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
Maybe Event -> IO (Maybe Event)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Event
maybeResult
#if defined(ENABLE_OVERLOADING)
data DisplayPeekEventMethodInfo
instance (signature ~ (m (Maybe Gdk.Event.Event)), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayPeekEventMethodInfo a signature where
overloadedMethod = displayPeekEvent
instance O.OverloadedMethodInfo DisplayPeekEventMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayPeekEvent",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayPeekEvent"
})
#endif
foreign import ccall "gdk_display_pointer_is_grabbed" gdk_display_pointer_is_grabbed ::
Ptr Display ->
IO CInt
{-# DEPRECATED displayPointerIsGrabbed ["(Since version 3.0)","Use 'GI.Gdk.Objects.Display.displayDeviceIsGrabbed' instead."] #-}
displayPointerIsGrabbed ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m Bool
displayPointerIsGrabbed :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Bool
displayPointerIsGrabbed a
display = IO Bool -> m Bool
forall a. IO a -> m a
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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
CInt
result <- Ptr Display -> IO CInt
gdk_display_pointer_is_grabbed Ptr Display
display'
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
display
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DisplayPointerIsGrabbedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayPointerIsGrabbedMethodInfo a signature where
overloadedMethod = displayPointerIsGrabbed
instance O.OverloadedMethodInfo DisplayPointerIsGrabbedMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayPointerIsGrabbed",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayPointerIsGrabbed"
})
#endif
foreign import ccall "gdk_display_pointer_ungrab" gdk_display_pointer_ungrab ::
Ptr Display ->
Word32 ->
IO ()
{-# DEPRECATED displayPointerUngrab ["(Since version 3.0)","Use 'GI.Gdk.Objects.Device.deviceUngrab', together with 'GI.Gdk.Objects.Device.deviceGrab'"," instead."] #-}
displayPointerUngrab ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> Word32
-> m ()
displayPointerUngrab :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> Word32 -> m ()
displayPointerUngrab a
display Word32
time_ = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
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 Display -> Word32 -> IO ()
gdk_display_pointer_ungrab Ptr Display
display' Word32
time_
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DisplayPointerUngrabMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayPointerUngrabMethodInfo a signature where
overloadedMethod = displayPointerUngrab
instance O.OverloadedMethodInfo DisplayPointerUngrabMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayPointerUngrab",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayPointerUngrab"
})
#endif
foreign import ccall "gdk_display_put_event" gdk_display_put_event ::
Ptr Display ->
Ptr Gdk.Event.Event ->
IO ()
displayPutEvent ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> Gdk.Event.Event
-> m ()
displayPutEvent :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> Event -> m ()
displayPutEvent a
display Event
event = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
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 Event
event' <- Event -> IO (Ptr Event)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Event
event
Ptr Display -> Ptr Event -> IO ()
gdk_display_put_event Ptr Display
display' Ptr Event
event'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
Event -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Event
event
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DisplayPutEventMethodInfo
instance (signature ~ (Gdk.Event.Event -> m ()), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayPutEventMethodInfo a signature where
overloadedMethod = displayPutEvent
instance O.OverloadedMethodInfo DisplayPutEventMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayPutEvent",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayPutEvent"
})
#endif
foreign import ccall "gdk_display_request_selection_notification" gdk_display_request_selection_notification ::
Ptr Display ->
Ptr Gdk.Atom.Atom ->
IO CInt
displayRequestSelectionNotification ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> Gdk.Atom.Atom
-> m Bool
displayRequestSelectionNotification :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> Atom -> m Bool
displayRequestSelectionNotification a
display Atom
selection = IO Bool -> m Bool
forall a. IO a -> m a
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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
Ptr Atom
selection' <- Atom -> IO (Ptr Atom)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Atom
selection
CInt
result <- Ptr Display -> Ptr Atom -> IO CInt
gdk_display_request_selection_notification Ptr Display
display' Ptr Atom
selection'
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
display
Atom -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Atom
selection
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DisplayRequestSelectionNotificationMethodInfo
instance (signature ~ (Gdk.Atom.Atom -> m Bool), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplayRequestSelectionNotificationMethodInfo a signature where
overloadedMethod = displayRequestSelectionNotification
instance O.OverloadedMethodInfo DisplayRequestSelectionNotificationMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayRequestSelectionNotification",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayRequestSelectionNotification"
})
#endif
foreign import ccall "gdk_display_set_double_click_distance" gdk_display_set_double_click_distance ::
Ptr Display ->
Word32 ->
IO ()
displaySetDoubleClickDistance ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> Word32
-> m ()
displaySetDoubleClickDistance :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> Word32 -> m ()
displaySetDoubleClickDistance a
display Word32
distance = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
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 Display -> Word32 -> IO ()
gdk_display_set_double_click_distance Ptr Display
display' Word32
distance
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DisplaySetDoubleClickDistanceMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplaySetDoubleClickDistanceMethodInfo a signature where
overloadedMethod = displaySetDoubleClickDistance
instance O.OverloadedMethodInfo DisplaySetDoubleClickDistanceMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displaySetDoubleClickDistance",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displaySetDoubleClickDistance"
})
#endif
foreign import ccall "gdk_display_set_double_click_time" gdk_display_set_double_click_time ::
Ptr Display ->
Word32 ->
IO ()
displaySetDoubleClickTime ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> Word32
-> m ()
displaySetDoubleClickTime :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> Word32 -> m ()
displaySetDoubleClickTime a
display Word32
msec = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
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 Display -> Word32 -> IO ()
gdk_display_set_double_click_time Ptr Display
display' Word32
msec
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DisplaySetDoubleClickTimeMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplaySetDoubleClickTimeMethodInfo a signature where
overloadedMethod = displaySetDoubleClickTime
instance O.OverloadedMethodInfo DisplaySetDoubleClickTimeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displaySetDoubleClickTime",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displaySetDoubleClickTime"
})
#endif
foreign import ccall "gdk_display_store_clipboard" gdk_display_store_clipboard ::
Ptr Display ->
Ptr Gdk.Window.Window ->
Word32 ->
Ptr (Ptr Gdk.Atom.Atom) ->
Int32 ->
IO ()
displayStoreClipboard ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a, Gdk.Window.IsWindow b) =>
a
-> b
-> Word32
-> Maybe ([Gdk.Atom.Atom])
-> m ()
displayStoreClipboard :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDisplay a, IsWindow b) =>
a -> b -> Word32 -> Maybe [Atom] -> m ()
displayStoreClipboard a
display b
clipboardWindow Word32
time_ Maybe [Atom]
targets = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
let nTargets :: Int32
nTargets = case Maybe [Atom]
targets of
Maybe [Atom]
Nothing -> Int32
0
Just [Atom]
jTargets -> Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [Atom] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Atom]
jTargets
Ptr Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
Ptr Window
clipboardWindow' <- b -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
clipboardWindow
Ptr (Ptr Atom)
maybeTargets <- case Maybe [Atom]
targets of
Maybe [Atom]
Nothing -> Ptr (Ptr Atom) -> IO (Ptr (Ptr Atom))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr Atom)
forall a. Ptr a
nullPtr
Just [Atom]
jTargets -> do
[Ptr Atom]
jTargets' <- (Atom -> IO (Ptr Atom)) -> [Atom] -> IO [Ptr Atom]
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 Atom -> IO (Ptr Atom)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [Atom]
jTargets
Ptr (Ptr Atom)
jTargets'' <- [Ptr Atom] -> IO (Ptr (Ptr Atom))
forall a. [Ptr a] -> IO (Ptr (Ptr a))
packPtrArray [Ptr Atom]
jTargets'
Ptr (Ptr Atom) -> IO (Ptr (Ptr Atom))
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr (Ptr Atom)
jTargets''
Ptr Display
-> Ptr Window -> Word32 -> Ptr (Ptr Atom) -> Int32 -> IO ()
gdk_display_store_clipboard Ptr Display
display' Ptr Window
clipboardWindow' Word32
time_ Ptr (Ptr Atom)
maybeTargets Int32
nTargets
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
clipboardWindow
Maybe [Atom] -> ([Atom] -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe [Atom]
targets ((Atom -> IO ()) -> [Atom] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Atom -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr)
Ptr (Ptr Atom) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Atom)
maybeTargets
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DisplayStoreClipboardMethodInfo
instance (signature ~ (b -> Word32 -> Maybe ([Gdk.Atom.Atom]) -> m ()), MonadIO m, IsDisplay a, Gdk.Window.IsWindow b) => O.OverloadedMethod DisplayStoreClipboardMethodInfo a signature where
overloadedMethod = displayStoreClipboard
instance O.OverloadedMethodInfo DisplayStoreClipboardMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayStoreClipboard",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayStoreClipboard"
})
#endif
foreign import ccall "gdk_display_supports_clipboard_persistence" gdk_display_supports_clipboard_persistence ::
Ptr Display ->
IO CInt
displaySupportsClipboardPersistence ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m Bool
displaySupportsClipboardPersistence :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Bool
displaySupportsClipboardPersistence a
display = IO Bool -> m Bool
forall a. IO a -> m a
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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
CInt
result <- Ptr Display -> IO CInt
gdk_display_supports_clipboard_persistence Ptr Display
display'
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
display
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DisplaySupportsClipboardPersistenceMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplaySupportsClipboardPersistenceMethodInfo a signature where
overloadedMethod = displaySupportsClipboardPersistence
instance O.OverloadedMethodInfo DisplaySupportsClipboardPersistenceMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displaySupportsClipboardPersistence",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displaySupportsClipboardPersistence"
})
#endif
foreign import ccall "gdk_display_supports_composite" gdk_display_supports_composite ::
Ptr Display ->
IO CInt
{-# DEPRECATED displaySupportsComposite ["(Since version 3.16)","Compositing is an outdated technology that"," only ever worked on X11."] #-}
displaySupportsComposite ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m Bool
displaySupportsComposite :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Bool
displaySupportsComposite a
display = IO Bool -> m Bool
forall a. IO a -> m a
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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
CInt
result <- Ptr Display -> IO CInt
gdk_display_supports_composite Ptr Display
display'
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
display
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DisplaySupportsCompositeMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplaySupportsCompositeMethodInfo a signature where
overloadedMethod = displaySupportsComposite
instance O.OverloadedMethodInfo DisplaySupportsCompositeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displaySupportsComposite",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displaySupportsComposite"
})
#endif
foreign import ccall "gdk_display_supports_cursor_alpha" gdk_display_supports_cursor_alpha ::
Ptr Display ->
IO CInt
displaySupportsCursorAlpha ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m Bool
displaySupportsCursorAlpha :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Bool
displaySupportsCursorAlpha a
display = IO Bool -> m Bool
forall a. IO a -> m a
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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
CInt
result <- Ptr Display -> IO CInt
gdk_display_supports_cursor_alpha Ptr Display
display'
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
display
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DisplaySupportsCursorAlphaMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplaySupportsCursorAlphaMethodInfo a signature where
overloadedMethod = displaySupportsCursorAlpha
instance O.OverloadedMethodInfo DisplaySupportsCursorAlphaMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displaySupportsCursorAlpha",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displaySupportsCursorAlpha"
})
#endif
foreign import ccall "gdk_display_supports_cursor_color" gdk_display_supports_cursor_color ::
Ptr Display ->
IO CInt
displaySupportsCursorColor ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m Bool
displaySupportsCursorColor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Bool
displaySupportsCursorColor a
display = IO Bool -> m Bool
forall a. IO a -> m a
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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
CInt
result <- Ptr Display -> IO CInt
gdk_display_supports_cursor_color Ptr Display
display'
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
display
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DisplaySupportsCursorColorMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplaySupportsCursorColorMethodInfo a signature where
overloadedMethod = displaySupportsCursorColor
instance O.OverloadedMethodInfo DisplaySupportsCursorColorMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displaySupportsCursorColor",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displaySupportsCursorColor"
})
#endif
foreign import ccall "gdk_display_supports_input_shapes" gdk_display_supports_input_shapes ::
Ptr Display ->
IO CInt
displaySupportsInputShapes ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m Bool
displaySupportsInputShapes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Bool
displaySupportsInputShapes a
display = IO Bool -> m Bool
forall a. IO a -> m a
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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
CInt
result <- Ptr Display -> IO CInt
gdk_display_supports_input_shapes Ptr Display
display'
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
display
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DisplaySupportsInputShapesMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplaySupportsInputShapesMethodInfo a signature where
overloadedMethod = displaySupportsInputShapes
instance O.OverloadedMethodInfo DisplaySupportsInputShapesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displaySupportsInputShapes",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displaySupportsInputShapes"
})
#endif
foreign import ccall "gdk_display_supports_selection_notification" gdk_display_supports_selection_notification ::
Ptr Display ->
IO CInt
displaySupportsSelectionNotification ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m Bool
displaySupportsSelectionNotification :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Bool
displaySupportsSelectionNotification a
display = IO Bool -> m Bool
forall a. IO a -> m a
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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
CInt
result <- Ptr Display -> IO CInt
gdk_display_supports_selection_notification Ptr Display
display'
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
display
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DisplaySupportsSelectionNotificationMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplaySupportsSelectionNotificationMethodInfo a signature where
overloadedMethod = displaySupportsSelectionNotification
instance O.OverloadedMethodInfo DisplaySupportsSelectionNotificationMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displaySupportsSelectionNotification",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displaySupportsSelectionNotification"
})
#endif
foreign import ccall "gdk_display_supports_shapes" gdk_display_supports_shapes ::
Ptr Display ->
IO CInt
displaySupportsShapes ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m Bool
displaySupportsShapes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m Bool
displaySupportsShapes a
display = IO Bool -> m Bool
forall a. IO a -> m a
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 Display
display' <- a -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
display
CInt
result <- Ptr Display -> IO CInt
gdk_display_supports_shapes Ptr Display
display'
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
display
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DisplaySupportsShapesMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplaySupportsShapesMethodInfo a signature where
overloadedMethod = displaySupportsShapes
instance O.OverloadedMethodInfo DisplaySupportsShapesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displaySupportsShapes",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displaySupportsShapes"
})
#endif
foreign import ccall "gdk_display_sync" gdk_display_sync ::
Ptr Display ->
IO ()
displaySync ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
a
-> m ()
displaySync :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDisplay a) =>
a -> m ()
displaySync a
display = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
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 Display -> IO ()
gdk_display_sync Ptr Display
display'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DisplaySyncMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDisplay a) => O.OverloadedMethod DisplaySyncMethodInfo a signature where
overloadedMethod = displaySync
instance O.OverloadedMethodInfo DisplaySyncMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displaySync",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displaySync"
})
#endif
foreign import ccall "gdk_display_warp_pointer" gdk_display_warp_pointer ::
Ptr Display ->
Ptr Gdk.Screen.Screen ->
Int32 ->
Int32 ->
IO ()
{-# DEPRECATED displayWarpPointer ["(Since version 3.0)","Use 'GI.Gdk.Objects.Device.deviceWarp' instead."] #-}
displayWarpPointer ::
(B.CallStack.HasCallStack, MonadIO m, IsDisplay a, Gdk.Screen.IsScreen b) =>
a
-> b
-> Int32
-> Int32
-> m ()
displayWarpPointer :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDisplay a, IsScreen b) =>
a -> b -> Int32 -> Int32 -> m ()
displayWarpPointer a
display b
screen Int32
x Int32
y = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
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 Screen
screen' <- b -> IO (Ptr Screen)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
screen
Ptr Display -> Ptr Screen -> Int32 -> Int32 -> IO ()
gdk_display_warp_pointer Ptr Display
display' Ptr Screen
screen' Int32
x Int32
y
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
display
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
screen
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DisplayWarpPointerMethodInfo
instance (signature ~ (b -> Int32 -> Int32 -> m ()), MonadIO m, IsDisplay a, Gdk.Screen.IsScreen b) => O.OverloadedMethod DisplayWarpPointerMethodInfo a signature where
overloadedMethod = displayWarpPointer
instance O.OverloadedMethodInfo DisplayWarpPointerMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.Display.displayWarpPointer",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-Display.html#v:displayWarpPointer"
})
#endif
foreign import ccall "gdk_display_get_default" gdk_display_get_default ::
IO (Ptr Display)
displayGetDefault ::
(B.CallStack.HasCallStack, MonadIO m) =>
m (Maybe Display)
displayGetDefault :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m (Maybe Display)
displayGetDefault = 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 Display
result <- IO (Ptr Display)
gdk_display_get_default
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
Display) Ptr Display
result'
Display -> IO Display
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Display
result''
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)
#endif
foreign import ccall "gdk_display_open" gdk_display_open ::
CString ->
IO (Ptr Display)
displayOpen ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> m (Maybe Display)
displayOpen :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m (Maybe Display)
displayOpen Text
displayName = 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
CString
displayName' <- Text -> IO CString
textToCString Text
displayName
Ptr Display
result <- CString -> IO (Ptr Display)
gdk_display_open CString
displayName'
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
Display) Ptr Display
result'
Display -> IO Display
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Display
result''
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
displayName'
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)
#endif
foreign import ccall "gdk_display_open_default_libgtk_only" gdk_display_open_default_libgtk_only ::
IO (Ptr Display)
{-# DEPRECATED displayOpenDefaultLibgtkOnly ["(Since version 3.16)","This symbol was never meant to be used outside"," of GTK+"] #-}
displayOpenDefaultLibgtkOnly ::
(B.CallStack.HasCallStack, MonadIO m) =>
m (Maybe Display)
displayOpenDefaultLibgtkOnly :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m (Maybe Display)
displayOpenDefaultLibgtkOnly = 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 Display
result <- IO (Ptr Display)
gdk_display_open_default_libgtk_only
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
Display) Ptr Display
result'
Display -> IO Display
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Display
result''
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)
#endif