{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Integrating the launch with the launching application. This is used to
-- handle for instance startup notification and launching the new application
-- on the same screen as the launching window.

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

module GI.Gio.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"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveAppLaunchContextMethod           ,
#endif

-- ** getDisplay #method:getDisplay#

#if defined(ENABLE_OVERLOADING)
    AppLaunchContextGetDisplayMethodInfo    ,
#endif
    appLaunchContextGetDisplay              ,


-- ** getEnvironment #method:getEnvironment#

#if defined(ENABLE_OVERLOADING)
    AppLaunchContextGetEnvironmentMethodInfo,
#endif
    appLaunchContextGetEnvironment          ,


-- ** getStartupNotifyId #method:getStartupNotifyId#

#if defined(ENABLE_OVERLOADING)
    AppLaunchContextGetStartupNotifyIdMethodInfo,
#endif
    appLaunchContextGetStartupNotifyId      ,


-- ** launchFailed #method:launchFailed#

#if defined(ENABLE_OVERLOADING)
    AppLaunchContextLaunchFailedMethodInfo  ,
#endif
    appLaunchContextLaunchFailed            ,


-- ** new #method:new#

    appLaunchContextNew                     ,


-- ** setenv #method:setenv#

#if defined(ENABLE_OVERLOADING)
    AppLaunchContextSetenvMethodInfo        ,
#endif
    appLaunchContextSetenv                  ,


-- ** unsetenv #method:unsetenv#

#if defined(ENABLE_OVERLOADING)
    AppLaunchContextUnsetenvMethodInfo      ,
#endif
    appLaunchContextUnsetenv                ,




 -- * Signals


-- ** launchFailed #signal:launchFailed#

    AppLaunchContextLaunchFailedCallback    ,
#if defined(ENABLE_OVERLOADING)
    AppLaunchContextLaunchFailedSignalInfo  ,
#endif
    afterAppLaunchContextLaunchFailed       ,
    onAppLaunchContextLaunchFailed          ,


-- ** launchStarted #signal:launchStarted#

    AppLaunchContextLaunchStartedCallback   ,
#if defined(ENABLE_OVERLOADING)
    AppLaunchContextLaunchStartedSignalInfo ,
#endif
    afterAppLaunchContextLaunchStarted      ,
    onAppLaunchContextLaunchStarted         ,


-- ** launched #signal:launched#

    AppLaunchContextLaunchedCallback        ,
#if defined(ENABLE_OVERLOADING)
    AppLaunchContextLaunchedSignalInfo      ,
#endif
    afterAppLaunchContextLaunched           ,
    onAppLaunchContextLaunched              ,




    ) 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.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Enums as GLib.Enums
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.DateTime as GLib.DateTime
import qualified GI.GLib.Structs.PollFD as GLib.PollFD
import qualified GI.GLib.Structs.Source as GLib.Source
import qualified GI.GLib.Structs.TimeVal as GLib.TimeVal
import qualified GI.GObject.Callbacks as GObject.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Enums as Gio.Enums
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AppInfo as Gio.AppInfo
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Drive as Gio.Drive
import {-# SOURCE #-} qualified GI.Gio.Interfaces.File as Gio.File
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Icon as Gio.Icon
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Mount as Gio.Mount
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Seekable as Gio.Seekable
import {-# SOURCE #-} qualified GI.Gio.Interfaces.Volume as Gio.Volume
import {-# SOURCE #-} qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Gio.Objects.FileEnumerator as Gio.FileEnumerator
import {-# SOURCE #-} qualified GI.Gio.Objects.FileIOStream as Gio.FileIOStream
import {-# SOURCE #-} qualified GI.Gio.Objects.FileInfo as Gio.FileInfo
import {-# SOURCE #-} qualified GI.Gio.Objects.FileInputStream as Gio.FileInputStream
import {-# SOURCE #-} qualified GI.Gio.Objects.FileMonitor as Gio.FileMonitor
import {-# SOURCE #-} qualified GI.Gio.Objects.FileOutputStream as Gio.FileOutputStream
import {-# SOURCE #-} qualified GI.Gio.Objects.IOStream as Gio.IOStream
import {-# SOURCE #-} qualified GI.Gio.Objects.InputStream as Gio.InputStream
import {-# SOURCE #-} qualified GI.Gio.Objects.MountOperation as Gio.MountOperation
import {-# SOURCE #-} qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
import {-# SOURCE #-} qualified GI.Gio.Structs.FileAttributeInfo as Gio.FileAttributeInfo
import {-# SOURCE #-} qualified GI.Gio.Structs.FileAttributeInfoList as Gio.FileAttributeInfoList
import {-# SOURCE #-} qualified GI.Gio.Structs.FileAttributeMatcher as Gio.FileAttributeMatcher
import {-# SOURCE #-} qualified GI.Gio.Structs.OutputVector as Gio.OutputVector

#else
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AppInfo as Gio.AppInfo
import {-# SOURCE #-} qualified GI.Gio.Interfaces.File as Gio.File

#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 "g_app_launch_context_get_type"
    c_g_app_launch_context_get_type :: IO B.Types.GType

instance B.Types.TypedObject AppLaunchContext where
    glibType :: IO GType
glibType = IO GType
c_g_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 = '[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_g_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 <- 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 /= FP.nullPtr
        then P.Just <$> B.ManagedPtr.newObject AppLaunchContext ptr
        else return 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 = 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 = 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 = AppLaunchContextUnsetenvMethodInfo
    ResolveAppLaunchContextMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveAppLaunchContextMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveAppLaunchContextMethod "getDisplay" o = AppLaunchContextGetDisplayMethodInfo
    ResolveAppLaunchContextMethod "getEnvironment" o = AppLaunchContextGetEnvironmentMethodInfo
    ResolveAppLaunchContextMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveAppLaunchContextMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveAppLaunchContextMethod "getStartupNotifyId" o = AppLaunchContextGetStartupNotifyIdMethodInfo
    ResolveAppLaunchContextMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveAppLaunchContextMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveAppLaunchContextMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    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

-- signal AppLaunchContext::launch-failed
-- | The [AppLaunchContext::launchFailed]("GI.Gio.Objects.AppLaunchContext#g:signal:launchFailed") signal is emitted when a t'GI.Gio.Interfaces.AppInfo.AppInfo' launch
-- fails. The startup notification id is provided, so that the launcher
-- can cancel the startup notification.
-- 
-- Because a launch operation may involve spawning multiple instances of the
-- target application, you should expect this signal to be emitted multiple
-- times, one for each spawned instance.
-- 
-- /Since: 2.36/
type AppLaunchContextLaunchFailedCallback =
    T.Text
    -- ^ /@startupNotifyId@/: the startup notification id for the failed launch
    -> IO ()

type C_AppLaunchContextLaunchFailedCallback =
    Ptr AppLaunchContext ->                 -- object
    CString ->
    Ptr () ->                               -- user_data
    IO ()

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

wrap_AppLaunchContextLaunchFailedCallback :: 
    GObject a => (a -> AppLaunchContextLaunchFailedCallback) ->
    C_AppLaunchContextLaunchFailedCallback
wrap_AppLaunchContextLaunchFailedCallback :: forall a.
GObject a =>
(a -> AppLaunchContextLaunchFailedCallback)
-> C_AppLaunchContextLaunchFailedCallback
wrap_AppLaunchContextLaunchFailedCallback a -> AppLaunchContextLaunchFailedCallback
gi'cb Ptr AppLaunchContext
gi'selfPtr CString
startupNotifyId Ptr ()
_ = do
    startupNotifyId' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
startupNotifyId
    B.ManagedPtr.withNewObject gi'selfPtr $ \AppLaunchContext
gi'self -> a -> AppLaunchContextLaunchFailedCallback
gi'cb (AppLaunchContext -> a
forall a b. Coercible a b => a -> b
Coerce.coerce AppLaunchContext
gi'self)  Text
startupNotifyId'


-- | Connect a signal handler for the [launchFailed](#signal:launchFailed) 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' appLaunchContext #launchFailed callback
-- @
-- 
-- 
onAppLaunchContextLaunchFailed :: (IsAppLaunchContext a, MonadIO m) => a -> ((?self :: a) => AppLaunchContextLaunchFailedCallback) -> m SignalHandlerId
onAppLaunchContextLaunchFailed :: forall a (m :: * -> *).
(IsAppLaunchContext a, MonadIO m) =>
a
-> ((?self::a) => AppLaunchContextLaunchFailedCallback)
-> m SignalHandlerId
onAppLaunchContextLaunchFailed a
obj (?self::a) => AppLaunchContextLaunchFailedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> AppLaunchContextLaunchFailedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => AppLaunchContextLaunchFailedCallback
AppLaunchContextLaunchFailedCallback
cb
    let wrapped' :: C_AppLaunchContextLaunchFailedCallback
wrapped' = (a -> AppLaunchContextLaunchFailedCallback)
-> C_AppLaunchContextLaunchFailedCallback
forall a.
GObject a =>
(a -> AppLaunchContextLaunchFailedCallback)
-> C_AppLaunchContextLaunchFailedCallback
wrap_AppLaunchContextLaunchFailedCallback a -> AppLaunchContextLaunchFailedCallback
wrapped
    wrapped'' <- C_AppLaunchContextLaunchFailedCallback
-> IO (FunPtr C_AppLaunchContextLaunchFailedCallback)
mk_AppLaunchContextLaunchFailedCallback C_AppLaunchContextLaunchFailedCallback
wrapped'
    connectSignalFunPtr obj "launch-failed" wrapped'' SignalConnectBefore Nothing

-- | Connect a signal handler for the [launchFailed](#signal:launchFailed) 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' appLaunchContext #launchFailed callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterAppLaunchContextLaunchFailed :: (IsAppLaunchContext a, MonadIO m) => a -> ((?self :: a) => AppLaunchContextLaunchFailedCallback) -> m SignalHandlerId
afterAppLaunchContextLaunchFailed :: forall a (m :: * -> *).
(IsAppLaunchContext a, MonadIO m) =>
a
-> ((?self::a) => AppLaunchContextLaunchFailedCallback)
-> m SignalHandlerId
afterAppLaunchContextLaunchFailed a
obj (?self::a) => AppLaunchContextLaunchFailedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> AppLaunchContextLaunchFailedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => AppLaunchContextLaunchFailedCallback
AppLaunchContextLaunchFailedCallback
cb
    let wrapped' :: C_AppLaunchContextLaunchFailedCallback
wrapped' = (a -> AppLaunchContextLaunchFailedCallback)
-> C_AppLaunchContextLaunchFailedCallback
forall a.
GObject a =>
(a -> AppLaunchContextLaunchFailedCallback)
-> C_AppLaunchContextLaunchFailedCallback
wrap_AppLaunchContextLaunchFailedCallback a -> AppLaunchContextLaunchFailedCallback
wrapped
    wrapped'' <- C_AppLaunchContextLaunchFailedCallback
-> IO (FunPtr C_AppLaunchContextLaunchFailedCallback)
mk_AppLaunchContextLaunchFailedCallback C_AppLaunchContextLaunchFailedCallback
wrapped'
    connectSignalFunPtr obj "launch-failed" wrapped'' SignalConnectAfter Nothing


#if defined(ENABLE_OVERLOADING)
data AppLaunchContextLaunchFailedSignalInfo
instance SignalInfo AppLaunchContextLaunchFailedSignalInfo where
    type HaskellCallbackType AppLaunchContextLaunchFailedSignalInfo = AppLaunchContextLaunchFailedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_AppLaunchContextLaunchFailedCallback cb
        cb'' <- mk_AppLaunchContextLaunchFailedCallback cb'
        connectSignalFunPtr obj "launch-failed" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.AppLaunchContext::launch-failed"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-AppLaunchContext.html#g:signal:launchFailed"})

#endif

-- signal AppLaunchContext::launch-started
-- | The [AppLaunchContext::launchStarted]("GI.Gio.Objects.AppLaunchContext#g:signal:launchStarted") signal is emitted when a t'GI.Gio.Interfaces.AppInfo.AppInfo' is
-- about to be launched. If non-null the /@platformData@/ is an
-- GVariant dictionary mapping strings to variants (ie @a{sv}@), which
-- contains additional, platform-specific data about this launch. On
-- UNIX, at least the @startup-notification-id@ keys will be
-- present.
-- 
-- The value of the @startup-notification-id@ key (type @s@) is a startup
-- notification ID corresponding to the format from the <https://specifications.freedesktop.org/startup-notification-spec/startup-notification-0.1.txt startup-notification
-- specification>.
-- It allows tracking the progress of the launchee through startup.
-- 
-- It is guaranteed that this signal is followed by either a [AppLaunchContext::launched]("GI.Gio.Objects.AppLaunchContext#g:signal:launched") or
-- [AppLaunchContext::launchFailed]("GI.Gio.Objects.AppLaunchContext#g:signal:launchFailed") signal.
-- 
-- Because a launch operation may involve spawning multiple instances of the
-- target application, you should expect this signal to be emitted multiple
-- times, one for each spawned instance.
-- 
-- /Since: 2.72/
type AppLaunchContextLaunchStartedCallback =
    Gio.AppInfo.AppInfo
    -- ^ /@info@/: the t'GI.Gio.Interfaces.AppInfo.AppInfo' that is about to be launched
    -> Maybe GVariant
    -- ^ /@platformData@/: additional platform-specific data for this launch
    -> IO ()

type C_AppLaunchContextLaunchStartedCallback =
    Ptr AppLaunchContext ->                 -- object
    Ptr Gio.AppInfo.AppInfo ->
    Ptr GVariant ->
    Ptr () ->                               -- user_data
    IO ()

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

wrap_AppLaunchContextLaunchStartedCallback :: 
    GObject a => (a -> AppLaunchContextLaunchStartedCallback) ->
    C_AppLaunchContextLaunchStartedCallback
wrap_AppLaunchContextLaunchStartedCallback :: forall a.
GObject a =>
(a -> AppLaunchContextLaunchStartedCallback)
-> C_AppLaunchContextLaunchStartedCallback
wrap_AppLaunchContextLaunchStartedCallback a -> AppLaunchContextLaunchStartedCallback
gi'cb Ptr AppLaunchContext
gi'selfPtr Ptr AppInfo
info Ptr GVariant
platformData Ptr ()
_ = do
    info' <- ((ManagedPtr AppInfo -> AppInfo) -> Ptr AppInfo -> IO AppInfo
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr AppInfo -> AppInfo
Gio.AppInfo.AppInfo) Ptr AppInfo
info
    maybePlatformData <-
        if platformData == FP.nullPtr
        then return Nothing
        else do
            platformData' <- B.GVariant.newGVariantFromPtr platformData
            return $ Just platformData'
    B.ManagedPtr.withNewObject gi'selfPtr $ \AppLaunchContext
gi'self -> a -> AppLaunchContextLaunchStartedCallback
gi'cb (AppLaunchContext -> a
forall a b. Coercible a b => a -> b
Coerce.coerce AppLaunchContext
gi'self)  AppInfo
info' Maybe GVariant
maybePlatformData


-- | Connect a signal handler for the [launchStarted](#signal:launchStarted) 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' appLaunchContext #launchStarted callback
-- @
-- 
-- 
onAppLaunchContextLaunchStarted :: (IsAppLaunchContext a, MonadIO m) => a -> ((?self :: a) => AppLaunchContextLaunchStartedCallback) -> m SignalHandlerId
onAppLaunchContextLaunchStarted :: forall a (m :: * -> *).
(IsAppLaunchContext a, MonadIO m) =>
a
-> ((?self::a) => AppLaunchContextLaunchStartedCallback)
-> m SignalHandlerId
onAppLaunchContextLaunchStarted a
obj (?self::a) => AppLaunchContextLaunchStartedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> AppLaunchContextLaunchStartedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => AppLaunchContextLaunchStartedCallback
AppLaunchContextLaunchStartedCallback
cb
    let wrapped' :: C_AppLaunchContextLaunchStartedCallback
wrapped' = (a -> AppLaunchContextLaunchStartedCallback)
-> C_AppLaunchContextLaunchStartedCallback
forall a.
GObject a =>
(a -> AppLaunchContextLaunchStartedCallback)
-> C_AppLaunchContextLaunchStartedCallback
wrap_AppLaunchContextLaunchStartedCallback a -> AppLaunchContextLaunchStartedCallback
wrapped
    wrapped'' <- C_AppLaunchContextLaunchStartedCallback
-> IO (FunPtr C_AppLaunchContextLaunchStartedCallback)
mk_AppLaunchContextLaunchStartedCallback C_AppLaunchContextLaunchStartedCallback
wrapped'
    connectSignalFunPtr obj "launch-started" wrapped'' SignalConnectBefore Nothing

-- | Connect a signal handler for the [launchStarted](#signal:launchStarted) 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' appLaunchContext #launchStarted callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterAppLaunchContextLaunchStarted :: (IsAppLaunchContext a, MonadIO m) => a -> ((?self :: a) => AppLaunchContextLaunchStartedCallback) -> m SignalHandlerId
afterAppLaunchContextLaunchStarted :: forall a (m :: * -> *).
(IsAppLaunchContext a, MonadIO m) =>
a
-> ((?self::a) => AppLaunchContextLaunchStartedCallback)
-> m SignalHandlerId
afterAppLaunchContextLaunchStarted a
obj (?self::a) => AppLaunchContextLaunchStartedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> AppLaunchContextLaunchStartedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => AppLaunchContextLaunchStartedCallback
AppLaunchContextLaunchStartedCallback
cb
    let wrapped' :: C_AppLaunchContextLaunchStartedCallback
wrapped' = (a -> AppLaunchContextLaunchStartedCallback)
-> C_AppLaunchContextLaunchStartedCallback
forall a.
GObject a =>
(a -> AppLaunchContextLaunchStartedCallback)
-> C_AppLaunchContextLaunchStartedCallback
wrap_AppLaunchContextLaunchStartedCallback a -> AppLaunchContextLaunchStartedCallback
wrapped
    wrapped'' <- C_AppLaunchContextLaunchStartedCallback
-> IO (FunPtr C_AppLaunchContextLaunchStartedCallback)
mk_AppLaunchContextLaunchStartedCallback C_AppLaunchContextLaunchStartedCallback
wrapped'
    connectSignalFunPtr obj "launch-started" wrapped'' SignalConnectAfter Nothing


#if defined(ENABLE_OVERLOADING)
data AppLaunchContextLaunchStartedSignalInfo
instance SignalInfo AppLaunchContextLaunchStartedSignalInfo where
    type HaskellCallbackType AppLaunchContextLaunchStartedSignalInfo = AppLaunchContextLaunchStartedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_AppLaunchContextLaunchStartedCallback cb
        cb'' <- mk_AppLaunchContextLaunchStartedCallback cb'
        connectSignalFunPtr obj "launch-started" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.AppLaunchContext::launch-started"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-AppLaunchContext.html#g:signal:launchStarted"})

#endif

-- signal AppLaunchContext::launched
-- | The [AppLaunchContext::launched]("GI.Gio.Objects.AppLaunchContext#g:signal:launched") signal is emitted when a t'GI.Gio.Interfaces.AppInfo.AppInfo' is successfully
-- launched.
-- 
-- Because a launch operation may involve spawning multiple instances of the
-- target application, you should expect this signal to be emitted multiple
-- times, one time for each spawned instance.
-- 
-- The /@platformData@/ is an GVariant dictionary mapping
-- strings to variants (ie @a{sv}@), which contains additional,
-- platform-specific data about this launch. On UNIX, at least the
-- @pid@ and @startup-notification-id@ keys will be present.
-- 
-- Since 2.72 the @pid@ may be 0 if the process id wasn\'t known (for
-- example if the process was launched via D-Bus). The @pid@ may not be
-- set at all in subsequent releases.
-- 
-- On Windows, @pid@ is guaranteed to be valid only for the duration of the
-- [AppLaunchContext::launched]("GI.Gio.Objects.AppLaunchContext#g:signal:launched") signal emission; after the signal is emitted,
-- GLib will call 'GI.GLib.Functions.spawnClosePid'. If you need to keep the @/GPid/@ after the
-- signal has been emitted, then you can duplicate @pid@ using @DuplicateHandle()@.
-- 
-- /Since: 2.36/
type AppLaunchContextLaunchedCallback =
    Gio.AppInfo.AppInfo
    -- ^ /@info@/: the t'GI.Gio.Interfaces.AppInfo.AppInfo' that was just launched
    -> GVariant
    -- ^ /@platformData@/: additional platform-specific data for this launch
    -> IO ()

type C_AppLaunchContextLaunchedCallback =
    Ptr AppLaunchContext ->                 -- object
    Ptr Gio.AppInfo.AppInfo ->
    Ptr GVariant ->
    Ptr () ->                               -- user_data
    IO ()

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

wrap_AppLaunchContextLaunchedCallback :: 
    GObject a => (a -> AppLaunchContextLaunchedCallback) ->
    C_AppLaunchContextLaunchedCallback
wrap_AppLaunchContextLaunchedCallback :: forall a.
GObject a =>
(a -> AppLaunchContextLaunchedCallback)
-> C_AppLaunchContextLaunchStartedCallback
wrap_AppLaunchContextLaunchedCallback a -> AppLaunchContextLaunchedCallback
gi'cb Ptr AppLaunchContext
gi'selfPtr Ptr AppInfo
info Ptr GVariant
platformData Ptr ()
_ = do
    info' <- ((ManagedPtr AppInfo -> AppInfo) -> Ptr AppInfo -> IO AppInfo
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr AppInfo -> AppInfo
Gio.AppInfo.AppInfo) Ptr AppInfo
info
    platformData' <- B.GVariant.newGVariantFromPtr platformData
    B.ManagedPtr.withNewObject gi'selfPtr $ \AppLaunchContext
gi'self -> a -> AppLaunchContextLaunchedCallback
gi'cb (AppLaunchContext -> a
forall a b. Coercible a b => a -> b
Coerce.coerce AppLaunchContext
gi'self)  AppInfo
info' GVariant
platformData'


-- | Connect a signal handler for the [launched](#signal:launched) 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' appLaunchContext #launched callback
-- @
-- 
-- 
onAppLaunchContextLaunched :: (IsAppLaunchContext a, MonadIO m) => a -> ((?self :: a) => AppLaunchContextLaunchedCallback) -> m SignalHandlerId
onAppLaunchContextLaunched :: forall a (m :: * -> *).
(IsAppLaunchContext a, MonadIO m) =>
a
-> ((?self::a) => AppLaunchContextLaunchedCallback)
-> m SignalHandlerId
onAppLaunchContextLaunched a
obj (?self::a) => AppLaunchContextLaunchedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> AppLaunchContextLaunchedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => AppLaunchContextLaunchedCallback
AppLaunchContextLaunchedCallback
cb
    let wrapped' :: C_AppLaunchContextLaunchStartedCallback
wrapped' = (a -> AppLaunchContextLaunchedCallback)
-> C_AppLaunchContextLaunchStartedCallback
forall a.
GObject a =>
(a -> AppLaunchContextLaunchedCallback)
-> C_AppLaunchContextLaunchStartedCallback
wrap_AppLaunchContextLaunchedCallback a -> AppLaunchContextLaunchedCallback
wrapped
    wrapped'' <- C_AppLaunchContextLaunchStartedCallback
-> IO (FunPtr C_AppLaunchContextLaunchStartedCallback)
mk_AppLaunchContextLaunchedCallback C_AppLaunchContextLaunchStartedCallback
wrapped'
    connectSignalFunPtr obj "launched" wrapped'' SignalConnectBefore Nothing

-- | Connect a signal handler for the [launched](#signal:launched) 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' appLaunchContext #launched callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterAppLaunchContextLaunched :: (IsAppLaunchContext a, MonadIO m) => a -> ((?self :: a) => AppLaunchContextLaunchedCallback) -> m SignalHandlerId
afterAppLaunchContextLaunched :: forall a (m :: * -> *).
(IsAppLaunchContext a, MonadIO m) =>
a
-> ((?self::a) => AppLaunchContextLaunchedCallback)
-> m SignalHandlerId
afterAppLaunchContextLaunched a
obj (?self::a) => AppLaunchContextLaunchedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> AppLaunchContextLaunchedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => AppLaunchContextLaunchedCallback
AppLaunchContextLaunchedCallback
cb
    let wrapped' :: C_AppLaunchContextLaunchStartedCallback
wrapped' = (a -> AppLaunchContextLaunchedCallback)
-> C_AppLaunchContextLaunchStartedCallback
forall a.
GObject a =>
(a -> AppLaunchContextLaunchedCallback)
-> C_AppLaunchContextLaunchStartedCallback
wrap_AppLaunchContextLaunchedCallback a -> AppLaunchContextLaunchedCallback
wrapped
    wrapped'' <- C_AppLaunchContextLaunchStartedCallback
-> IO (FunPtr C_AppLaunchContextLaunchStartedCallback)
mk_AppLaunchContextLaunchedCallback C_AppLaunchContextLaunchStartedCallback
wrapped'
    connectSignalFunPtr obj "launched" wrapped'' SignalConnectAfter Nothing


#if defined(ENABLE_OVERLOADING)
data AppLaunchContextLaunchedSignalInfo
instance SignalInfo AppLaunchContextLaunchedSignalInfo where
    type HaskellCallbackType AppLaunchContextLaunchedSignalInfo = AppLaunchContextLaunchedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_AppLaunchContextLaunchedCallback cb
        cb'' <- mk_AppLaunchContextLaunchedCallback cb'
        connectSignalFunPtr obj "launched" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.AppLaunchContext::launched"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-AppLaunchContext.html#g:signal:launched"})

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

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

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

-- | Creates a new application launch context. This is not normally used,
-- instead you instantiate a subclass of this, such as @/GdkAppLaunchContext/@.
appLaunchContextNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m AppLaunchContext
    -- ^ __Returns:__ a t'GI.Gio.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
    result <- IO (Ptr AppLaunchContext)
g_app_launch_context_new
    checkUnexpectedReturnNULL "appLaunchContextNew" result
    result' <- (wrapObject AppLaunchContext) result
    return result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method AppLaunchContext::get_display
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AppLaunchContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAppLaunchContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AppInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAppInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "files"
--           , argType =
--               TGList (TInterface Name { namespace = "Gio" , name = "File" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GList of #GFile objects"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_app_launch_context_get_display" g_app_launch_context_get_display :: 
    Ptr AppLaunchContext ->                 -- context : TInterface (Name {namespace = "Gio", name = "AppLaunchContext"})
    Ptr Gio.AppInfo.AppInfo ->              -- info : TInterface (Name {namespace = "Gio", name = "AppInfo"})
    Ptr (GList (Ptr Gio.File.File)) ->      -- files : TGList (TInterface (Name {namespace = "Gio", name = "File"}))
    IO CString

-- | Gets the display string for the /@context@/. This is used to ensure new
-- applications are started on the same display as the launching
-- application, by setting the @DISPLAY@ environment variable.
appLaunchContextGetDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppLaunchContext a, Gio.AppInfo.IsAppInfo b, Gio.File.IsFile c) =>
    a
    -- ^ /@context@/: a t'GI.Gio.Objects.AppLaunchContext.AppLaunchContext'
    -> b
    -- ^ /@info@/: a t'GI.Gio.Interfaces.AppInfo.AppInfo'
    -> [c]
    -- ^ /@files@/: a t'GI.GLib.Structs.List.List' of t'GI.Gio.Interfaces.File.File' objects
    -> m (Maybe T.Text)
    -- ^ __Returns:__ a display string for the display.
appLaunchContextGetDisplay :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsAppLaunchContext a, IsAppInfo b,
 IsFile c) =>
a -> b -> [c] -> m (Maybe Text)
appLaunchContextGetDisplay a
context b
info [c]
files = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    context' <- a -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    info' <- unsafeManagedPtrCastPtr info
    files' <- mapM unsafeManagedPtrCastPtr files
    files'' <- packGList files'
    result <- g_app_launch_context_get_display context' info' files''
    maybeResult <- convertIfNonNull result $ \CString
result' -> do
        result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        freeMem result'
        return result''
    touchManagedPtr context
    touchManagedPtr info
    mapM_ touchManagedPtr files
    g_list_free files''
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data AppLaunchContextGetDisplayMethodInfo
instance (signature ~ (b -> [c] -> m (Maybe T.Text)), MonadIO m, IsAppLaunchContext a, Gio.AppInfo.IsAppInfo b, Gio.File.IsFile c) => O.OverloadedMethod AppLaunchContextGetDisplayMethodInfo a signature where
    overloadedMethod = appLaunchContextGetDisplay

instance O.OverloadedMethodInfo AppLaunchContextGetDisplayMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.AppLaunchContext.appLaunchContextGetDisplay",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-AppLaunchContext.html#v:appLaunchContextGetDisplay"
        })


#endif

-- method AppLaunchContext::get_environment
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AppLaunchContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAppLaunchContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) (-1) (TBasicType TFileName))
-- throws : False
-- Skip return : False

foreign import ccall "g_app_launch_context_get_environment" g_app_launch_context_get_environment :: 
    Ptr AppLaunchContext ->                 -- context : TInterface (Name {namespace = "Gio", name = "AppLaunchContext"})
    IO (Ptr CString)

-- | Gets the complete environment variable list to be passed to
-- the child process when /@context@/ is used to launch an application.
-- This is a 'P.Nothing'-terminated array of strings, where each string has
-- the form @KEY=VALUE@.
-- 
-- /Since: 2.32/
appLaunchContextGetEnvironment ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppLaunchContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gio.Objects.AppLaunchContext.AppLaunchContext'
    -> m [[Char]]
    -- ^ __Returns:__ 
    --     the child\'s environment
appLaunchContextGetEnvironment :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAppLaunchContext a) =>
a -> m [String]
appLaunchContextGetEnvironment a
context = IO [String] -> m [String]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [String] -> m [String]) -> IO [String] -> m [String]
forall a b. (a -> b) -> a -> b
$ do
    context' <- a -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    result <- g_app_launch_context_get_environment context'
    checkUnexpectedReturnNULL "appLaunchContextGetEnvironment" result
    result' <- unpackZeroTerminatedFileNameArray result
    mapZeroTerminatedCArray freeMem result
    freeMem result
    touchManagedPtr context
    return result'

#if defined(ENABLE_OVERLOADING)
data AppLaunchContextGetEnvironmentMethodInfo
instance (signature ~ (m [[Char]]), MonadIO m, IsAppLaunchContext a) => O.OverloadedMethod AppLaunchContextGetEnvironmentMethodInfo a signature where
    overloadedMethod = appLaunchContextGetEnvironment

instance O.OverloadedMethodInfo AppLaunchContextGetEnvironmentMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.AppLaunchContext.appLaunchContextGetEnvironment",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-AppLaunchContext.html#v:appLaunchContextGetEnvironment"
        })


#endif

-- method AppLaunchContext::get_startup_notify_id
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AppLaunchContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAppLaunchContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AppInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAppInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "files"
--           , argType =
--               TGList (TInterface Name { namespace = "Gio" , name = "File" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GList of #GFile objects"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_app_launch_context_get_startup_notify_id" g_app_launch_context_get_startup_notify_id :: 
    Ptr AppLaunchContext ->                 -- context : TInterface (Name {namespace = "Gio", name = "AppLaunchContext"})
    Ptr Gio.AppInfo.AppInfo ->              -- info : TInterface (Name {namespace = "Gio", name = "AppInfo"})
    Ptr (GList (Ptr Gio.File.File)) ->      -- files : TGList (TInterface (Name {namespace = "Gio", name = "File"}))
    IO CString

-- | Initiates startup notification for the application and returns the
-- @XDG_ACTIVATION_TOKEN@ or @DESKTOP_STARTUP_ID@ for the launched operation,
-- if supported.
-- 
-- The returned token may be referred to equivalently as an ‘activation token’
-- (using Wayland terminology) or a ‘startup sequence ID’ (using X11 terminology).
-- The two <https://gitlab.freedesktop.org/wayland/wayland-protocols/-/blob/main/staging/xdg-activation/x11-interoperation.rst are interoperable>.
-- 
-- Activation tokens are defined in the <https://wayland.app/protocols/xdg-activation-v1 XDG Activation Protocol>,
-- and startup notification IDs are defined in the
-- <http://standards.freedesktop.org/startup-notification-spec/startup-notification-latest.txt freedesktop.org Startup Notification Protocol>.
-- 
-- Support for the XDG Activation Protocol was added in GLib 2.76.
appLaunchContextGetStartupNotifyId ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppLaunchContext a, Gio.AppInfo.IsAppInfo b, Gio.File.IsFile c) =>
    a
    -- ^ /@context@/: a t'GI.Gio.Objects.AppLaunchContext.AppLaunchContext'
    -> b
    -- ^ /@info@/: a t'GI.Gio.Interfaces.AppInfo.AppInfo'
    -> [c]
    -- ^ /@files@/: a t'GI.GLib.Structs.List.List' of t'GI.Gio.Interfaces.File.File' objects
    -> m (Maybe T.Text)
    -- ^ __Returns:__ a startup notification ID for the application, or 'P.Nothing' if
    --     not supported.
appLaunchContextGetStartupNotifyId :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsAppLaunchContext a, IsAppInfo b,
 IsFile c) =>
a -> b -> [c] -> m (Maybe Text)
appLaunchContextGetStartupNotifyId a
context b
info [c]
files = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
    context' <- a -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    info' <- unsafeManagedPtrCastPtr info
    files' <- mapM unsafeManagedPtrCastPtr files
    files'' <- packGList files'
    result <- g_app_launch_context_get_startup_notify_id context' info' files''
    maybeResult <- convertIfNonNull result $ \CString
result' -> do
        result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        freeMem result'
        return result''
    touchManagedPtr context
    touchManagedPtr info
    mapM_ touchManagedPtr files
    g_list_free files''
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data AppLaunchContextGetStartupNotifyIdMethodInfo
instance (signature ~ (b -> [c] -> m (Maybe T.Text)), MonadIO m, IsAppLaunchContext a, Gio.AppInfo.IsAppInfo b, Gio.File.IsFile c) => O.OverloadedMethod AppLaunchContextGetStartupNotifyIdMethodInfo a signature where
    overloadedMethod = appLaunchContextGetStartupNotifyId

instance O.OverloadedMethodInfo AppLaunchContextGetStartupNotifyIdMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.AppLaunchContext.appLaunchContextGetStartupNotifyId",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-AppLaunchContext.html#v:appLaunchContextGetStartupNotifyId"
        })


#endif

-- method AppLaunchContext::launch_failed
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AppLaunchContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAppLaunchContext."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "startup_notify_id"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the startup notification id that was returned by g_app_launch_context_get_startup_notify_id()."
--                 , 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 "g_app_launch_context_launch_failed" g_app_launch_context_launch_failed :: 
    Ptr AppLaunchContext ->                 -- context : TInterface (Name {namespace = "Gio", name = "AppLaunchContext"})
    CString ->                              -- startup_notify_id : TBasicType TUTF8
    IO ()

-- | Called when an application has failed to launch, so that it can cancel
-- the application startup notification started in 'GI.Gio.Objects.AppLaunchContext.appLaunchContextGetStartupNotifyId'.
appLaunchContextLaunchFailed ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppLaunchContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gio.Objects.AppLaunchContext.AppLaunchContext'.
    -> T.Text
    -- ^ /@startupNotifyId@/: the startup notification id that was returned by 'GI.Gio.Objects.AppLaunchContext.appLaunchContextGetStartupNotifyId'.
    -> m ()
appLaunchContextLaunchFailed :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAppLaunchContext a) =>
a -> Text -> m ()
appLaunchContextLaunchFailed a
context Text
startupNotifyId = 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
    context' <- a -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    startupNotifyId' <- textToCString startupNotifyId
    g_app_launch_context_launch_failed context' startupNotifyId'
    touchManagedPtr context
    freeMem startupNotifyId'
    return ()

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

instance O.OverloadedMethodInfo AppLaunchContextLaunchFailedMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.AppLaunchContext.appLaunchContextLaunchFailed",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-AppLaunchContext.html#v:appLaunchContextLaunchFailed"
        })


#endif

-- method AppLaunchContext::setenv
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AppLaunchContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAppLaunchContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "variable"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the environment variable to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the value for to set the variable to."
--                 , 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 "g_app_launch_context_setenv" g_app_launch_context_setenv :: 
    Ptr AppLaunchContext ->                 -- context : TInterface (Name {namespace = "Gio", name = "AppLaunchContext"})
    CString ->                              -- variable : TBasicType TFileName
    CString ->                              -- value : TBasicType TFileName
    IO ()

-- | Arranges for /@variable@/ to be set to /@value@/ in the child\'s
-- environment when /@context@/ is used to launch an application.
-- 
-- /Since: 2.32/
appLaunchContextSetenv ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppLaunchContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gio.Objects.AppLaunchContext.AppLaunchContext'
    -> [Char]
    -- ^ /@variable@/: the environment variable to set
    -> [Char]
    -- ^ /@value@/: the value for to set the variable to.
    -> m ()
appLaunchContextSetenv :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAppLaunchContext a) =>
a -> String -> String -> m ()
appLaunchContextSetenv a
context String
variable String
value = 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
    context' <- a -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    variable' <- stringToCString variable
    value' <- stringToCString value
    g_app_launch_context_setenv context' variable' value'
    touchManagedPtr context
    freeMem variable'
    freeMem value'
    return ()

#if defined(ENABLE_OVERLOADING)
data AppLaunchContextSetenvMethodInfo
instance (signature ~ ([Char] -> [Char] -> m ()), MonadIO m, IsAppLaunchContext a) => O.OverloadedMethod AppLaunchContextSetenvMethodInfo a signature where
    overloadedMethod = appLaunchContextSetenv

instance O.OverloadedMethodInfo AppLaunchContextSetenvMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.AppLaunchContext.appLaunchContextSetenv",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-AppLaunchContext.html#v:appLaunchContextSetenv"
        })


#endif

-- method AppLaunchContext::unsetenv
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AppLaunchContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAppLaunchContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "variable"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the environment variable to remove"
--                 , 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 "g_app_launch_context_unsetenv" g_app_launch_context_unsetenv :: 
    Ptr AppLaunchContext ->                 -- context : TInterface (Name {namespace = "Gio", name = "AppLaunchContext"})
    CString ->                              -- variable : TBasicType TFileName
    IO ()

-- | Arranges for /@variable@/ to be unset in the child\'s environment
-- when /@context@/ is used to launch an application.
-- 
-- /Since: 2.32/
appLaunchContextUnsetenv ::
    (B.CallStack.HasCallStack, MonadIO m, IsAppLaunchContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gio.Objects.AppLaunchContext.AppLaunchContext'
    -> [Char]
    -- ^ /@variable@/: the environment variable to remove
    -> m ()
appLaunchContextUnsetenv :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsAppLaunchContext a) =>
a -> String -> m ()
appLaunchContextUnsetenv a
context String
variable = 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
    context' <- a -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    variable' <- stringToCString variable
    g_app_launch_context_unsetenv context' variable'
    touchManagedPtr context
    freeMem variable'
    return ()

#if defined(ENABLE_OVERLOADING)
data AppLaunchContextUnsetenvMethodInfo
instance (signature ~ ([Char] -> m ()), MonadIO m, IsAppLaunchContext a) => O.OverloadedMethod AppLaunchContextUnsetenvMethodInfo a signature where
    overloadedMethod = appLaunchContextUnsetenv

instance O.OverloadedMethodInfo AppLaunchContextUnsetenvMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.AppLaunchContext.appLaunchContextUnsetenv",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-AppLaunchContext.html#v:appLaunchContextUnsetenv"
        })


#endif