{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gdk.Objects.Display.Display' objects purpose are two fold:
-- 
-- * To manage and provide information about input devices (pointers and keyboards)
-- * To manage and provide information about the available @/GdkScreens/@
-- 
-- 
-- GdkDisplay objects are the GDK representation of an X Display,
-- which can be described as a workstation consisting of
-- a keyboard, a pointing device (such as a mouse) and one or more
-- screens.
-- It is used to open and keep track of various GdkScreen objects
-- currently instantiated by the application. It is also used to
-- access the keyboard(s) and mouse pointer(s) of the display.
-- 
-- Most of the input device handling has been factored out into
-- the separate t'GI.Gdk.Objects.DeviceManager.DeviceManager' object. Every display has a
-- device manager, which you can obtain using
-- 'GI.Gdk.Objects.Display.displayGetDeviceManager'.

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

module GI.Gdk.Objects.Display
    ( 

-- * Exported types
    Display(..)                             ,
    IsDisplay                               ,
    toDisplay                               ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveDisplayMethod                    ,
#endif


-- ** beep #method:beep#

#if defined(ENABLE_OVERLOADING)
    DisplayBeepMethodInfo                   ,
#endif
    displayBeep                             ,


-- ** close #method:close#

#if defined(ENABLE_OVERLOADING)
    DisplayCloseMethodInfo                  ,
#endif
    displayClose                            ,


-- ** deviceIsGrabbed #method:deviceIsGrabbed#

#if defined(ENABLE_OVERLOADING)
    DisplayDeviceIsGrabbedMethodInfo        ,
#endif
    displayDeviceIsGrabbed                  ,


-- ** flush #method:flush#

#if defined(ENABLE_OVERLOADING)
    DisplayFlushMethodInfo                  ,
#endif
    displayFlush                            ,


-- ** getAppLaunchContext #method:getAppLaunchContext#

#if defined(ENABLE_OVERLOADING)
    DisplayGetAppLaunchContextMethodInfo    ,
#endif
    displayGetAppLaunchContext              ,


-- ** getDefault #method:getDefault#

    displayGetDefault                       ,


-- ** getDefaultCursorSize #method:getDefaultCursorSize#

#if defined(ENABLE_OVERLOADING)
    DisplayGetDefaultCursorSizeMethodInfo   ,
#endif
    displayGetDefaultCursorSize             ,


-- ** getDefaultGroup #method:getDefaultGroup#

#if defined(ENABLE_OVERLOADING)
    DisplayGetDefaultGroupMethodInfo        ,
#endif
    displayGetDefaultGroup                  ,


-- ** getDefaultScreen #method:getDefaultScreen#

#if defined(ENABLE_OVERLOADING)
    DisplayGetDefaultScreenMethodInfo       ,
#endif
    displayGetDefaultScreen                 ,


-- ** getDefaultSeat #method:getDefaultSeat#

#if defined(ENABLE_OVERLOADING)
    DisplayGetDefaultSeatMethodInfo         ,
#endif
    displayGetDefaultSeat                   ,


-- ** getDeviceManager #method:getDeviceManager#

#if defined(ENABLE_OVERLOADING)
    DisplayGetDeviceManagerMethodInfo       ,
#endif
    displayGetDeviceManager                 ,


-- ** getEvent #method:getEvent#

#if defined(ENABLE_OVERLOADING)
    DisplayGetEventMethodInfo               ,
#endif
    displayGetEvent                         ,


-- ** getMaximalCursorSize #method:getMaximalCursorSize#

#if defined(ENABLE_OVERLOADING)
    DisplayGetMaximalCursorSizeMethodInfo   ,
#endif
    displayGetMaximalCursorSize             ,


-- ** getMonitor #method:getMonitor#

#if defined(ENABLE_OVERLOADING)
    DisplayGetMonitorMethodInfo             ,
#endif
    displayGetMonitor                       ,


-- ** getMonitorAtPoint #method:getMonitorAtPoint#

#if defined(ENABLE_OVERLOADING)
    DisplayGetMonitorAtPointMethodInfo      ,
#endif
    displayGetMonitorAtPoint                ,


-- ** getMonitorAtWindow #method:getMonitorAtWindow#

#if defined(ENABLE_OVERLOADING)
    DisplayGetMonitorAtWindowMethodInfo     ,
#endif
    displayGetMonitorAtWindow               ,


-- ** getNMonitors #method:getNMonitors#

#if defined(ENABLE_OVERLOADING)
    DisplayGetNMonitorsMethodInfo           ,
#endif
    displayGetNMonitors                     ,


-- ** getNScreens #method:getNScreens#

#if defined(ENABLE_OVERLOADING)
    DisplayGetNScreensMethodInfo            ,
#endif
    displayGetNScreens                      ,


-- ** getName #method:getName#

#if defined(ENABLE_OVERLOADING)
    DisplayGetNameMethodInfo                ,
#endif
    displayGetName                          ,


-- ** getPointer #method:getPointer#

#if defined(ENABLE_OVERLOADING)
    DisplayGetPointerMethodInfo             ,
#endif
    displayGetPointer                       ,


-- ** getPrimaryMonitor #method:getPrimaryMonitor#

#if defined(ENABLE_OVERLOADING)
    DisplayGetPrimaryMonitorMethodInfo      ,
#endif
    displayGetPrimaryMonitor                ,


-- ** getScreen #method:getScreen#

#if defined(ENABLE_OVERLOADING)
    DisplayGetScreenMethodInfo              ,
#endif
    displayGetScreen                        ,


-- ** getWindowAtPointer #method:getWindowAtPointer#

#if defined(ENABLE_OVERLOADING)
    DisplayGetWindowAtPointerMethodInfo     ,
#endif
    displayGetWindowAtPointer               ,


-- ** hasPending #method:hasPending#

#if defined(ENABLE_OVERLOADING)
    DisplayHasPendingMethodInfo             ,
#endif
    displayHasPending                       ,


-- ** isClosed #method:isClosed#

#if defined(ENABLE_OVERLOADING)
    DisplayIsClosedMethodInfo               ,
#endif
    displayIsClosed                         ,


-- ** keyboardUngrab #method:keyboardUngrab#

#if defined(ENABLE_OVERLOADING)
    DisplayKeyboardUngrabMethodInfo         ,
#endif
    displayKeyboardUngrab                   ,


-- ** listDevices #method:listDevices#

#if defined(ENABLE_OVERLOADING)
    DisplayListDevicesMethodInfo            ,
#endif
    displayListDevices                      ,


-- ** listSeats #method:listSeats#

#if defined(ENABLE_OVERLOADING)
    DisplayListSeatsMethodInfo              ,
#endif
    displayListSeats                        ,


-- ** notifyStartupComplete #method:notifyStartupComplete#

#if defined(ENABLE_OVERLOADING)
    DisplayNotifyStartupCompleteMethodInfo  ,
#endif
    displayNotifyStartupComplete            ,


-- ** open #method:open#

    displayOpen                             ,


-- ** openDefaultLibgtkOnly #method:openDefaultLibgtkOnly#

    displayOpenDefaultLibgtkOnly            ,


-- ** peekEvent #method:peekEvent#

#if defined(ENABLE_OVERLOADING)
    DisplayPeekEventMethodInfo              ,
#endif
    displayPeekEvent                        ,


-- ** pointerIsGrabbed #method:pointerIsGrabbed#

#if defined(ENABLE_OVERLOADING)
    DisplayPointerIsGrabbedMethodInfo       ,
#endif
    displayPointerIsGrabbed                 ,


-- ** pointerUngrab #method:pointerUngrab#

#if defined(ENABLE_OVERLOADING)
    DisplayPointerUngrabMethodInfo          ,
#endif
    displayPointerUngrab                    ,


-- ** putEvent #method:putEvent#

#if defined(ENABLE_OVERLOADING)
    DisplayPutEventMethodInfo               ,
#endif
    displayPutEvent                         ,


-- ** requestSelectionNotification #method:requestSelectionNotification#

#if defined(ENABLE_OVERLOADING)
    DisplayRequestSelectionNotificationMethodInfo,
#endif
    displayRequestSelectionNotification     ,


-- ** setDoubleClickDistance #method:setDoubleClickDistance#

#if defined(ENABLE_OVERLOADING)
    DisplaySetDoubleClickDistanceMethodInfo ,
#endif
    displaySetDoubleClickDistance           ,


-- ** setDoubleClickTime #method:setDoubleClickTime#

#if defined(ENABLE_OVERLOADING)
    DisplaySetDoubleClickTimeMethodInfo     ,
#endif
    displaySetDoubleClickTime               ,


-- ** storeClipboard #method:storeClipboard#

#if defined(ENABLE_OVERLOADING)
    DisplayStoreClipboardMethodInfo         ,
#endif
    displayStoreClipboard                   ,


-- ** supportsClipboardPersistence #method:supportsClipboardPersistence#

#if defined(ENABLE_OVERLOADING)
    DisplaySupportsClipboardPersistenceMethodInfo,
#endif
    displaySupportsClipboardPersistence     ,


-- ** supportsComposite #method:supportsComposite#

#if defined(ENABLE_OVERLOADING)
    DisplaySupportsCompositeMethodInfo      ,
#endif
    displaySupportsComposite                ,


-- ** supportsCursorAlpha #method:supportsCursorAlpha#

#if defined(ENABLE_OVERLOADING)
    DisplaySupportsCursorAlphaMethodInfo    ,
#endif
    displaySupportsCursorAlpha              ,


-- ** supportsCursorColor #method:supportsCursorColor#

#if defined(ENABLE_OVERLOADING)
    DisplaySupportsCursorColorMethodInfo    ,
#endif
    displaySupportsCursorColor              ,


-- ** supportsInputShapes #method:supportsInputShapes#

#if defined(ENABLE_OVERLOADING)
    DisplaySupportsInputShapesMethodInfo    ,
#endif
    displaySupportsInputShapes              ,


-- ** supportsSelectionNotification #method:supportsSelectionNotification#

#if defined(ENABLE_OVERLOADING)
    DisplaySupportsSelectionNotificationMethodInfo,
#endif
    displaySupportsSelectionNotification    ,


-- ** supportsShapes #method:supportsShapes#

#if defined(ENABLE_OVERLOADING)
    DisplaySupportsShapesMethodInfo         ,
#endif
    displaySupportsShapes                   ,


-- ** sync #method:sync#

#if defined(ENABLE_OVERLOADING)
    DisplaySyncMethodInfo                   ,
#endif
    displaySync                             ,


-- ** warpPointer #method:warpPointer#

#if defined(ENABLE_OVERLOADING)
    DisplayWarpPointerMethodInfo            ,
#endif
    displayWarpPointer                      ,




 -- * Signals
-- ** closed #signal:closed#

    C_DisplayClosedCallback                 ,
    DisplayClosedCallback                   ,
#if defined(ENABLE_OVERLOADING)
    DisplayClosedSignalInfo                 ,
#endif
    afterDisplayClosed                      ,
    genClosure_DisplayClosed                ,
    mk_DisplayClosedCallback                ,
    noDisplayClosedCallback                 ,
    onDisplayClosed                         ,
    wrap_DisplayClosedCallback              ,


-- ** monitorAdded #signal:monitorAdded#

    C_DisplayMonitorAddedCallback           ,
    DisplayMonitorAddedCallback             ,
#if defined(ENABLE_OVERLOADING)
    DisplayMonitorAddedSignalInfo           ,
#endif
    afterDisplayMonitorAdded                ,
    genClosure_DisplayMonitorAdded          ,
    mk_DisplayMonitorAddedCallback          ,
    noDisplayMonitorAddedCallback           ,
    onDisplayMonitorAdded                   ,
    wrap_DisplayMonitorAddedCallback        ,


-- ** monitorRemoved #signal:monitorRemoved#

    C_DisplayMonitorRemovedCallback         ,
    DisplayMonitorRemovedCallback           ,
#if defined(ENABLE_OVERLOADING)
    DisplayMonitorRemovedSignalInfo         ,
#endif
    afterDisplayMonitorRemoved              ,
    genClosure_DisplayMonitorRemoved        ,
    mk_DisplayMonitorRemovedCallback        ,
    noDisplayMonitorRemovedCallback         ,
    onDisplayMonitorRemoved                 ,
    wrap_DisplayMonitorRemovedCallback      ,


-- ** opened #signal:opened#

    C_DisplayOpenedCallback                 ,
    DisplayOpenedCallback                   ,
#if defined(ENABLE_OVERLOADING)
    DisplayOpenedSignalInfo                 ,
#endif
    afterDisplayOpened                      ,
    genClosure_DisplayOpened                ,
    mk_DisplayOpenedCallback                ,
    noDisplayOpenedCallback                 ,
    onDisplayOpened                         ,
    wrap_DisplayOpenedCallback              ,


-- ** seatAdded #signal:seatAdded#

    C_DisplaySeatAddedCallback              ,
    DisplaySeatAddedCallback                ,
#if defined(ENABLE_OVERLOADING)
    DisplaySeatAddedSignalInfo              ,
#endif
    afterDisplaySeatAdded                   ,
    genClosure_DisplaySeatAdded             ,
    mk_DisplaySeatAddedCallback             ,
    noDisplaySeatAddedCallback              ,
    onDisplaySeatAdded                      ,
    wrap_DisplaySeatAddedCallback           ,


-- ** seatRemoved #signal:seatRemoved#

    C_DisplaySeatRemovedCallback            ,
    DisplaySeatRemovedCallback              ,
#if defined(ENABLE_OVERLOADING)
    DisplaySeatRemovedSignalInfo            ,
#endif
    afterDisplaySeatRemoved                 ,
    genClosure_DisplaySeatRemoved           ,
    mk_DisplaySeatRemovedCallback           ,
    noDisplaySeatRemovedCallback            ,
    onDisplaySeatRemoved                    ,
    wrap_DisplaySeatRemovedCallback         ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gdk.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

-- | Memory-managed wrapper type.
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
/= :: Display -> Display -> Bool
$c/= :: Display -> Display -> Bool
== :: Display -> Display -> Bool
$c== :: 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

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

-- | Type class for types which can be safely cast to `Display`, for instance with `toDisplay`.
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]

-- | Cast to `Display`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toDisplay :: (MonadIO m, IsDisplay o) => o -> m Display
toDisplay :: o -> m Display
toDisplay = IO Display -> m Display
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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'
unsafeCastTo ManagedPtr Display -> Display
Display

#if defined(ENABLE_OVERLOADING)
type family ResolveDisplayMethod (t :: Symbol) (o :: *) :: * 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.MethodInfo 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

#endif

-- signal Display::closed
-- | The [closed](#g:signal:closed) signal is emitted when the connection to the windowing
-- system for /@display@/ is closed.
-- 
-- /Since: 2.2/
type DisplayClosedCallback =
    Bool
    -- ^ /@isError@/: 'P.True' if the display was closed due to an error
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DisplayClosedCallback`@.
noDisplayClosedCallback :: Maybe DisplayClosedCallback
noDisplayClosedCallback :: Maybe DisplayClosedCallback
noDisplayClosedCallback = Maybe DisplayClosedCallback
forall a. Maybe a
Nothing

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

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

-- | Wrap the callback into a `GClosure`.
genClosure_DisplayClosed :: MonadIO m => DisplayClosedCallback -> m (GClosure C_DisplayClosedCallback)
genClosure_DisplayClosed :: DisplayClosedCallback -> m (GClosure C_DisplayClosedCallback)
genClosure_DisplayClosed DisplayClosedCallback
cb = IO (GClosure C_DisplayClosedCallback)
-> m (GClosure C_DisplayClosedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DisplayClosedCallback)
 -> m (GClosure C_DisplayClosedCallback))
-> IO (GClosure C_DisplayClosedCallback)
-> m (GClosure C_DisplayClosedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplayClosedCallback
cb' = DisplayClosedCallback -> C_DisplayClosedCallback
wrap_DisplayClosedCallback DisplayClosedCallback
cb
    C_DisplayClosedCallback -> IO (FunPtr C_DisplayClosedCallback)
mk_DisplayClosedCallback C_DisplayClosedCallback
cb' IO (FunPtr C_DisplayClosedCallback)
-> (FunPtr C_DisplayClosedCallback
    -> IO (GClosure C_DisplayClosedCallback))
-> IO (GClosure C_DisplayClosedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DisplayClosedCallback
-> IO (GClosure C_DisplayClosedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DisplayClosedCallback` into a `C_DisplayClosedCallback`.
wrap_DisplayClosedCallback ::
    DisplayClosedCallback ->
    C_DisplayClosedCallback
wrap_DisplayClosedCallback :: DisplayClosedCallback -> C_DisplayClosedCallback
wrap_DisplayClosedCallback DisplayClosedCallback
_cb Ptr ()
_ CInt
isError Ptr ()
_ = do
    let isError' :: Bool
isError' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
isError
    DisplayClosedCallback
_cb  Bool
isError'


-- | Connect a signal handler for the [closed](#signal:closed) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' display #closed callback
-- @
-- 
-- 
onDisplayClosed :: (IsDisplay a, MonadIO m) => a -> DisplayClosedCallback -> m SignalHandlerId
onDisplayClosed :: a -> DisplayClosedCallback -> m SignalHandlerId
onDisplayClosed a
obj DisplayClosedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplayClosedCallback
cb' = DisplayClosedCallback -> C_DisplayClosedCallback
wrap_DisplayClosedCallback DisplayClosedCallback
cb
    FunPtr C_DisplayClosedCallback
cb'' <- C_DisplayClosedCallback -> IO (FunPtr C_DisplayClosedCallback)
mk_DisplayClosedCallback C_DisplayClosedCallback
cb'
    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
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [closed](#signal:closed) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' display #closed callback
-- @
-- 
-- 
afterDisplayClosed :: (IsDisplay a, MonadIO m) => a -> DisplayClosedCallback -> m SignalHandlerId
afterDisplayClosed :: a -> DisplayClosedCallback -> m SignalHandlerId
afterDisplayClosed a
obj DisplayClosedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplayClosedCallback
cb' = DisplayClosedCallback -> C_DisplayClosedCallback
wrap_DisplayClosedCallback DisplayClosedCallback
cb
    FunPtr C_DisplayClosedCallback
cb'' <- C_DisplayClosedCallback -> IO (FunPtr C_DisplayClosedCallback)
mk_DisplayClosedCallback C_DisplayClosedCallback
cb'
    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
cb'' 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

#endif

-- signal Display::monitor-added
-- | The [monitorAdded](#g:signal:monitorAdded) signal is emitted whenever a monitor is
-- added.
-- 
-- /Since: 3.22/
type DisplayMonitorAddedCallback =
    Gdk.Monitor.Monitor
    -- ^ /@monitor@/: the monitor that was just added
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DisplayMonitorAddedCallback`@.
noDisplayMonitorAddedCallback :: Maybe DisplayMonitorAddedCallback
noDisplayMonitorAddedCallback :: Maybe DisplayMonitorAddedCallback
noDisplayMonitorAddedCallback = Maybe DisplayMonitorAddedCallback
forall a. Maybe a
Nothing

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

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

-- | Wrap the callback into a `GClosure`.
genClosure_DisplayMonitorAdded :: MonadIO m => DisplayMonitorAddedCallback -> m (GClosure C_DisplayMonitorAddedCallback)
genClosure_DisplayMonitorAdded :: DisplayMonitorAddedCallback
-> m (GClosure C_DisplayMonitorAddedCallback)
genClosure_DisplayMonitorAdded DisplayMonitorAddedCallback
cb = IO (GClosure C_DisplayMonitorAddedCallback)
-> m (GClosure C_DisplayMonitorAddedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DisplayMonitorAddedCallback)
 -> m (GClosure C_DisplayMonitorAddedCallback))
-> IO (GClosure C_DisplayMonitorAddedCallback)
-> m (GClosure C_DisplayMonitorAddedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplayMonitorAddedCallback
cb' = DisplayMonitorAddedCallback -> C_DisplayMonitorAddedCallback
wrap_DisplayMonitorAddedCallback DisplayMonitorAddedCallback
cb
    C_DisplayMonitorAddedCallback
-> IO (FunPtr C_DisplayMonitorAddedCallback)
mk_DisplayMonitorAddedCallback C_DisplayMonitorAddedCallback
cb' IO (FunPtr C_DisplayMonitorAddedCallback)
-> (FunPtr C_DisplayMonitorAddedCallback
    -> IO (GClosure C_DisplayMonitorAddedCallback))
-> IO (GClosure C_DisplayMonitorAddedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DisplayMonitorAddedCallback
-> IO (GClosure C_DisplayMonitorAddedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DisplayMonitorAddedCallback` into a `C_DisplayMonitorAddedCallback`.
wrap_DisplayMonitorAddedCallback ::
    DisplayMonitorAddedCallback ->
    C_DisplayMonitorAddedCallback
wrap_DisplayMonitorAddedCallback :: DisplayMonitorAddedCallback -> C_DisplayMonitorAddedCallback
wrap_DisplayMonitorAddedCallback DisplayMonitorAddedCallback
_cb Ptr ()
_ 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
    DisplayMonitorAddedCallback
_cb  Monitor
monitor'


-- | Connect a signal handler for the [monitorAdded](#signal:monitorAdded) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' display #monitorAdded callback
-- @
-- 
-- 
onDisplayMonitorAdded :: (IsDisplay a, MonadIO m) => a -> DisplayMonitorAddedCallback -> m SignalHandlerId
onDisplayMonitorAdded :: a -> DisplayMonitorAddedCallback -> m SignalHandlerId
onDisplayMonitorAdded a
obj DisplayMonitorAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplayMonitorAddedCallback
cb' = DisplayMonitorAddedCallback -> C_DisplayMonitorAddedCallback
wrap_DisplayMonitorAddedCallback DisplayMonitorAddedCallback
cb
    FunPtr C_DisplayMonitorAddedCallback
cb'' <- C_DisplayMonitorAddedCallback
-> IO (FunPtr C_DisplayMonitorAddedCallback)
mk_DisplayMonitorAddedCallback C_DisplayMonitorAddedCallback
cb'
    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
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [monitorAdded](#signal:monitorAdded) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' display #monitorAdded callback
-- @
-- 
-- 
afterDisplayMonitorAdded :: (IsDisplay a, MonadIO m) => a -> DisplayMonitorAddedCallback -> m SignalHandlerId
afterDisplayMonitorAdded :: a -> DisplayMonitorAddedCallback -> m SignalHandlerId
afterDisplayMonitorAdded a
obj DisplayMonitorAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplayMonitorAddedCallback
cb' = DisplayMonitorAddedCallback -> C_DisplayMonitorAddedCallback
wrap_DisplayMonitorAddedCallback DisplayMonitorAddedCallback
cb
    FunPtr C_DisplayMonitorAddedCallback
cb'' <- C_DisplayMonitorAddedCallback
-> IO (FunPtr C_DisplayMonitorAddedCallback)
mk_DisplayMonitorAddedCallback C_DisplayMonitorAddedCallback
cb'
    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
cb'' 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

#endif

-- signal Display::monitor-removed
-- | The [monitorRemoved](#g:signal:monitorRemoved) signal is emitted whenever a monitor is
-- removed.
-- 
-- /Since: 3.22/
type DisplayMonitorRemovedCallback =
    Gdk.Monitor.Monitor
    -- ^ /@monitor@/: the monitor that was just removed
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DisplayMonitorRemovedCallback`@.
noDisplayMonitorRemovedCallback :: Maybe DisplayMonitorRemovedCallback
noDisplayMonitorRemovedCallback :: Maybe DisplayMonitorAddedCallback
noDisplayMonitorRemovedCallback = Maybe DisplayMonitorAddedCallback
forall a. Maybe a
Nothing

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

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

-- | Wrap the callback into a `GClosure`.
genClosure_DisplayMonitorRemoved :: MonadIO m => DisplayMonitorRemovedCallback -> m (GClosure C_DisplayMonitorRemovedCallback)
genClosure_DisplayMonitorRemoved :: DisplayMonitorAddedCallback
-> m (GClosure C_DisplayMonitorAddedCallback)
genClosure_DisplayMonitorRemoved DisplayMonitorAddedCallback
cb = IO (GClosure C_DisplayMonitorAddedCallback)
-> m (GClosure C_DisplayMonitorAddedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DisplayMonitorAddedCallback)
 -> m (GClosure C_DisplayMonitorAddedCallback))
-> IO (GClosure C_DisplayMonitorAddedCallback)
-> m (GClosure C_DisplayMonitorAddedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplayMonitorAddedCallback
cb' = DisplayMonitorAddedCallback -> C_DisplayMonitorAddedCallback
wrap_DisplayMonitorRemovedCallback DisplayMonitorAddedCallback
cb
    C_DisplayMonitorAddedCallback
-> IO (FunPtr C_DisplayMonitorAddedCallback)
mk_DisplayMonitorRemovedCallback C_DisplayMonitorAddedCallback
cb' IO (FunPtr C_DisplayMonitorAddedCallback)
-> (FunPtr C_DisplayMonitorAddedCallback
    -> IO (GClosure C_DisplayMonitorAddedCallback))
-> IO (GClosure C_DisplayMonitorAddedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DisplayMonitorAddedCallback
-> IO (GClosure C_DisplayMonitorAddedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DisplayMonitorRemovedCallback` into a `C_DisplayMonitorRemovedCallback`.
wrap_DisplayMonitorRemovedCallback ::
    DisplayMonitorRemovedCallback ->
    C_DisplayMonitorRemovedCallback
wrap_DisplayMonitorRemovedCallback :: DisplayMonitorAddedCallback -> C_DisplayMonitorAddedCallback
wrap_DisplayMonitorRemovedCallback DisplayMonitorAddedCallback
_cb Ptr ()
_ 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
    DisplayMonitorAddedCallback
_cb  Monitor
monitor'


-- | Connect a signal handler for the [monitorRemoved](#signal:monitorRemoved) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' display #monitorRemoved callback
-- @
-- 
-- 
onDisplayMonitorRemoved :: (IsDisplay a, MonadIO m) => a -> DisplayMonitorRemovedCallback -> m SignalHandlerId
onDisplayMonitorRemoved :: a -> DisplayMonitorAddedCallback -> m SignalHandlerId
onDisplayMonitorRemoved a
obj DisplayMonitorAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplayMonitorAddedCallback
cb' = DisplayMonitorAddedCallback -> C_DisplayMonitorAddedCallback
wrap_DisplayMonitorRemovedCallback DisplayMonitorAddedCallback
cb
    FunPtr C_DisplayMonitorAddedCallback
cb'' <- C_DisplayMonitorAddedCallback
-> IO (FunPtr C_DisplayMonitorAddedCallback)
mk_DisplayMonitorRemovedCallback C_DisplayMonitorAddedCallback
cb'
    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
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [monitorRemoved](#signal:monitorRemoved) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' display #monitorRemoved callback
-- @
-- 
-- 
afterDisplayMonitorRemoved :: (IsDisplay a, MonadIO m) => a -> DisplayMonitorRemovedCallback -> m SignalHandlerId
afterDisplayMonitorRemoved :: a -> DisplayMonitorAddedCallback -> m SignalHandlerId
afterDisplayMonitorRemoved a
obj DisplayMonitorAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplayMonitorAddedCallback
cb' = DisplayMonitorAddedCallback -> C_DisplayMonitorAddedCallback
wrap_DisplayMonitorRemovedCallback DisplayMonitorAddedCallback
cb
    FunPtr C_DisplayMonitorAddedCallback
cb'' <- C_DisplayMonitorAddedCallback
-> IO (FunPtr C_DisplayMonitorAddedCallback)
mk_DisplayMonitorRemovedCallback C_DisplayMonitorAddedCallback
cb'
    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
cb'' 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

#endif

-- signal Display::opened
-- | The [opened](#g:signal:opened) signal is emitted when the connection to the windowing
-- system for /@display@/ is opened.
type DisplayOpenedCallback =
    IO ()

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

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

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

-- | Wrap the callback into a `GClosure`.
genClosure_DisplayOpened :: MonadIO m => DisplayOpenedCallback -> m (GClosure C_DisplayOpenedCallback)
genClosure_DisplayOpened :: IO () -> m (GClosure C_DisplayOpenedCallback)
genClosure_DisplayOpened IO ()
cb = IO (GClosure C_DisplayOpenedCallback)
-> m (GClosure C_DisplayOpenedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DisplayOpenedCallback)
 -> m (GClosure C_DisplayOpenedCallback))
-> IO (GClosure C_DisplayOpenedCallback)
-> m (GClosure C_DisplayOpenedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplayOpenedCallback
cb' = IO () -> C_DisplayOpenedCallback
wrap_DisplayOpenedCallback IO ()
cb
    C_DisplayOpenedCallback -> IO (FunPtr C_DisplayOpenedCallback)
mk_DisplayOpenedCallback C_DisplayOpenedCallback
cb' IO (FunPtr C_DisplayOpenedCallback)
-> (FunPtr C_DisplayOpenedCallback
    -> IO (GClosure C_DisplayOpenedCallback))
-> IO (GClosure C_DisplayOpenedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DisplayOpenedCallback
-> IO (GClosure C_DisplayOpenedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DisplayOpenedCallback` into a `C_DisplayOpenedCallback`.
wrap_DisplayOpenedCallback ::
    DisplayOpenedCallback ->
    C_DisplayOpenedCallback
wrap_DisplayOpenedCallback :: IO () -> C_DisplayOpenedCallback
wrap_DisplayOpenedCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 


-- | Connect a signal handler for the [opened](#signal:opened) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' display #opened callback
-- @
-- 
-- 
onDisplayOpened :: (IsDisplay a, MonadIO m) => a -> DisplayOpenedCallback -> m SignalHandlerId
onDisplayOpened :: a -> IO () -> m SignalHandlerId
onDisplayOpened a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplayOpenedCallback
cb' = IO () -> C_DisplayOpenedCallback
wrap_DisplayOpenedCallback IO ()
cb
    FunPtr C_DisplayOpenedCallback
cb'' <- C_DisplayOpenedCallback -> IO (FunPtr C_DisplayOpenedCallback)
mk_DisplayOpenedCallback C_DisplayOpenedCallback
cb'
    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
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [opened](#signal:opened) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' display #opened callback
-- @
-- 
-- 
afterDisplayOpened :: (IsDisplay a, MonadIO m) => a -> DisplayOpenedCallback -> m SignalHandlerId
afterDisplayOpened :: a -> IO () -> m SignalHandlerId
afterDisplayOpened a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplayOpenedCallback
cb' = IO () -> C_DisplayOpenedCallback
wrap_DisplayOpenedCallback IO ()
cb
    FunPtr C_DisplayOpenedCallback
cb'' <- C_DisplayOpenedCallback -> IO (FunPtr C_DisplayOpenedCallback)
mk_DisplayOpenedCallback C_DisplayOpenedCallback
cb'
    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
cb'' 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

#endif

-- signal Display::seat-added
-- | The [seatAdded](#g:signal:seatAdded) signal is emitted whenever a new seat is made
-- known to the windowing system.
-- 
-- /Since: 3.20/
type DisplaySeatAddedCallback =
    Gdk.Seat.Seat
    -- ^ /@seat@/: the seat that was just added
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DisplaySeatAddedCallback`@.
noDisplaySeatAddedCallback :: Maybe DisplaySeatAddedCallback
noDisplaySeatAddedCallback :: Maybe DisplaySeatAddedCallback
noDisplaySeatAddedCallback = Maybe DisplaySeatAddedCallback
forall a. Maybe a
Nothing

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

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

-- | Wrap the callback into a `GClosure`.
genClosure_DisplaySeatAdded :: MonadIO m => DisplaySeatAddedCallback -> m (GClosure C_DisplaySeatAddedCallback)
genClosure_DisplaySeatAdded :: DisplaySeatAddedCallback -> m (GClosure C_DisplaySeatAddedCallback)
genClosure_DisplaySeatAdded DisplaySeatAddedCallback
cb = IO (GClosure C_DisplaySeatAddedCallback)
-> m (GClosure C_DisplaySeatAddedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DisplaySeatAddedCallback)
 -> m (GClosure C_DisplaySeatAddedCallback))
-> IO (GClosure C_DisplaySeatAddedCallback)
-> m (GClosure C_DisplaySeatAddedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplaySeatAddedCallback
cb' = DisplaySeatAddedCallback -> C_DisplaySeatAddedCallback
wrap_DisplaySeatAddedCallback DisplaySeatAddedCallback
cb
    C_DisplaySeatAddedCallback
-> IO (FunPtr C_DisplaySeatAddedCallback)
mk_DisplaySeatAddedCallback C_DisplaySeatAddedCallback
cb' IO (FunPtr C_DisplaySeatAddedCallback)
-> (FunPtr C_DisplaySeatAddedCallback
    -> IO (GClosure C_DisplaySeatAddedCallback))
-> IO (GClosure C_DisplaySeatAddedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DisplaySeatAddedCallback
-> IO (GClosure C_DisplaySeatAddedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DisplaySeatAddedCallback` into a `C_DisplaySeatAddedCallback`.
wrap_DisplaySeatAddedCallback ::
    DisplaySeatAddedCallback ->
    C_DisplaySeatAddedCallback
wrap_DisplaySeatAddedCallback :: DisplaySeatAddedCallback -> C_DisplaySeatAddedCallback
wrap_DisplaySeatAddedCallback DisplaySeatAddedCallback
_cb Ptr ()
_ 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
    DisplaySeatAddedCallback
_cb  Seat
seat'


-- | Connect a signal handler for the [seatAdded](#signal:seatAdded) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' display #seatAdded callback
-- @
-- 
-- 
onDisplaySeatAdded :: (IsDisplay a, MonadIO m) => a -> DisplaySeatAddedCallback -> m SignalHandlerId
onDisplaySeatAdded :: a -> DisplaySeatAddedCallback -> m SignalHandlerId
onDisplaySeatAdded a
obj DisplaySeatAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplaySeatAddedCallback
cb' = DisplaySeatAddedCallback -> C_DisplaySeatAddedCallback
wrap_DisplaySeatAddedCallback DisplaySeatAddedCallback
cb
    FunPtr C_DisplaySeatAddedCallback
cb'' <- C_DisplaySeatAddedCallback
-> IO (FunPtr C_DisplaySeatAddedCallback)
mk_DisplaySeatAddedCallback C_DisplaySeatAddedCallback
cb'
    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
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [seatAdded](#signal:seatAdded) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' display #seatAdded callback
-- @
-- 
-- 
afterDisplaySeatAdded :: (IsDisplay a, MonadIO m) => a -> DisplaySeatAddedCallback -> m SignalHandlerId
afterDisplaySeatAdded :: a -> DisplaySeatAddedCallback -> m SignalHandlerId
afterDisplaySeatAdded a
obj DisplaySeatAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplaySeatAddedCallback
cb' = DisplaySeatAddedCallback -> C_DisplaySeatAddedCallback
wrap_DisplaySeatAddedCallback DisplaySeatAddedCallback
cb
    FunPtr C_DisplaySeatAddedCallback
cb'' <- C_DisplaySeatAddedCallback
-> IO (FunPtr C_DisplaySeatAddedCallback)
mk_DisplaySeatAddedCallback C_DisplaySeatAddedCallback
cb'
    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
cb'' 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

#endif

-- signal Display::seat-removed
-- | The [seatRemoved](#g:signal:seatRemoved) signal is emitted whenever a seat is removed
-- by the windowing system.
-- 
-- /Since: 3.20/
type DisplaySeatRemovedCallback =
    Gdk.Seat.Seat
    -- ^ /@seat@/: the seat that was just removed
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DisplaySeatRemovedCallback`@.
noDisplaySeatRemovedCallback :: Maybe DisplaySeatRemovedCallback
noDisplaySeatRemovedCallback :: Maybe DisplaySeatAddedCallback
noDisplaySeatRemovedCallback = Maybe DisplaySeatAddedCallback
forall a. Maybe a
Nothing

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

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

-- | Wrap the callback into a `GClosure`.
genClosure_DisplaySeatRemoved :: MonadIO m => DisplaySeatRemovedCallback -> m (GClosure C_DisplaySeatRemovedCallback)
genClosure_DisplaySeatRemoved :: DisplaySeatAddedCallback -> m (GClosure C_DisplaySeatAddedCallback)
genClosure_DisplaySeatRemoved DisplaySeatAddedCallback
cb = IO (GClosure C_DisplaySeatAddedCallback)
-> m (GClosure C_DisplaySeatAddedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DisplaySeatAddedCallback)
 -> m (GClosure C_DisplaySeatAddedCallback))
-> IO (GClosure C_DisplaySeatAddedCallback)
-> m (GClosure C_DisplaySeatAddedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplaySeatAddedCallback
cb' = DisplaySeatAddedCallback -> C_DisplaySeatAddedCallback
wrap_DisplaySeatRemovedCallback DisplaySeatAddedCallback
cb
    C_DisplaySeatAddedCallback
-> IO (FunPtr C_DisplaySeatAddedCallback)
mk_DisplaySeatRemovedCallback C_DisplaySeatAddedCallback
cb' IO (FunPtr C_DisplaySeatAddedCallback)
-> (FunPtr C_DisplaySeatAddedCallback
    -> IO (GClosure C_DisplaySeatAddedCallback))
-> IO (GClosure C_DisplaySeatAddedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DisplaySeatAddedCallback
-> IO (GClosure C_DisplaySeatAddedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DisplaySeatRemovedCallback` into a `C_DisplaySeatRemovedCallback`.
wrap_DisplaySeatRemovedCallback ::
    DisplaySeatRemovedCallback ->
    C_DisplaySeatRemovedCallback
wrap_DisplaySeatRemovedCallback :: DisplaySeatAddedCallback -> C_DisplaySeatAddedCallback
wrap_DisplaySeatRemovedCallback DisplaySeatAddedCallback
_cb Ptr ()
_ 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
    DisplaySeatAddedCallback
_cb  Seat
seat'


-- | Connect a signal handler for the [seatRemoved](#signal:seatRemoved) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' display #seatRemoved callback
-- @
-- 
-- 
onDisplaySeatRemoved :: (IsDisplay a, MonadIO m) => a -> DisplaySeatRemovedCallback -> m SignalHandlerId
onDisplaySeatRemoved :: a -> DisplaySeatAddedCallback -> m SignalHandlerId
onDisplaySeatRemoved a
obj DisplaySeatAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplaySeatAddedCallback
cb' = DisplaySeatAddedCallback -> C_DisplaySeatAddedCallback
wrap_DisplaySeatRemovedCallback DisplaySeatAddedCallback
cb
    FunPtr C_DisplaySeatAddedCallback
cb'' <- C_DisplaySeatAddedCallback
-> IO (FunPtr C_DisplaySeatAddedCallback)
mk_DisplaySeatRemovedCallback C_DisplaySeatAddedCallback
cb'
    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
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [seatRemoved](#signal:seatRemoved) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' display #seatRemoved callback
-- @
-- 
-- 
afterDisplaySeatRemoved :: (IsDisplay a, MonadIO m) => a -> DisplaySeatRemovedCallback -> m SignalHandlerId
afterDisplaySeatRemoved :: a -> DisplaySeatAddedCallback -> m SignalHandlerId
afterDisplaySeatRemoved a
obj DisplaySeatAddedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplaySeatAddedCallback
cb' = DisplaySeatAddedCallback -> C_DisplaySeatAddedCallback
wrap_DisplaySeatRemovedCallback DisplaySeatAddedCallback
cb
    FunPtr C_DisplaySeatAddedCallback
cb'' <- C_DisplaySeatAddedCallback
-> IO (FunPtr C_DisplaySeatAddedCallback)
mk_DisplaySeatRemovedCallback C_DisplaySeatAddedCallback
cb'
    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
cb'' 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

#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Display
type instance O.AttributeList Display = DisplayAttributeList
type DisplayAttributeList = ('[ ] :: [(Symbol, *)])
#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, *)])

#endif

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

foreign import ccall "gdk_display_beep" gdk_display_beep :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO ()

-- | Emits a short beep on /@display@/
-- 
-- /Since: 2.2/
displayBeep ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m ()
displayBeep :: a -> m ()
displayBeep a
display = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DisplayBeepMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDisplay a) => O.MethodInfo DisplayBeepMethodInfo a signature where
    overloadedMethod = displayBeep

#endif

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

foreign import ccall "gdk_display_close" gdk_display_close :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO ()

-- | Closes the connection to the windowing system for the given display,
-- and cleans up associated resources.
-- 
-- /Since: 2.2/
displayClose ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m ()
displayClose :: a -> m ()
displayClose a
display = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DisplayCloseMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDisplay a) => O.MethodInfo DisplayCloseMethodInfo a signature where
    overloadedMethod = displayClose

#endif

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

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

-- | Returns 'P.True' if there is an ongoing grab on /@device@/ for /@display@/.
displayDeviceIsGrabbed ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a, Gdk.Device.IsDevice b) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> b
    -- ^ /@device@/: a t'GI.Gdk.Objects.Device.Device'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if there is a grab in effect for /@device@/.
displayDeviceIsGrabbed :: a -> b -> m Bool
displayDeviceIsGrabbed a
display b
device = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo DisplayDeviceIsGrabbedMethodInfo a signature where
    overloadedMethod = displayDeviceIsGrabbed

#endif

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

foreign import ccall "gdk_display_flush" gdk_display_flush :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO ()

-- | Flushes any requests queued for the windowing system; this happens automatically
-- when the main loop blocks waiting for new events, but if your application
-- is drawing without returning control to the main loop, you may need
-- to call this function explicitly. A common case where this function
-- needs to be called is when an application is executing drawing commands
-- from a thread other than the thread where the main loop is running.
-- 
-- This is most useful for X11. On windowing systems where requests are
-- handled synchronously, this function will do nothing.
-- 
-- /Since: 2.4/
displayFlush ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m ()
displayFlush :: a -> m ()
displayFlush a
display = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DisplayFlushMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDisplay a) => O.MethodInfo DisplayFlushMethodInfo a signature where
    overloadedMethod = displayFlush

#endif

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

foreign import ccall "gdk_display_get_app_launch_context" gdk_display_get_app_launch_context :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO (Ptr Gdk.AppLaunchContext.AppLaunchContext)

-- | Returns a t'GI.Gdk.Objects.AppLaunchContext.AppLaunchContext' suitable for launching
-- applications on the given display.
-- 
-- /Since: 3.0/
displayGetAppLaunchContext ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m Gdk.AppLaunchContext.AppLaunchContext
    -- ^ __Returns:__ a new t'GI.Gdk.Objects.AppLaunchContext.AppLaunchContext' for /@display@/.
    --     Free with 'GI.GObject.Objects.Object.objectUnref' when done
displayGetAppLaunchContext :: a -> m AppLaunchContext
displayGetAppLaunchContext a
display = IO AppLaunchContext -> m AppLaunchContext
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 (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.MethodInfo DisplayGetAppLaunchContextMethodInfo a signature where
    overloadedMethod = displayGetAppLaunchContext

#endif

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

foreign import ccall "gdk_display_get_default_cursor_size" gdk_display_get_default_cursor_size :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO Word32

-- | Returns the default size to use for cursors on /@display@/.
-- 
-- /Since: 2.4/
displayGetDefaultCursorSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m Word32
    -- ^ __Returns:__ the default cursor size.
displayGetDefaultCursorSize :: a -> m Word32
displayGetDefaultCursorSize a
display = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ 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 (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.MethodInfo DisplayGetDefaultCursorSizeMethodInfo a signature where
    overloadedMethod = displayGetDefaultCursorSize

#endif

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

foreign import ccall "gdk_display_get_default_group" gdk_display_get_default_group :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO (Ptr Gdk.Window.Window)

-- | Returns the default group leader window for all toplevel windows
-- on /@display@/. This window is implicitly created by GDK.
-- See 'GI.Gdk.Objects.Window.windowSetGroup'.
-- 
-- /Since: 2.4/
displayGetDefaultGroup ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m Gdk.Window.Window
    -- ^ __Returns:__ The default group leader window
    -- for /@display@/
displayGetDefaultGroup :: a -> m Window
displayGetDefaultGroup a
display = IO Window -> m Window
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 (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.MethodInfo DisplayGetDefaultGroupMethodInfo a signature where
    overloadedMethod = displayGetDefaultGroup

#endif

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

foreign import ccall "gdk_display_get_default_screen" gdk_display_get_default_screen :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO (Ptr Gdk.Screen.Screen)

-- | Get the default t'GI.Gdk.Objects.Screen.Screen' for /@display@/.
-- 
-- /Since: 2.2/
displayGetDefaultScreen ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m Gdk.Screen.Screen
    -- ^ __Returns:__ the default t'GI.Gdk.Objects.Screen.Screen' object for /@display@/
displayGetDefaultScreen :: a -> m Screen
displayGetDefaultScreen a
display = IO Screen -> m Screen
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 (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.MethodInfo DisplayGetDefaultScreenMethodInfo a signature where
    overloadedMethod = displayGetDefaultScreen

#endif

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

foreign import ccall "gdk_display_get_default_seat" gdk_display_get_default_seat :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO (Ptr Gdk.Seat.Seat)

-- | Returns the default t'GI.Gdk.Objects.Seat.Seat' for this display.
-- 
-- /Since: 3.20/
displayGetDefaultSeat ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m Gdk.Seat.Seat
    -- ^ __Returns:__ the default seat.
displayGetDefaultSeat :: a -> m Seat
displayGetDefaultSeat a
display = IO Seat -> m Seat
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Seat -> m Seat) -> IO Seat -> m Seat
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo DisplayGetDefaultSeatMethodInfo a signature where
    overloadedMethod = displayGetDefaultSeat

#endif

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

foreign import ccall "gdk_display_get_device_manager" gdk_display_get_device_manager :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "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."] #-}
-- | Returns the t'GI.Gdk.Objects.DeviceManager.DeviceManager' associated to /@display@/.
-- 
-- /Since: 3.0/
displayGetDeviceManager ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'.
    -> m (Maybe Gdk.DeviceManager.DeviceManager)
    -- ^ __Returns:__ A t'GI.Gdk.Objects.DeviceManager.DeviceManager', or
    --          'P.Nothing'. This memory is owned by GDK and must not be freed
    --          or unreferenced.
displayGetDeviceManager :: a -> m (Maybe DeviceManager)
displayGetDeviceManager a
display = IO (Maybe DeviceManager) -> m (Maybe DeviceManager)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DeviceManager) -> m (Maybe DeviceManager))
-> IO (Maybe DeviceManager) -> m (Maybe DeviceManager)
forall a b. (a -> b) -> a -> b
$ 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 (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 (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.MethodInfo DisplayGetDeviceManagerMethodInfo a signature where
    overloadedMethod = displayGetDeviceManager

#endif

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

foreign import ccall "gdk_display_get_event" gdk_display_get_event :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO (Ptr Gdk.Event.Event)

-- | Gets the next t'GI.Gdk.Unions.Event.Event' to be processed for /@display@/, fetching events from the
-- windowing system if necessary.
-- 
-- /Since: 2.2/
displayGetEvent ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m (Maybe Gdk.Event.Event)
    -- ^ __Returns:__ the next t'GI.Gdk.Unions.Event.Event' to be processed, or 'P.Nothing'
    -- if no events are pending. The returned t'GI.Gdk.Unions.Event.Event' should be freed
    -- with 'GI.Gdk.Unions.Event.eventFree'.
displayGetEvent :: a -> m (Maybe Event)
displayGetEvent a
display = IO (Maybe Event) -> m (Maybe Event)
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 (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 (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.MethodInfo DisplayGetEventMethodInfo a signature where
    overloadedMethod = displayGetEvent

#endif

-- method Display::get_maximal_cursor_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDisplay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the return location for the maximal cursor width"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TUInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the return location for the maximal cursor height"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_display_get_maximal_cursor_size" gdk_display_get_maximal_cursor_size :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    Ptr Word32 ->                           -- width : TBasicType TUInt
    Ptr Word32 ->                           -- height : TBasicType TUInt
    IO ()

-- | Gets the maximal size to use for cursors on /@display@/.
-- 
-- /Since: 2.4/
displayGetMaximalCursorSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m ((Word32, Word32))
displayGetMaximalCursorSize :: a -> m (Word32, Word32)
displayGetMaximalCursorSize a
display = IO (Word32, Word32) -> m (Word32, Word32)
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 (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.MethodInfo DisplayGetMaximalCursorSizeMethodInfo a signature where
    overloadedMethod = displayGetMaximalCursorSize

#endif

-- method Display::get_monitor
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDisplay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "monitor_num"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of the monitor"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Monitor" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_display_get_monitor" gdk_display_get_monitor :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    Int32 ->                                -- monitor_num : TBasicType TInt
    IO (Ptr Gdk.Monitor.Monitor)

-- | Gets a monitor associated with this display.
-- 
-- /Since: 3.22/
displayGetMonitor ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> Int32
    -- ^ /@monitorNum@/: number of the monitor
    -> m (Maybe Gdk.Monitor.Monitor)
    -- ^ __Returns:__ the t'GI.Gdk.Objects.Monitor.Monitor', or 'P.Nothing' if
    --    /@monitorNum@/ is not a valid monitor number
displayGetMonitor :: a -> Int32 -> m (Maybe Monitor)
displayGetMonitor a
display Int32
monitorNum = IO (Maybe Monitor) -> m (Maybe Monitor)
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 (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 (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.MethodInfo DisplayGetMonitorMethodInfo a signature where
    overloadedMethod = displayGetMonitor

#endif

-- method Display::get_monitor_at_point
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDisplay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the x coordinate of the point"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the y coordinate of the point"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Monitor" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_display_get_monitor_at_point" gdk_display_get_monitor_at_point :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    IO (Ptr Gdk.Monitor.Monitor)

-- | Gets the monitor in which the point (/@x@/, /@y@/) is located,
-- or a nearby monitor if the point is not in any monitor.
-- 
-- /Since: 3.22/
displayGetMonitorAtPoint ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> Int32
    -- ^ /@x@/: the x coordinate of the point
    -> Int32
    -- ^ /@y@/: the y coordinate of the point
    -> m Gdk.Monitor.Monitor
    -- ^ __Returns:__ the monitor containing the point
displayGetMonitorAtPoint :: a -> Int32 -> Int32 -> m Monitor
displayGetMonitorAtPoint a
display Int32
x Int32
y = IO Monitor -> m Monitor
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 (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.MethodInfo DisplayGetMonitorAtPointMethodInfo a signature where
    overloadedMethod = displayGetMonitorAtPoint

#endif

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

foreign import ccall "gdk_display_get_monitor_at_window" gdk_display_get_monitor_at_window :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    Ptr Gdk.Window.Window ->                -- window : TInterface (Name {namespace = "Gdk", name = "Window"})
    IO (Ptr Gdk.Monitor.Monitor)

-- | Gets the monitor in which the largest area of /@window@/
-- resides, or a monitor close to /@window@/ if it is outside
-- of all monitors.
-- 
-- /Since: 3.22/
displayGetMonitorAtWindow ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a, Gdk.Window.IsWindow b) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> b
    -- ^ /@window@/: a t'GI.Gdk.Objects.Window.Window'
    -> m Gdk.Monitor.Monitor
    -- ^ __Returns:__ the monitor with the largest overlap with /@window@/
displayGetMonitorAtWindow :: a -> b -> m Monitor
displayGetMonitorAtWindow a
display b
window = IO Monitor -> m Monitor
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 (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.MethodInfo DisplayGetMonitorAtWindowMethodInfo a signature where
    overloadedMethod = displayGetMonitorAtWindow

#endif

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

foreign import ccall "gdk_display_get_n_monitors" gdk_display_get_n_monitors :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO Int32

-- | Gets the number of monitors that belong to /@display@/.
-- 
-- The returned number is valid until the next emission of the
-- [monitorAdded]("GI.Gdk.Objects.Display#g:signal:monitorAdded") or [monitorRemoved]("GI.Gdk.Objects.Display#g:signal:monitorRemoved") signal.
-- 
-- /Since: 3.22/
displayGetNMonitors ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m Int32
    -- ^ __Returns:__ the number of monitors
displayGetNMonitors :: a -> m Int32
displayGetNMonitors a
display = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo DisplayGetNMonitorsMethodInfo a signature where
    overloadedMethod = displayGetNMonitors

#endif

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

foreign import ccall "gdk_display_get_n_screens" gdk_display_get_n_screens :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO Int32

{-# DEPRECATED displayGetNScreens ["(Since version 3.10)","The number of screens is always 1."] #-}
-- | Gets the number of screen managed by the /@display@/.
-- 
-- /Since: 2.2/
displayGetNScreens ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m Int32
    -- ^ __Returns:__ number of screens.
displayGetNScreens :: a -> m Int32
displayGetNScreens a
display = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo DisplayGetNScreensMethodInfo a signature where
    overloadedMethod = displayGetNScreens

#endif

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

foreign import ccall "gdk_display_get_name" gdk_display_get_name :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO CString

-- | Gets the name of the display.
-- 
-- /Since: 2.2/
displayGetName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m T.Text
    -- ^ __Returns:__ a string representing the display name. This string is owned
    -- by GDK and should not be modified or freed.
displayGetName :: a -> m Text
displayGetName a
display = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo DisplayGetNameMethodInfo a signature where
    overloadedMethod = displayGetName

#endif

-- method Display::get_pointer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDisplay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "screen"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Screen" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store the screen that the\n         cursor is on, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store root window X coordinate of pointer, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store root window Y coordinate of pointer, or %NULL."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "mask"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "ModifierType" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "location to store current modifier mask, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_display_get_pointer" gdk_display_get_pointer :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    Ptr (Ptr Gdk.Screen.Screen) ->          -- screen : TInterface (Name {namespace = "Gdk", name = "Screen"})
    Ptr Int32 ->                            -- x : TBasicType TInt
    Ptr Int32 ->                            -- y : TBasicType TInt
    Ptr CUInt ->                            -- mask : TInterface (Name {namespace = "Gdk", name = "ModifierType"})
    IO ()

{-# DEPRECATED displayGetPointer ["(Since version 3.0)","Use 'GI.Gdk.Objects.Device.deviceGetPosition' instead."] #-}
-- | Gets the current location of the pointer and the current modifier
-- mask for a given display.
-- 
-- /Since: 2.2/
displayGetPointer ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m ((Gdk.Screen.Screen, Int32, Int32, [Gdk.Flags.ModifierType]))
displayGetPointer :: a -> m (Screen, Int32, Int32, [ModifierType])
displayGetPointer a
display = IO (Screen, Int32, Int32, [ModifierType])
-> m (Screen, Int32, Int32, [ModifierType])
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 (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.MethodInfo DisplayGetPointerMethodInfo a signature where
    overloadedMethod = displayGetPointer

#endif

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

foreign import ccall "gdk_display_get_primary_monitor" gdk_display_get_primary_monitor :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO (Ptr Gdk.Monitor.Monitor)

-- | Gets the primary monitor for the display.
-- 
-- The primary monitor is considered the monitor where the “main desktop”
-- lives. While normal application windows typically allow the window
-- manager to place the windows, specialized desktop applications
-- such as panels should place themselves on the primary monitor.
-- 
-- /Since: 3.22/
displayGetPrimaryMonitor ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m (Maybe Gdk.Monitor.Monitor)
    -- ^ __Returns:__ the primary monitor, or 'P.Nothing' if no primary
    --     monitor is configured by the user
displayGetPrimaryMonitor :: a -> m (Maybe Monitor)
displayGetPrimaryMonitor a
display = IO (Maybe Monitor) -> m (Maybe Monitor)
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 (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 (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.MethodInfo DisplayGetPrimaryMonitorMethodInfo a signature where
    overloadedMethod = displayGetPrimaryMonitor

#endif

-- method Display::get_screen
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDisplay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "screen_num"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the screen number" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Screen" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_display_get_screen" gdk_display_get_screen :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    Int32 ->                                -- screen_num : TBasicType TInt
    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."] #-}
-- | Returns a screen object for one of the screens of the display.
-- 
-- /Since: 2.2/
displayGetScreen ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> Int32
    -- ^ /@screenNum@/: the screen number
    -> m Gdk.Screen.Screen
    -- ^ __Returns:__ the t'GI.Gdk.Objects.Screen.Screen' object
displayGetScreen :: a -> Int32 -> m Screen
displayGetScreen a
display Int32
screenNum = IO Screen -> m Screen
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 (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.MethodInfo DisplayGetScreenMethodInfo a signature where
    overloadedMethod = displayGetScreen

#endif

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

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

{-# DEPRECATED displayGetWindowAtPointer ["(Since version 3.0)","Use 'GI.Gdk.Objects.Device.deviceGetWindowAtPosition' instead."] #-}
-- | Obtains the window underneath the mouse pointer, returning the location
-- of the pointer in that window in /@winX@/, /@winY@/ for /@screen@/. Returns 'P.Nothing'
-- if the window under the mouse pointer is not known to GDK (for example,
-- belongs to another application).
-- 
-- /Since: 2.2/
displayGetWindowAtPointer ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m ((Maybe Gdk.Window.Window, Int32, Int32))
    -- ^ __Returns:__ the window under the mouse
    --   pointer, or 'P.Nothing'
displayGetWindowAtPointer :: a -> m (Maybe Window, Int32, Int32)
displayGetWindowAtPointer a
display = IO (Maybe Window, Int32, Int32) -> m (Maybe Window, Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Window, Int32, Int32) -> m (Maybe Window, Int32, Int32))
-> IO (Maybe Window, Int32, Int32)
-> m (Maybe Window, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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 (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.MethodInfo DisplayGetWindowAtPointerMethodInfo a signature where
    overloadedMethod = displayGetWindowAtPointer

#endif

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

foreign import ccall "gdk_display_has_pending" gdk_display_has_pending :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO CInt

-- | Returns whether the display has events that are waiting
-- to be processed.
-- 
-- /Since: 3.0/
displayHasPending ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if there are events ready to be processed.
displayHasPending :: a -> m Bool
displayHasPending a
display = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo DisplayHasPendingMethodInfo a signature where
    overloadedMethod = displayHasPending

#endif

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

foreign import ccall "gdk_display_is_closed" gdk_display_is_closed :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO CInt

-- | Finds out if the display has been closed.
-- 
-- /Since: 2.22/
displayIsClosed ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the display is closed.
displayIsClosed :: a -> m Bool
displayIsClosed a
display = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo DisplayIsClosedMethodInfo a signature where
    overloadedMethod = displayIsClosed

#endif

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

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

{-# DEPRECATED displayKeyboardUngrab ["(Since version 3.0)","Use 'GI.Gdk.Objects.Device.deviceUngrab', together with 'GI.Gdk.Objects.Device.deviceGrab'","            instead."] #-}
-- | Release any keyboard grab
-- 
-- /Since: 2.2/
displayKeyboardUngrab ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'.
    -> Word32
    -- ^ /@time_@/: a timestap (e.g 'GI.Gdk.Constants.CURRENT_TIME').
    -> m ()
displayKeyboardUngrab :: a -> Word32 -> m ()
displayKeyboardUngrab a
display Word32
time_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DisplayKeyboardUngrabMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDisplay a) => O.MethodInfo DisplayKeyboardUngrabMethodInfo a signature where
    overloadedMethod = displayKeyboardUngrab

#endif

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

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

{-# DEPRECATED displayListDevices ["(Since version 3.0)","Use 'GI.Gdk.Objects.DeviceManager.deviceManagerListDevices' instead."] #-}
-- | Returns the list of available input devices attached to /@display@/.
-- The list is statically allocated and should not be freed.
-- 
-- /Since: 2.2/
displayListDevices ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m [Gdk.Device.Device]
    -- ^ __Returns:__ 
    --     a list of t'GI.Gdk.Objects.Device.Device'
displayListDevices :: a -> m [Device]
displayListDevices a
display = IO [Device] -> m [Device]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Device] -> m [Device]) -> IO [Device] -> m [Device]
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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)
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 (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.MethodInfo DisplayListDevicesMethodInfo a signature where
    overloadedMethod = displayListDevices

#endif

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

foreign import ccall "gdk_display_list_seats" gdk_display_list_seats :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO (Ptr (GList (Ptr Gdk.Seat.Seat)))

-- | Returns the list of seats known to /@display@/.
-- 
-- /Since: 3.20/
displayListSeats ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m [Gdk.Seat.Seat]
    -- ^ __Returns:__ the
    --          list of seats known to the t'GI.Gdk.Objects.Display.Display'
displayListSeats :: a -> m [Seat]
displayListSeats a
display = IO [Seat] -> m [Seat]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Seat] -> m [Seat]) -> IO [Seat] -> m [Seat]
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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)
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 (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.MethodInfo DisplayListSeatsMethodInfo a signature where
    overloadedMethod = displayListSeats

#endif

-- method Display::notify_startup_complete
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDisplay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "startup_id"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a startup-notification identifier, for which\n    notification process should be completed"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_display_notify_startup_complete" gdk_display_notify_startup_complete :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    CString ->                              -- startup_id : TBasicType TUTF8
    IO ()

-- | Indicates to the GUI environment that the application has
-- finished loading, using a given identifier.
-- 
-- GTK+ will call this function automatically for @/GtkWindow/@
-- with custom startup-notification identifier unless
-- @/gtk_window_set_auto_startup_notification()/@ is called to
-- disable that feature.
-- 
-- /Since: 3.0/
displayNotifyStartupComplete ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> T.Text
    -- ^ /@startupId@/: a startup-notification identifier, for which
    --     notification process should be completed
    -> m ()
displayNotifyStartupComplete :: a -> Text -> m ()
displayNotifyStartupComplete a
display Text
startupId = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DisplayNotifyStartupCompleteMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsDisplay a) => O.MethodInfo DisplayNotifyStartupCompleteMethodInfo a signature where
    overloadedMethod = displayNotifyStartupComplete

#endif

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

foreign import ccall "gdk_display_peek_event" gdk_display_peek_event :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO (Ptr Gdk.Event.Event)

-- | Gets a copy of the first t'GI.Gdk.Unions.Event.Event' in the /@display@/’s event queue, without
-- removing the event from the queue.  (Note that this function will
-- not get more events from the windowing system.  It only checks the events
-- that have already been moved to the GDK event queue.)
-- 
-- /Since: 2.2/
displayPeekEvent ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m (Maybe Gdk.Event.Event)
    -- ^ __Returns:__ a copy of the first t'GI.Gdk.Unions.Event.Event' on the event
    -- queue, or 'P.Nothing' if no events are in the queue. The returned
    -- t'GI.Gdk.Unions.Event.Event' should be freed with 'GI.Gdk.Unions.Event.eventFree'.
displayPeekEvent :: a -> m (Maybe Event)
displayPeekEvent a
display = IO (Maybe Event) -> m (Maybe Event)
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 (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 (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.MethodInfo DisplayPeekEventMethodInfo a signature where
    overloadedMethod = displayPeekEvent

#endif

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

foreign import ccall "gdk_display_pointer_is_grabbed" gdk_display_pointer_is_grabbed :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO CInt

{-# DEPRECATED displayPointerIsGrabbed ["(Since version 3.0)","Use 'GI.Gdk.Objects.Display.displayDeviceIsGrabbed' instead."] #-}
-- | Test if the pointer is grabbed.
-- 
-- /Since: 2.2/
displayPointerIsGrabbed ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if an active X pointer grab is in effect
displayPointerIsGrabbed :: a -> m Bool
displayPointerIsGrabbed a
display = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo DisplayPointerIsGrabbedMethodInfo a signature where
    overloadedMethod = displayPointerIsGrabbed

#endif

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

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

{-# DEPRECATED displayPointerUngrab ["(Since version 3.0)","Use 'GI.Gdk.Objects.Device.deviceUngrab', together with 'GI.Gdk.Objects.Device.deviceGrab'","            instead."] #-}
-- | Release any pointer grab.
-- 
-- /Since: 2.2/
displayPointerUngrab ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'.
    -> Word32
    -- ^ /@time_@/: a timestap (e.g. 'GI.Gdk.Constants.CURRENT_TIME').
    -> m ()
displayPointerUngrab :: a -> Word32 -> m ()
displayPointerUngrab a
display Word32
time_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DisplayPointerUngrabMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDisplay a) => O.MethodInfo DisplayPointerUngrabMethodInfo a signature where
    overloadedMethod = displayPointerUngrab

#endif

-- method Display::put_event
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDisplay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "event"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Event" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkEvent." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_display_put_event" gdk_display_put_event :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    Ptr Gdk.Event.Event ->                  -- event : TInterface (Name {namespace = "Gdk", name = "Event"})
    IO ()

-- | Appends a copy of the given event onto the front of the event
-- queue for /@display@/.
-- 
-- /Since: 2.2/
displayPutEvent ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> Gdk.Event.Event
    -- ^ /@event@/: a t'GI.Gdk.Unions.Event.Event'.
    -> m ()
displayPutEvent :: a -> Event -> m ()
displayPutEvent a
display Event
event = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo DisplayPutEventMethodInfo a signature where
    overloadedMethod = displayPutEvent

#endif

-- method Display::request_selection_notification
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDisplay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "selection"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Atom" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the #GdkAtom naming the selection for which\n            ownership change notification is requested"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_display_request_selection_notification" gdk_display_request_selection_notification :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    Ptr Gdk.Atom.Atom ->                    -- selection : TInterface (Name {namespace = "Gdk", name = "Atom"})
    IO CInt

-- | Request t'GI.Gdk.Structs.EventOwnerChange.EventOwnerChange' events for ownership changes
-- of the selection named by the given atom.
-- 
-- /Since: 2.6/
displayRequestSelectionNotification ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> Gdk.Atom.Atom
    -- ^ /@selection@/: the t'GI.Gdk.Structs.Atom.Atom' naming the selection for which
    --             ownership change notification is requested
    -> m Bool
    -- ^ __Returns:__ whether t'GI.Gdk.Structs.EventOwnerChange.EventOwnerChange' events will
    --               be sent.
displayRequestSelectionNotification :: a -> Atom -> m Bool
displayRequestSelectionNotification a
display Atom
selection = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo DisplayRequestSelectionNotificationMethodInfo a signature where
    overloadedMethod = displayRequestSelectionNotification

#endif

-- method Display::set_double_click_distance
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDisplay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "distance"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "distance in pixels" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_display_set_double_click_distance" gdk_display_set_double_click_distance :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    Word32 ->                               -- distance : TBasicType TUInt
    IO ()

-- | Sets the double click distance (two clicks within this distance
-- count as a double click and result in a @/GDK_2BUTTON_PRESS/@ event).
-- See also 'GI.Gdk.Objects.Display.displaySetDoubleClickTime'.
-- Applications should not set this, it is a global
-- user-configured setting.
-- 
-- /Since: 2.4/
displaySetDoubleClickDistance ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> Word32
    -- ^ /@distance@/: distance in pixels
    -> m ()
displaySetDoubleClickDistance :: a -> Word32 -> m ()
displaySetDoubleClickDistance a
display Word32
distance = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DisplaySetDoubleClickDistanceMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDisplay a) => O.MethodInfo DisplaySetDoubleClickDistanceMethodInfo a signature where
    overloadedMethod = displaySetDoubleClickDistance

#endif

-- method Display::set_double_click_time
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDisplay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "msec"
--           , argType = TBasicType TUInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "double click time in milliseconds (thousandths of a second)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_display_set_double_click_time" gdk_display_set_double_click_time :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    Word32 ->                               -- msec : TBasicType TUInt
    IO ()

-- | Sets the double click time (two clicks within this time interval
-- count as a double click and result in a @/GDK_2BUTTON_PRESS/@ event).
-- Applications should not set this, it is a global
-- user-configured setting.
-- 
-- /Since: 2.2/
displaySetDoubleClickTime ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> Word32
    -- ^ /@msec@/: double click time in milliseconds (thousandths of a second)
    -> m ()
displaySetDoubleClickTime :: a -> Word32 -> m ()
displaySetDoubleClickTime a
display Word32
msec = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DisplaySetDoubleClickTimeMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsDisplay a) => O.MethodInfo DisplaySetDoubleClickTimeMethodInfo a signature where
    overloadedMethod = displaySetDoubleClickTime

#endif

-- method Display::store_clipboard
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "display"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "Display" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDisplay" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "clipboard_window"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkWindow belonging to the clipboard owner"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "time_"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a timestamp" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "targets"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 4
--                 (TInterface Name { namespace = "Gdk" , name = "Atom" })
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "an array of targets\n                   that should be saved, or %NULL\n                   if all available targets should be saved."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_targets"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "length of the @targets array"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_targets"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "length of the @targets array"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_display_store_clipboard" gdk_display_store_clipboard :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    Ptr Gdk.Window.Window ->                -- clipboard_window : TInterface (Name {namespace = "Gdk", name = "Window"})
    Word32 ->                               -- time_ : TBasicType TUInt32
    Ptr (Ptr Gdk.Atom.Atom) ->              -- targets : TCArray False (-1) 4 (TInterface (Name {namespace = "Gdk", name = "Atom"}))
    Int32 ->                                -- n_targets : TBasicType TInt
    IO ()

-- | Issues a request to the clipboard manager to store the
-- clipboard data. On X11, this is a special program that works
-- according to the
-- <http://www.freedesktop.org/Standards/clipboard-manager-spec FreeDesktop Clipboard Specification>.
-- 
-- /Since: 2.6/
displayStoreClipboard ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a, Gdk.Window.IsWindow b) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> b
    -- ^ /@clipboardWindow@/: a t'GI.Gdk.Objects.Window.Window' belonging to the clipboard owner
    -> Word32
    -- ^ /@time_@/: a timestamp
    -> Maybe ([Gdk.Atom.Atom])
    -- ^ /@targets@/: an array of targets
    --                    that should be saved, or 'P.Nothing'
    --                    if all available targets should be saved.
    -> m ()
displayStoreClipboard :: a -> b -> Word32 -> Maybe [Atom] -> m ()
displayStoreClipboard a
display b
clipboardWindow Word32
time_ Maybe [Atom]
targets = IO () -> m ()
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 (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 (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)
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 (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 (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.MethodInfo DisplayStoreClipboardMethodInfo a signature where
    overloadedMethod = displayStoreClipboard

#endif

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

foreign import ccall "gdk_display_supports_clipboard_persistence" gdk_display_supports_clipboard_persistence :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO CInt

-- | Returns whether the speicifed display supports clipboard
-- persistance; i.e. if it’s possible to store the clipboard data after an
-- application has quit. On X11 this checks if a clipboard daemon is
-- running.
-- 
-- /Since: 2.6/
displaySupportsClipboardPersistence ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the display supports clipboard persistance.
displaySupportsClipboardPersistence :: a -> m Bool
displaySupportsClipboardPersistence a
display = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo DisplaySupportsClipboardPersistenceMethodInfo a signature where
    overloadedMethod = displaySupportsClipboardPersistence

#endif

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

foreign import ccall "gdk_display_supports_composite" gdk_display_supports_composite :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO CInt

{-# DEPRECATED displaySupportsComposite ["(Since version 3.16)","Compositing is an outdated technology that","  only ever worked on X11."] #-}
-- | Returns 'P.True' if 'GI.Gdk.Objects.Window.windowSetComposited' can be used
-- to redirect drawing on the window using compositing.
-- 
-- Currently this only works on X11 with XComposite and
-- XDamage extensions available.
-- 
-- /Since: 2.12/
displaySupportsComposite ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if windows may be composited.
displaySupportsComposite :: a -> m Bool
displaySupportsComposite a
display = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo DisplaySupportsCompositeMethodInfo a signature where
    overloadedMethod = displaySupportsComposite

#endif

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

foreign import ccall "gdk_display_supports_cursor_alpha" gdk_display_supports_cursor_alpha :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO CInt

-- | Returns 'P.True' if cursors can use an 8bit alpha channel
-- on /@display@/. Otherwise, cursors are restricted to bilevel
-- alpha (i.e. a mask).
-- 
-- /Since: 2.4/
displaySupportsCursorAlpha ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m Bool
    -- ^ __Returns:__ whether cursors can have alpha channels.
displaySupportsCursorAlpha :: a -> m Bool
displaySupportsCursorAlpha a
display = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo DisplaySupportsCursorAlphaMethodInfo a signature where
    overloadedMethod = displaySupportsCursorAlpha

#endif

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

foreign import ccall "gdk_display_supports_cursor_color" gdk_display_supports_cursor_color :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO CInt

-- | Returns 'P.True' if multicolored cursors are supported
-- on /@display@/. Otherwise, cursors have only a forground
-- and a background color.
-- 
-- /Since: 2.4/
displaySupportsCursorColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m Bool
    -- ^ __Returns:__ whether cursors can have multiple colors.
displaySupportsCursorColor :: a -> m Bool
displaySupportsCursorColor a
display = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo DisplaySupportsCursorColorMethodInfo a signature where
    overloadedMethod = displaySupportsCursorColor

#endif

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

foreign import ccall "gdk_display_supports_input_shapes" gdk_display_supports_input_shapes :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO CInt

-- | Returns 'P.True' if @/gdk_window_input_shape_combine_mask()/@ can
-- be used to modify the input shape of windows on /@display@/.
-- 
-- /Since: 2.10/
displaySupportsInputShapes ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if windows with modified input shape are supported
displaySupportsInputShapes :: a -> m Bool
displaySupportsInputShapes a
display = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo DisplaySupportsInputShapesMethodInfo a signature where
    overloadedMethod = displaySupportsInputShapes

#endif

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

foreign import ccall "gdk_display_supports_selection_notification" gdk_display_supports_selection_notification :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO CInt

-- | Returns whether t'GI.Gdk.Structs.EventOwnerChange.EventOwnerChange' events will be
-- sent when the owner of a selection changes.
-- 
-- /Since: 2.6/
displaySupportsSelectionNotification ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m Bool
    -- ^ __Returns:__ whether t'GI.Gdk.Structs.EventOwnerChange.EventOwnerChange' events will
    --               be sent.
displaySupportsSelectionNotification :: a -> m Bool
displaySupportsSelectionNotification a
display = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo DisplaySupportsSelectionNotificationMethodInfo a signature where
    overloadedMethod = displaySupportsSelectionNotification

#endif

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

foreign import ccall "gdk_display_supports_shapes" gdk_display_supports_shapes :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO CInt

-- | Returns 'P.True' if @/gdk_window_shape_combine_mask()/@ can
-- be used to create shaped windows on /@display@/.
-- 
-- /Since: 2.10/
displaySupportsShapes ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if shaped windows are supported
displaySupportsShapes :: a -> m Bool
displaySupportsShapes a
display = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo DisplaySupportsShapesMethodInfo a signature where
    overloadedMethod = displaySupportsShapes

#endif

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

foreign import ccall "gdk_display_sync" gdk_display_sync :: 
    Ptr Display ->                          -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO ()

-- | Flushes any requests queued for the windowing system and waits until all
-- requests have been handled. This is often used for making sure that the
-- display is synchronized with the current state of the program. Calling
-- 'GI.Gdk.Objects.Display.displaySync' before 'GI.Gdk.Functions.errorTrapPop' makes sure that any errors
-- generated from earlier requests are handled before the error trap is
-- removed.
-- 
-- This is most useful for X11. On windowing systems where requests are
-- handled synchronously, this function will do nothing.
-- 
-- /Since: 2.2/
displaySync ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m ()
displaySync :: a -> m ()
displaySync a
display = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DisplaySyncMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDisplay a) => O.MethodInfo DisplaySyncMethodInfo a signature where
    overloadedMethod = displaySync

#endif

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

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

{-# DEPRECATED displayWarpPointer ["(Since version 3.0)","Use 'GI.Gdk.Objects.Device.deviceWarp' instead."] #-}
-- | Warps the pointer of /@display@/ to the point /@x@/,/@y@/ on
-- the screen /@screen@/, unless the pointer is confined
-- to a window by a grab, in which case it will be moved
-- as far as allowed by the grab. Warping the pointer
-- creates events as if the user had moved the mouse
-- instantaneously to the destination.
-- 
-- Note that the pointer should normally be under the
-- control of the user. This function was added to cover
-- some rare use cases like keyboard navigation support
-- for the color picker in the @/GtkColorSelectionDialog/@.
-- 
-- /Since: 2.8/
displayWarpPointer ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplay a, Gdk.Screen.IsScreen b) =>
    a
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> b
    -- ^ /@screen@/: the screen of /@display@/ to warp the pointer to
    -> Int32
    -- ^ /@x@/: the x coordinate of the destination
    -> Int32
    -- ^ /@y@/: the y coordinate of the destination
    -> m ()
displayWarpPointer :: a -> b -> Int32 -> Int32 -> m ()
displayWarpPointer a
display b
screen Int32
x Int32
y = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (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.MethodInfo DisplayWarpPointerMethodInfo a signature where
    overloadedMethod = displayWarpPointer

#endif

-- method Display::get_default
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Display" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_display_get_default" gdk_display_get_default :: 
    IO (Ptr Display)

-- | Gets the default t'GI.Gdk.Objects.Display.Display'. This is a convenience
-- function for:
-- @gdk_display_manager_get_default_display (gdk_display_manager_get ())@.
-- 
-- /Since: 2.2/
displayGetDefault ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m (Maybe Display)
    -- ^ __Returns:__ a t'GI.Gdk.Objects.Display.Display', or 'P.Nothing' if
    --   there is no default display.
displayGetDefault :: m (Maybe Display)
displayGetDefault  = IO (Maybe Display) -> m (Maybe Display)
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 (m :: * -> *) a. Monad m => a -> m a
return Display
result''
    Maybe Display -> IO (Maybe Display)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Display
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

-- method Display::open
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "display_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the display to open"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Display" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_display_open" gdk_display_open :: 
    CString ->                              -- display_name : TBasicType TUTF8
    IO (Ptr Display)

-- | Opens a display.
-- 
-- /Since: 2.2/
displayOpen ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@displayName@/: the name of the display to open
    -> m (Maybe Display)
    -- ^ __Returns:__ a t'GI.Gdk.Objects.Display.Display', or 'P.Nothing' if the
    --     display could not be opened
displayOpen :: Text -> m (Maybe Display)
displayOpen Text
displayName = IO (Maybe Display) -> m (Maybe Display)
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 (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 (m :: * -> *) a. Monad m => a -> m a
return Maybe Display
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

-- method Display::open_default_libgtk_only
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Display" })
-- throws : False
-- Skip return : False

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+"] #-}
-- | Opens the default display specified by command line arguments or
-- environment variables, sets it as the default display, and returns
-- it. 'GI.Gdk.Functions.parseArgs' must have been called first. If the default
-- display has previously been set, simply returns that. An internal
-- function that should not be used by applications.
displayOpenDefaultLibgtkOnly ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m (Maybe Display)
    -- ^ __Returns:__ the default display, if it
    --   could be opened, otherwise 'P.Nothing'.
displayOpenDefaultLibgtkOnly :: m (Maybe Display)
displayOpenDefaultLibgtkOnly  = IO (Maybe Display) -> m (Maybe Display)
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 (m :: * -> *) a. Monad m => a -> m a
return Display
result''
    Maybe Display -> IO (Maybe Display)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Display
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif