{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- This class contains a set of options for launching child processes,
-- such as where its standard input and output will be directed, the
-- argument list, the environment, and more.
-- 
-- While the t'GI.Gio.Objects.Subprocess.Subprocess' class has high level functions covering
-- popular cases, use of this class allows access to more advanced
-- options.  It can also be used to launch multiple subprocesses with
-- a similar configuration.
-- 
-- /Since: 2.40/

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

module GI.Gio.Objects.SubprocessLauncher
    ( 

-- * Exported types
    SubprocessLauncher(..)                  ,
    IsSubprocessLauncher                    ,
    toSubprocessLauncher                    ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [close]("GI.Gio.Objects.SubprocessLauncher#g:method:close"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getenv]("GI.Gio.Objects.SubprocessLauncher#g:method:getenv"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [setenv]("GI.Gio.Objects.SubprocessLauncher#g:method:setenv"), [spawnv]("GI.Gio.Objects.SubprocessLauncher#g:method:spawnv"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [takeFd]("GI.Gio.Objects.SubprocessLauncher#g:method:takeFd"), [takeStderrFd]("GI.Gio.Objects.SubprocessLauncher#g:method:takeStderrFd"), [takeStdinFd]("GI.Gio.Objects.SubprocessLauncher#g:method:takeStdinFd"), [takeStdoutFd]("GI.Gio.Objects.SubprocessLauncher#g:method:takeStdoutFd"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [unsetenv]("GI.Gio.Objects.SubprocessLauncher#g:method:unsetenv"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setCwd]("GI.Gio.Objects.SubprocessLauncher#g:method:setCwd"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setEnviron]("GI.Gio.Objects.SubprocessLauncher#g:method:setEnviron"), [setFlags]("GI.Gio.Objects.SubprocessLauncher#g:method:setFlags"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setStderrFilePath]("GI.Gio.Objects.SubprocessLauncher#g:method:setStderrFilePath"), [setStdinFilePath]("GI.Gio.Objects.SubprocessLauncher#g:method:setStdinFilePath"), [setStdoutFilePath]("GI.Gio.Objects.SubprocessLauncher#g:method:setStdoutFilePath").

#if defined(ENABLE_OVERLOADING)
    ResolveSubprocessLauncherMethod         ,
#endif

-- ** close #method:close#

#if defined(ENABLE_OVERLOADING)
    SubprocessLauncherCloseMethodInfo       ,
#endif
    subprocessLauncherClose                 ,


-- ** getenv #method:getenv#

#if defined(ENABLE_OVERLOADING)
    SubprocessLauncherGetenvMethodInfo      ,
#endif
    subprocessLauncherGetenv                ,


-- ** new #method:new#

    subprocessLauncherNew                   ,


-- ** setCwd #method:setCwd#

#if defined(ENABLE_OVERLOADING)
    SubprocessLauncherSetCwdMethodInfo      ,
#endif
    subprocessLauncherSetCwd                ,


-- ** setEnviron #method:setEnviron#

#if defined(ENABLE_OVERLOADING)
    SubprocessLauncherSetEnvironMethodInfo  ,
#endif
    subprocessLauncherSetEnviron            ,


-- ** setFlags #method:setFlags#

#if defined(ENABLE_OVERLOADING)
    SubprocessLauncherSetFlagsMethodInfo    ,
#endif
    subprocessLauncherSetFlags              ,


-- ** setStderrFilePath #method:setStderrFilePath#

#if defined(ENABLE_OVERLOADING)
    SubprocessLauncherSetStderrFilePathMethodInfo,
#endif
    subprocessLauncherSetStderrFilePath     ,


-- ** setStdinFilePath #method:setStdinFilePath#

#if defined(ENABLE_OVERLOADING)
    SubprocessLauncherSetStdinFilePathMethodInfo,
#endif
    subprocessLauncherSetStdinFilePath      ,


-- ** setStdoutFilePath #method:setStdoutFilePath#

#if defined(ENABLE_OVERLOADING)
    SubprocessLauncherSetStdoutFilePathMethodInfo,
#endif
    subprocessLauncherSetStdoutFilePath     ,


-- ** setenv #method:setenv#

#if defined(ENABLE_OVERLOADING)
    SubprocessLauncherSetenvMethodInfo      ,
#endif
    subprocessLauncherSetenv                ,


-- ** spawnv #method:spawnv#

#if defined(ENABLE_OVERLOADING)
    SubprocessLauncherSpawnvMethodInfo      ,
#endif
    subprocessLauncherSpawnv                ,


-- ** takeFd #method:takeFd#

#if defined(ENABLE_OVERLOADING)
    SubprocessLauncherTakeFdMethodInfo      ,
#endif
    subprocessLauncherTakeFd                ,


-- ** takeStderrFd #method:takeStderrFd#

#if defined(ENABLE_OVERLOADING)
    SubprocessLauncherTakeStderrFdMethodInfo,
#endif
    subprocessLauncherTakeStderrFd          ,


-- ** takeStdinFd #method:takeStdinFd#

#if defined(ENABLE_OVERLOADING)
    SubprocessLauncherTakeStdinFdMethodInfo ,
#endif
    subprocessLauncherTakeStdinFd           ,


-- ** takeStdoutFd #method:takeStdoutFd#

#if defined(ENABLE_OVERLOADING)
    SubprocessLauncherTakeStdoutFdMethodInfo,
#endif
    subprocessLauncherTakeStdoutFd          ,


-- ** unsetenv #method:unsetenv#

#if defined(ENABLE_OVERLOADING)
    SubprocessLauncherUnsetenvMethodInfo    ,
#endif
    subprocessLauncherUnsetenv              ,




 -- * Properties


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

#if defined(ENABLE_OVERLOADING)
    SubprocessLauncherFlagsPropertyInfo     ,
#endif
    constructSubprocessLauncherFlags        ,
#if defined(ENABLE_OVERLOADING)
    subprocessLauncherFlags                 ,
#endif




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gio.Flags as Gio.Flags
import {-# SOURCE #-} qualified GI.Gio.Objects.Subprocess as Gio.Subprocess

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

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

foreign import ccall "g_subprocess_launcher_get_type"
    c_g_subprocess_launcher_get_type :: IO B.Types.GType

instance B.Types.TypedObject SubprocessLauncher where
    glibType :: IO GType
glibType = IO GType
c_g_subprocess_launcher_get_type

instance B.Types.GObject SubprocessLauncher

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveSubprocessLauncherMethod (t :: Symbol) (o :: *) :: * where
    ResolveSubprocessLauncherMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveSubprocessLauncherMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveSubprocessLauncherMethod "close" o = SubprocessLauncherCloseMethodInfo
    ResolveSubprocessLauncherMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveSubprocessLauncherMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveSubprocessLauncherMethod "getenv" o = SubprocessLauncherGetenvMethodInfo
    ResolveSubprocessLauncherMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveSubprocessLauncherMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveSubprocessLauncherMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveSubprocessLauncherMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveSubprocessLauncherMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveSubprocessLauncherMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveSubprocessLauncherMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveSubprocessLauncherMethod "setenv" o = SubprocessLauncherSetenvMethodInfo
    ResolveSubprocessLauncherMethod "spawnv" o = SubprocessLauncherSpawnvMethodInfo
    ResolveSubprocessLauncherMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveSubprocessLauncherMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveSubprocessLauncherMethod "takeFd" o = SubprocessLauncherTakeFdMethodInfo
    ResolveSubprocessLauncherMethod "takeStderrFd" o = SubprocessLauncherTakeStderrFdMethodInfo
    ResolveSubprocessLauncherMethod "takeStdinFd" o = SubprocessLauncherTakeStdinFdMethodInfo
    ResolveSubprocessLauncherMethod "takeStdoutFd" o = SubprocessLauncherTakeStdoutFdMethodInfo
    ResolveSubprocessLauncherMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveSubprocessLauncherMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveSubprocessLauncherMethod "unsetenv" o = SubprocessLauncherUnsetenvMethodInfo
    ResolveSubprocessLauncherMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveSubprocessLauncherMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveSubprocessLauncherMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveSubprocessLauncherMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveSubprocessLauncherMethod "setCwd" o = SubprocessLauncherSetCwdMethodInfo
    ResolveSubprocessLauncherMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveSubprocessLauncherMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveSubprocessLauncherMethod "setEnviron" o = SubprocessLauncherSetEnvironMethodInfo
    ResolveSubprocessLauncherMethod "setFlags" o = SubprocessLauncherSetFlagsMethodInfo
    ResolveSubprocessLauncherMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveSubprocessLauncherMethod "setStderrFilePath" o = SubprocessLauncherSetStderrFilePathMethodInfo
    ResolveSubprocessLauncherMethod "setStdinFilePath" o = SubprocessLauncherSetStdinFilePathMethodInfo
    ResolveSubprocessLauncherMethod "setStdoutFilePath" o = SubprocessLauncherSetStdoutFilePathMethodInfo
    ResolveSubprocessLauncherMethod l o = O.MethodResolutionFailed l o

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

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

#endif

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

#endif

-- VVV Prop "flags"
   -- Type: TInterface (Name {namespace = "Gio", name = "SubprocessFlags"})
   -- Flags: [PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Just False)

-- | Construct a `GValueConstruct` with valid value for the “@flags@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructSubprocessLauncherFlags :: (IsSubprocessLauncher o, MIO.MonadIO m) => [Gio.Flags.SubprocessFlags] -> m (GValueConstruct o)
constructSubprocessLauncherFlags :: forall o (m :: * -> *).
(IsSubprocessLauncher o, MonadIO m) =>
[SubprocessFlags] -> m (GValueConstruct o)
constructSubprocessLauncherFlags [SubprocessFlags]
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> [SubprocessFlags] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"flags" [SubprocessFlags]
val

#if defined(ENABLE_OVERLOADING)
data SubprocessLauncherFlagsPropertyInfo
instance AttrInfo SubprocessLauncherFlagsPropertyInfo where
    type AttrAllowedOps SubprocessLauncherFlagsPropertyInfo = '[ 'AttrConstruct]
    type AttrBaseTypeConstraint SubprocessLauncherFlagsPropertyInfo = IsSubprocessLauncher
    type AttrSetTypeConstraint SubprocessLauncherFlagsPropertyInfo = (~) [Gio.Flags.SubprocessFlags]
    type AttrTransferTypeConstraint SubprocessLauncherFlagsPropertyInfo = (~) [Gio.Flags.SubprocessFlags]
    type AttrTransferType SubprocessLauncherFlagsPropertyInfo = [Gio.Flags.SubprocessFlags]
    type AttrGetType SubprocessLauncherFlagsPropertyInfo = ()
    type AttrLabel SubprocessLauncherFlagsPropertyInfo = "flags"
    type AttrOrigin SubprocessLauncherFlagsPropertyInfo = SubprocessLauncher
    attrGet = undefined
    attrSet = undefined
    attrTransfer _ v = do
        return v
    attrConstruct = constructSubprocessLauncherFlags
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Objects.SubprocessLauncher.flags"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Objects-SubprocessLauncher.html#g:attr:flags"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SubprocessLauncher
type instance O.AttributeList SubprocessLauncher = SubprocessLauncherAttributeList
type SubprocessLauncherAttributeList = ('[ '("flags", SubprocessLauncherFlagsPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
subprocessLauncherFlags :: AttrLabelProxy "flags"
subprocessLauncherFlags = AttrLabelProxy

#endif

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

#endif

-- method SubprocessLauncher::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SubprocessFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GSubprocessFlags" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "SubprocessLauncher" })
-- throws : False
-- Skip return : False

foreign import ccall "g_subprocess_launcher_new" g_subprocess_launcher_new :: 
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "SubprocessFlags"})
    IO (Ptr SubprocessLauncher)

-- | Creates a new t'GI.Gio.Objects.SubprocessLauncher.SubprocessLauncher'.
-- 
-- The launcher is created with the default options.  A copy of the
-- environment of the calling process is made at the time of this call
-- and will be used as the environment that the process is launched in.
-- 
-- /Since: 2.40/
subprocessLauncherNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Gio.Flags.SubprocessFlags]
    -- ^ /@flags@/: t'GI.Gio.Flags.SubprocessFlags'
    -> m SubprocessLauncher
subprocessLauncherNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
[SubprocessFlags] -> m SubprocessLauncher
subprocessLauncherNew [SubprocessFlags]
flags = IO SubprocessLauncher -> m SubprocessLauncher
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SubprocessLauncher -> m SubprocessLauncher)
-> IO SubprocessLauncher -> m SubprocessLauncher
forall a b. (a -> b) -> a -> b
$ do
    let flags' :: CUInt
flags' = [SubprocessFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [SubprocessFlags]
flags
    Ptr SubprocessLauncher
result <- CUInt -> IO (Ptr SubprocessLauncher)
g_subprocess_launcher_new CUInt
flags'
    Text -> Ptr SubprocessLauncher -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"subprocessLauncherNew" Ptr SubprocessLauncher
result
    SubprocessLauncher
result' <- ((ManagedPtr SubprocessLauncher -> SubprocessLauncher)
-> Ptr SubprocessLauncher -> IO SubprocessLauncher
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SubprocessLauncher -> SubprocessLauncher
SubprocessLauncher) Ptr SubprocessLauncher
result
    SubprocessLauncher -> IO SubprocessLauncher
forall (m :: * -> *) a. Monad m => a -> m a
return SubprocessLauncher
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method SubprocessLauncher::close
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SubprocessLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSubprocessLauncher"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_subprocess_launcher_close" g_subprocess_launcher_close :: 
    Ptr SubprocessLauncher ->               -- self : TInterface (Name {namespace = "Gio", name = "SubprocessLauncher"})
    IO ()

-- | Closes all the file descriptors previously passed to the object with
-- 'GI.Gio.Objects.SubprocessLauncher.subprocessLauncherTakeFd', 'GI.Gio.Objects.SubprocessLauncher.subprocessLauncherTakeStderrFd', etc.
-- 
-- After calling this method, any subsequent calls to @/g_subprocess_launcher_spawn()/@ or 'GI.Gio.Objects.SubprocessLauncher.subprocessLauncherSpawnv' will
-- return 'GI.Gio.Enums.IOErrorEnumClosed'. This method is idempotent if
-- called more than once.
-- 
-- This function is called automatically when the t'GI.Gio.Objects.SubprocessLauncher.SubprocessLauncher'
-- is disposed, but is provided separately so that garbage collected
-- language bindings can call it earlier to guarantee when FDs are closed.
-- 
-- /Since: 2.68/
subprocessLauncherClose ::
    (B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.SubprocessLauncher.SubprocessLauncher'
    -> m ()
subprocessLauncherClose :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a -> m ()
subprocessLauncherClose a
self = 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 SubprocessLauncher
self' <- a -> IO (Ptr SubprocessLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr SubprocessLauncher -> IO ()
g_subprocess_launcher_close Ptr SubprocessLauncher
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SubprocessLauncherCloseMethodInfo
instance (signature ~ (m ()), MonadIO m, IsSubprocessLauncher a) => O.OverloadedMethod SubprocessLauncherCloseMethodInfo a signature where
    overloadedMethod = subprocessLauncherClose

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


#endif

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

-- | Returns the value of the environment variable /@variable@/ in the
-- environment of processes launched from this launcher.
-- 
-- On UNIX, the returned string can be an arbitrary byte string.
-- On Windows, it will be UTF-8.
-- 
-- /Since: 2.40/
subprocessLauncherGetenv ::
    (B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.SubprocessLauncher.SubprocessLauncher'
    -> [Char]
    -- ^ /@variable@/: the environment variable to get
    -> m (Maybe [Char])
    -- ^ __Returns:__ the value of the environment variable,
    --     'P.Nothing' if unset
subprocessLauncherGetenv :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a -> String -> m (Maybe String)
subprocessLauncherGetenv a
self String
variable = IO (Maybe String) -> m (Maybe String)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe String) -> m (Maybe String))
-> IO (Maybe String) -> m (Maybe String)
forall a b. (a -> b) -> a -> b
$ do
    Ptr SubprocessLauncher
self' <- a -> IO (Ptr SubprocessLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
variable' <- String -> IO CString
stringToCString String
variable
    CString
result <- Ptr SubprocessLauncher -> CString -> IO CString
g_subprocess_launcher_getenv Ptr SubprocessLauncher
self' CString
variable'
    Maybe String
maybeResult <- CString -> (CString -> IO String) -> IO (Maybe String)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO String) -> IO (Maybe String))
-> (CString -> IO String) -> IO (Maybe String)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        String
result'' <- HasCallStack => CString -> IO String
CString -> IO String
cstringToString CString
result'
        String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
variable'
    Maybe String -> IO (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe String
maybeResult

#if defined(ENABLE_OVERLOADING)
data SubprocessLauncherGetenvMethodInfo
instance (signature ~ ([Char] -> m (Maybe [Char])), MonadIO m, IsSubprocessLauncher a) => O.OverloadedMethod SubprocessLauncherGetenvMethodInfo a signature where
    overloadedMethod = subprocessLauncherGetenv

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


#endif

-- method SubprocessLauncher::set_cwd
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SubprocessLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSubprocessLauncher"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cwd"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the cwd for launched processes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_subprocess_launcher_set_cwd" g_subprocess_launcher_set_cwd :: 
    Ptr SubprocessLauncher ->               -- self : TInterface (Name {namespace = "Gio", name = "SubprocessLauncher"})
    CString ->                              -- cwd : TBasicType TFileName
    IO ()

-- | Sets the current working directory that processes will be launched
-- with.
-- 
-- By default processes are launched with the current working directory
-- of the launching process at the time of launch.
-- 
-- /Since: 2.40/
subprocessLauncherSetCwd ::
    (B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.SubprocessLauncher.SubprocessLauncher'
    -> [Char]
    -- ^ /@cwd@/: the cwd for launched processes
    -> m ()
subprocessLauncherSetCwd :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a -> String -> m ()
subprocessLauncherSetCwd a
self String
cwd = 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 SubprocessLauncher
self' <- a -> IO (Ptr SubprocessLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
cwd' <- String -> IO CString
stringToCString String
cwd
    Ptr SubprocessLauncher -> CString -> IO ()
g_subprocess_launcher_set_cwd Ptr SubprocessLauncher
self' CString
cwd'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
cwd'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

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


#endif

-- method SubprocessLauncher::set_environ
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SubprocessLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSubprocessLauncher"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "env"
--           , argType = TCArray True (-1) (-1) (TBasicType TFileName)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "\n    the replacement environment"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_subprocess_launcher_set_environ" g_subprocess_launcher_set_environ :: 
    Ptr SubprocessLauncher ->               -- self : TInterface (Name {namespace = "Gio", name = "SubprocessLauncher"})
    Ptr CString ->                          -- env : TCArray True (-1) (-1) (TBasicType TFileName)
    IO ()

-- | Replace the entire environment of processes launched from this
-- launcher with the given \'environ\' variable.
-- 
-- Typically you will build this variable by using 'GI.GLib.Functions.listenv' to copy
-- the process \'environ\' and using the functions 'GI.GLib.Functions.environSetenv',
-- 'GI.GLib.Functions.environUnsetenv', etc.
-- 
-- As an alternative, you can use 'GI.Gio.Objects.SubprocessLauncher.subprocessLauncherSetenv',
-- 'GI.Gio.Objects.SubprocessLauncher.subprocessLauncherUnsetenv', etc.
-- 
-- Pass an empty array to set an empty environment. Pass 'P.Nothing' to inherit the
-- parent process’ environment. As of GLib 2.54, the parent process’ environment
-- will be copied when 'GI.Gio.Objects.SubprocessLauncher.subprocessLauncherSetEnviron' is called.
-- Previously, it was copied when the subprocess was executed. This means the
-- copied environment may now be modified (using 'GI.Gio.Objects.SubprocessLauncher.subprocessLauncherSetenv',
-- etc.) before launching the subprocess.
-- 
-- On UNIX, all strings in this array can be arbitrary byte strings.
-- On Windows, they should be in UTF-8.
-- 
-- /Since: 2.40/
subprocessLauncherSetEnviron ::
    (B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.SubprocessLauncher.SubprocessLauncher'
    -> [[Char]]
    -- ^ /@env@/: 
    --     the replacement environment
    -> m ()
subprocessLauncherSetEnviron :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a -> [String] -> m ()
subprocessLauncherSetEnviron a
self [String]
env = 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 SubprocessLauncher
self' <- a -> IO (Ptr SubprocessLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CString
env' <- [String] -> IO (Ptr CString)
packZeroTerminatedFileNameArray [String]
env
    Ptr SubprocessLauncher -> Ptr CString -> IO ()
g_subprocess_launcher_set_environ Ptr SubprocessLauncher
self' Ptr CString
env'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    (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
env'
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
env'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

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


#endif

-- method SubprocessLauncher::set_flags
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SubprocessLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSubprocessLauncher"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SubprocessFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "#GSubprocessFlags" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_subprocess_launcher_set_flags" g_subprocess_launcher_set_flags :: 
    Ptr SubprocessLauncher ->               -- self : TInterface (Name {namespace = "Gio", name = "SubprocessLauncher"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Gio", name = "SubprocessFlags"})
    IO ()

-- | Sets the flags on the launcher.
-- 
-- The default flags are 'GI.Gio.Flags.SubprocessFlagsNone'.
-- 
-- You may not set flags that specify conflicting options for how to
-- handle a particular stdio stream (eg: specifying both
-- 'GI.Gio.Flags.SubprocessFlagsStdinPipe' and
-- 'GI.Gio.Flags.SubprocessFlagsStdinInherit').
-- 
-- You may also not set a flag that conflicts with a previous call to a
-- function like 'GI.Gio.Objects.SubprocessLauncher.subprocessLauncherSetStdinFilePath' or
-- 'GI.Gio.Objects.SubprocessLauncher.subprocessLauncherTakeStdoutFd'.
-- 
-- /Since: 2.40/
subprocessLauncherSetFlags ::
    (B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.SubprocessLauncher.SubprocessLauncher'
    -> [Gio.Flags.SubprocessFlags]
    -- ^ /@flags@/: t'GI.Gio.Flags.SubprocessFlags'
    -> m ()
subprocessLauncherSetFlags :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a -> [SubprocessFlags] -> m ()
subprocessLauncherSetFlags a
self [SubprocessFlags]
flags = 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 SubprocessLauncher
self' <- a -> IO (Ptr SubprocessLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let flags' :: CUInt
flags' = [SubprocessFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [SubprocessFlags]
flags
    Ptr SubprocessLauncher -> CUInt -> IO ()
g_subprocess_launcher_set_flags Ptr SubprocessLauncher
self' CUInt
flags'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SubprocessLauncherSetFlagsMethodInfo
instance (signature ~ ([Gio.Flags.SubprocessFlags] -> m ()), MonadIO m, IsSubprocessLauncher a) => O.OverloadedMethod SubprocessLauncherSetFlagsMethodInfo a signature where
    overloadedMethod = subprocessLauncherSetFlags

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


#endif

-- method SubprocessLauncher::set_stderr_file_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SubprocessLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSubprocessLauncher"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a filename or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_subprocess_launcher_set_stderr_file_path" g_subprocess_launcher_set_stderr_file_path :: 
    Ptr SubprocessLauncher ->               -- self : TInterface (Name {namespace = "Gio", name = "SubprocessLauncher"})
    CString ->                              -- path : TBasicType TFileName
    IO ()

-- | Sets the file path to use as the stderr for spawned processes.
-- 
-- If /@path@/ is 'P.Nothing' then any previously given path is unset.
-- 
-- The file will be created or truncated when the process is spawned, as
-- would be the case if using \'2>\' at the shell.
-- 
-- If you want to send both stdout and stderr to the same file then use
-- 'GI.Gio.Flags.SubprocessFlagsStderrMerge'.
-- 
-- You may not set a stderr file path if a stderr fd is already set or
-- if the launcher flags contain any flags directing stderr elsewhere.
-- 
-- This feature is only available on UNIX.
-- 
-- /Since: 2.40/
subprocessLauncherSetStderrFilePath ::
    (B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.SubprocessLauncher.SubprocessLauncher'
    -> Maybe ([Char])
    -- ^ /@path@/: a filename or 'P.Nothing'
    -> m ()
subprocessLauncherSetStderrFilePath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a -> Maybe String -> m ()
subprocessLauncherSetStderrFilePath a
self Maybe String
path = 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 SubprocessLauncher
self' <- a -> IO (Ptr SubprocessLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
maybePath <- case Maybe String
path of
        Maybe String
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just String
jPath -> do
            CString
jPath' <- String -> IO CString
stringToCString String
jPath
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jPath'
    Ptr SubprocessLauncher -> CString -> IO ()
g_subprocess_launcher_set_stderr_file_path Ptr SubprocessLauncher
self' CString
maybePath
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybePath
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SubprocessLauncherSetStderrFilePathMethodInfo
instance (signature ~ (Maybe ([Char]) -> m ()), MonadIO m, IsSubprocessLauncher a) => O.OverloadedMethod SubprocessLauncherSetStderrFilePathMethodInfo a signature where
    overloadedMethod = subprocessLauncherSetStderrFilePath

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


#endif

-- method SubprocessLauncher::set_stdin_file_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SubprocessLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSubprocessLauncher"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation { rawDocText = Nothing , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_subprocess_launcher_set_stdin_file_path" g_subprocess_launcher_set_stdin_file_path :: 
    Ptr SubprocessLauncher ->               -- self : TInterface (Name {namespace = "Gio", name = "SubprocessLauncher"})
    CString ->                              -- path : TBasicType TUTF8
    IO ()

-- | Sets the file path to use as the stdin for spawned processes.
-- 
-- If /@path@/ is 'P.Nothing' then any previously given path is unset.
-- 
-- The file must exist or spawning the process will fail.
-- 
-- You may not set a stdin file path if a stdin fd is already set or if
-- the launcher flags contain any flags directing stdin elsewhere.
-- 
-- This feature is only available on UNIX.
-- 
-- /Since: 2.40/
subprocessLauncherSetStdinFilePath ::
    (B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.SubprocessLauncher.SubprocessLauncher'
    -> T.Text
    -> m ()
subprocessLauncherSetStdinFilePath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a -> Text -> m ()
subprocessLauncherSetStdinFilePath a
self Text
path = 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 SubprocessLauncher
self' <- a -> IO (Ptr SubprocessLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
path' <- Text -> IO CString
textToCString Text
path
    Ptr SubprocessLauncher -> CString -> IO ()
g_subprocess_launcher_set_stdin_file_path Ptr SubprocessLauncher
self' CString
path'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

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


#endif

-- method SubprocessLauncher::set_stdout_file_path
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SubprocessLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSubprocessLauncher"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "path"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a filename or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_subprocess_launcher_set_stdout_file_path" g_subprocess_launcher_set_stdout_file_path :: 
    Ptr SubprocessLauncher ->               -- self : TInterface (Name {namespace = "Gio", name = "SubprocessLauncher"})
    CString ->                              -- path : TBasicType TFileName
    IO ()

-- | Sets the file path to use as the stdout for spawned processes.
-- 
-- If /@path@/ is 'P.Nothing' then any previously given path is unset.
-- 
-- The file will be created or truncated when the process is spawned, as
-- would be the case if using \'>\' at the shell.
-- 
-- You may not set a stdout file path if a stdout fd is already set or
-- if the launcher flags contain any flags directing stdout elsewhere.
-- 
-- This feature is only available on UNIX.
-- 
-- /Since: 2.40/
subprocessLauncherSetStdoutFilePath ::
    (B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.SubprocessLauncher.SubprocessLauncher'
    -> Maybe ([Char])
    -- ^ /@path@/: a filename or 'P.Nothing'
    -> m ()
subprocessLauncherSetStdoutFilePath :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a -> Maybe String -> m ()
subprocessLauncherSetStdoutFilePath a
self Maybe String
path = 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 SubprocessLauncher
self' <- a -> IO (Ptr SubprocessLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
maybePath <- case Maybe String
path of
        Maybe String
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just String
jPath -> do
            CString
jPath' <- String -> IO CString
stringToCString String
jPath
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jPath'
    Ptr SubprocessLauncher -> CString -> IO ()
g_subprocess_launcher_set_stdout_file_path Ptr SubprocessLauncher
self' CString
maybePath
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybePath
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SubprocessLauncherSetStdoutFilePathMethodInfo
instance (signature ~ (Maybe ([Char]) -> m ()), MonadIO m, IsSubprocessLauncher a) => O.OverloadedMethod SubprocessLauncherSetStdoutFilePathMethodInfo a signature where
    overloadedMethod = subprocessLauncherSetStdoutFilePath

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


#endif

-- method SubprocessLauncher::setenv
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SubprocessLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSubprocessLauncher"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "variable"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the environment variable to set,\n    must not contain '='"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new value for the variable"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "overwrite"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "whether to change the variable if it already exists"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_subprocess_launcher_setenv" g_subprocess_launcher_setenv :: 
    Ptr SubprocessLauncher ->               -- self : TInterface (Name {namespace = "Gio", name = "SubprocessLauncher"})
    CString ->                              -- variable : TBasicType TFileName
    CString ->                              -- value : TBasicType TFileName
    CInt ->                                 -- overwrite : TBasicType TBoolean
    IO ()

-- | Sets the environment variable /@variable@/ in the environment of
-- processes launched from this launcher.
-- 
-- On UNIX, both the variable\'s name and value can be arbitrary byte
-- strings, except that the variable\'s name cannot contain \'=\'.
-- On Windows, they should be in UTF-8.
-- 
-- /Since: 2.40/
subprocessLauncherSetenv ::
    (B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.SubprocessLauncher.SubprocessLauncher'
    -> [Char]
    -- ^ /@variable@/: the environment variable to set,
    --     must not contain \'=\'
    -> [Char]
    -- ^ /@value@/: the new value for the variable
    -> Bool
    -- ^ /@overwrite@/: whether to change the variable if it already exists
    -> m ()
subprocessLauncherSetenv :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a -> String -> String -> Bool -> m ()
subprocessLauncherSetenv a
self String
variable String
value Bool
overwrite = 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 SubprocessLauncher
self' <- a -> IO (Ptr SubprocessLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
variable' <- String -> IO CString
stringToCString String
variable
    CString
value' <- String -> IO CString
stringToCString String
value
    let overwrite' :: CInt
overwrite' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
overwrite
    Ptr SubprocessLauncher -> CString -> CString -> CInt -> IO ()
g_subprocess_launcher_setenv Ptr SubprocessLauncher
self' CString
variable' CString
value' CInt
overwrite'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
variable'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
value'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SubprocessLauncherSetenvMethodInfo
instance (signature ~ ([Char] -> [Char] -> Bool -> m ()), MonadIO m, IsSubprocessLauncher a) => O.OverloadedMethod SubprocessLauncherSetenvMethodInfo a signature where
    overloadedMethod = subprocessLauncherSetenv

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


#endif

-- method SubprocessLauncher::spawnv
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SubprocessLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSubprocessLauncher"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "argv"
--           , argType = TCArray True (-1) (-1) (TBasicType TFileName)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Command line arguments"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gio" , name = "Subprocess" })
-- throws : True
-- Skip return : False

foreign import ccall "g_subprocess_launcher_spawnv" g_subprocess_launcher_spawnv :: 
    Ptr SubprocessLauncher ->               -- self : TInterface (Name {namespace = "Gio", name = "SubprocessLauncher"})
    Ptr CString ->                          -- argv : TCArray True (-1) (-1) (TBasicType TFileName)
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Gio.Subprocess.Subprocess)

-- | Creates a t'GI.Gio.Objects.Subprocess.Subprocess' given a provided array of arguments.
-- 
-- /Since: 2.40/
subprocessLauncherSpawnv ::
    (B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.SubprocessLauncher.SubprocessLauncher'
    -> [[Char]]
    -- ^ /@argv@/: Command line arguments
    -> m Gio.Subprocess.Subprocess
    -- ^ __Returns:__ A new t'GI.Gio.Objects.Subprocess.Subprocess', or 'P.Nothing' on error (and /@error@/ will be set) /(Can throw 'Data.GI.Base.GError.GError')/
subprocessLauncherSpawnv :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a -> [String] -> m Subprocess
subprocessLauncherSpawnv a
self [String]
argv = IO Subprocess -> m Subprocess
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Subprocess -> m Subprocess) -> IO Subprocess -> m Subprocess
forall a b. (a -> b) -> a -> b
$ do
    Ptr SubprocessLauncher
self' <- a -> IO (Ptr SubprocessLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr CString
argv' <- [String] -> IO (Ptr CString)
packZeroTerminatedFileNameArray [String]
argv
    IO Subprocess -> IO () -> IO Subprocess
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Subprocess
result <- (Ptr (Ptr GError) -> IO (Ptr Subprocess)) -> IO (Ptr Subprocess)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Subprocess)) -> IO (Ptr Subprocess))
-> (Ptr (Ptr GError) -> IO (Ptr Subprocess)) -> IO (Ptr Subprocess)
forall a b. (a -> b) -> a -> b
$ Ptr SubprocessLauncher
-> Ptr CString -> Ptr (Ptr GError) -> IO (Ptr Subprocess)
g_subprocess_launcher_spawnv Ptr SubprocessLauncher
self' Ptr CString
argv'
        Text -> Ptr Subprocess -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"subprocessLauncherSpawnv" Ptr Subprocess
result
        Subprocess
result' <- ((ManagedPtr Subprocess -> Subprocess)
-> Ptr Subprocess -> IO Subprocess
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Subprocess -> Subprocess
Gio.Subprocess.Subprocess) Ptr Subprocess
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        (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
argv'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
argv'
        Subprocess -> IO Subprocess
forall (m :: * -> *) a. Monad m => a -> m a
return Subprocess
result'
     ) (do
        (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
argv'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
argv'
     )

#if defined(ENABLE_OVERLOADING)
data SubprocessLauncherSpawnvMethodInfo
instance (signature ~ ([[Char]] -> m Gio.Subprocess.Subprocess), MonadIO m, IsSubprocessLauncher a) => O.OverloadedMethod SubprocessLauncherSpawnvMethodInfo a signature where
    overloadedMethod = subprocessLauncherSpawnv

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


#endif

-- method SubprocessLauncher::take_fd
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SubprocessLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSubprocessLauncher"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "source_fd"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "File descriptor in parent process"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "target_fd"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Target descriptor for child process"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_subprocess_launcher_take_fd" g_subprocess_launcher_take_fd :: 
    Ptr SubprocessLauncher ->               -- self : TInterface (Name {namespace = "Gio", name = "SubprocessLauncher"})
    Int32 ->                                -- source_fd : TBasicType TInt
    Int32 ->                                -- target_fd : TBasicType TInt
    IO ()

-- | Transfer an arbitrary file descriptor from parent process to the
-- child.  This function takes ownership of the /@sourceFd@/; it will be closed
-- in the parent when /@self@/ is freed.
-- 
-- By default, all file descriptors from the parent will be closed.
-- This function allows you to create (for example) a custom @pipe()@ or
-- @socketpair()@ before launching the process, and choose the target
-- descriptor in the child.
-- 
-- An example use case is GNUPG, which has a command line argument
-- @--passphrase-fd@ providing a file descriptor number where it expects
-- the passphrase to be written.
subprocessLauncherTakeFd ::
    (B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.SubprocessLauncher.SubprocessLauncher'
    -> Int32
    -- ^ /@sourceFd@/: File descriptor in parent process
    -> Int32
    -- ^ /@targetFd@/: Target descriptor for child process
    -> m ()
subprocessLauncherTakeFd :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a -> Int32 -> Int32 -> m ()
subprocessLauncherTakeFd a
self Int32
sourceFd Int32
targetFd = 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 SubprocessLauncher
self' <- a -> IO (Ptr SubprocessLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr SubprocessLauncher -> Int32 -> Int32 -> IO ()
g_subprocess_launcher_take_fd Ptr SubprocessLauncher
self' Int32
sourceFd Int32
targetFd
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SubprocessLauncherTakeFdMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m, IsSubprocessLauncher a) => O.OverloadedMethod SubprocessLauncherTakeFdMethodInfo a signature where
    overloadedMethod = subprocessLauncherTakeFd

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


#endif

-- method SubprocessLauncher::take_stderr_fd
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SubprocessLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSubprocessLauncher"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "fd"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a file descriptor, or -1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_subprocess_launcher_take_stderr_fd" g_subprocess_launcher_take_stderr_fd :: 
    Ptr SubprocessLauncher ->               -- self : TInterface (Name {namespace = "Gio", name = "SubprocessLauncher"})
    Int32 ->                                -- fd : TBasicType TInt
    IO ()

-- | Sets the file descriptor to use as the stderr for spawned processes.
-- 
-- If /@fd@/ is -1 then any previously given fd is unset.
-- 
-- Note that the default behaviour is to pass stderr through to the
-- stderr of the parent process.
-- 
-- The passed /@fd@/ belongs to the t'GI.Gio.Objects.SubprocessLauncher.SubprocessLauncher'.  It will be
-- automatically closed when the launcher is finalized.  The file
-- descriptor will also be closed on the child side when executing the
-- spawned process.
-- 
-- You may not set a stderr fd if a stderr file path is already set or
-- if the launcher flags contain any flags directing stderr elsewhere.
-- 
-- This feature is only available on UNIX.
-- 
-- /Since: 2.40/
subprocessLauncherTakeStderrFd ::
    (B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.SubprocessLauncher.SubprocessLauncher'
    -> Int32
    -- ^ /@fd@/: a file descriptor, or -1
    -> m ()
subprocessLauncherTakeStderrFd :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a -> Int32 -> m ()
subprocessLauncherTakeStderrFd a
self Int32
fd = 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 SubprocessLauncher
self' <- a -> IO (Ptr SubprocessLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr SubprocessLauncher -> Int32 -> IO ()
g_subprocess_launcher_take_stderr_fd Ptr SubprocessLauncher
self' Int32
fd
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SubprocessLauncherTakeStderrFdMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsSubprocessLauncher a) => O.OverloadedMethod SubprocessLauncherTakeStderrFdMethodInfo a signature where
    overloadedMethod = subprocessLauncherTakeStderrFd

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


#endif

-- method SubprocessLauncher::take_stdin_fd
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SubprocessLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSubprocessLauncher"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "fd"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a file descriptor, or -1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_subprocess_launcher_take_stdin_fd" g_subprocess_launcher_take_stdin_fd :: 
    Ptr SubprocessLauncher ->               -- self : TInterface (Name {namespace = "Gio", name = "SubprocessLauncher"})
    Int32 ->                                -- fd : TBasicType TInt
    IO ()

-- | Sets the file descriptor to use as the stdin for spawned processes.
-- 
-- If /@fd@/ is -1 then any previously given fd is unset.
-- 
-- Note that if your intention is to have the stdin of the calling
-- process inherited by the child then 'GI.Gio.Flags.SubprocessFlagsStdinInherit'
-- is a better way to go about doing that.
-- 
-- The passed /@fd@/ is noted but will not be touched in the current
-- process.  It is therefore necessary that it be kept open by the
-- caller until the subprocess is spawned.  The file descriptor will
-- also not be explicitly closed on the child side, so it must be marked
-- O_CLOEXEC if that\'s what you want.
-- 
-- You may not set a stdin fd if a stdin file path is already set or if
-- the launcher flags contain any flags directing stdin elsewhere.
-- 
-- This feature is only available on UNIX.
-- 
-- /Since: 2.40/
subprocessLauncherTakeStdinFd ::
    (B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.SubprocessLauncher.SubprocessLauncher'
    -> Int32
    -- ^ /@fd@/: a file descriptor, or -1
    -> m ()
subprocessLauncherTakeStdinFd :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a -> Int32 -> m ()
subprocessLauncherTakeStdinFd a
self Int32
fd = 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 SubprocessLauncher
self' <- a -> IO (Ptr SubprocessLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr SubprocessLauncher -> Int32 -> IO ()
g_subprocess_launcher_take_stdin_fd Ptr SubprocessLauncher
self' Int32
fd
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SubprocessLauncherTakeStdinFdMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsSubprocessLauncher a) => O.OverloadedMethod SubprocessLauncherTakeStdinFdMethodInfo a signature where
    overloadedMethod = subprocessLauncherTakeStdinFd

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


#endif

-- method SubprocessLauncher::take_stdout_fd
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SubprocessLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSubprocessLauncher"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "fd"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a file descriptor, or -1"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_subprocess_launcher_take_stdout_fd" g_subprocess_launcher_take_stdout_fd :: 
    Ptr SubprocessLauncher ->               -- self : TInterface (Name {namespace = "Gio", name = "SubprocessLauncher"})
    Int32 ->                                -- fd : TBasicType TInt
    IO ()

-- | Sets the file descriptor to use as the stdout for spawned processes.
-- 
-- If /@fd@/ is -1 then any previously given fd is unset.
-- 
-- Note that the default behaviour is to pass stdout through to the
-- stdout of the parent process.
-- 
-- The passed /@fd@/ is noted but will not be touched in the current
-- process.  It is therefore necessary that it be kept open by the
-- caller until the subprocess is spawned.  The file descriptor will
-- also not be explicitly closed on the child side, so it must be marked
-- O_CLOEXEC if that\'s what you want.
-- 
-- You may not set a stdout fd if a stdout file path is already set or
-- if the launcher flags contain any flags directing stdout elsewhere.
-- 
-- This feature is only available on UNIX.
-- 
-- /Since: 2.40/
subprocessLauncherTakeStdoutFd ::
    (B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.SubprocessLauncher.SubprocessLauncher'
    -> Int32
    -- ^ /@fd@/: a file descriptor, or -1
    -> m ()
subprocessLauncherTakeStdoutFd :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a -> Int32 -> m ()
subprocessLauncherTakeStdoutFd a
self Int32
fd = 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 SubprocessLauncher
self' <- a -> IO (Ptr SubprocessLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr SubprocessLauncher -> Int32 -> IO ()
g_subprocess_launcher_take_stdout_fd Ptr SubprocessLauncher
self' Int32
fd
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data SubprocessLauncherTakeStdoutFdMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsSubprocessLauncher a) => O.OverloadedMethod SubprocessLauncherTakeStdoutFdMethodInfo a signature where
    overloadedMethod = subprocessLauncherTakeStdoutFd

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


#endif

-- method SubprocessLauncher::unsetenv
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "SubprocessLauncher" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSubprocessLauncher"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "variable"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the environment variable to unset,\n    must not contain '='"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_subprocess_launcher_unsetenv" g_subprocess_launcher_unsetenv :: 
    Ptr SubprocessLauncher ->               -- self : TInterface (Name {namespace = "Gio", name = "SubprocessLauncher"})
    CString ->                              -- variable : TBasicType TFileName
    IO ()

-- | Removes the environment variable /@variable@/ from the environment of
-- processes launched from this launcher.
-- 
-- On UNIX, the variable\'s name can be an arbitrary byte string not
-- containing \'=\'. On Windows, it should be in UTF-8.
-- 
-- /Since: 2.40/
subprocessLauncherUnsetenv ::
    (B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
    a
    -- ^ /@self@/: a t'GI.Gio.Objects.SubprocessLauncher.SubprocessLauncher'
    -> [Char]
    -- ^ /@variable@/: the environment variable to unset,
    --     must not contain \'=\'
    -> m ()
subprocessLauncherUnsetenv :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a -> String -> m ()
subprocessLauncherUnsetenv a
self String
variable = 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 SubprocessLauncher
self' <- a -> IO (Ptr SubprocessLauncher)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
variable' <- String -> IO CString
stringToCString String
variable
    Ptr SubprocessLauncher -> CString -> IO ()
g_subprocess_launcher_unsetenv Ptr SubprocessLauncher
self' CString
variable'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
variable'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

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


#endif