{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- GdkAppLaunchContext is an implementation of t'GI.Gio.Objects.AppLaunchContext.AppLaunchContext' that
-- handles launching an application in a graphical context. It provides
-- startup notification and allows to launch applications on a specific
-- screen or workspace.
-- 
-- == Launching an application
-- 
-- 
-- === /C code/
-- >
-- >GdkAppLaunchContext *context;
-- >
-- >context = gdk_display_get_app_launch_context (display);
-- >
-- >gdk_app_launch_context_set_screen (screen);
-- >gdk_app_launch_context_set_timestamp (event->time);
-- >
-- >if (!g_app_info_launch_default_for_uri ("http://www.gtk.org", context, &error))
-- >  g_warning ("Launching failed: %s\n", error->message);
-- >
-- >g_object_unref (context);
-- 

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

module GI.Gdk.Objects.AppLaunchContext
    ( 

-- * Exported types
    AppLaunchContext(..)                    ,
    IsAppLaunchContext                      ,
    toAppLaunchContext                      ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [launchFailed]("GI.Gio.Objects.AppLaunchContext#g:method:launchFailed"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [setenv]("GI.Gio.Objects.AppLaunchContext#g:method:setenv"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unsetenv]("GI.Gio.Objects.AppLaunchContext#g:method:unsetenv"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDisplay]("GI.Gio.Objects.AppLaunchContext#g:method:getDisplay"), [getEnvironment]("GI.Gio.Objects.AppLaunchContext#g:method:getEnvironment"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getStartupNotifyId]("GI.Gio.Objects.AppLaunchContext#g:method:getStartupNotifyId").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDesktop]("GI.Gdk.Objects.AppLaunchContext#g:method:setDesktop"), [setDisplay]("GI.Gdk.Objects.AppLaunchContext#g:method:setDisplay"), [setIcon]("GI.Gdk.Objects.AppLaunchContext#g:method:setIcon"), [setIconName]("GI.Gdk.Objects.AppLaunchContext#g:method:setIconName"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setScreen]("GI.Gdk.Objects.AppLaunchContext#g:method:setScreen"), [setTimestamp]("GI.Gdk.Objects.AppLaunchContext#g:method:setTimestamp").

#if defined(ENABLE_OVERLOADING)
    ResolveAppLaunchContextMethod           ,
#endif

-- ** new #method:new#

    appLaunchContextNew                     ,


-- ** setDesktop #method:setDesktop#

#if defined(ENABLE_OVERLOADING)
    AppLaunchContextSetDesktopMethodInfo    ,
#endif
    appLaunchContextSetDesktop              ,


-- ** setDisplay #method:setDisplay#

#if defined(ENABLE_OVERLOADING)
    AppLaunchContextSetDisplayMethodInfo    ,
#endif
    appLaunchContextSetDisplay              ,


-- ** setIcon #method:setIcon#

#if defined(ENABLE_OVERLOADING)
    AppLaunchContextSetIconMethodInfo       ,
#endif
    appLaunchContextSetIcon                 ,


-- ** setIconName #method:setIconName#

#if defined(ENABLE_OVERLOADING)
    AppLaunchContextSetIconNameMethodInfo   ,
#endif
    appLaunchContextSetIconName             ,


-- ** setScreen #method:setScreen#

#if defined(ENABLE_OVERLOADING)
    AppLaunchContextSetScreenMethodInfo     ,
#endif
    appLaunchContextSetScreen               ,


-- ** setTimestamp #method:setTimestamp#

#if defined(ENABLE_OVERLOADING)
    AppLaunchContextSetTimestampMethodInfo  ,
#endif
    appLaunchContextSetTimestamp            ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    AppLaunchContextDisplayPropertyInfo     ,
#endif
#if defined(ENABLE_OVERLOADING)
    appLaunchContextDisplay                 ,
#endif
    constructAppLaunchContextDisplay        ,
    getAppLaunchContextDisplay              ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.Cairo.Enums as Cairo.Enums
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.Cairo.Structs.Pattern as Cairo.Pattern
import qualified GI.Cairo.Structs.Region as Cairo.Region
import qualified GI.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Callbacks as Gdk.Callbacks
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Objects.Cursor as Gdk.Cursor
import {-# SOURCE #-} qualified GI.Gdk.Objects.Device as Gdk.Device
import {-# SOURCE #-} qualified GI.Gdk.Objects.DeviceManager as Gdk.DeviceManager
import {-# SOURCE #-} qualified GI.Gdk.Objects.DeviceTool as Gdk.DeviceTool
import {-# SOURCE #-} qualified GI.Gdk.Objects.Display as Gdk.Display
import {-# SOURCE #-} qualified GI.Gdk.Objects.DragContext as Gdk.DragContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.DrawingContext as Gdk.DrawingContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import {-# SOURCE #-} qualified GI.Gdk.Objects.GLContext as Gdk.GLContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Monitor as Gdk.Monitor
import {-# SOURCE #-} qualified GI.Gdk.Objects.Screen as Gdk.Screen
import {-# SOURCE #-} qualified GI.Gdk.Objects.Seat as Gdk.Seat
import {-# SOURCE #-} qualified GI.Gdk.Objects.Visual as Gdk.Visual
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window
import {-# SOURCE #-} qualified GI.Gdk.Structs.Atom as Gdk.Atom
import {-# SOURCE #-} qualified GI.Gdk.Structs.Color as Gdk.Color
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventAny as Gdk.EventAny
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventButton as Gdk.EventButton
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventConfigure as Gdk.EventConfigure
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventCrossing as Gdk.EventCrossing
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventDND as Gdk.EventDND
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventExpose as Gdk.EventExpose
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventFocus as Gdk.EventFocus
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventGrabBroken as Gdk.EventGrabBroken
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventKey as Gdk.EventKey
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventMotion as Gdk.EventMotion
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventOwnerChange as Gdk.EventOwnerChange
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadAxis as Gdk.EventPadAxis
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadButton as Gdk.EventPadButton
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadGroupMode as Gdk.EventPadGroupMode
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventProperty as Gdk.EventProperty
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventProximity as Gdk.EventProximity
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventScroll as Gdk.EventScroll
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSelection as Gdk.EventSelection
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSequence as Gdk.EventSequence
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSetting as Gdk.EventSetting
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouch as Gdk.EventTouch
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouchpadPinch as Gdk.EventTouchpadPinch
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouchpadSwipe as Gdk.EventTouchpadSwipe
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventVisibility as Gdk.EventVisibility
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventWindowState as Gdk.EventWindowState
import {-# SOURCE #-} qualified GI.Gdk.Structs.FrameTimings as Gdk.FrameTimings
import {-# SOURCE #-} qualified GI.Gdk.Structs.Geometry as Gdk.Geometry
import {-# SOURCE #-} qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import {-# SOURCE #-} qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import {-# SOURCE #-} qualified GI.Gdk.Structs.WindowAttr as Gdk.WindowAttr
import {-# SOURCE #-} qualified GI.Gdk.Unions.Event as Gdk.Event
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Objects.AppLaunchContext as Gio.AppLaunchContext

#else
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gdk.Objects.Display as Gdk.Display
import {-# SOURCE #-} qualified GI.Gdk.Objects.Screen as Gdk.Screen
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Objects.AppLaunchContext as Gio.AppLaunchContext

#endif

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

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

foreign import ccall "gdk_app_launch_context_get_type"
    c_gdk_app_launch_context_get_type :: IO B.Types.GType

instance B.Types.TypedObject AppLaunchContext where
    glibType :: IO GType
glibType = IO GType
c_gdk_app_launch_context_get_type

instance B.Types.GObject AppLaunchContext

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

instance O.HasParentTypes AppLaunchContext
type instance O.ParentTypes AppLaunchContext = '[Gio.AppLaunchContext.AppLaunchContext, GObject.Object.Object]

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

-- | Convert 'AppLaunchContext' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe AppLaunchContext) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_app_launch_context_get_type
    gvalueSet_ :: Ptr GValue -> Maybe AppLaunchContext -> IO ()
gvalueSet_ Ptr GValue
gv Maybe AppLaunchContext
P.Nothing = Ptr GValue -> Ptr AppLaunchContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr AppLaunchContext
forall a. Ptr a
FP.nullPtr :: FP.Ptr AppLaunchContext)
    gvalueSet_ Ptr GValue
gv (P.Just AppLaunchContext
obj) = AppLaunchContext -> (Ptr AppLaunchContext -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AppLaunchContext
obj (Ptr GValue -> Ptr AppLaunchContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe AppLaunchContext)
gvalueGet_ Ptr GValue
gv = do
        Ptr AppLaunchContext
ptr <- Ptr GValue -> IO (Ptr AppLaunchContext)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr AppLaunchContext)
        if Ptr AppLaunchContext
ptr Ptr AppLaunchContext -> Ptr AppLaunchContext -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr AppLaunchContext
forall a. Ptr a
FP.nullPtr
        then AppLaunchContext -> Maybe AppLaunchContext
forall a. a -> Maybe a
P.Just (AppLaunchContext -> Maybe AppLaunchContext)
-> IO AppLaunchContext -> IO (Maybe AppLaunchContext)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr AppLaunchContext -> AppLaunchContext)
-> Ptr AppLaunchContext -> IO AppLaunchContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr AppLaunchContext -> AppLaunchContext
AppLaunchContext Ptr AppLaunchContext
ptr
        else Maybe AppLaunchContext -> IO (Maybe AppLaunchContext)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AppLaunchContext
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveAppLaunchContextMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveAppLaunchContextMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveAppLaunchContextMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveAppLaunchContextMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveAppLaunchContextMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveAppLaunchContextMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveAppLaunchContextMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveAppLaunchContextMethod "launchFailed" o = Gio.AppLaunchContext.AppLaunchContextLaunchFailedMethodInfo
    ResolveAppLaunchContextMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveAppLaunchContextMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveAppLaunchContextMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveAppLaunchContextMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveAppLaunchContextMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveAppLaunchContextMethod "setenv" o = Gio.AppLaunchContext.AppLaunchContextSetenvMethodInfo
    ResolveAppLaunchContextMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveAppLaunchContextMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveAppLaunchContextMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveAppLaunchContextMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveAppLaunchContextMethod "unsetenv" o = Gio.AppLaunchContext.AppLaunchContextUnsetenvMethodInfo
    ResolveAppLaunchContextMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveAppLaunchContextMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveAppLaunchContextMethod "getDisplay" o = Gio.AppLaunchContext.AppLaunchContextGetDisplayMethodInfo
    ResolveAppLaunchContextMethod "getEnvironment" o = Gio.AppLaunchContext.AppLaunchContextGetEnvironmentMethodInfo
    ResolveAppLaunchContextMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveAppLaunchContextMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveAppLaunchContextMethod "getStartupNotifyId" o = Gio.AppLaunchContext.AppLaunchContextGetStartupNotifyIdMethodInfo
    ResolveAppLaunchContextMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveAppLaunchContextMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveAppLaunchContextMethod "setDesktop" o = AppLaunchContextSetDesktopMethodInfo
    ResolveAppLaunchContextMethod "setDisplay" o = AppLaunchContextSetDisplayMethodInfo
    ResolveAppLaunchContextMethod "setIcon" o = AppLaunchContextSetIconMethodInfo
    ResolveAppLaunchContextMethod "setIconName" o = AppLaunchContextSetIconNameMethodInfo
    ResolveAppLaunchContextMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveAppLaunchContextMethod "setScreen" o = AppLaunchContextSetScreenMethodInfo
    ResolveAppLaunchContextMethod "setTimestamp" o = AppLaunchContextSetTimestampMethodInfo
    ResolveAppLaunchContextMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveAppLaunchContextMethod t AppLaunchContext, O.OverloadedMethod info AppLaunchContext p, R.HasField t AppLaunchContext p) => R.HasField t AppLaunchContext p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveAppLaunchContextMethod t AppLaunchContext, O.OverloadedMethodInfo info AppLaunchContext) => OL.IsLabel t (O.MethodProxy info AppLaunchContext) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

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

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

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

#if defined(ENABLE_OVERLOADING)
data AppLaunchContextDisplayPropertyInfo
instance AttrInfo AppLaunchContextDisplayPropertyInfo where
    type AttrAllowedOps AppLaunchContextDisplayPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint AppLaunchContextDisplayPropertyInfo = IsAppLaunchContext
    type AttrSetTypeConstraint AppLaunchContextDisplayPropertyInfo = Gdk.Display.IsDisplay
    type AttrTransferTypeConstraint AppLaunchContextDisplayPropertyInfo = Gdk.Display.IsDisplay
    type AttrTransferType AppLaunchContextDisplayPropertyInfo = Gdk.Display.Display
    type AttrGetType AppLaunchContextDisplayPropertyInfo = (Maybe Gdk.Display.Display)
    type AttrLabel AppLaunchContextDisplayPropertyInfo = "display"
    type AttrOrigin AppLaunchContextDisplayPropertyInfo = AppLaunchContext
    attrGet = getAppLaunchContextDisplay
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gdk.Display.Display v
    attrConstruct = constructAppLaunchContextDisplay
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.AppLaunchContext.display"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-AppLaunchContext.html#g:attr:display"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AppLaunchContext
type instance O.AttributeList AppLaunchContext = AppLaunchContextAttributeList
type AppLaunchContextAttributeList = ('[ '("display", AppLaunchContextDisplayPropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
appLaunchContextDisplay :: AttrLabelProxy "display"
appLaunchContextDisplay = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList AppLaunchContext = AppLaunchContextSignalList
type AppLaunchContextSignalList = ('[ '("launchFailed", Gio.AppLaunchContext.AppLaunchContextLaunchFailedSignalInfo), '("launchStarted", Gio.AppLaunchContext.AppLaunchContextLaunchStartedSignalInfo), '("launched", Gio.AppLaunchContext.AppLaunchContextLaunchedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

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

foreign import ccall "gdk_app_launch_context_new" gdk_app_launch_context_new :: 
    IO (Ptr AppLaunchContext)

{-# DEPRECATED appLaunchContextNew ["(Since version 3.0)","Use 'GI.Gdk.Objects.Display.displayGetAppLaunchContext' instead"] #-}
-- | Creates a new t'GI.Gdk.Objects.AppLaunchContext.AppLaunchContext'.
-- 
-- /Since: 2.14/
appLaunchContextNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m AppLaunchContext
    -- ^ __Returns:__ a new t'GI.Gdk.Objects.AppLaunchContext.AppLaunchContext'
appLaunchContextNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m AppLaunchContext
appLaunchContextNew  = IO AppLaunchContext -> m AppLaunchContext
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AppLaunchContext -> m AppLaunchContext)
-> IO AppLaunchContext -> m AppLaunchContext
forall a b. (a -> b) -> a -> b
$ do
    Ptr AppLaunchContext
result <- IO (Ptr AppLaunchContext)
gdk_app_launch_context_new
    Text -> Ptr AppLaunchContext -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"appLaunchContextNew" 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
AppLaunchContext) Ptr AppLaunchContext
result
    AppLaunchContext -> IO AppLaunchContext
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return AppLaunchContext
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method AppLaunchContext::set_desktop
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "AppLaunchContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkAppLaunchContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "desktop"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of a workspace, or -1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_app_launch_context_set_desktop" gdk_app_launch_context_set_desktop :: 
    Ptr AppLaunchContext ->                 -- context : TInterface (Name {namespace = "Gdk", name = "AppLaunchContext"})
    Int32 ->                                -- desktop : TBasicType TInt
    IO ()

-- | Sets the workspace on which applications will be launched when
-- using this context when running under a window manager that
-- supports multiple workspaces, as described in the
-- <http://www.freedesktop.org/Standards/wm-spec Extended Window Manager Hints>.
-- 
-- When the workspace is not specified or /@desktop@/ is set to -1,
-- it is up to the window manager to pick one, typically it will
-- be the current workspace.
-- 
-- /Since: 2.14/
appLaunchContextSetDesktop ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppLaunchContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gdk.Objects.AppLaunchContext.AppLaunchContext'
    -> Int32
    -- ^ /@desktop@/: the number of a workspace, or -1
    -> m ()
appLaunchContextSetDesktop :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAppLaunchContext a) =>
a -> Int32 -> m ()
appLaunchContextSetDesktop a
context Int32
desktop = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr AppLaunchContext
context' <- a -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr AppLaunchContext -> Int32 -> IO ()
gdk_app_launch_context_set_desktop Ptr AppLaunchContext
context' Int32
desktop
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AppLaunchContextSetDesktopMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsAppLaunchContext a) => O.OverloadedMethod AppLaunchContextSetDesktopMethodInfo a signature where
    overloadedMethod = appLaunchContextSetDesktop

instance O.OverloadedMethodInfo AppLaunchContextSetDesktopMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.AppLaunchContext.appLaunchContextSetDesktop",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-AppLaunchContext.html#v:appLaunchContextSetDesktop"
        })


#endif

-- method AppLaunchContext::set_display
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "AppLaunchContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkAppLaunchContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = 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
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

{-# DEPRECATED appLaunchContextSetDisplay ["(Since version 3.0)","Use 'GI.Gdk.Objects.Display.displayGetAppLaunchContext' instead"] #-}
-- | Sets the display on which applications will be launched when
-- using this context. See also 'GI.Gdk.Objects.AppLaunchContext.appLaunchContextSetScreen'.
-- 
-- /Since: 2.14/
appLaunchContextSetDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppLaunchContext a, Gdk.Display.IsDisplay b) =>
    a
    -- ^ /@context@/: a t'GI.Gdk.Objects.AppLaunchContext.AppLaunchContext'
    -> b
    -- ^ /@display@/: a t'GI.Gdk.Objects.Display.Display'
    -> m ()
appLaunchContextSetDisplay :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsAppLaunchContext a, IsDisplay b) =>
a -> b -> m ()
appLaunchContextSetDisplay a
context b
display = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr AppLaunchContext
context' <- a -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Display
display' <- b -> IO (Ptr Display)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
display
    Ptr AppLaunchContext -> Ptr Display -> IO ()
gdk_app_launch_context_set_display Ptr AppLaunchContext
context' Ptr Display
display'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
display
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AppLaunchContextSetDisplayMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsAppLaunchContext a, Gdk.Display.IsDisplay b) => O.OverloadedMethod AppLaunchContextSetDisplayMethodInfo a signature where
    overloadedMethod = appLaunchContextSetDisplay

instance O.OverloadedMethodInfo AppLaunchContextSetDisplayMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.AppLaunchContext.appLaunchContextSetDisplay",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-AppLaunchContext.html#v:appLaunchContextSetDisplay"
        })


#endif

-- method AppLaunchContext::set_icon
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "AppLaunchContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkAppLaunchContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon"
--           , argType = TInterface Name { namespace = "Gio" , name = "Icon" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GIcon, or %NULL" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_app_launch_context_set_icon" gdk_app_launch_context_set_icon :: 
    Ptr AppLaunchContext ->                 -- context : TInterface (Name {namespace = "Gdk", name = "AppLaunchContext"})
    Ptr Gio.Icon.Icon ->                    -- icon : TInterface (Name {namespace = "Gio", name = "Icon"})
    IO ()

-- | Sets the icon for applications that are launched with this
-- context.
-- 
-- Window Managers can use this information when displaying startup
-- notification.
-- 
-- See also 'GI.Gdk.Objects.AppLaunchContext.appLaunchContextSetIconName'.
-- 
-- /Since: 2.14/
appLaunchContextSetIcon ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppLaunchContext a, Gio.Icon.IsIcon b) =>
    a
    -- ^ /@context@/: a t'GI.Gdk.Objects.AppLaunchContext.AppLaunchContext'
    -> Maybe (b)
    -- ^ /@icon@/: a t'GI.Gio.Interfaces.Icon.Icon', or 'P.Nothing'
    -> m ()
appLaunchContextSetIcon :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsAppLaunchContext a, IsIcon b) =>
a -> Maybe b -> m ()
appLaunchContextSetIcon a
context Maybe b
icon = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr AppLaunchContext
context' <- a -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Icon
maybeIcon <- case Maybe b
icon of
        Maybe b
Nothing -> Ptr Icon -> IO (Ptr Icon)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Icon
forall a. Ptr a
nullPtr
        Just b
jIcon -> do
            Ptr Icon
jIcon' <- b -> IO (Ptr Icon)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jIcon
            Ptr Icon -> IO (Ptr Icon)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Icon
jIcon'
    Ptr AppLaunchContext -> Ptr Icon -> IO ()
gdk_app_launch_context_set_icon Ptr AppLaunchContext
context' Ptr Icon
maybeIcon
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
icon b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AppLaunchContextSetIconMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsAppLaunchContext a, Gio.Icon.IsIcon b) => O.OverloadedMethod AppLaunchContextSetIconMethodInfo a signature where
    overloadedMethod = appLaunchContextSetIcon

instance O.OverloadedMethodInfo AppLaunchContextSetIconMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.AppLaunchContext.appLaunchContextSetIcon",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-AppLaunchContext.html#v:appLaunchContextSetIcon"
        })


#endif

-- method AppLaunchContext::set_icon_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "AppLaunchContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkAppLaunchContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "icon_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an icon name, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_app_launch_context_set_icon_name" gdk_app_launch_context_set_icon_name :: 
    Ptr AppLaunchContext ->                 -- context : TInterface (Name {namespace = "Gdk", name = "AppLaunchContext"})
    CString ->                              -- icon_name : TBasicType TUTF8
    IO ()

-- | Sets the icon for applications that are launched with this context.
-- The /@iconName@/ will be interpreted in the same way as the Icon field
-- in desktop files. See also 'GI.Gdk.Objects.AppLaunchContext.appLaunchContextSetIcon'.
-- 
-- If both /@icon@/ and /@iconName@/ are set, the /@iconName@/ takes priority.
-- If neither /@icon@/ or /@iconName@/ is set, the icon is taken from either
-- the file that is passed to launched application or from the t'GI.Gio.Interfaces.AppInfo.AppInfo'
-- for the launched application itself.
-- 
-- /Since: 2.14/
appLaunchContextSetIconName ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppLaunchContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gdk.Objects.AppLaunchContext.AppLaunchContext'
    -> Maybe (T.Text)
    -- ^ /@iconName@/: an icon name, or 'P.Nothing'
    -> m ()
appLaunchContextSetIconName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAppLaunchContext a) =>
a -> Maybe Text -> m ()
appLaunchContextSetIconName a
context Maybe Text
iconName = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr AppLaunchContext
context' <- a -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr CChar
maybeIconName <- case Maybe Text
iconName of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jIconName -> do
            Ptr CChar
jIconName' <- Text -> IO (Ptr CChar)
textToCString Text
jIconName
            Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jIconName'
    Ptr AppLaunchContext -> Ptr CChar -> IO ()
gdk_app_launch_context_set_icon_name Ptr AppLaunchContext
context' Ptr CChar
maybeIconName
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeIconName
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AppLaunchContextSetIconNameMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsAppLaunchContext a) => O.OverloadedMethod AppLaunchContextSetIconNameMethodInfo a signature where
    overloadedMethod = appLaunchContextSetIconName

instance O.OverloadedMethodInfo AppLaunchContextSetIconNameMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.AppLaunchContext.appLaunchContextSetIconName",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-AppLaunchContext.html#v:appLaunchContextSetIconName"
        })


#endif

-- method AppLaunchContext::set_screen
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "AppLaunchContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkAppLaunchContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "screen"
--           , argType = TInterface Name { namespace = "Gdk" , name = "Screen" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkScreen" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_app_launch_context_set_screen" gdk_app_launch_context_set_screen :: 
    Ptr AppLaunchContext ->                 -- context : TInterface (Name {namespace = "Gdk", name = "AppLaunchContext"})
    Ptr Gdk.Screen.Screen ->                -- screen : TInterface (Name {namespace = "Gdk", name = "Screen"})
    IO ()

-- | Sets the screen on which applications will be launched when
-- using this context. See also 'GI.Gdk.Objects.AppLaunchContext.appLaunchContextSetDisplay'.
-- 
-- Note that, typically, a t'GI.Gdk.Objects.Screen.Screen' represents a logical screen,
-- not a physical monitor.
-- 
-- If both /@screen@/ and /@display@/ are set, the /@screen@/ takes priority.
-- If neither /@screen@/ or /@display@/ are set, the default screen and
-- display are used.
-- 
-- /Since: 2.14/
appLaunchContextSetScreen ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppLaunchContext a, Gdk.Screen.IsScreen b) =>
    a
    -- ^ /@context@/: a t'GI.Gdk.Objects.AppLaunchContext.AppLaunchContext'
    -> b
    -- ^ /@screen@/: a t'GI.Gdk.Objects.Screen.Screen'
    -> m ()
appLaunchContextSetScreen :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsAppLaunchContext a, IsScreen b) =>
a -> b -> m ()
appLaunchContextSetScreen a
context b
screen = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr AppLaunchContext
context' <- a -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Screen
screen' <- b -> IO (Ptr Screen)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
screen
    Ptr AppLaunchContext -> Ptr Screen -> IO ()
gdk_app_launch_context_set_screen Ptr AppLaunchContext
context' Ptr Screen
screen'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
screen
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AppLaunchContextSetScreenMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsAppLaunchContext a, Gdk.Screen.IsScreen b) => O.OverloadedMethod AppLaunchContextSetScreenMethodInfo a signature where
    overloadedMethod = appLaunchContextSetScreen

instance O.OverloadedMethodInfo AppLaunchContextSetScreenMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.AppLaunchContext.appLaunchContextSetScreen",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-AppLaunchContext.html#v:appLaunchContextSetScreen"
        })


#endif

-- method AppLaunchContext::set_timestamp
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "AppLaunchContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GdkAppLaunchContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "timestamp"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a timestamp" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_app_launch_context_set_timestamp" gdk_app_launch_context_set_timestamp :: 
    Ptr AppLaunchContext ->                 -- context : TInterface (Name {namespace = "Gdk", name = "AppLaunchContext"})
    Word32 ->                               -- timestamp : TBasicType TUInt32
    IO ()

-- | Sets the timestamp of /@context@/. The timestamp should ideally
-- be taken from the event that triggered the launch.
-- 
-- Window managers can use this information to avoid moving the
-- focus to the newly launched application when the user is busy
-- typing in another window. This is also known as \'focus stealing
-- prevention\'.
-- 
-- /Since: 2.14/
appLaunchContextSetTimestamp ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppLaunchContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gdk.Objects.AppLaunchContext.AppLaunchContext'
    -> Word32
    -- ^ /@timestamp@/: a timestamp
    -> m ()
appLaunchContextSetTimestamp :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAppLaunchContext a) =>
a -> Word32 -> m ()
appLaunchContextSetTimestamp a
context Word32
timestamp = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr AppLaunchContext
context' <- a -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr AppLaunchContext -> Word32 -> IO ()
gdk_app_launch_context_set_timestamp Ptr AppLaunchContext
context' Word32
timestamp
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AppLaunchContextSetTimestampMethodInfo
instance (signature ~ (Word32 -> m ()), MonadIO m, IsAppLaunchContext a) => O.OverloadedMethod AppLaunchContextSetTimestampMethodInfo a signature where
    overloadedMethod = appLaunchContextSetTimestamp

instance O.OverloadedMethodInfo AppLaunchContextSetTimestampMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.AppLaunchContext.appLaunchContextSetTimestamp",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-AppLaunchContext.html#v:appLaunchContextSetTimestamp"
        })


#endif