{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The purpose of the t'GI.Gdk.Objects.DisplayManager.DisplayManager' singleton object is to offer
-- notification when displays appear or disappear or the default display
-- changes.
-- 
-- You can use 'GI.Gdk.Objects.DisplayManager.displayManagerGet' to obtain the t'GI.Gdk.Objects.DisplayManager.DisplayManager'
-- singleton, but that should be rarely necessary. Typically, initializing
-- GTK opens a display that you can work with without ever accessing the
-- t'GI.Gdk.Objects.DisplayManager.DisplayManager'.
-- 
-- The GDK library can be built with support for multiple backends.
-- The t'GI.Gdk.Objects.DisplayManager.DisplayManager' object determines which backend is used
-- at runtime.
-- 
-- When writing backend-specific code that is supposed to work with
-- multiple GDK backends, you have to consider both compile time and
-- runtime. At compile time, use the @/GDK_WINDOWING_X11/@, @/GDK_WINDOWING_WIN32/@
-- macros, etc. to find out which backends are present in the GDK library
-- you are building your application against. At runtime, use type-check
-- macros like @/GDK_IS_X11_DISPLAY()/@ to find out which backend is in use:
-- 
-- ## Backend-specific code ## {@/backend/@-specific}
-- 
-- 
-- === /C code/
-- >
-- >#ifdef GDK_WINDOWING_X11
-- >  if (GDK_IS_X11_DISPLAY (display))
-- >    {
-- >      // make X11-specific calls here
-- >    }
-- >  else
-- >#endif
-- >#ifdef GDK_WINDOWING_QUARTZ
-- >  if (GDK_IS_QUARTZ_DISPLAY (display))
-- >    {
-- >      // make Quartz-specific calls here
-- >    }
-- >  else
-- >#endif
-- >  g_error ("Unsupported GDK backend");
-- 

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

module GI.Gdk.Objects.DisplayManager
    ( 

-- * Exported types
    DisplayManager(..)                      ,
    IsDisplayManager                        ,
    toDisplayManager                        ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveDisplayManagerMethod             ,
#endif


-- ** get #method:get#

    displayManagerGet                       ,


-- ** getDefaultDisplay #method:getDefaultDisplay#

#if defined(ENABLE_OVERLOADING)
    DisplayManagerGetDefaultDisplayMethodInfo,
#endif
    displayManagerGetDefaultDisplay         ,


-- ** listDisplays #method:listDisplays#

#if defined(ENABLE_OVERLOADING)
    DisplayManagerListDisplaysMethodInfo    ,
#endif
    displayManagerListDisplays              ,


-- ** openDisplay #method:openDisplay#

#if defined(ENABLE_OVERLOADING)
    DisplayManagerOpenDisplayMethodInfo     ,
#endif
    displayManagerOpenDisplay               ,


-- ** setDefaultDisplay #method:setDefaultDisplay#

#if defined(ENABLE_OVERLOADING)
    DisplayManagerSetDefaultDisplayMethodInfo,
#endif
    displayManagerSetDefaultDisplay         ,




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

#if defined(ENABLE_OVERLOADING)
    DisplayManagerDefaultDisplayPropertyInfo,
#endif
    constructDisplayManagerDefaultDisplay   ,
#if defined(ENABLE_OVERLOADING)
    displayManagerDefaultDisplay            ,
#endif
    getDisplayManagerDefaultDisplay         ,
    setDisplayManagerDefaultDisplay         ,




 -- * Signals
-- ** displayOpened #signal:displayOpened#

    C_DisplayManagerDisplayOpenedCallback   ,
    DisplayManagerDisplayOpenedCallback     ,
#if defined(ENABLE_OVERLOADING)
    DisplayManagerDisplayOpenedSignalInfo   ,
#endif
    afterDisplayManagerDisplayOpened        ,
    genClosure_DisplayManagerDisplayOpened  ,
    mk_DisplayManagerDisplayOpenedCallback  ,
    noDisplayManagerDisplayOpenedCallback   ,
    onDisplayManagerDisplayOpened           ,
    wrap_DisplayManagerDisplayOpenedCallback,




    ) 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.Objects.Display as Gdk.Display

-- | Memory-managed wrapper type.
newtype DisplayManager = DisplayManager (SP.ManagedPtr DisplayManager)
    deriving (DisplayManager -> DisplayManager -> Bool
(DisplayManager -> DisplayManager -> Bool)
-> (DisplayManager -> DisplayManager -> Bool) -> Eq DisplayManager
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisplayManager -> DisplayManager -> Bool
$c/= :: DisplayManager -> DisplayManager -> Bool
== :: DisplayManager -> DisplayManager -> Bool
$c== :: DisplayManager -> DisplayManager -> Bool
Eq)

instance SP.ManagedPtrNewtype DisplayManager where
    toManagedPtr :: DisplayManager -> ManagedPtr DisplayManager
toManagedPtr (DisplayManager ManagedPtr DisplayManager
p) = ManagedPtr DisplayManager
p

foreign import ccall "gdk_display_manager_get_type"
    c_gdk_display_manager_get_type :: IO B.Types.GType

instance B.Types.TypedObject DisplayManager where
    glibType :: IO GType
glibType = IO GType
c_gdk_display_manager_get_type

instance B.Types.GObject DisplayManager

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

-- | Type class for types which can be safely cast to `DisplayManager`, for instance with `toDisplayManager`.
class (SP.GObject o, O.IsDescendantOf DisplayManager o) => IsDisplayManager o
instance (SP.GObject o, O.IsDescendantOf DisplayManager o) => IsDisplayManager o

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveDisplayManagerMethod (t :: Symbol) (o :: *) :: * where
    ResolveDisplayManagerMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDisplayManagerMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDisplayManagerMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDisplayManagerMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDisplayManagerMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDisplayManagerMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDisplayManagerMethod "listDisplays" o = DisplayManagerListDisplaysMethodInfo
    ResolveDisplayManagerMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDisplayManagerMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDisplayManagerMethod "openDisplay" o = DisplayManagerOpenDisplayMethodInfo
    ResolveDisplayManagerMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDisplayManagerMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDisplayManagerMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDisplayManagerMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDisplayManagerMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDisplayManagerMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDisplayManagerMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDisplayManagerMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDisplayManagerMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDisplayManagerMethod "getDefaultDisplay" o = DisplayManagerGetDefaultDisplayMethodInfo
    ResolveDisplayManagerMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDisplayManagerMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDisplayManagerMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDisplayManagerMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDisplayManagerMethod "setDefaultDisplay" o = DisplayManagerSetDefaultDisplayMethodInfo
    ResolveDisplayManagerMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDisplayManagerMethod l o = O.MethodResolutionFailed l o

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

#endif

-- signal DisplayManager::display-opened
-- | The [displayOpened](#g:signal:displayOpened) signal is emitted when a display is opened.
type DisplayManagerDisplayOpenedCallback =
    Gdk.Display.Display
    -- ^ /@display@/: the opened display
    -> IO ()

-- | A convenience synonym for @`Nothing` :: `Maybe` `DisplayManagerDisplayOpenedCallback`@.
noDisplayManagerDisplayOpenedCallback :: Maybe DisplayManagerDisplayOpenedCallback
noDisplayManagerDisplayOpenedCallback :: Maybe DisplayManagerDisplayOpenedCallback
noDisplayManagerDisplayOpenedCallback = Maybe DisplayManagerDisplayOpenedCallback
forall a. Maybe a
Nothing

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

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

-- | Wrap the callback into a `GClosure`.
genClosure_DisplayManagerDisplayOpened :: MonadIO m => DisplayManagerDisplayOpenedCallback -> m (GClosure C_DisplayManagerDisplayOpenedCallback)
genClosure_DisplayManagerDisplayOpened :: DisplayManagerDisplayOpenedCallback
-> m (GClosure C_DisplayManagerDisplayOpenedCallback)
genClosure_DisplayManagerDisplayOpened DisplayManagerDisplayOpenedCallback
cb = IO (GClosure C_DisplayManagerDisplayOpenedCallback)
-> m (GClosure C_DisplayManagerDisplayOpenedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_DisplayManagerDisplayOpenedCallback)
 -> m (GClosure C_DisplayManagerDisplayOpenedCallback))
-> IO (GClosure C_DisplayManagerDisplayOpenedCallback)
-> m (GClosure C_DisplayManagerDisplayOpenedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_DisplayManagerDisplayOpenedCallback
cb' = DisplayManagerDisplayOpenedCallback
-> C_DisplayManagerDisplayOpenedCallback
wrap_DisplayManagerDisplayOpenedCallback DisplayManagerDisplayOpenedCallback
cb
    C_DisplayManagerDisplayOpenedCallback
-> IO (FunPtr C_DisplayManagerDisplayOpenedCallback)
mk_DisplayManagerDisplayOpenedCallback C_DisplayManagerDisplayOpenedCallback
cb' IO (FunPtr C_DisplayManagerDisplayOpenedCallback)
-> (FunPtr C_DisplayManagerDisplayOpenedCallback
    -> IO (GClosure C_DisplayManagerDisplayOpenedCallback))
-> IO (GClosure C_DisplayManagerDisplayOpenedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_DisplayManagerDisplayOpenedCallback
-> IO (GClosure C_DisplayManagerDisplayOpenedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure


-- | Wrap a `DisplayManagerDisplayOpenedCallback` into a `C_DisplayManagerDisplayOpenedCallback`.
wrap_DisplayManagerDisplayOpenedCallback ::
    DisplayManagerDisplayOpenedCallback ->
    C_DisplayManagerDisplayOpenedCallback
wrap_DisplayManagerDisplayOpenedCallback :: DisplayManagerDisplayOpenedCallback
-> C_DisplayManagerDisplayOpenedCallback
wrap_DisplayManagerDisplayOpenedCallback DisplayManagerDisplayOpenedCallback
_cb Ptr ()
_ Ptr Display
display Ptr ()
_ = do
    Display
display' <- ((ManagedPtr Display -> Display) -> Ptr Display -> IO Display
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Display -> Display
Gdk.Display.Display) Ptr Display
display
    DisplayManagerDisplayOpenedCallback
_cb  Display
display'


-- | Connect a signal handler for the [displayOpened](#signal:displayOpened) 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' displayManager #displayOpened callback
-- @
-- 
-- 
onDisplayManagerDisplayOpened :: (IsDisplayManager a, MonadIO m) => a -> DisplayManagerDisplayOpenedCallback -> m SignalHandlerId
onDisplayManagerDisplayOpened :: a -> DisplayManagerDisplayOpenedCallback -> m SignalHandlerId
onDisplayManagerDisplayOpened a
obj DisplayManagerDisplayOpenedCallback
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_DisplayManagerDisplayOpenedCallback
cb' = DisplayManagerDisplayOpenedCallback
-> C_DisplayManagerDisplayOpenedCallback
wrap_DisplayManagerDisplayOpenedCallback DisplayManagerDisplayOpenedCallback
cb
    FunPtr C_DisplayManagerDisplayOpenedCallback
cb'' <- C_DisplayManagerDisplayOpenedCallback
-> IO (FunPtr C_DisplayManagerDisplayOpenedCallback)
mk_DisplayManagerDisplayOpenedCallback C_DisplayManagerDisplayOpenedCallback
cb'
    a
-> Text
-> FunPtr C_DisplayManagerDisplayOpenedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"display-opened" FunPtr C_DisplayManagerDisplayOpenedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [displayOpened](#signal:displayOpened) 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' displayManager #displayOpened callback
-- @
-- 
-- 
afterDisplayManagerDisplayOpened :: (IsDisplayManager a, MonadIO m) => a -> DisplayManagerDisplayOpenedCallback -> m SignalHandlerId
afterDisplayManagerDisplayOpened :: a -> DisplayManagerDisplayOpenedCallback -> m SignalHandlerId
afterDisplayManagerDisplayOpened a
obj DisplayManagerDisplayOpenedCallback
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_DisplayManagerDisplayOpenedCallback
cb' = DisplayManagerDisplayOpenedCallback
-> C_DisplayManagerDisplayOpenedCallback
wrap_DisplayManagerDisplayOpenedCallback DisplayManagerDisplayOpenedCallback
cb
    FunPtr C_DisplayManagerDisplayOpenedCallback
cb'' <- C_DisplayManagerDisplayOpenedCallback
-> IO (FunPtr C_DisplayManagerDisplayOpenedCallback)
mk_DisplayManagerDisplayOpenedCallback C_DisplayManagerDisplayOpenedCallback
cb'
    a
-> Text
-> FunPtr C_DisplayManagerDisplayOpenedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"display-opened" FunPtr C_DisplayManagerDisplayOpenedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data DisplayManagerDisplayOpenedSignalInfo
instance SignalInfo DisplayManagerDisplayOpenedSignalInfo where
    type HaskellCallbackType DisplayManagerDisplayOpenedSignalInfo = DisplayManagerDisplayOpenedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_DisplayManagerDisplayOpenedCallback cb
        cb'' <- mk_DisplayManagerDisplayOpenedCallback cb'
        connectSignalFunPtr obj "display-opened" cb'' connectMode detail

#endif

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

-- | Get the value of the “@default-display@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' displayManager #defaultDisplay
-- @
getDisplayManagerDefaultDisplay :: (MonadIO m, IsDisplayManager o) => o -> m (Maybe Gdk.Display.Display)
getDisplayManagerDefaultDisplay :: o -> m (Maybe Display)
getDisplayManagerDefaultDisplay o
obj = 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
$ o
-> String -> (ManagedPtr Display -> Display) -> IO (Maybe Display)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"default-display" ManagedPtr Display -> Display
Gdk.Display.Display

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

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

#if defined(ENABLE_OVERLOADING)
data DisplayManagerDefaultDisplayPropertyInfo
instance AttrInfo DisplayManagerDefaultDisplayPropertyInfo where
    type AttrAllowedOps DisplayManagerDefaultDisplayPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint DisplayManagerDefaultDisplayPropertyInfo = IsDisplayManager
    type AttrSetTypeConstraint DisplayManagerDefaultDisplayPropertyInfo = Gdk.Display.IsDisplay
    type AttrTransferTypeConstraint DisplayManagerDefaultDisplayPropertyInfo = Gdk.Display.IsDisplay
    type AttrTransferType DisplayManagerDefaultDisplayPropertyInfo = Gdk.Display.Display
    type AttrGetType DisplayManagerDefaultDisplayPropertyInfo = (Maybe Gdk.Display.Display)
    type AttrLabel DisplayManagerDefaultDisplayPropertyInfo = "default-display"
    type AttrOrigin DisplayManagerDefaultDisplayPropertyInfo = DisplayManager
    attrGet = getDisplayManagerDefaultDisplay
    attrSet = setDisplayManagerDefaultDisplay
    attrTransfer _ v = do
        unsafeCastTo Gdk.Display.Display v
    attrConstruct = constructDisplayManagerDefaultDisplay
    attrClear = undefined
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DisplayManager
type instance O.AttributeList DisplayManager = DisplayManagerAttributeList
type DisplayManagerAttributeList = ('[ '("defaultDisplay", DisplayManagerDefaultDisplayPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
displayManagerDefaultDisplay :: AttrLabelProxy "defaultDisplay"
displayManagerDefaultDisplay = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DisplayManager = DisplayManagerSignalList
type DisplayManagerSignalList = ('[ '("displayOpened", DisplayManagerDisplayOpenedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method DisplayManager::get_default_display
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DisplayManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDisplayManager"
--                 , 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_manager_get_default_display" gdk_display_manager_get_default_display :: 
    Ptr DisplayManager ->                   -- manager : TInterface (Name {namespace = "Gdk", name = "DisplayManager"})
    IO (Ptr Gdk.Display.Display)

-- | Gets the default t'GI.Gdk.Objects.Display.Display'.
displayManagerGetDefaultDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplayManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Gdk.Objects.DisplayManager.DisplayManager'
    -> m (Maybe Gdk.Display.Display)
    -- ^ __Returns:__ a t'GI.Gdk.Objects.Display.Display', or 'P.Nothing' if
    --     there is no default display.
displayManagerGetDefaultDisplay :: a -> m (Maybe Display)
displayManagerGetDefaultDisplay a
manager = 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 DisplayManager
manager' <- a -> IO (Ptr DisplayManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr Display
result <- Ptr DisplayManager -> IO (Ptr Display)
gdk_display_manager_get_default_display Ptr DisplayManager
manager'
    Maybe Display
maybeResult <- Ptr Display -> (Ptr Display -> IO Display) -> IO (Maybe Display)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Display
result ((Ptr Display -> IO Display) -> IO (Maybe Display))
-> (Ptr Display -> IO Display) -> IO (Maybe Display)
forall a b. (a -> b) -> a -> b
$ \Ptr Display
result' -> do
        Display
result'' <- ((ManagedPtr Display -> Display) -> Ptr Display -> IO Display
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Display -> Display
Gdk.Display.Display) Ptr Display
result'
        Display -> IO Display
forall (m :: * -> *) a. Monad m => a -> m a
return Display
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    Maybe Display -> IO (Maybe Display)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Display
maybeResult

#if defined(ENABLE_OVERLOADING)
data DisplayManagerGetDefaultDisplayMethodInfo
instance (signature ~ (m (Maybe Gdk.Display.Display)), MonadIO m, IsDisplayManager a) => O.MethodInfo DisplayManagerGetDefaultDisplayMethodInfo a signature where
    overloadedMethod = displayManagerGetDefaultDisplay

#endif

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

foreign import ccall "gdk_display_manager_list_displays" gdk_display_manager_list_displays :: 
    Ptr DisplayManager ->                   -- manager : TInterface (Name {namespace = "Gdk", name = "DisplayManager"})
    IO (Ptr (GSList (Ptr Gdk.Display.Display)))

-- | List all currently open displays.
displayManagerListDisplays ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplayManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Gdk.Objects.DisplayManager.DisplayManager'
    -> m [Gdk.Display.Display]
    -- ^ __Returns:__ a newly
    --     allocated t'GI.GLib.Structs.SList.SList' of t'GI.Gdk.Objects.Display.Display' objects. Free with @/g_slist_free()/@
    --     when you are done with it.
displayManagerListDisplays :: a -> m [Display]
displayManagerListDisplays a
manager = IO [Display] -> m [Display]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Display] -> m [Display]) -> IO [Display] -> m [Display]
forall a b. (a -> b) -> a -> b
$ do
    Ptr DisplayManager
manager' <- a -> IO (Ptr DisplayManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr (GSList (Ptr Display))
result <- Ptr DisplayManager -> IO (Ptr (GSList (Ptr Display)))
gdk_display_manager_list_displays Ptr DisplayManager
manager'
    [Ptr Display]
result' <- Ptr (GSList (Ptr Display)) -> IO [Ptr Display]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr Display))
result
    [Display]
result'' <- (Ptr Display -> IO Display) -> [Ptr Display] -> IO [Display]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Display -> Display) -> Ptr Display -> IO Display
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Display -> Display
Gdk.Display.Display) [Ptr Display]
result'
    Ptr (GSList (Ptr Display)) -> IO ()
forall a. Ptr (GSList a) -> IO ()
g_slist_free Ptr (GSList (Ptr Display))
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    [Display] -> IO [Display]
forall (m :: * -> *) a. Monad m => a -> m a
return [Display]
result''

#if defined(ENABLE_OVERLOADING)
data DisplayManagerListDisplaysMethodInfo
instance (signature ~ (m [Gdk.Display.Display]), MonadIO m, IsDisplayManager a) => O.MethodInfo DisplayManagerListDisplaysMethodInfo a signature where
    overloadedMethod = displayManagerListDisplays

#endif

-- method DisplayManager::open_display
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DisplayManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDisplayManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "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_manager_open_display" gdk_display_manager_open_display :: 
    Ptr DisplayManager ->                   -- manager : TInterface (Name {namespace = "Gdk", name = "DisplayManager"})
    CString ->                              -- name : TBasicType TUTF8
    IO (Ptr Gdk.Display.Display)

-- | Opens a display.
displayManagerOpenDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplayManager a) =>
    a
    -- ^ /@manager@/: a t'GI.Gdk.Objects.DisplayManager.DisplayManager'
    -> T.Text
    -- ^ /@name@/: the name of the display to open
    -> m (Maybe Gdk.Display.Display)
    -- ^ __Returns:__ a t'GI.Gdk.Objects.Display.Display', or 'P.Nothing' if the
    --     display could not be opened
displayManagerOpenDisplay :: a -> Text -> m (Maybe Display)
displayManagerOpenDisplay a
manager Text
name = 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 DisplayManager
manager' <- a -> IO (Ptr DisplayManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    CString
name' <- Text -> IO CString
textToCString Text
name
    Ptr Display
result <- Ptr DisplayManager -> CString -> IO (Ptr Display)
gdk_display_manager_open_display Ptr DisplayManager
manager' CString
name'
    Maybe Display
maybeResult <- Ptr Display -> (Ptr Display -> IO Display) -> IO (Maybe Display)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Display
result ((Ptr Display -> IO Display) -> IO (Maybe Display))
-> (Ptr Display -> IO Display) -> IO (Maybe Display)
forall a b. (a -> b) -> a -> b
$ \Ptr Display
result' -> do
        Display
result'' <- ((ManagedPtr Display -> Display) -> Ptr Display -> IO Display
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Display -> Display
Gdk.Display.Display) Ptr Display
result'
        Display -> IO Display
forall (m :: * -> *) a. Monad m => a -> m a
return Display
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
    Maybe Display -> IO (Maybe Display)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Display
maybeResult

#if defined(ENABLE_OVERLOADING)
data DisplayManagerOpenDisplayMethodInfo
instance (signature ~ (T.Text -> m (Maybe Gdk.Display.Display)), MonadIO m, IsDisplayManager a) => O.MethodInfo DisplayManagerOpenDisplayMethodInfo a signature where
    overloadedMethod = displayManagerOpenDisplay

#endif

-- method DisplayManager::set_default_display
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "manager"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DisplayManager" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkDisplayManager"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , 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_manager_set_default_display" gdk_display_manager_set_default_display :: 
    Ptr DisplayManager ->                   -- manager : TInterface (Name {namespace = "Gdk", name = "DisplayManager"})
    Ptr Gdk.Display.Display ->              -- display : TInterface (Name {namespace = "Gdk", name = "Display"})
    IO ()

-- | Sets /@display@/ as the default display.
displayManagerSetDefaultDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsDisplayManager a, Gdk.Display.IsDisplay b) =>
    a
    -- ^ /@manager@/: a t'GI.Gdk.Objects.DisplayManager.DisplayManager'
    -> b
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m ()
displayManagerSetDefaultDisplay :: a -> b -> m ()
displayManagerSetDefaultDisplay a
manager b
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 DisplayManager
manager' <- a -> IO (Ptr DisplayManager)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
manager
    Ptr Display
display' <- b -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
display
    Ptr DisplayManager -> Ptr Display -> IO ()
gdk_display_manager_set_default_display Ptr DisplayManager
manager' Ptr Display
display'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
manager
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
display
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data DisplayManagerSetDefaultDisplayMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsDisplayManager a, Gdk.Display.IsDisplay b) => O.MethodInfo DisplayManagerSetDefaultDisplayMethodInfo a signature where
    overloadedMethod = displayManagerSetDefaultDisplay

#endif

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

foreign import ccall "gdk_display_manager_get" gdk_display_manager_get :: 
    IO (Ptr DisplayManager)

-- | Gets the singleton t'GI.Gdk.Objects.DisplayManager.DisplayManager' object.
-- 
-- When called for the first time, this function consults the
-- @GDK_BACKEND@ environment variable to find out which
-- of the supported GDK backends to use (in case GDK has been compiled
-- with multiple backends). Applications can use 'GI.Gdk.Functions.setAllowedBackends'
-- to limit what backends can be used.
displayManagerGet ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m DisplayManager
    -- ^ __Returns:__ The global t'GI.Gdk.Objects.DisplayManager.DisplayManager' singleton;
    --     @/gdk_parse_args()/@, @/gdk_init()/@, or @/gdk_init_check()/@ must have
    --     been called first.
displayManagerGet :: m DisplayManager
displayManagerGet  = IO DisplayManager -> m DisplayManager
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DisplayManager -> m DisplayManager)
-> IO DisplayManager -> m DisplayManager
forall a b. (a -> b) -> a -> b
$ do
    Ptr DisplayManager
result <- IO (Ptr DisplayManager)
gdk_display_manager_get
    Text -> Ptr DisplayManager -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"displayManagerGet" Ptr DisplayManager
result
    DisplayManager
result' <- ((ManagedPtr DisplayManager -> DisplayManager)
-> Ptr DisplayManager -> IO DisplayManager
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr DisplayManager -> DisplayManager
DisplayManager) Ptr DisplayManager
result
    DisplayManager -> IO DisplayManager
forall (m :: * -> *) a. Monad m => a -> m a
return DisplayManager
result'

#if defined(ENABLE_OVERLOADING)
#endif