{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GDesktopAppInfo@ is an implementation of t'GI.Gio.Interfaces.AppInfo.AppInfo' based on
-- desktop files.
-- 
-- Note that @\<gio\/gdesktopappinfo.h>@ belongs to the UNIX-specific
-- GIO interfaces, thus you have to use the @gio-unix-2.0.pc@ pkg-config
-- file or the @GioUnix-2.0@ GIR namespace when using it.

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

module GI.Gio.Objects.DesktopAppInfo
    ( 

-- * Exported types
    DesktopAppInfo(..)                      ,
    IsDesktopAppInfo                        ,
    toDesktopAppInfo                        ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [addSupportsType]("GI.Gio.Interfaces.AppInfo#g:method:addSupportsType"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [canDelete]("GI.Gio.Interfaces.AppInfo#g:method:canDelete"), [canRemoveSupportsType]("GI.Gio.Interfaces.AppInfo#g:method:canRemoveSupportsType"), [delete]("GI.Gio.Interfaces.AppInfo#g:method:delete"), [dup]("GI.Gio.Interfaces.AppInfo#g:method:dup"), [equal]("GI.Gio.Interfaces.AppInfo#g:method:equal"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [hasKey]("GI.Gio.Objects.DesktopAppInfo#g:method:hasKey"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [launch]("GI.Gio.Interfaces.AppInfo#g:method:launch"), [launchAction]("GI.Gio.Objects.DesktopAppInfo#g:method:launchAction"), [launchUris]("GI.Gio.Interfaces.AppInfo#g:method:launchUris"), [launchUrisAsManager]("GI.Gio.Objects.DesktopAppInfo#g:method:launchUrisAsManager"), [launchUrisAsManagerWithFds]("GI.Gio.Objects.DesktopAppInfo#g:method:launchUrisAsManagerWithFds"), [launchUrisAsync]("GI.Gio.Interfaces.AppInfo#g:method:launchUrisAsync"), [launchUrisFinish]("GI.Gio.Interfaces.AppInfo#g:method:launchUrisFinish"), [listActions]("GI.Gio.Objects.DesktopAppInfo#g:method:listActions"), [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"), [removeSupportsType]("GI.Gio.Interfaces.AppInfo#g:method:removeSupportsType"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [shouldShow]("GI.Gio.Interfaces.AppInfo#g:method:shouldShow"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [supportsFiles]("GI.Gio.Interfaces.AppInfo#g:method:supportsFiles"), [supportsUris]("GI.Gio.Interfaces.AppInfo#g:method:supportsUris"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getActionName]("GI.Gio.Objects.DesktopAppInfo#g:method:getActionName"), [getBoolean]("GI.Gio.Objects.DesktopAppInfo#g:method:getBoolean"), [getCategories]("GI.Gio.Objects.DesktopAppInfo#g:method:getCategories"), [getCommandline]("GI.Gio.Interfaces.AppInfo#g:method:getCommandline"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDescription]("GI.Gio.Interfaces.AppInfo#g:method:getDescription"), [getDisplayName]("GI.Gio.Interfaces.AppInfo#g:method:getDisplayName"), [getExecutable]("GI.Gio.Interfaces.AppInfo#g:method:getExecutable"), [getFilename]("GI.Gio.Objects.DesktopAppInfo#g:method:getFilename"), [getGenericName]("GI.Gio.Objects.DesktopAppInfo#g:method:getGenericName"), [getIcon]("GI.Gio.Interfaces.AppInfo#g:method:getIcon"), [getId]("GI.Gio.Interfaces.AppInfo#g:method:getId"), [getIsHidden]("GI.Gio.Objects.DesktopAppInfo#g:method:getIsHidden"), [getKeywords]("GI.Gio.Objects.DesktopAppInfo#g:method:getKeywords"), [getLocaleString]("GI.Gio.Objects.DesktopAppInfo#g:method:getLocaleString"), [getName]("GI.Gio.Interfaces.AppInfo#g:method:getName"), [getNodisplay]("GI.Gio.Objects.DesktopAppInfo#g:method:getNodisplay"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getShowIn]("GI.Gio.Objects.DesktopAppInfo#g:method:getShowIn"), [getStartupWmClass]("GI.Gio.Objects.DesktopAppInfo#g:method:getStartupWmClass"), [getString]("GI.Gio.Objects.DesktopAppInfo#g:method:getString"), [getStringList]("GI.Gio.Objects.DesktopAppInfo#g:method:getStringList"), [getSupportedTypes]("GI.Gio.Interfaces.AppInfo#g:method:getSupportedTypes").
-- 
-- ==== Setters
-- [setAsDefaultForExtension]("GI.Gio.Interfaces.AppInfo#g:method:setAsDefaultForExtension"), [setAsDefaultForType]("GI.Gio.Interfaces.AppInfo#g:method:setAsDefaultForType"), [setAsLastUsedForType]("GI.Gio.Interfaces.AppInfo#g:method:setAsLastUsedForType"), [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)
    ResolveDesktopAppInfoMethod             ,
#endif

-- ** getActionName #method:getActionName#

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoGetActionNameMethodInfo   ,
#endif
    desktopAppInfoGetActionName             ,


-- ** getBoolean #method:getBoolean#

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoGetBooleanMethodInfo      ,
#endif
    desktopAppInfoGetBoolean                ,


-- ** getCategories #method:getCategories#

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoGetCategoriesMethodInfo   ,
#endif
    desktopAppInfoGetCategories             ,


-- ** getFilename #method:getFilename#

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoGetFilenameMethodInfo     ,
#endif
    desktopAppInfoGetFilename               ,


-- ** getGenericName #method:getGenericName#

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoGetGenericNameMethodInfo  ,
#endif
    desktopAppInfoGetGenericName            ,


-- ** getImplementations #method:getImplementations#

    desktopAppInfoGetImplementations        ,


-- ** getIsHidden #method:getIsHidden#

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoGetIsHiddenMethodInfo     ,
#endif
    desktopAppInfoGetIsHidden               ,


-- ** getKeywords #method:getKeywords#

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoGetKeywordsMethodInfo     ,
#endif
    desktopAppInfoGetKeywords               ,


-- ** getLocaleString #method:getLocaleString#

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoGetLocaleStringMethodInfo ,
#endif
    desktopAppInfoGetLocaleString           ,


-- ** getNodisplay #method:getNodisplay#

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoGetNodisplayMethodInfo    ,
#endif
    desktopAppInfoGetNodisplay              ,


-- ** getShowIn #method:getShowIn#

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoGetShowInMethodInfo       ,
#endif
    desktopAppInfoGetShowIn                 ,


-- ** getStartupWmClass #method:getStartupWmClass#

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoGetStartupWmClassMethodInfo,
#endif
    desktopAppInfoGetStartupWmClass         ,


-- ** getString #method:getString#

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoGetStringMethodInfo       ,
#endif
    desktopAppInfoGetString                 ,


-- ** getStringList #method:getStringList#

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoGetStringListMethodInfo   ,
#endif
    desktopAppInfoGetStringList             ,


-- ** hasKey #method:hasKey#

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoHasKeyMethodInfo          ,
#endif
    desktopAppInfoHasKey                    ,


-- ** launchAction #method:launchAction#

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoLaunchActionMethodInfo    ,
#endif
    desktopAppInfoLaunchAction              ,


-- ** launchUrisAsManager #method:launchUrisAsManager#

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoLaunchUrisAsManagerMethodInfo,
#endif
    desktopAppInfoLaunchUrisAsManager       ,


-- ** launchUrisAsManagerWithFds #method:launchUrisAsManagerWithFds#

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoLaunchUrisAsManagerWithFdsMethodInfo,
#endif
    desktopAppInfoLaunchUrisAsManagerWithFds,


-- ** listActions #method:listActions#

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoListActionsMethodInfo     ,
#endif
    desktopAppInfoListActions               ,


-- ** new #method:new#

    desktopAppInfoNew                       ,


-- ** newFromFilename #method:newFromFilename#

    desktopAppInfoNewFromFilename           ,


-- ** newFromKeyfile #method:newFromKeyfile#

    desktopAppInfoNewFromKeyfile            ,


-- ** search #method:search#

    desktopAppInfoSearch                    ,


-- ** setDesktopEnv #method:setDesktopEnv#

    desktopAppInfoSetDesktopEnv             ,




 -- * Properties


-- ** filename #attr:filename#
-- | The origin filename of this t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'

#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoFilenamePropertyInfo      ,
#endif
    constructDesktopAppInfoFilename         ,
#if defined(ENABLE_OVERLOADING)
    desktopAppInfoFilename                  ,
#endif
    getDesktopAppInfoFilename               ,




    ) 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.Flags as GLib.Flags
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.DateTime as GLib.DateTime
import qualified GI.GLib.Structs.KeyFile as GLib.KeyFile
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.AppLaunchContext as Gio.AppLaunchContext
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.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Flags as GLib.Flags
import qualified GI.GLib.Structs.KeyFile as GLib.KeyFile
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AppInfo as Gio.AppInfo
import {-# SOURCE #-} qualified GI.Gio.Objects.AppLaunchContext as Gio.AppLaunchContext

#endif

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

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

foreign import ccall "g_desktop_app_info_get_type"
    c_g_desktop_app_info_get_type :: IO B.Types.GType

instance B.Types.TypedObject DesktopAppInfo where
    glibType :: IO GType
glibType = IO GType
c_g_desktop_app_info_get_type

instance B.Types.GObject DesktopAppInfo

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

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

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

-- | Convert 'DesktopAppInfo' 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 DesktopAppInfo) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_desktop_app_info_get_type
    gvalueSet_ :: Ptr GValue -> Maybe DesktopAppInfo -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DesktopAppInfo
P.Nothing = Ptr GValue -> Ptr DesktopAppInfo -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DesktopAppInfo
forall a. Ptr a
FP.nullPtr :: FP.Ptr DesktopAppInfo)
    gvalueSet_ Ptr GValue
gv (P.Just DesktopAppInfo
obj) = DesktopAppInfo -> (Ptr DesktopAppInfo -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DesktopAppInfo
obj (Ptr GValue -> Ptr DesktopAppInfo -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe DesktopAppInfo)
gvalueGet_ Ptr GValue
gv = do
        ptr <- Ptr GValue -> IO (Ptr DesktopAppInfo)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DesktopAppInfo)
        if ptr /= FP.nullPtr
        then P.Just <$> B.ManagedPtr.newObject DesktopAppInfo ptr
        else return P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveDesktopAppInfoMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveDesktopAppInfoMethod "addSupportsType" o = Gio.AppInfo.AppInfoAddSupportsTypeMethodInfo
    ResolveDesktopAppInfoMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveDesktopAppInfoMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveDesktopAppInfoMethod "canDelete" o = Gio.AppInfo.AppInfoCanDeleteMethodInfo
    ResolveDesktopAppInfoMethod "canRemoveSupportsType" o = Gio.AppInfo.AppInfoCanRemoveSupportsTypeMethodInfo
    ResolveDesktopAppInfoMethod "delete" o = Gio.AppInfo.AppInfoDeleteMethodInfo
    ResolveDesktopAppInfoMethod "dup" o = Gio.AppInfo.AppInfoDupMethodInfo
    ResolveDesktopAppInfoMethod "equal" o = Gio.AppInfo.AppInfoEqualMethodInfo
    ResolveDesktopAppInfoMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveDesktopAppInfoMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveDesktopAppInfoMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveDesktopAppInfoMethod "hasKey" o = DesktopAppInfoHasKeyMethodInfo
    ResolveDesktopAppInfoMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveDesktopAppInfoMethod "launch" o = Gio.AppInfo.AppInfoLaunchMethodInfo
    ResolveDesktopAppInfoMethod "launchAction" o = DesktopAppInfoLaunchActionMethodInfo
    ResolveDesktopAppInfoMethod "launchUris" o = Gio.AppInfo.AppInfoLaunchUrisMethodInfo
    ResolveDesktopAppInfoMethod "launchUrisAsManager" o = DesktopAppInfoLaunchUrisAsManagerMethodInfo
    ResolveDesktopAppInfoMethod "launchUrisAsManagerWithFds" o = DesktopAppInfoLaunchUrisAsManagerWithFdsMethodInfo
    ResolveDesktopAppInfoMethod "launchUrisAsync" o = Gio.AppInfo.AppInfoLaunchUrisAsyncMethodInfo
    ResolveDesktopAppInfoMethod "launchUrisFinish" o = Gio.AppInfo.AppInfoLaunchUrisFinishMethodInfo
    ResolveDesktopAppInfoMethod "listActions" o = DesktopAppInfoListActionsMethodInfo
    ResolveDesktopAppInfoMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveDesktopAppInfoMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveDesktopAppInfoMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveDesktopAppInfoMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveDesktopAppInfoMethod "removeSupportsType" o = Gio.AppInfo.AppInfoRemoveSupportsTypeMethodInfo
    ResolveDesktopAppInfoMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveDesktopAppInfoMethod "shouldShow" o = Gio.AppInfo.AppInfoShouldShowMethodInfo
    ResolveDesktopAppInfoMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveDesktopAppInfoMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveDesktopAppInfoMethod "supportsFiles" o = Gio.AppInfo.AppInfoSupportsFilesMethodInfo
    ResolveDesktopAppInfoMethod "supportsUris" o = Gio.AppInfo.AppInfoSupportsUrisMethodInfo
    ResolveDesktopAppInfoMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveDesktopAppInfoMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveDesktopAppInfoMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveDesktopAppInfoMethod "getActionName" o = DesktopAppInfoGetActionNameMethodInfo
    ResolveDesktopAppInfoMethod "getBoolean" o = DesktopAppInfoGetBooleanMethodInfo
    ResolveDesktopAppInfoMethod "getCategories" o = DesktopAppInfoGetCategoriesMethodInfo
    ResolveDesktopAppInfoMethod "getCommandline" o = Gio.AppInfo.AppInfoGetCommandlineMethodInfo
    ResolveDesktopAppInfoMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveDesktopAppInfoMethod "getDescription" o = Gio.AppInfo.AppInfoGetDescriptionMethodInfo
    ResolveDesktopAppInfoMethod "getDisplayName" o = Gio.AppInfo.AppInfoGetDisplayNameMethodInfo
    ResolveDesktopAppInfoMethod "getExecutable" o = Gio.AppInfo.AppInfoGetExecutableMethodInfo
    ResolveDesktopAppInfoMethod "getFilename" o = DesktopAppInfoGetFilenameMethodInfo
    ResolveDesktopAppInfoMethod "getGenericName" o = DesktopAppInfoGetGenericNameMethodInfo
    ResolveDesktopAppInfoMethod "getIcon" o = Gio.AppInfo.AppInfoGetIconMethodInfo
    ResolveDesktopAppInfoMethod "getId" o = Gio.AppInfo.AppInfoGetIdMethodInfo
    ResolveDesktopAppInfoMethod "getIsHidden" o = DesktopAppInfoGetIsHiddenMethodInfo
    ResolveDesktopAppInfoMethod "getKeywords" o = DesktopAppInfoGetKeywordsMethodInfo
    ResolveDesktopAppInfoMethod "getLocaleString" o = DesktopAppInfoGetLocaleStringMethodInfo
    ResolveDesktopAppInfoMethod "getName" o = Gio.AppInfo.AppInfoGetNameMethodInfo
    ResolveDesktopAppInfoMethod "getNodisplay" o = DesktopAppInfoGetNodisplayMethodInfo
    ResolveDesktopAppInfoMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveDesktopAppInfoMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveDesktopAppInfoMethod "getShowIn" o = DesktopAppInfoGetShowInMethodInfo
    ResolveDesktopAppInfoMethod "getStartupWmClass" o = DesktopAppInfoGetStartupWmClassMethodInfo
    ResolveDesktopAppInfoMethod "getString" o = DesktopAppInfoGetStringMethodInfo
    ResolveDesktopAppInfoMethod "getStringList" o = DesktopAppInfoGetStringListMethodInfo
    ResolveDesktopAppInfoMethod "getSupportedTypes" o = Gio.AppInfo.AppInfoGetSupportedTypesMethodInfo
    ResolveDesktopAppInfoMethod "setAsDefaultForExtension" o = Gio.AppInfo.AppInfoSetAsDefaultForExtensionMethodInfo
    ResolveDesktopAppInfoMethod "setAsDefaultForType" o = Gio.AppInfo.AppInfoSetAsDefaultForTypeMethodInfo
    ResolveDesktopAppInfoMethod "setAsLastUsedForType" o = Gio.AppInfo.AppInfoSetAsLastUsedForTypeMethodInfo
    ResolveDesktopAppInfoMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveDesktopAppInfoMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveDesktopAppInfoMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveDesktopAppInfoMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveDesktopAppInfoMethod t DesktopAppInfo, O.OverloadedMethod info DesktopAppInfo p) => OL.IsLabel t (DesktopAppInfo -> 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 ~ ResolveDesktopAppInfoMethod t DesktopAppInfo, O.OverloadedMethod info DesktopAppInfo p, R.HasField t DesktopAppInfo p) => R.HasField t DesktopAppInfo p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- VVV Prop "filename"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@filename@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' desktopAppInfo #filename
-- @
getDesktopAppInfoFilename :: (MonadIO m, IsDesktopAppInfo o) => o -> m (Maybe T.Text)
getDesktopAppInfoFilename :: forall (m :: * -> *) o.
(MonadIO m, IsDesktopAppInfo o) =>
o -> m (Maybe Text)
getDesktopAppInfoFilename o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"filename"

-- | Construct a `GValueConstruct` with valid value for the “@filename@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructDesktopAppInfoFilename :: (IsDesktopAppInfo o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructDesktopAppInfoFilename :: forall o (m :: * -> *).
(IsDesktopAppInfo o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructDesktopAppInfoFilename Text
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 Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"filename" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoFilenamePropertyInfo
instance AttrInfo DesktopAppInfoFilenamePropertyInfo where
    type AttrAllowedOps DesktopAppInfoFilenamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint DesktopAppInfoFilenamePropertyInfo = IsDesktopAppInfo
    type AttrSetTypeConstraint DesktopAppInfoFilenamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint DesktopAppInfoFilenamePropertyInfo = (~) T.Text
    type AttrTransferType DesktopAppInfoFilenamePropertyInfo = T.Text
    type AttrGetType DesktopAppInfoFilenamePropertyInfo = (Maybe T.Text)
    type AttrLabel DesktopAppInfoFilenamePropertyInfo = "filename"
    type AttrOrigin DesktopAppInfoFilenamePropertyInfo = DesktopAppInfo
    attrGet = getDesktopAppInfoFilename
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructDesktopAppInfoFilename
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.DesktopAppInfo.filename"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.35/docs/GI-Gio-Objects-DesktopAppInfo.html#g:attr:filename"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DesktopAppInfo
type instance O.AttributeList DesktopAppInfo = DesktopAppInfoAttributeList
type DesktopAppInfoAttributeList = ('[ '("filename", DesktopAppInfoFilenamePropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
desktopAppInfoFilename :: AttrLabelProxy "filename"
desktopAppInfoFilename = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DesktopAppInfo = DesktopAppInfoSignalList
type DesktopAppInfoSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method DesktopAppInfo::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "desktop_id"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the desktop file id"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "DesktopAppInfo" })
-- throws : False
-- Skip return : False

foreign import ccall "g_desktop_app_info_new" g_desktop_app_info_new :: 
    CString ->                              -- desktop_id : TBasicType TUTF8
    IO (Ptr DesktopAppInfo)

-- | Creates a new t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo' based on a desktop file id.
-- 
-- A desktop file id is the basename of the desktop file, including the
-- .desktop extension. GIO is looking for a desktop file with this name
-- in the @applications@ subdirectories of the XDG
-- data directories (i.e. the directories specified in the @XDG_DATA_HOME@
-- and @XDG_DATA_DIRS@ environment variables). GIO also supports the
-- prefix-to-subdirectory mapping that is described in the
-- <http://standards.freedesktop.org/menu-spec/latest/ Menu Spec>
-- (i.e. a desktop id of kde-foo.desktop will match
-- @\/usr\/share\/applications\/kde\/foo.desktop@).
desktopAppInfoNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@desktopId@/: the desktop file id
    -> m (Maybe DesktopAppInfo)
    -- ^ __Returns:__ a new t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo', or 'P.Nothing' if no desktop
    --     file with that id exists.
desktopAppInfoNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m (Maybe DesktopAppInfo)
desktopAppInfoNew Text
desktopId = IO (Maybe DesktopAppInfo) -> m (Maybe DesktopAppInfo)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DesktopAppInfo) -> m (Maybe DesktopAppInfo))
-> IO (Maybe DesktopAppInfo) -> m (Maybe DesktopAppInfo)
forall a b. (a -> b) -> a -> b
$ do
    desktopId' <- Text -> IO CString
textToCString Text
desktopId
    result <- g_desktop_app_info_new desktopId'
    maybeResult <- convertIfNonNull result $ \Ptr DesktopAppInfo
result' -> do
        result'' <- ((ManagedPtr DesktopAppInfo -> DesktopAppInfo)
-> Ptr DesktopAppInfo -> IO DesktopAppInfo
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DesktopAppInfo -> DesktopAppInfo
DesktopAppInfo) Ptr DesktopAppInfo
result'
        return result''
    freeMem desktopId'
    return maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

-- method DesktopAppInfo::new_from_filename
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "filename"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the path of a desktop file, in the GLib\n     filename encoding"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "DesktopAppInfo" })
-- throws : False
-- Skip return : False

foreign import ccall "g_desktop_app_info_new_from_filename" g_desktop_app_info_new_from_filename :: 
    CString ->                              -- filename : TBasicType TFileName
    IO (Ptr DesktopAppInfo)

-- | Creates a new t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'.
desktopAppInfoNewFromFilename ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Char]
    -- ^ /@filename@/: the path of a desktop file, in the GLib
    --      filename encoding
    -> m (Maybe DesktopAppInfo)
    -- ^ __Returns:__ a new t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo' or 'P.Nothing' on error.
desktopAppInfoNewFromFilename :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
String -> m (Maybe DesktopAppInfo)
desktopAppInfoNewFromFilename String
filename = IO (Maybe DesktopAppInfo) -> m (Maybe DesktopAppInfo)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DesktopAppInfo) -> m (Maybe DesktopAppInfo))
-> IO (Maybe DesktopAppInfo) -> m (Maybe DesktopAppInfo)
forall a b. (a -> b) -> a -> b
$ do
    filename' <- String -> IO CString
stringToCString String
filename
    result <- g_desktop_app_info_new_from_filename filename'
    maybeResult <- convertIfNonNull result $ \Ptr DesktopAppInfo
result' -> do
        result'' <- ((ManagedPtr DesktopAppInfo -> DesktopAppInfo)
-> Ptr DesktopAppInfo -> IO DesktopAppInfo
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DesktopAppInfo -> DesktopAppInfo
DesktopAppInfo) Ptr DesktopAppInfo
result'
        return result''
    freeMem filename'
    return maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

-- method DesktopAppInfo::new_from_keyfile
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an opened #GKeyFile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "DesktopAppInfo" })
-- throws : False
-- Skip return : False

foreign import ccall "g_desktop_app_info_new_from_keyfile" g_desktop_app_info_new_from_keyfile :: 
    Ptr GLib.KeyFile.KeyFile ->             -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    IO (Ptr DesktopAppInfo)

-- | Creates a new t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'.
-- 
-- /Since: 2.18/
desktopAppInfoNewFromKeyfile ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.KeyFile.KeyFile
    -- ^ /@keyFile@/: an opened t'GI.GLib.Structs.KeyFile.KeyFile'
    -> m (Maybe DesktopAppInfo)
    -- ^ __Returns:__ a new t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo' or 'P.Nothing' on error.
desktopAppInfoNewFromKeyfile :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> m (Maybe DesktopAppInfo)
desktopAppInfoNewFromKeyfile KeyFile
keyFile = IO (Maybe DesktopAppInfo) -> m (Maybe DesktopAppInfo)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe DesktopAppInfo) -> m (Maybe DesktopAppInfo))
-> IO (Maybe DesktopAppInfo) -> m (Maybe DesktopAppInfo)
forall a b. (a -> b) -> a -> b
$ do
    keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    result <- g_desktop_app_info_new_from_keyfile keyFile'
    maybeResult <- convertIfNonNull result $ \Ptr DesktopAppInfo
result' -> do
        result'' <- ((ManagedPtr DesktopAppInfo -> DesktopAppInfo)
-> Ptr DesktopAppInfo -> IO DesktopAppInfo
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr DesktopAppInfo -> DesktopAppInfo
DesktopAppInfo) Ptr DesktopAppInfo
result'
        return result''
    touchManagedPtr keyFile
    return maybeResult

#if defined(ENABLE_OVERLOADING)
#endif

-- method DesktopAppInfo::get_action_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DesktopAppInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDesktopAppInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the name of the action as from\n  g_desktop_app_info_list_actions()"
--                 , 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_desktop_app_info_get_action_name" g_desktop_app_info_get_action_name :: 
    Ptr DesktopAppInfo ->                   -- info : TInterface (Name {namespace = "Gio", name = "DesktopAppInfo"})
    CString ->                              -- action_name : TBasicType TUTF8
    IO CString

-- | Gets the user-visible display name of the \"additional application
-- action\" specified by /@actionName@/.
-- 
-- This corresponds to the \"Name\" key within the keyfile group for the
-- action.
-- 
-- /Since: 2.38/
desktopAppInfoGetActionName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'
    -> T.Text
    -- ^ /@actionName@/: the name of the action as from
    --   'GI.Gio.Objects.DesktopAppInfo.desktopAppInfoListActions'
    -> m T.Text
    -- ^ __Returns:__ the locale-specific action name
desktopAppInfoGetActionName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
a -> Text -> m Text
desktopAppInfoGetActionName a
info Text
actionName = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    actionName' <- textToCString actionName
    result <- g_desktop_app_info_get_action_name info' actionName'
    checkUnexpectedReturnNULL "desktopAppInfoGetActionName" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr info
    freeMem actionName'
    return result'

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

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


#endif

-- method DesktopAppInfo::get_boolean
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DesktopAppInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDesktopAppInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to look up" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_desktop_app_info_get_boolean" g_desktop_app_info_get_boolean :: 
    Ptr DesktopAppInfo ->                   -- info : TInterface (Name {namespace = "Gio", name = "DesktopAppInfo"})
    CString ->                              -- key : TBasicType TUTF8
    IO CInt

-- | Looks up a boolean value in the keyfile backing /@info@/.
-- 
-- The /@key@/ is looked up in the \"Desktop Entry\" group.
-- 
-- /Since: 2.36/
desktopAppInfoGetBoolean ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'
    -> T.Text
    -- ^ /@key@/: the key to look up
    -> m Bool
    -- ^ __Returns:__ the boolean value, or 'P.False' if the key
    --     is not found
desktopAppInfoGetBoolean :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
a -> Text -> m Bool
desktopAppInfoGetBoolean a
info Text
key = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    key' <- textToCString key
    result <- g_desktop_app_info_get_boolean info' key'
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr info
    freeMem key'
    return result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetBooleanMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsDesktopAppInfo a) => O.OverloadedMethod DesktopAppInfoGetBooleanMethodInfo a signature where
    overloadedMethod = desktopAppInfoGetBoolean

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


#endif

-- method DesktopAppInfo::get_categories
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DesktopAppInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDesktopAppInfo" , 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_desktop_app_info_get_categories" g_desktop_app_info_get_categories :: 
    Ptr DesktopAppInfo ->                   -- info : TInterface (Name {namespace = "Gio", name = "DesktopAppInfo"})
    IO CString

-- | Gets the categories from the desktop file.
desktopAppInfoGetCategories ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The unparsed Categories key from the desktop file;
    --     i.e. no attempt is made to split it by \';\' or validate it.
desktopAppInfoGetCategories :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
a -> m (Maybe Text)
desktopAppInfoGetCategories a
info = 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
    info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    result <- g_desktop_app_info_get_categories info'
    maybeResult <- convertIfNonNull result $ \CString
result' -> do
        result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        return result''
    touchManagedPtr info
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetCategoriesMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDesktopAppInfo a) => O.OverloadedMethod DesktopAppInfoGetCategoriesMethodInfo a signature where
    overloadedMethod = desktopAppInfoGetCategories

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


#endif

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

foreign import ccall "g_desktop_app_info_get_filename" g_desktop_app_info_get_filename :: 
    Ptr DesktopAppInfo ->                   -- info : TInterface (Name {namespace = "Gio", name = "DesktopAppInfo"})
    IO CString

-- | When /@info@/ was created from a known filename, return it.  In some
-- situations such as the t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo' returned from
-- 'GI.Gio.Objects.DesktopAppInfo.desktopAppInfoNewFromKeyfile', this function will return 'P.Nothing'.
-- 
-- /Since: 2.24/
desktopAppInfoGetFilename ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'
    -> m (Maybe [Char])
    -- ^ __Returns:__ The full path to the file for /@info@/,
    --     or 'P.Nothing' if not known.
desktopAppInfoGetFilename :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
a -> m (Maybe String)
desktopAppInfoGetFilename a
info = IO (Maybe String) -> m (Maybe String)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe String) -> m (Maybe String))
-> IO (Maybe String) -> m (Maybe String)
forall a b. (a -> b) -> a -> b
$ do
    info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    result <- g_desktop_app_info_get_filename info'
    maybeResult <- convertIfNonNull result $ \CString
result' -> do
        result'' <- HasCallStack => CString -> IO String
CString -> IO String
cstringToString CString
result'
        return result''
    touchManagedPtr info
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetFilenameMethodInfo
instance (signature ~ (m (Maybe [Char])), MonadIO m, IsDesktopAppInfo a) => O.OverloadedMethod DesktopAppInfoGetFilenameMethodInfo a signature where
    overloadedMethod = desktopAppInfoGetFilename

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


#endif

-- method DesktopAppInfo::get_generic_name
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DesktopAppInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDesktopAppInfo" , 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_desktop_app_info_get_generic_name" g_desktop_app_info_get_generic_name :: 
    Ptr DesktopAppInfo ->                   -- info : TInterface (Name {namespace = "Gio", name = "DesktopAppInfo"})
    IO CString

-- | Gets the generic name from the desktop file.
desktopAppInfoGetGenericName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The value of the GenericName key
desktopAppInfoGetGenericName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
a -> m (Maybe Text)
desktopAppInfoGetGenericName a
info = 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
    info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    result <- g_desktop_app_info_get_generic_name info'
    maybeResult <- convertIfNonNull result $ \CString
result' -> do
        result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        return result''
    touchManagedPtr info
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetGenericNameMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDesktopAppInfo a) => O.OverloadedMethod DesktopAppInfoGetGenericNameMethodInfo a signature where
    overloadedMethod = desktopAppInfoGetGenericName

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


#endif

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

foreign import ccall "g_desktop_app_info_get_is_hidden" g_desktop_app_info_get_is_hidden :: 
    Ptr DesktopAppInfo ->                   -- info : TInterface (Name {namespace = "Gio", name = "DesktopAppInfo"})
    IO CInt

-- | A desktop file is hidden if the Hidden key in it is
-- set to True.
desktopAppInfoGetIsHidden ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'.
    -> m Bool
    -- ^ __Returns:__ 'P.True' if hidden, 'P.False' otherwise.
desktopAppInfoGetIsHidden :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
a -> m Bool
desktopAppInfoGetIsHidden a
info = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    result <- g_desktop_app_info_get_is_hidden info'
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr info
    return result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetIsHiddenMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDesktopAppInfo a) => O.OverloadedMethod DesktopAppInfoGetIsHiddenMethodInfo a signature where
    overloadedMethod = desktopAppInfoGetIsHidden

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


#endif

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

foreign import ccall "g_desktop_app_info_get_keywords" g_desktop_app_info_get_keywords :: 
    Ptr DesktopAppInfo ->                   -- info : TInterface (Name {namespace = "Gio", name = "DesktopAppInfo"})
    IO (Ptr CString)

-- | Gets the keywords from the desktop file.
-- 
-- /Since: 2.32/
desktopAppInfoGetKeywords ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'
    -> m [T.Text]
    -- ^ __Returns:__ The value of the Keywords key
desktopAppInfoGetKeywords :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
a -> m [Text]
desktopAppInfoGetKeywords a
info = IO [Text] -> m [Text]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
    info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    result <- g_desktop_app_info_get_keywords info'
    checkUnexpectedReturnNULL "desktopAppInfoGetKeywords" result
    result' <- unpackZeroTerminatedUTF8CArray result
    touchManagedPtr info
    return result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetKeywordsMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsDesktopAppInfo a) => O.OverloadedMethod DesktopAppInfoGetKeywordsMethodInfo a signature where
    overloadedMethod = desktopAppInfoGetKeywords

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


#endif

-- method DesktopAppInfo::get_locale_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DesktopAppInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDesktopAppInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to look up" , 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_desktop_app_info_get_locale_string" g_desktop_app_info_get_locale_string :: 
    Ptr DesktopAppInfo ->                   -- info : TInterface (Name {namespace = "Gio", name = "DesktopAppInfo"})
    CString ->                              -- key : TBasicType TUTF8
    IO CString

-- | Looks up a localized string value in the keyfile backing /@info@/
-- translated to the current locale.
-- 
-- The /@key@/ is looked up in the \"Desktop Entry\" group.
-- 
-- /Since: 2.56/
desktopAppInfoGetLocaleString ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'
    -> T.Text
    -- ^ /@key@/: the key to look up
    -> m (Maybe T.Text)
    -- ^ __Returns:__ a newly allocated string, or 'P.Nothing' if the key
    --     is not found
desktopAppInfoGetLocaleString :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
a -> Text -> m (Maybe Text)
desktopAppInfoGetLocaleString a
info Text
key = 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
    info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    key' <- textToCString key
    result <- g_desktop_app_info_get_locale_string info' key'
    maybeResult <- convertIfNonNull result $ \CString
result' -> do
        result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        freeMem result'
        return result''
    touchManagedPtr info
    freeMem key'
    return maybeResult

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

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


#endif

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

foreign import ccall "g_desktop_app_info_get_nodisplay" g_desktop_app_info_get_nodisplay :: 
    Ptr DesktopAppInfo ->                   -- info : TInterface (Name {namespace = "Gio", name = "DesktopAppInfo"})
    IO CInt

-- | Gets the value of the NoDisplay key, which helps determine if the
-- application info should be shown in menus. See
-- 'GI.GLib.Constants.KEY_FILE_DESKTOP_KEY_NO_DISPLAY' and 'GI.Gio.Interfaces.AppInfo.appInfoShouldShow'.
-- 
-- /Since: 2.30/
desktopAppInfoGetNodisplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'
    -> m Bool
    -- ^ __Returns:__ The value of the NoDisplay key
desktopAppInfoGetNodisplay :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
a -> m Bool
desktopAppInfoGetNodisplay a
info = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    result <- g_desktop_app_info_get_nodisplay info'
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr info
    return result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetNodisplayMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDesktopAppInfo a) => O.OverloadedMethod DesktopAppInfoGetNodisplayMethodInfo a signature where
    overloadedMethod = desktopAppInfoGetNodisplay

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


#endif

-- method DesktopAppInfo::get_show_in
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DesktopAppInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDesktopAppInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "desktop_env"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string specifying a desktop name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_desktop_app_info_get_show_in" g_desktop_app_info_get_show_in :: 
    Ptr DesktopAppInfo ->                   -- info : TInterface (Name {namespace = "Gio", name = "DesktopAppInfo"})
    CString ->                              -- desktop_env : TBasicType TUTF8
    IO CInt

-- | Checks if the application info should be shown in menus that list available
-- applications for a specific name of the desktop, based on the
-- @OnlyShowIn@ and @NotShowIn@ keys.
-- 
-- /@desktopEnv@/ should typically be given as 'P.Nothing', in which case the
-- @XDG_CURRENT_DESKTOP@ environment variable is consulted.  If you want
-- to override the default mechanism then you may specify /@desktopEnv@/,
-- but this is not recommended.
-- 
-- Note that 'GI.Gio.Interfaces.AppInfo.appInfoShouldShow' for /@info@/ will include this check (with
-- 'P.Nothing' for /@desktopEnv@/) as well as additional checks.
-- 
-- /Since: 2.30/
desktopAppInfoGetShowIn ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'
    -> Maybe (T.Text)
    -- ^ /@desktopEnv@/: a string specifying a desktop name
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the /@info@/ should be shown in /@desktopEnv@/ according to the
    -- @OnlyShowIn@ and @NotShowIn@ keys, 'P.False'
    -- otherwise.
desktopAppInfoGetShowIn :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
a -> Maybe Text -> m Bool
desktopAppInfoGetShowIn a
info Maybe Text
desktopEnv = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    maybeDesktopEnv <- case desktopEnv of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
FP.nullPtr
        Just Text
jDesktopEnv -> do
            jDesktopEnv' <- Text -> IO CString
textToCString Text
jDesktopEnv
            return jDesktopEnv'
    result <- g_desktop_app_info_get_show_in info' maybeDesktopEnv
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr info
    freeMem maybeDesktopEnv
    return result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetShowInMethodInfo
instance (signature ~ (Maybe (T.Text) -> m Bool), MonadIO m, IsDesktopAppInfo a) => O.OverloadedMethod DesktopAppInfoGetShowInMethodInfo a signature where
    overloadedMethod = desktopAppInfoGetShowIn

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


#endif

-- method DesktopAppInfo::get_startup_wm_class
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DesktopAppInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GDesktopAppInfo that supports startup notify"
--                 , 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_desktop_app_info_get_startup_wm_class" g_desktop_app_info_get_startup_wm_class :: 
    Ptr DesktopAppInfo ->                   -- info : TInterface (Name {namespace = "Gio", name = "DesktopAppInfo"})
    IO CString

-- | Retrieves the StartupWMClass field from /@info@/. This represents the
-- WM_CLASS property of the main window of the application, if launched
-- through /@info@/.
-- 
-- /Since: 2.34/
desktopAppInfoGetStartupWmClass ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo' that supports startup notify
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the startup WM class, or 'P.Nothing' if none is set
    -- in the desktop file.
desktopAppInfoGetStartupWmClass :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
a -> m (Maybe Text)
desktopAppInfoGetStartupWmClass a
info = 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
    info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    result <- g_desktop_app_info_get_startup_wm_class info'
    maybeResult <- convertIfNonNull result $ \CString
result' -> do
        result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        return result''
    touchManagedPtr info
    return maybeResult

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetStartupWmClassMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m, IsDesktopAppInfo a) => O.OverloadedMethod DesktopAppInfoGetStartupWmClassMethodInfo a signature where
    overloadedMethod = desktopAppInfoGetStartupWmClass

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


#endif

-- method DesktopAppInfo::get_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DesktopAppInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDesktopAppInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to look up" , 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_desktop_app_info_get_string" g_desktop_app_info_get_string :: 
    Ptr DesktopAppInfo ->                   -- info : TInterface (Name {namespace = "Gio", name = "DesktopAppInfo"})
    CString ->                              -- key : TBasicType TUTF8
    IO CString

-- | Looks up a string value in the keyfile backing /@info@/.
-- 
-- The /@key@/ is looked up in the \"Desktop Entry\" group.
-- 
-- /Since: 2.36/
desktopAppInfoGetString ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'
    -> T.Text
    -- ^ /@key@/: the key to look up
    -> m (Maybe T.Text)
    -- ^ __Returns:__ a newly allocated string, or 'P.Nothing' if the key
    --     is not found
desktopAppInfoGetString :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
a -> Text -> m (Maybe Text)
desktopAppInfoGetString a
info Text
key = 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
    info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    key' <- textToCString key
    result <- g_desktop_app_info_get_string info' key'
    maybeResult <- convertIfNonNull result $ \CString
result' -> do
        result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        freeMem result'
        return result''
    touchManagedPtr info
    freeMem key'
    return maybeResult

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

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


#endif

-- method DesktopAppInfo::get_string_list
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DesktopAppInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDesktopAppInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to look up" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TSize
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the number of returned strings, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) 2 (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "g_desktop_app_info_get_string_list" g_desktop_app_info_get_string_list :: 
    Ptr DesktopAppInfo ->                   -- info : TInterface (Name {namespace = "Gio", name = "DesktopAppInfo"})
    CString ->                              -- key : TBasicType TUTF8
    Ptr FCT.CSize ->                        -- length : TBasicType TSize
    IO (Ptr CString)

-- | Looks up a string list value in the keyfile backing /@info@/.
-- 
-- The /@key@/ is looked up in the \"Desktop Entry\" group.
-- 
-- /Since: 2.60/
desktopAppInfoGetStringList ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'
    -> T.Text
    -- ^ /@key@/: the key to look up
    -> m (([T.Text], FCT.CSize))
    -- ^ __Returns:__ 
    --  a 'P.Nothing'-terminated string array or 'P.Nothing' if the specified
    --  key cannot be found. The array should be freed with 'GI.GLib.Functions.strfreev'.
desktopAppInfoGetStringList :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
a -> Text -> m ([Text], CSize)
desktopAppInfoGetStringList a
info Text
key = IO ([Text], CSize) -> m ([Text], CSize)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ([Text], CSize) -> m ([Text], CSize))
-> IO ([Text], CSize) -> m ([Text], CSize)
forall a b. (a -> b) -> a -> b
$ do
    info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    key' <- textToCString key
    length_ <- allocMem :: IO (Ptr FCT.CSize)
    result <- g_desktop_app_info_get_string_list info' key' length_
    checkUnexpectedReturnNULL "desktopAppInfoGetStringList" result
    result' <- unpackZeroTerminatedUTF8CArray result
    mapZeroTerminatedCArray freeMem result
    freeMem result
    length_' <- peek length_
    touchManagedPtr info
    freeMem key'
    freeMem length_
    return (result', length_')

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetStringListMethodInfo
instance (signature ~ (T.Text -> m (([T.Text], FCT.CSize))), MonadIO m, IsDesktopAppInfo a) => O.OverloadedMethod DesktopAppInfoGetStringListMethodInfo a signature where
    overloadedMethod = desktopAppInfoGetStringList

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


#endif

-- method DesktopAppInfo::has_key
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DesktopAppInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDesktopAppInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the key to look up" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_desktop_app_info_has_key" g_desktop_app_info_has_key :: 
    Ptr DesktopAppInfo ->                   -- info : TInterface (Name {namespace = "Gio", name = "DesktopAppInfo"})
    CString ->                              -- key : TBasicType TUTF8
    IO CInt

-- | Returns whether /@key@/ exists in the \"Desktop Entry\" group
-- of the keyfile backing /@info@/.
-- 
-- /Since: 2.36/
desktopAppInfoHasKey ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'
    -> T.Text
    -- ^ /@key@/: the key to look up
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the /@key@/ exists
desktopAppInfoHasKey :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
a -> Text -> m Bool
desktopAppInfoHasKey a
info Text
key = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    key' <- textToCString key
    result <- g_desktop_app_info_has_key info' key'
    let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    touchManagedPtr info
    freeMem key'
    return result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoHasKeyMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsDesktopAppInfo a) => O.OverloadedMethod DesktopAppInfoHasKeyMethodInfo a signature where
    overloadedMethod = desktopAppInfoHasKey

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


#endif

-- method DesktopAppInfo::launch_action
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "info"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DesktopAppInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDesktopAppInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "action_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the name of the action as from\n  g_desktop_app_info_list_actions()"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "launch_context"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AppLaunchContext" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAppLaunchContext"
--                 , 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_desktop_app_info_launch_action" g_desktop_app_info_launch_action :: 
    Ptr DesktopAppInfo ->                   -- info : TInterface (Name {namespace = "Gio", name = "DesktopAppInfo"})
    CString ->                              -- action_name : TBasicType TUTF8
    Ptr Gio.AppLaunchContext.AppLaunchContext -> -- launch_context : TInterface (Name {namespace = "Gio", name = "AppLaunchContext"})
    IO ()

-- | Activates the named application action.
-- 
-- You may only call this function on action names that were
-- returned from 'GI.Gio.Objects.DesktopAppInfo.desktopAppInfoListActions'.
-- 
-- Note that if the main entry of the desktop file indicates that the
-- application supports startup notification, and /@launchContext@/ is
-- non-'P.Nothing', then startup notification will be used when activating the
-- action (and as such, invocation of the action on the receiving side
-- must signal the end of startup notification when it is completed).
-- This is the expected behaviour of applications declaring additional
-- actions, as per the desktop file specification.
-- 
-- As with 'GI.Gio.Interfaces.AppInfo.appInfoLaunch' there is no way to detect failures that
-- occur while using this function.
-- 
-- /Since: 2.38/
desktopAppInfoLaunchAction ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a, Gio.AppLaunchContext.IsAppLaunchContext b) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'
    -> T.Text
    -- ^ /@actionName@/: the name of the action as from
    --   'GI.Gio.Objects.DesktopAppInfo.desktopAppInfoListActions'
    -> Maybe (b)
    -- ^ /@launchContext@/: a t'GI.Gio.Objects.AppLaunchContext.AppLaunchContext'
    -> m ()
desktopAppInfoLaunchAction :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDesktopAppInfo a,
 IsAppLaunchContext b) =>
a -> Text -> Maybe b -> m ()
desktopAppInfoLaunchAction a
info Text
actionName Maybe b
launchContext = 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
    info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    actionName' <- textToCString actionName
    maybeLaunchContext <- case launchContext of
        Maybe b
Nothing -> Ptr AppLaunchContext -> IO (Ptr AppLaunchContext)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr AppLaunchContext
forall a. Ptr a
FP.nullPtr
        Just b
jLaunchContext -> do
            jLaunchContext' <- b -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jLaunchContext
            return jLaunchContext'
    g_desktop_app_info_launch_action info' actionName' maybeLaunchContext
    touchManagedPtr info
    whenJust launchContext touchManagedPtr
    freeMem actionName'
    return ()

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoLaunchActionMethodInfo
instance (signature ~ (T.Text -> Maybe (b) -> m ()), MonadIO m, IsDesktopAppInfo a, Gio.AppLaunchContext.IsAppLaunchContext b) => O.OverloadedMethod DesktopAppInfoLaunchActionMethodInfo a signature where
    overloadedMethod = desktopAppInfoLaunchAction

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


#endif

-- method DesktopAppInfo::launch_uris_as_manager
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "appinfo"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DesktopAppInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDesktopAppInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uris"
--           , argType = TGList (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "List of URIs" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "launch_context"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AppLaunchContext" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAppLaunchContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "spawn_flags"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "SpawnFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GSpawnFlags, used for each process"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_setup"
--           , argType =
--               TInterface
--                 Name { namespace = "GLib" , name = "SpawnChildSetupFunc" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GSpawnChildSetupFunc, used once\n    for each process."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 5
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_setup_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "User data for @user_setup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pid_callback"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DesktopAppLaunchCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Callback for child processes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeCall
--           , argClosure = 7
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pid_callback_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "User data for @callback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_desktop_app_info_launch_uris_as_manager" g_desktop_app_info_launch_uris_as_manager :: 
    Ptr DesktopAppInfo ->                   -- appinfo : TInterface (Name {namespace = "Gio", name = "DesktopAppInfo"})
    Ptr (GList CString) ->                  -- uris : TGList (TBasicType TUTF8)
    Ptr Gio.AppLaunchContext.AppLaunchContext -> -- launch_context : TInterface (Name {namespace = "Gio", name = "AppLaunchContext"})
    CUInt ->                                -- spawn_flags : TInterface (Name {namespace = "GLib", name = "SpawnFlags"})
    FunPtr GLib.Callbacks.C_SpawnChildSetupFunc -> -- user_setup : TInterface (Name {namespace = "GLib", name = "SpawnChildSetupFunc"})
    Ptr () ->                               -- user_setup_data : TBasicType TPtr
    FunPtr Gio.Callbacks.C_DesktopAppLaunchCallback -> -- pid_callback : TInterface (Name {namespace = "Gio", name = "DesktopAppLaunchCallback"})
    Ptr () ->                               -- pid_callback_data : TBasicType TPtr
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | This function performs the equivalent of 'GI.Gio.Interfaces.AppInfo.appInfoLaunchUris',
-- but is intended primarily for operating system components that
-- launch applications.  Ordinary applications should use
-- 'GI.Gio.Interfaces.AppInfo.appInfoLaunchUris'.
-- 
-- If the application is launched via GSpawn, then /@spawnFlags@/, /@userSetup@/
-- and /@userSetupData@/ are used for the call to 'GI.GLib.Functions.spawnAsync'.
-- Additionally, /@pidCallback@/ (with /@pidCallbackData@/) will be called to
-- inform about the PID of the created process. See 'GI.GLib.Functions.spawnAsyncWithPipes'
-- for information on certain parameter conditions that can enable an
-- optimized @/posix_spawn()/@ codepath to be used.
-- 
-- If application launching occurs via some other mechanism (eg: D-Bus
-- activation) then /@spawnFlags@/, /@userSetup@/, /@userSetupData@/,
-- /@pidCallback@/ and /@pidCallbackData@/ are ignored.
desktopAppInfoLaunchUrisAsManager ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a, Gio.AppLaunchContext.IsAppLaunchContext b) =>
    a
    -- ^ /@appinfo@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'
    -> [T.Text]
    -- ^ /@uris@/: List of URIs
    -> Maybe (b)
    -- ^ /@launchContext@/: a t'GI.Gio.Objects.AppLaunchContext.AppLaunchContext'
    -> [GLib.Flags.SpawnFlags]
    -- ^ /@spawnFlags@/: t'GI.GLib.Flags.SpawnFlags', used for each process
    -> Maybe (GLib.Callbacks.SpawnChildSetupFunc)
    -- ^ /@userSetup@/: a t'GI.GLib.Callbacks.SpawnChildSetupFunc', used once
    --     for each process.
    -> Maybe (Gio.Callbacks.DesktopAppLaunchCallback)
    -- ^ /@pidCallback@/: Callback for child processes
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
desktopAppInfoLaunchUrisAsManager :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDesktopAppInfo a,
 IsAppLaunchContext b) =>
a
-> [Text]
-> Maybe b
-> [SpawnFlags]
-> Maybe SpawnChildSetupFunc
-> Maybe DesktopAppLaunchCallback
-> m ()
desktopAppInfoLaunchUrisAsManager a
appinfo [Text]
uris Maybe b
launchContext [SpawnFlags]
spawnFlags Maybe SpawnChildSetupFunc
userSetup Maybe DesktopAppLaunchCallback
pidCallback = 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
    appinfo' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
appinfo
    uris' <- mapM textToCString uris
    uris'' <- packGList uris'
    maybeLaunchContext <- case launchContext of
        Maybe b
Nothing -> Ptr AppLaunchContext -> IO (Ptr AppLaunchContext)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr AppLaunchContext
forall a. Ptr a
FP.nullPtr
        Just b
jLaunchContext -> do
            jLaunchContext' <- b -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jLaunchContext
            return jLaunchContext'
    let spawnFlags' = [SpawnFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [SpawnFlags]
spawnFlags
    maybeUserSetup <- case userSetup of
        Maybe SpawnChildSetupFunc
Nothing -> FunPtr SpawnChildSetupFunc -> IO (FunPtr SpawnChildSetupFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr SpawnChildSetupFunc
forall a. FunPtr a
FP.nullFunPtr
        Just SpawnChildSetupFunc
jUserSetup -> do
            ptruserSetup <- IO (Ptr (FunPtr SpawnChildSetupFunc))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr GLib.Callbacks.C_SpawnChildSetupFunc))
            jUserSetup' <- GLib.Callbacks.mk_SpawnChildSetupFunc (GLib.Callbacks.wrap_SpawnChildSetupFunc (Just ptruserSetup) jUserSetup)
            poke ptruserSetup jUserSetup'
            return jUserSetup'
    maybePidCallback <- case pidCallback of
        Maybe DesktopAppLaunchCallback
Nothing -> FunPtr C_DesktopAppLaunchCallback
-> IO (FunPtr C_DesktopAppLaunchCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_DesktopAppLaunchCallback
forall a. FunPtr a
FP.nullFunPtr
        Just DesktopAppLaunchCallback
jPidCallback -> do
            jPidCallback' <- C_DesktopAppLaunchCallback
-> IO (FunPtr C_DesktopAppLaunchCallback)
Gio.Callbacks.mk_DesktopAppLaunchCallback (Maybe (Ptr (FunPtr C_DesktopAppLaunchCallback))
-> DesktopAppLaunchCallback_WithClosures
-> C_DesktopAppLaunchCallback
Gio.Callbacks.wrap_DesktopAppLaunchCallback Maybe (Ptr (FunPtr C_DesktopAppLaunchCallback))
forall a. Maybe a
Nothing (DesktopAppLaunchCallback -> DesktopAppLaunchCallback_WithClosures
Gio.Callbacks.drop_closures_DesktopAppLaunchCallback DesktopAppLaunchCallback
jPidCallback))
            return jPidCallback'
    let userSetupData = Ptr a
forall a. Ptr a
nullPtr
    let pidCallbackData = Ptr a
forall a. Ptr a
nullPtr
    onException (do
        _ <- propagateGError $ g_desktop_app_info_launch_uris_as_manager appinfo' uris'' maybeLaunchContext spawnFlags' maybeUserSetup userSetupData maybePidCallback pidCallbackData
        safeFreeFunPtr $ castFunPtrToPtr maybePidCallback
        touchManagedPtr appinfo
        whenJust launchContext touchManagedPtr
        mapGList freeMem uris''
        g_list_free uris''
        return ()
     ) (do
        safeFreeFunPtr $ castFunPtrToPtr maybePidCallback
        mapGList freeMem uris''
        g_list_free uris''
     )

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoLaunchUrisAsManagerMethodInfo
instance (signature ~ ([T.Text] -> Maybe (b) -> [GLib.Flags.SpawnFlags] -> Maybe (GLib.Callbacks.SpawnChildSetupFunc) -> Maybe (Gio.Callbacks.DesktopAppLaunchCallback) -> m ()), MonadIO m, IsDesktopAppInfo a, Gio.AppLaunchContext.IsAppLaunchContext b) => O.OverloadedMethod DesktopAppInfoLaunchUrisAsManagerMethodInfo a signature where
    overloadedMethod = desktopAppInfoLaunchUrisAsManager

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


#endif

-- method DesktopAppInfo::launch_uris_as_manager_with_fds
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "appinfo"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "DesktopAppInfo" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GDesktopAppInfo" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "uris"
--           , argType = TGList (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "List of URIs" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "launch_context"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AppLaunchContext" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GAppLaunchContext"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "spawn_flags"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "SpawnFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GSpawnFlags, used for each process"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_setup"
--           , argType =
--               TInterface
--                 Name { namespace = "GLib" , name = "SpawnChildSetupFunc" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a #GSpawnChildSetupFunc, used once\n    for each process."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 5
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_setup_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "User data for @user_setup"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pid_callback"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "DesktopAppLaunchCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Callback for child processes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeCall
--           , argClosure = 7
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pid_callback_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "User data for @callback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "stdin_fd"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "file descriptor to use for child's stdin, or -1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "stdout_fd"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "file descriptor to use for child's stdout, or -1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "stderr_fd"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "file descriptor to use for child's stderr, or -1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_desktop_app_info_launch_uris_as_manager_with_fds" g_desktop_app_info_launch_uris_as_manager_with_fds :: 
    Ptr DesktopAppInfo ->                   -- appinfo : TInterface (Name {namespace = "Gio", name = "DesktopAppInfo"})
    Ptr (GList CString) ->                  -- uris : TGList (TBasicType TUTF8)
    Ptr Gio.AppLaunchContext.AppLaunchContext -> -- launch_context : TInterface (Name {namespace = "Gio", name = "AppLaunchContext"})
    CUInt ->                                -- spawn_flags : TInterface (Name {namespace = "GLib", name = "SpawnFlags"})
    FunPtr GLib.Callbacks.C_SpawnChildSetupFunc -> -- user_setup : TInterface (Name {namespace = "GLib", name = "SpawnChildSetupFunc"})
    Ptr () ->                               -- user_setup_data : TBasicType TPtr
    FunPtr Gio.Callbacks.C_DesktopAppLaunchCallback -> -- pid_callback : TInterface (Name {namespace = "Gio", name = "DesktopAppLaunchCallback"})
    Ptr () ->                               -- pid_callback_data : TBasicType TPtr
    Int32 ->                                -- stdin_fd : TBasicType TInt
    Int32 ->                                -- stdout_fd : TBasicType TInt
    Int32 ->                                -- stderr_fd : TBasicType TInt
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Equivalent to 'GI.Gio.Objects.DesktopAppInfo.desktopAppInfoLaunchUrisAsManager' but allows
-- you to pass in file descriptors for the stdin, stdout and stderr streams
-- of the launched process.
-- 
-- If application launching occurs via some non-spawn mechanism (e.g. D-Bus
-- activation) then /@stdinFd@/, /@stdoutFd@/ and /@stderrFd@/ are ignored.
-- 
-- /Since: 2.58/
desktopAppInfoLaunchUrisAsManagerWithFds ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a, Gio.AppLaunchContext.IsAppLaunchContext b) =>
    a
    -- ^ /@appinfo@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'
    -> [T.Text]
    -- ^ /@uris@/: List of URIs
    -> Maybe (b)
    -- ^ /@launchContext@/: a t'GI.Gio.Objects.AppLaunchContext.AppLaunchContext'
    -> [GLib.Flags.SpawnFlags]
    -- ^ /@spawnFlags@/: t'GI.GLib.Flags.SpawnFlags', used for each process
    -> Maybe (GLib.Callbacks.SpawnChildSetupFunc)
    -- ^ /@userSetup@/: a t'GI.GLib.Callbacks.SpawnChildSetupFunc', used once
    --     for each process.
    -> Maybe (Gio.Callbacks.DesktopAppLaunchCallback)
    -- ^ /@pidCallback@/: Callback for child processes
    -> Int32
    -- ^ /@stdinFd@/: file descriptor to use for child\'s stdin, or -1
    -> Int32
    -- ^ /@stdoutFd@/: file descriptor to use for child\'s stdout, or -1
    -> Int32
    -- ^ /@stderrFd@/: file descriptor to use for child\'s stderr, or -1
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
desktopAppInfoLaunchUrisAsManagerWithFds :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsDesktopAppInfo a,
 IsAppLaunchContext b) =>
a
-> [Text]
-> Maybe b
-> [SpawnFlags]
-> Maybe SpawnChildSetupFunc
-> Maybe DesktopAppLaunchCallback
-> Int32
-> Int32
-> Int32
-> m ()
desktopAppInfoLaunchUrisAsManagerWithFds a
appinfo [Text]
uris Maybe b
launchContext [SpawnFlags]
spawnFlags Maybe SpawnChildSetupFunc
userSetup Maybe DesktopAppLaunchCallback
pidCallback Int32
stdinFd Int32
stdoutFd Int32
stderrFd = 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
    appinfo' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
appinfo
    uris' <- mapM textToCString uris
    uris'' <- packGList uris'
    maybeLaunchContext <- case launchContext of
        Maybe b
Nothing -> Ptr AppLaunchContext -> IO (Ptr AppLaunchContext)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr AppLaunchContext
forall a. Ptr a
FP.nullPtr
        Just b
jLaunchContext -> do
            jLaunchContext' <- b -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jLaunchContext
            return jLaunchContext'
    let spawnFlags' = [SpawnFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [SpawnFlags]
spawnFlags
    maybeUserSetup <- case userSetup of
        Maybe SpawnChildSetupFunc
Nothing -> FunPtr SpawnChildSetupFunc -> IO (FunPtr SpawnChildSetupFunc)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr SpawnChildSetupFunc
forall a. FunPtr a
FP.nullFunPtr
        Just SpawnChildSetupFunc
jUserSetup -> do
            ptruserSetup <- IO (Ptr (FunPtr SpawnChildSetupFunc))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr GLib.Callbacks.C_SpawnChildSetupFunc))
            jUserSetup' <- GLib.Callbacks.mk_SpawnChildSetupFunc (GLib.Callbacks.wrap_SpawnChildSetupFunc (Just ptruserSetup) jUserSetup)
            poke ptruserSetup jUserSetup'
            return jUserSetup'
    maybePidCallback <- case pidCallback of
        Maybe DesktopAppLaunchCallback
Nothing -> FunPtr C_DesktopAppLaunchCallback
-> IO (FunPtr C_DesktopAppLaunchCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_DesktopAppLaunchCallback
forall a. FunPtr a
FP.nullFunPtr
        Just DesktopAppLaunchCallback
jPidCallback -> do
            jPidCallback' <- C_DesktopAppLaunchCallback
-> IO (FunPtr C_DesktopAppLaunchCallback)
Gio.Callbacks.mk_DesktopAppLaunchCallback (Maybe (Ptr (FunPtr C_DesktopAppLaunchCallback))
-> DesktopAppLaunchCallback_WithClosures
-> C_DesktopAppLaunchCallback
Gio.Callbacks.wrap_DesktopAppLaunchCallback Maybe (Ptr (FunPtr C_DesktopAppLaunchCallback))
forall a. Maybe a
Nothing (DesktopAppLaunchCallback -> DesktopAppLaunchCallback_WithClosures
Gio.Callbacks.drop_closures_DesktopAppLaunchCallback DesktopAppLaunchCallback
jPidCallback))
            return jPidCallback'
    let userSetupData = Ptr a
forall a. Ptr a
nullPtr
    let pidCallbackData = Ptr a
forall a. Ptr a
nullPtr
    onException (do
        _ <- propagateGError $ g_desktop_app_info_launch_uris_as_manager_with_fds appinfo' uris'' maybeLaunchContext spawnFlags' maybeUserSetup userSetupData maybePidCallback pidCallbackData stdinFd stdoutFd stderrFd
        safeFreeFunPtr $ castFunPtrToPtr maybePidCallback
        touchManagedPtr appinfo
        whenJust launchContext touchManagedPtr
        mapGList freeMem uris''
        g_list_free uris''
        return ()
     ) (do
        safeFreeFunPtr $ castFunPtrToPtr maybePidCallback
        mapGList freeMem uris''
        g_list_free uris''
     )

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoLaunchUrisAsManagerWithFdsMethodInfo
instance (signature ~ ([T.Text] -> Maybe (b) -> [GLib.Flags.SpawnFlags] -> Maybe (GLib.Callbacks.SpawnChildSetupFunc) -> Maybe (Gio.Callbacks.DesktopAppLaunchCallback) -> Int32 -> Int32 -> Int32 -> m ()), MonadIO m, IsDesktopAppInfo a, Gio.AppLaunchContext.IsAppLaunchContext b) => O.OverloadedMethod DesktopAppInfoLaunchUrisAsManagerWithFdsMethodInfo a signature where
    overloadedMethod = desktopAppInfoLaunchUrisAsManagerWithFds

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


#endif

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

foreign import ccall "g_desktop_app_info_list_actions" g_desktop_app_info_list_actions :: 
    Ptr DesktopAppInfo ->                   -- info : TInterface (Name {namespace = "Gio", name = "DesktopAppInfo"})
    IO (Ptr CString)

-- | Returns the list of \"additional application actions\" supported on the
-- desktop file, as per the desktop file specification.
-- 
-- As per the specification, this is the list of actions that are
-- explicitly listed in the \"Actions\" key of the [Desktop Entry] group.
-- 
-- /Since: 2.38/
desktopAppInfoListActions ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'
    -> m [T.Text]
    -- ^ __Returns:__ a list of strings, always non-'P.Nothing'
desktopAppInfoListActions :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
a -> m [Text]
desktopAppInfoListActions a
info = IO [Text] -> m [Text]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
    info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    result <- g_desktop_app_info_list_actions info'
    checkUnexpectedReturnNULL "desktopAppInfoListActions" result
    result' <- unpackZeroTerminatedUTF8CArray result
    touchManagedPtr info
    return result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoListActionsMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsDesktopAppInfo a) => O.OverloadedMethod DesktopAppInfoListActionsMethodInfo a signature where
    overloadedMethod = desktopAppInfoListActions

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


#endif

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

foreign import ccall "g_desktop_app_info_get_implementations" g_desktop_app_info_get_implementations :: 
    CString ->                              -- interface : TBasicType TUTF8
    IO (Ptr (GList (Ptr DesktopAppInfo)))

-- | Gets all applications that implement /@interface@/.
-- 
-- An application implements an interface if that interface is listed in
-- the Implements= line of the desktop file of the application.
-- 
-- /Since: 2.42/
desktopAppInfoGetImplementations ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@interface@/: the name of the interface
    -> m [DesktopAppInfo]
    -- ^ __Returns:__ a list of t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'
    -- objects.
desktopAppInfoGetImplementations :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m [DesktopAppInfo]
desktopAppInfoGetImplementations Text
interface = IO [DesktopAppInfo] -> m [DesktopAppInfo]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [DesktopAppInfo] -> m [DesktopAppInfo])
-> IO [DesktopAppInfo] -> m [DesktopAppInfo]
forall a b. (a -> b) -> a -> b
$ do
    interface' <- Text -> IO CString
textToCString Text
interface
    result <- g_desktop_app_info_get_implementations interface'
    result' <- unpackGList result
    result'' <- mapM (wrapObject DesktopAppInfo) result'
    g_list_free result
    freeMem interface'
    return result''

#if defined(ENABLE_OVERLOADING)
#endif

-- method DesktopAppInfo::search
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "search_string"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the search string to use"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TCArray
--                  True (-1) (-1) (TCArray True (-1) (-1) (TBasicType TUTF8)))
-- throws : False
-- Skip return : False

foreign import ccall "g_desktop_app_info_search" g_desktop_app_info_search :: 
    CString ->                              -- search_string : TBasicType TUTF8
    IO (Ptr (Ptr CString))

-- | Searches desktop files for ones that match /@searchString@/.
-- 
-- The return value is an array of strvs.  Each strv contains a list of
-- applications that matched /@searchString@/ with an equal score.  The
-- outer list is sorted by score so that the first strv contains the
-- best-matching applications, and so on.
-- The algorithm for determining matches is undefined and may change at
-- any time.
-- 
-- None of the search results are subjected to the normal validation
-- checks performed by 'GI.Gio.Objects.DesktopAppInfo.desktopAppInfoNew' (for example, checking that
-- the executable referenced by a result exists), and so it is possible for
-- 'GI.Gio.Objects.DesktopAppInfo.desktopAppInfoNew' to return 'P.Nothing' when passed an app ID returned by
-- this function. It is expected that calling code will do this when
-- subsequently creating a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo' for each result.
desktopAppInfoSearch ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@searchString@/: the search string to use
    -> m [[T.Text]]
    -- ^ __Returns:__ a
    --   list of strvs.  Free each item with 'GI.GLib.Functions.strfreev' and free the outer
    --   list with 'GI.GLib.Functions.free'.
desktopAppInfoSearch :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> m [[Text]]
desktopAppInfoSearch Text
searchString = IO [[Text]] -> m [[Text]]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [[Text]] -> m [[Text]]) -> IO [[Text]] -> m [[Text]]
forall a b. (a -> b) -> a -> b
$ do
    searchString' <- Text -> IO CString
textToCString Text
searchString
    result <- g_desktop_app_info_search searchString'
    checkUnexpectedReturnNULL "desktopAppInfoSearch" result
    result' <- unpackZeroTerminatedPtrArray result
    result'' <- mapM unpackZeroTerminatedUTF8CArray result'
    let freeElemOfResult Ptr (Ptr a)
e = (Ptr a -> IO ()) -> Ptr (Ptr a) -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray Ptr a -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr a)
e IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr (Ptr a) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr a)
e
    mapZeroTerminatedCArray freeElemOfResult result
    freeMem result
    freeMem searchString'
    return result''

#if defined(ENABLE_OVERLOADING)
#endif

-- method DesktopAppInfo::set_desktop_env
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "desktop_env"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string specifying what desktop this is"
--                 , 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_desktop_app_info_set_desktop_env" g_desktop_app_info_set_desktop_env :: 
    CString ->                              -- desktop_env : TBasicType TUTF8
    IO ()

{-# DEPRECATED desktopAppInfoSetDesktopEnv ["(Since version 2.42)","do not use this API.  Since 2.42 the value of the","@XDG_CURRENT_DESKTOP@ environment variable will be used."] #-}
-- | Sets the name of the desktop that the application is running in.
-- This is used by 'GI.Gio.Interfaces.AppInfo.appInfoShouldShow' and
-- 'GI.Gio.Objects.DesktopAppInfo.desktopAppInfoGetShowIn' to evaluate the
-- @OnlyShowIn@ and @NotShowIn@
-- desktop entry fields.
-- 
-- Should be called only once; subsequent calls are ignored.
desktopAppInfoSetDesktopEnv ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    T.Text
    -- ^ /@desktopEnv@/: a string specifying what desktop this is
    -> m ()
desktopAppInfoSetDesktopEnv :: forall (m :: * -> *). (HasCallStack, MonadIO m) => Text -> m ()
desktopAppInfoSetDesktopEnv Text
desktopEnv = 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
    desktopEnv' <- Text -> IO CString
textToCString Text
desktopEnv
    g_desktop_app_info_set_desktop_env desktopEnv'
    freeMem desktopEnv'
    return ()

#if defined(ENABLE_OVERLOADING)
#endif