{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo' 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 when using it.

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

module GI.Gio.Objects.DesktopAppInfo
    ( 
#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoLaunchUrisAsManagerMethodInfo,
#endif
#if defined(ENABLE_OVERLOADING)
    DesktopAppInfoLaunchUrisAsManagerWithFdsMethodInfo,
#endif

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


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

#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              ,


-- ** 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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import qualified GI.GLib.Structs.KeyFile as GLib.KeyFile
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Interfaces.AppInfo as Gio.AppInfo
import {-# SOURCE #-} qualified GI.Gio.Objects.AppLaunchContext as Gio.AppLaunchContext

-- | Memory-managed wrapper type.
newtype DesktopAppInfo = DesktopAppInfo (ManagedPtr DesktopAppInfo)
    deriving (DesktopAppInfo -> DesktopAppInfo -> Bool
(DesktopAppInfo -> DesktopAppInfo -> Bool)
-> (DesktopAppInfo -> DesktopAppInfo -> Bool) -> Eq DesktopAppInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DesktopAppInfo -> DesktopAppInfo -> Bool
$c/= :: DesktopAppInfo -> DesktopAppInfo -> Bool
== :: DesktopAppInfo -> DesktopAppInfo -> Bool
$c== :: DesktopAppInfo -> DesktopAppInfo -> Bool
Eq)
foreign import ccall "g_desktop_app_info_get_type"
    c_g_desktop_app_info_get_type :: IO GType

instance GObject DesktopAppInfo where
    gobjectType :: IO GType
gobjectType = IO GType
c_g_desktop_app_info_get_type
    

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

-- | Type class for types which can be safely cast to `DesktopAppInfo`, for instance with `toDesktopAppInfo`.
class (GObject o, O.IsDescendantOf DesktopAppInfo o) => IsDesktopAppInfo o
instance (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 :: (MonadIO m, IsDesktopAppInfo o) => o -> m DesktopAppInfo
toDesktopAppInfo :: o -> m DesktopAppInfo
toDesktopAppInfo = IO DesktopAppInfo -> m DesktopAppInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr DesktopAppInfo -> DesktopAppInfo
DesktopAppInfo

-- | A convenience alias for `Nothing` :: `Maybe` `DesktopAppInfo`.
noDesktopAppInfo :: Maybe DesktopAppInfo
noDesktopAppInfo :: Maybe DesktopAppInfo
noDesktopAppInfo = Maybe DesktopAppInfo
forall a. Maybe a
Nothing

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

#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 :: o -> m (Maybe Text)
getDesktopAppInfoFilename obj :: o
obj = IO (Maybe Text) -> m (Maybe Text)
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
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj "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) => T.Text -> IO (GValueConstruct o)
constructDesktopAppInfoFilename :: Text -> IO (GValueConstruct o)
constructDesktopAppInfoFilename val :: Text
val = String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString "filename" (Text -> Maybe Text
forall a. a -> Maybe a
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
#endif

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

#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
--           , 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 :: Text -> m (Maybe DesktopAppInfo)
desktopAppInfoNew desktopId :: Text
desktopId = IO (Maybe DesktopAppInfo) -> m (Maybe DesktopAppInfo)
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
    CString
desktopId' <- Text -> IO CString
textToCString Text
desktopId
    Ptr DesktopAppInfo
result <- CString -> IO (Ptr DesktopAppInfo)
g_desktop_app_info_new CString
desktopId'
    Maybe DesktopAppInfo
maybeResult <- Ptr DesktopAppInfo
-> (Ptr DesktopAppInfo -> IO DesktopAppInfo)
-> IO (Maybe DesktopAppInfo)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr DesktopAppInfo
result ((Ptr DesktopAppInfo -> IO DesktopAppInfo)
 -> IO (Maybe DesktopAppInfo))
-> (Ptr DesktopAppInfo -> IO DesktopAppInfo)
-> IO (Maybe DesktopAppInfo)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr DesktopAppInfo
result' -> do
        DesktopAppInfo
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'
        DesktopAppInfo -> IO DesktopAppInfo
forall (m :: * -> *) a. Monad m => a -> m a
return DesktopAppInfo
result''
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
desktopId'
    Maybe DesktopAppInfo -> IO (Maybe DesktopAppInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DesktopAppInfo
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
--           , 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 :: String -> m (Maybe DesktopAppInfo)
desktopAppInfoNewFromFilename filename :: String
filename = IO (Maybe DesktopAppInfo) -> m (Maybe DesktopAppInfo)
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
    CString
filename' <- String -> IO CString
stringToCString String
filename
    Ptr DesktopAppInfo
result <- CString -> IO (Ptr DesktopAppInfo)
g_desktop_app_info_new_from_filename CString
filename'
    Maybe DesktopAppInfo
maybeResult <- Ptr DesktopAppInfo
-> (Ptr DesktopAppInfo -> IO DesktopAppInfo)
-> IO (Maybe DesktopAppInfo)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr DesktopAppInfo
result ((Ptr DesktopAppInfo -> IO DesktopAppInfo)
 -> IO (Maybe DesktopAppInfo))
-> (Ptr DesktopAppInfo -> IO DesktopAppInfo)
-> IO (Maybe DesktopAppInfo)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr DesktopAppInfo
result' -> do
        DesktopAppInfo
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'
        DesktopAppInfo -> IO DesktopAppInfo
forall (m :: * -> *) a. Monad m => a -> m a
return DesktopAppInfo
result''
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
    Maybe DesktopAppInfo -> IO (Maybe DesktopAppInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DesktopAppInfo
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
--           , 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 :: KeyFile -> m (Maybe DesktopAppInfo)
desktopAppInfoNewFromKeyfile keyFile :: KeyFile
keyFile = IO (Maybe DesktopAppInfo) -> m (Maybe DesktopAppInfo)
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
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    Ptr DesktopAppInfo
result <- Ptr KeyFile -> IO (Ptr DesktopAppInfo)
g_desktop_app_info_new_from_keyfile Ptr KeyFile
keyFile'
    Maybe DesktopAppInfo
maybeResult <- Ptr DesktopAppInfo
-> (Ptr DesktopAppInfo -> IO DesktopAppInfo)
-> IO (Maybe DesktopAppInfo)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr DesktopAppInfo
result ((Ptr DesktopAppInfo -> IO DesktopAppInfo)
 -> IO (Maybe DesktopAppInfo))
-> (Ptr DesktopAppInfo -> IO DesktopAppInfo)
-> IO (Maybe DesktopAppInfo)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr DesktopAppInfo
result' -> do
        DesktopAppInfo
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'
        DesktopAppInfo -> IO DesktopAppInfo
forall (m :: * -> *) a. Monad m => a -> m a
return DesktopAppInfo
result''
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    Maybe DesktopAppInfo -> IO (Maybe DesktopAppInfo)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DesktopAppInfo
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
--           , 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
--           , 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 :: a -> Text -> m Text
desktopAppInfoGetActionName info :: a
info actionName :: Text
actionName = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DesktopAppInfo
info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    CString
result <- Ptr DesktopAppInfo -> CString -> IO CString
g_desktop_app_info_get_action_name Ptr DesktopAppInfo
info' CString
actionName'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "desktopAppInfoGetActionName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
actionName'
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetActionNameMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m, IsDesktopAppInfo a) => O.MethodInfo DesktopAppInfoGetActionNameMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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 :: a -> Text -> m Bool
desktopAppInfoGetBoolean info :: a
info key :: Text
key = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr DesktopAppInfo
info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
key' <- Text -> IO CString
textToCString Text
key
    CInt
result <- Ptr DesktopAppInfo -> CString -> IO CInt
g_desktop_app_info_get_boolean Ptr DesktopAppInfo
info' CString
key'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetBooleanMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsDesktopAppInfo a) => O.MethodInfo DesktopAppInfoGetBooleanMethodInfo a signature where
    overloadedMethod = 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
--           , 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 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 :: a -> m Text
desktopAppInfoGetCategories info :: a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DesktopAppInfo
info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr DesktopAppInfo -> IO CString
g_desktop_app_info_get_categories Ptr DesktopAppInfo
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "desktopAppInfoGetCategories" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetCategoriesMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDesktopAppInfo a) => O.MethodInfo DesktopAppInfoGetCategoriesMethodInfo a signature where
    overloadedMethod = 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
--           , 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 [Char]
    -- ^ __Returns:__ The full path to the file for /@info@/,
    --     or 'P.Nothing' if not known.
desktopAppInfoGetFilename :: a -> m String
desktopAppInfoGetFilename info :: a
info = IO String -> m String
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO String -> m String) -> IO String -> m String
forall a b. (a -> b) -> a -> b
$ do
    Ptr DesktopAppInfo
info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr DesktopAppInfo -> IO CString
g_desktop_app_info_get_filename Ptr DesktopAppInfo
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "desktopAppInfoGetFilename" CString
result
    String
result' <- HasCallStack => CString -> IO String
CString -> IO String
cstringToString CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetFilenameMethodInfo
instance (signature ~ (m [Char]), MonadIO m, IsDesktopAppInfo a) => O.MethodInfo DesktopAppInfoGetFilenameMethodInfo a signature where
    overloadedMethod = 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
--           , 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 destkop file.
desktopAppInfoGetGenericName ::
    (B.CallStack.HasCallStack, MonadIO m, IsDesktopAppInfo a) =>
    a
    -- ^ /@info@/: a t'GI.Gio.Objects.DesktopAppInfo.DesktopAppInfo'
    -> m T.Text
    -- ^ __Returns:__ The value of the GenericName key
desktopAppInfoGetGenericName :: a -> m Text
desktopAppInfoGetGenericName info :: a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DesktopAppInfo
info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr DesktopAppInfo -> IO CString
g_desktop_app_info_get_generic_name Ptr DesktopAppInfo
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "desktopAppInfoGetGenericName" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetGenericNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDesktopAppInfo a) => O.MethodInfo DesktopAppInfoGetGenericNameMethodInfo a signature where
    overloadedMethod = 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
--           , 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 :: a -> m Bool
desktopAppInfoGetIsHidden info :: a
info = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr DesktopAppInfo
info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CInt
result <- Ptr DesktopAppInfo -> IO CInt
g_desktop_app_info_get_is_hidden Ptr DesktopAppInfo
info'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetIsHiddenMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDesktopAppInfo a) => O.MethodInfo DesktopAppInfoGetIsHiddenMethodInfo a signature where
    overloadedMethod = 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
--           , 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 :: a -> m [Text]
desktopAppInfoGetKeywords info :: a
info = IO [Text] -> m [Text]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
    Ptr DesktopAppInfo
info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Ptr CString
result <- Ptr DesktopAppInfo -> IO (Ptr CString)
g_desktop_app_info_get_keywords Ptr DesktopAppInfo
info'
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "desktopAppInfoGetKeywords" Ptr CString
result
    [Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetKeywordsMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsDesktopAppInfo a) => O.MethodInfo DesktopAppInfoGetKeywordsMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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 :: a -> Text -> m (Maybe Text)
desktopAppInfoGetLocaleString info :: a
info key :: Text
key = IO (Maybe Text) -> m (Maybe Text)
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
    Ptr DesktopAppInfo
info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
key' <- Text -> IO CString
textToCString Text
key
    CString
result <- Ptr DesktopAppInfo -> CString -> IO CString
g_desktop_app_info_get_locale_string Ptr DesktopAppInfo
info' CString
key'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \result' :: CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetLocaleStringMethodInfo
instance (signature ~ (T.Text -> m (Maybe T.Text)), MonadIO m, IsDesktopAppInfo a) => O.MethodInfo DesktopAppInfoGetLocaleStringMethodInfo a signature where
    overloadedMethod = 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
--           , 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 :: a -> m Bool
desktopAppInfoGetNodisplay info :: a
info = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr DesktopAppInfo
info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CInt
result <- Ptr DesktopAppInfo -> IO CInt
g_desktop_app_info_get_nodisplay Ptr DesktopAppInfo
info'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetNodisplayMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDesktopAppInfo a) => O.MethodInfo DesktopAppInfoGetNodisplayMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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 :: a -> Maybe Text -> m Bool
desktopAppInfoGetShowIn info :: a
info desktopEnv :: Maybe Text
desktopEnv = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr DesktopAppInfo
info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
maybeDesktopEnv <- case Maybe Text
desktopEnv of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jDesktopEnv :: Text
jDesktopEnv -> do
            CString
jDesktopEnv' <- Text -> IO CString
textToCString Text
jDesktopEnv
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jDesktopEnv'
    CInt
result <- Ptr DesktopAppInfo -> CString -> IO CInt
g_desktop_app_info_get_show_in Ptr DesktopAppInfo
info' CString
maybeDesktopEnv
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeDesktopEnv
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetShowInMethodInfo
instance (signature ~ (Maybe (T.Text) -> m Bool), MonadIO m, IsDesktopAppInfo a) => O.MethodInfo DesktopAppInfoGetShowInMethodInfo a signature where
    overloadedMethod = 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
--           , 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 T.Text
    -- ^ __Returns:__ the startup WM class, or 'P.Nothing' if none is set
    -- in the desktop file.
desktopAppInfoGetStartupWmClass :: a -> m Text
desktopAppInfoGetStartupWmClass info :: a
info = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DesktopAppInfo
info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
result <- Ptr DesktopAppInfo -> IO CString
g_desktop_app_info_get_startup_wm_class Ptr DesktopAppInfo
info'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "desktopAppInfoGetStartupWmClass" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetStartupWmClassMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsDesktopAppInfo a) => O.MethodInfo DesktopAppInfoGetStartupWmClassMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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 T.Text
    -- ^ __Returns:__ a newly allocated string, or 'P.Nothing' if the key
    --     is not found
desktopAppInfoGetString :: a -> Text -> m Text
desktopAppInfoGetString info :: a
info key :: Text
key = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr DesktopAppInfo
info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
key' <- Text -> IO CString
textToCString Text
key
    CString
result <- Ptr DesktopAppInfo -> CString -> IO CString
g_desktop_app_info_get_string Ptr DesktopAppInfo
info' CString
key'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "desktopAppInfoGetString" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetStringMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m, IsDesktopAppInfo a) => O.MethodInfo DesktopAppInfoGetStringMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , 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
--           , 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 Word64 ->                           -- length : TBasicType TUInt64
    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.0/
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], Word64))
    -- ^ __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 :: a -> Text -> m ([Text], Word64)
desktopAppInfoGetStringList info :: a
info key :: Text
key = IO ([Text], Word64) -> m ([Text], Word64)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ([Text], Word64) -> m ([Text], Word64))
-> IO ([Text], Word64) -> m ([Text], Word64)
forall a b. (a -> b) -> a -> b
$ do
    Ptr DesktopAppInfo
info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
key' <- Text -> IO CString
textToCString Text
key
    Ptr Word64
length_ <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    Ptr CString
result <- Ptr DesktopAppInfo -> CString -> Ptr Word64 -> IO (Ptr CString)
g_desktop_app_info_get_string_list Ptr DesktopAppInfo
info' CString
key' Ptr Word64
length_
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "desktopAppInfoGetStringList" Ptr CString
result
    [Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
    (CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
    Word64
length_' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
length_
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
    ([Text], Word64) -> IO ([Text], Word64)
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text]
result', Word64
length_')

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoGetStringListMethodInfo
instance (signature ~ (T.Text -> m (([T.Text], Word64))), MonadIO m, IsDesktopAppInfo a) => O.MethodInfo DesktopAppInfoGetStringListMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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 :: a -> Text -> m Bool
desktopAppInfoHasKey info :: a
info key :: Text
key = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr DesktopAppInfo
info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
key' <- Text -> IO CString
textToCString Text
key
    CInt
result <- Ptr DesktopAppInfo -> CString -> IO CInt
g_desktop_app_info_has_key Ptr DesktopAppInfo
info' CString
key'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoHasKeyMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsDesktopAppInfo a) => O.MethodInfo DesktopAppInfoHasKeyMethodInfo a signature where
    overloadedMethod = 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
--           , 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
--           , 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
--           , 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 :: a -> Text -> Maybe b -> m ()
desktopAppInfoLaunchAction info :: a
info actionName :: Text
actionName launchContext :: Maybe b
launchContext = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr DesktopAppInfo
info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    CString
actionName' <- Text -> IO CString
textToCString Text
actionName
    Ptr AppLaunchContext
maybeLaunchContext <- case Maybe b
launchContext of
        Nothing -> Ptr AppLaunchContext -> IO (Ptr AppLaunchContext)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr AppLaunchContext
forall a. Ptr a
nullPtr
        Just jLaunchContext :: b
jLaunchContext -> do
            Ptr AppLaunchContext
jLaunchContext' <- b -> IO (Ptr AppLaunchContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jLaunchContext
            Ptr AppLaunchContext -> IO (Ptr AppLaunchContext)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr AppLaunchContext
jLaunchContext'
    Ptr DesktopAppInfo -> CString -> Ptr AppLaunchContext -> IO ()
g_desktop_app_info_launch_action Ptr DesktopAppInfo
info' CString
actionName' Ptr AppLaunchContext
maybeLaunchContext
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
launchContext b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
actionName'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

#endif

-- XXX Could not generate method DesktopAppInfo::launch_uris_as_manager
-- Error was : Bad introspection data: "Closure not found! Callable\n  { returnType = Just (TBasicType TBoolean)\n  , returnMayBeNull = False\n  , returnTransfer = TransferNothing\n  , returnDocumentation =\n      Documentation\n        { rawDocText = Just \"%TRUE on successful launch, %FALSE otherwise.\"\n        , sinceVersion = Nothing\n        }\n  , args =\n      [ Arg\n          { argCName = \"appinfo\"\n          , argType =\n              TInterface Name { namespace = \"Gio\" , name = \"DesktopAppInfo\" }\n          , direction = DirectionIn\n          , mayBeNull = False\n          , argDoc =\n              Documentation\n                { rawDocText = Just \"a #GDesktopAppInfo\" , sinceVersion = Nothing }\n          , argScope = ScopeTypeInvalid\n          , argClosure = -1\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      , Arg\n          { argCName = \"uris\"\n          , argType = TGList (TBasicType TUTF8)\n          , direction = DirectionIn\n          , mayBeNull = False\n          , argDoc =\n              Documentation\n                { rawDocText = Just \"List of URIs\" , sinceVersion = Nothing }\n          , argScope = ScopeTypeInvalid\n          , argClosure = -1\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      , Arg\n          { argCName = \"launch_context\"\n          , argType =\n              TInterface Name { namespace = \"Gio\" , name = \"AppLaunchContext\" }\n          , direction = DirectionIn\n          , mayBeNull = True\n          , argDoc =\n              Documentation\n                { rawDocText = Just \"a #GAppLaunchContext\"\n                , sinceVersion = Nothing\n                }\n          , argScope = ScopeTypeInvalid\n          , argClosure = -1\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      , Arg\n          { argCName = \"spawn_flags\"\n          , argType =\n              TInterface Name { namespace = \"GLib\" , name = \"SpawnFlags\" }\n          , direction = DirectionIn\n          , mayBeNull = False\n          , argDoc =\n              Documentation\n                { rawDocText = Just \"#GSpawnFlags, used for each process\"\n                , sinceVersion = Nothing\n                }\n          , argScope = ScopeTypeInvalid\n          , argClosure = -1\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      , Arg\n          { argCName = \"user_setup\"\n          , argType =\n              TInterface\n                Name { namespace = \"GLib\" , name = \"SpawnChildSetupFunc\" }\n          , direction = DirectionIn\n          , mayBeNull = True\n          , argDoc =\n              Documentation\n                { rawDocText =\n                    Just \"a #GSpawnChildSetupFunc, used once\\n    for each process.\"\n                , sinceVersion = Nothing\n                }\n          , argScope = ScopeTypeAsync\n          , argClosure = 5\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      , Arg\n          { argCName = \"user_setup_data\"\n          , argType = TBasicType TPtr\n          , direction = DirectionIn\n          , mayBeNull = True\n          , argDoc =\n              Documentation\n                { rawDocText = Just \"User data for @user_setup\"\n                , sinceVersion = Nothing\n                }\n          , argScope = ScopeTypeInvalid\n          , argClosure = 4\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      , Arg\n          { argCName = \"pid_callback\"\n          , argType =\n              TInterface\n                Name { namespace = \"Gio\" , name = \"DesktopAppLaunchCallback\" }\n          , direction = DirectionIn\n          , mayBeNull = True\n          , argDoc =\n              Documentation\n                { rawDocText = Just \"Callback for child processes\"\n                , sinceVersion = Nothing\n                }\n          , argScope = ScopeTypeCall\n          , argClosure = 7\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      , Arg\n          { argCName = \"pid_callback_data\"\n          , argType = TBasicType TPtr\n          , direction = DirectionIn\n          , mayBeNull = True\n          , argDoc =\n              Documentation\n                { rawDocText = Just \"User data for @callback\"\n                , sinceVersion = Nothing\n                }\n          , argScope = ScopeTypeInvalid\n          , argClosure = 6\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      ]\n  , skipReturn = False\n  , callableThrows = True\n  , callableDeprecated = Nothing\n  , callableDocumentation =\n      Documentation\n        { rawDocText =\n            Just\n              \"This function performs the equivalent of g_app_info_launch_uris(),\\nbut is intended primarily for operating system components that\\nlaunch applications.  Ordinary applications should use\\ng_app_info_launch_uris().\\n\\nIf the application is launched via GSpawn, then @spawn_flags, @user_setup\\nand @user_setup_data are used for the call to g_spawn_async().\\nAdditionally, @pid_callback (with @pid_callback_data) will be called to\\ninform about the PID of the created process. See g_spawn_async_with_pipes()\\nfor information on certain parameter conditions that can enable an\\noptimized posix_spawn() codepath to be used.\\n\\nIf application launching occurs via some other mechanism (eg: D-Bus\\nactivation) then @spawn_flags, @user_setup, @user_setup_data,\\n@pid_callback and @pid_callback_data are ignored.\"\n        , sinceVersion = Nothing\n        }\n  }\nfromList\n  [ ( 5\n    , Arg\n        { argCName = \"user_setup\"\n        , argType =\n            TInterface\n              Name { namespace = \"GLib\" , name = \"SpawnChildSetupFunc\" }\n        , direction = DirectionIn\n        , mayBeNull = True\n        , argDoc =\n            Documentation\n              { rawDocText =\n                  Just \"a #GSpawnChildSetupFunc, used once\\n    for each process.\"\n              , sinceVersion = Nothing\n              }\n        , argScope = ScopeTypeAsync\n        , argClosure = 5\n        , argDestroy = -1\n        , argCallerAllocates = False\n        , transfer = TransferNothing\n        }\n    )\n  , ( 7\n    , Arg\n        { argCName = \"pid_callback\"\n        , argType =\n            TInterface\n              Name { namespace = \"Gio\" , name = \"DesktopAppLaunchCallback\" }\n        , direction = DirectionIn\n        , mayBeNull = True\n        , argDoc =\n            Documentation\n              { rawDocText = Just \"Callback for child processes\"\n              , sinceVersion = Nothing\n              }\n        , argScope = ScopeTypeCall\n        , argClosure = 7\n        , argDestroy = -1\n        , argCallerAllocates = False\n        , transfer = TransferNothing\n        }\n    )\n  ]\n4"
#if defined(ENABLE_OVERLOADING)
-- XXX: Dummy instance, since code generation failed.
-- Please file a bug at http://github.com/haskell-gi/haskell-gi.
data DesktopAppInfoLaunchUrisAsManagerMethodInfo
instance (p ~ (), o ~ O.UnsupportedMethodError "launchUrisAsManager" DesktopAppInfo) => O.MethodInfo DesktopAppInfoLaunchUrisAsManagerMethodInfo o p where
    overloadedMethod = undefined
#endif

-- XXX Could not generate method DesktopAppInfo::launch_uris_as_manager_with_fds
-- Error was : Bad introspection data: "Closure not found! Callable\n  { returnType = Just (TBasicType TBoolean)\n  , returnMayBeNull = False\n  , returnTransfer = TransferNothing\n  , returnDocumentation =\n      Documentation\n        { rawDocText = Just \"%TRUE on successful launch, %FALSE otherwise.\"\n        , sinceVersion = Nothing\n        }\n  , args =\n      [ Arg\n          { argCName = \"appinfo\"\n          , argType =\n              TInterface Name { namespace = \"Gio\" , name = \"DesktopAppInfo\" }\n          , direction = DirectionIn\n          , mayBeNull = False\n          , argDoc =\n              Documentation\n                { rawDocText = Just \"a #GDesktopAppInfo\" , sinceVersion = Nothing }\n          , argScope = ScopeTypeInvalid\n          , argClosure = -1\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      , Arg\n          { argCName = \"uris\"\n          , argType = TGList (TBasicType TUTF8)\n          , direction = DirectionIn\n          , mayBeNull = False\n          , argDoc =\n              Documentation\n                { rawDocText = Just \"List of URIs\" , sinceVersion = Nothing }\n          , argScope = ScopeTypeInvalid\n          , argClosure = -1\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      , Arg\n          { argCName = \"launch_context\"\n          , argType =\n              TInterface Name { namespace = \"Gio\" , name = \"AppLaunchContext\" }\n          , direction = DirectionIn\n          , mayBeNull = True\n          , argDoc =\n              Documentation\n                { rawDocText = Just \"a #GAppLaunchContext\"\n                , sinceVersion = Nothing\n                }\n          , argScope = ScopeTypeInvalid\n          , argClosure = -1\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      , Arg\n          { argCName = \"spawn_flags\"\n          , argType =\n              TInterface Name { namespace = \"GLib\" , name = \"SpawnFlags\" }\n          , direction = DirectionIn\n          , mayBeNull = False\n          , argDoc =\n              Documentation\n                { rawDocText = Just \"#GSpawnFlags, used for each process\"\n                , sinceVersion = Nothing\n                }\n          , argScope = ScopeTypeInvalid\n          , argClosure = -1\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      , Arg\n          { argCName = \"user_setup\"\n          , argType =\n              TInterface\n                Name { namespace = \"GLib\" , name = \"SpawnChildSetupFunc\" }\n          , direction = DirectionIn\n          , mayBeNull = True\n          , argDoc =\n              Documentation\n                { rawDocText =\n                    Just \"a #GSpawnChildSetupFunc, used once\\n    for each process.\"\n                , sinceVersion = Nothing\n                }\n          , argScope = ScopeTypeAsync\n          , argClosure = 5\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      , Arg\n          { argCName = \"user_setup_data\"\n          , argType = TBasicType TPtr\n          , direction = DirectionIn\n          , mayBeNull = True\n          , argDoc =\n              Documentation\n                { rawDocText = Just \"User data for @user_setup\"\n                , sinceVersion = Nothing\n                }\n          , argScope = ScopeTypeInvalid\n          , argClosure = 4\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      , Arg\n          { argCName = \"pid_callback\"\n          , argType =\n              TInterface\n                Name { namespace = \"Gio\" , name = \"DesktopAppLaunchCallback\" }\n          , direction = DirectionIn\n          , mayBeNull = True\n          , argDoc =\n              Documentation\n                { rawDocText = Just \"Callback for child processes\"\n                , sinceVersion = Nothing\n                }\n          , argScope = ScopeTypeCall\n          , argClosure = 7\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      , Arg\n          { argCName = \"pid_callback_data\"\n          , argType = TBasicType TPtr\n          , direction = DirectionIn\n          , mayBeNull = True\n          , argDoc =\n              Documentation\n                { rawDocText = Just \"User data for @callback\"\n                , sinceVersion = Nothing\n                }\n          , argScope = ScopeTypeInvalid\n          , argClosure = 6\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      , Arg\n          { argCName = \"stdin_fd\"\n          , argType = TBasicType TInt\n          , direction = DirectionIn\n          , mayBeNull = False\n          , argDoc =\n              Documentation\n                { rawDocText =\n                    Just \"file descriptor to use for child's stdin, or -1\"\n                , sinceVersion = Nothing\n                }\n          , argScope = ScopeTypeInvalid\n          , argClosure = -1\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      , Arg\n          { argCName = \"stdout_fd\"\n          , argType = TBasicType TInt\n          , direction = DirectionIn\n          , mayBeNull = False\n          , argDoc =\n              Documentation\n                { rawDocText =\n                    Just \"file descriptor to use for child's stdout, or -1\"\n                , sinceVersion = Nothing\n                }\n          , argScope = ScopeTypeInvalid\n          , argClosure = -1\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      , Arg\n          { argCName = \"stderr_fd\"\n          , argType = TBasicType TInt\n          , direction = DirectionIn\n          , mayBeNull = False\n          , argDoc =\n              Documentation\n                { rawDocText =\n                    Just \"file descriptor to use for child's stderr, or -1\"\n                , sinceVersion = Nothing\n                }\n          , argScope = ScopeTypeInvalid\n          , argClosure = -1\n          , argDestroy = -1\n          , argCallerAllocates = False\n          , transfer = TransferNothing\n          }\n      ]\n  , skipReturn = False\n  , callableThrows = True\n  , callableDeprecated = Nothing\n  , callableDocumentation =\n      Documentation\n        { rawDocText =\n            Just\n              \"Equivalent to g_desktop_app_info_launch_uris_as_manager() but allows\\nyou to pass in file descriptors for the stdin, stdout and stderr streams\\nof the launched process.\\n\\nIf application launching occurs via some non-spawn mechanism (e.g. D-Bus\\nactivation) then @stdin_fd, @stdout_fd and @stderr_fd are ignored.\"\n        , sinceVersion = Just \"2.58\"\n        }\n  }\nfromList\n  [ ( 5\n    , Arg\n        { argCName = \"user_setup\"\n        , argType =\n            TInterface\n              Name { namespace = \"GLib\" , name = \"SpawnChildSetupFunc\" }\n        , direction = DirectionIn\n        , mayBeNull = True\n        , argDoc =\n            Documentation\n              { rawDocText =\n                  Just \"a #GSpawnChildSetupFunc, used once\\n    for each process.\"\n              , sinceVersion = Nothing\n              }\n        , argScope = ScopeTypeAsync\n        , argClosure = 5\n        , argDestroy = -1\n        , argCallerAllocates = False\n        , transfer = TransferNothing\n        }\n    )\n  , ( 7\n    , Arg\n        { argCName = \"pid_callback\"\n        , argType =\n            TInterface\n              Name { namespace = \"Gio\" , name = \"DesktopAppLaunchCallback\" }\n        , direction = DirectionIn\n        , mayBeNull = True\n        , argDoc =\n            Documentation\n              { rawDocText = Just \"Callback for child processes\"\n              , sinceVersion = Nothing\n              }\n        , argScope = ScopeTypeCall\n        , argClosure = 7\n        , argDestroy = -1\n        , argCallerAllocates = False\n        , transfer = TransferNothing\n        }\n    )\n  ]\n4"
#if defined(ENABLE_OVERLOADING)
-- XXX: Dummy instance, since code generation failed.
-- Please file a bug at http://github.com/haskell-gi/haskell-gi.
data DesktopAppInfoLaunchUrisAsManagerWithFdsMethodInfo
instance (p ~ (), o ~ O.UnsupportedMethodError "launchUrisAsManagerWithFds" DesktopAppInfo) => O.MethodInfo DesktopAppInfoLaunchUrisAsManagerWithFdsMethodInfo o p where
    overloadedMethod = undefined
#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
--           , 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 :: a -> m [Text]
desktopAppInfoListActions info :: a
info = IO [Text] -> m [Text]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Text] -> m [Text]) -> IO [Text] -> m [Text]
forall a b. (a -> b) -> a -> b
$ do
    Ptr DesktopAppInfo
info' <- a -> IO (Ptr DesktopAppInfo)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
info
    Ptr CString
result <- Ptr DesktopAppInfo -> IO (Ptr CString)
g_desktop_app_info_list_actions Ptr DesktopAppInfo
info'
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "desktopAppInfoListActions" Ptr CString
result
    [Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
info
    [Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'

#if defined(ENABLE_OVERLOADING)
data DesktopAppInfoListActionsMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m, IsDesktopAppInfo a) => O.MethodInfo DesktopAppInfoListActionsMethodInfo a signature where
    overloadedMethod = 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
--           , 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 :: Text -> m [DesktopAppInfo]
desktopAppInfoGetImplementations interface :: Text
interface = IO [DesktopAppInfo] -> m [DesktopAppInfo]
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
    CString
interface' <- Text -> IO CString
textToCString Text
interface
    Ptr (GList (Ptr DesktopAppInfo))
result <- CString -> IO (Ptr (GList (Ptr DesktopAppInfo)))
g_desktop_app_info_get_implementations CString
interface'
    [Ptr DesktopAppInfo]
result' <- Ptr (GList (Ptr DesktopAppInfo)) -> IO [Ptr DesktopAppInfo]
forall a. Ptr (GList (Ptr a)) -> IO [Ptr a]
unpackGList Ptr (GList (Ptr DesktopAppInfo))
result
    [DesktopAppInfo]
result'' <- (Ptr DesktopAppInfo -> IO DesktopAppInfo)
-> [Ptr DesktopAppInfo] -> IO [DesktopAppInfo]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((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'
    Ptr (GList (Ptr DesktopAppInfo)) -> IO ()
forall a. Ptr (GList a) -> IO ()
g_list_free Ptr (GList (Ptr DesktopAppInfo))
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
interface'
    [DesktopAppInfo] -> IO [DesktopAppInfo]
forall (m :: * -> *) a. Monad m => a -> m a
return [DesktopAppInfo]
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
--           , 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.
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 :: Text -> m [[Text]]
desktopAppInfoSearch searchString :: Text
searchString = IO [[Text]] -> m [[Text]]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [[Text]] -> m [[Text]]) -> IO [[Text]] -> m [[Text]]
forall a b. (a -> b) -> a -> b
$ do
    CString
searchString' <- Text -> IO CString
textToCString Text
searchString
    Ptr (Ptr CString)
result <- CString -> IO (Ptr (Ptr CString))
g_desktop_app_info_search CString
searchString'
    Text -> Ptr (Ptr CString) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "desktopAppInfoSearch" Ptr (Ptr CString)
result
    [Ptr CString]
result' <- Ptr (Ptr CString) -> IO [Ptr CString]
forall a. Ptr (Ptr a) -> IO [Ptr a]
unpackZeroTerminatedPtrArray Ptr (Ptr CString)
result
    [[Text]]
result'' <- (Ptr CString -> IO [Text]) -> [Ptr CString] -> IO [[Text]]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray [Ptr CString]
result'
    let freeElemOfResult :: Ptr (Ptr a) -> IO ()
freeElemOfResult e :: 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 (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
    (Ptr CString -> IO ()) -> Ptr (Ptr CString) -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray Ptr CString -> IO ()
forall a. Ptr (Ptr a) -> IO ()
freeElemOfResult Ptr (Ptr CString)
result
    Ptr (Ptr CString) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CString)
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
searchString'
    [[Text]] -> IO [[Text]]
forall (m :: * -> *) a. Monad m => a -> m a
return [[Text]]
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
--           , 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 :: Text -> m ()
desktopAppInfoSetDesktopEnv desktopEnv :: Text
desktopEnv = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    CString
desktopEnv' <- Text -> IO CString
textToCString Text
desktopEnv
    CString -> IO ()
g_desktop_app_info_set_desktop_env CString
desktopEnv'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
desktopEnv'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif