{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Objects.SubprocessLauncher
(
SubprocessLauncher(..) ,
IsSubprocessLauncher ,
toSubprocessLauncher ,
#if defined(ENABLE_OVERLOADING)
ResolveSubprocessLauncherMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
SubprocessLauncherGetenvMethodInfo ,
#endif
subprocessLauncherGetenv ,
subprocessLauncherNew ,
#if defined(ENABLE_OVERLOADING)
SubprocessLauncherSetCwdMethodInfo ,
#endif
subprocessLauncherSetCwd ,
#if defined(ENABLE_OVERLOADING)
SubprocessLauncherSetEnvironMethodInfo ,
#endif
subprocessLauncherSetEnviron ,
#if defined(ENABLE_OVERLOADING)
SubprocessLauncherSetFlagsMethodInfo ,
#endif
subprocessLauncherSetFlags ,
#if defined(ENABLE_OVERLOADING)
SubprocessLauncherSetStderrFilePathMethodInfo,
#endif
subprocessLauncherSetStderrFilePath ,
#if defined(ENABLE_OVERLOADING)
SubprocessLauncherSetStdinFilePathMethodInfo,
#endif
subprocessLauncherSetStdinFilePath ,
#if defined(ENABLE_OVERLOADING)
SubprocessLauncherSetStdoutFilePathMethodInfo,
#endif
subprocessLauncherSetStdoutFilePath ,
#if defined(ENABLE_OVERLOADING)
SubprocessLauncherSetenvMethodInfo ,
#endif
subprocessLauncherSetenv ,
#if defined(ENABLE_OVERLOADING)
SubprocessLauncherSpawnvMethodInfo ,
#endif
subprocessLauncherSpawnv ,
#if defined(ENABLE_OVERLOADING)
SubprocessLauncherTakeFdMethodInfo ,
#endif
subprocessLauncherTakeFd ,
#if defined(ENABLE_OVERLOADING)
SubprocessLauncherTakeStderrFdMethodInfo,
#endif
subprocessLauncherTakeStderrFd ,
#if defined(ENABLE_OVERLOADING)
SubprocessLauncherTakeStdinFdMethodInfo ,
#endif
subprocessLauncherTakeStdinFd ,
#if defined(ENABLE_OVERLOADING)
SubprocessLauncherTakeStdoutFdMethodInfo,
#endif
subprocessLauncherTakeStdoutFd ,
#if defined(ENABLE_OVERLOADING)
SubprocessLauncherUnsetenvMethodInfo ,
#endif
subprocessLauncherUnsetenv ,
#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.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.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.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
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
instance B.GValue.IsGValue SubprocessLauncher where
toGValue :: SubprocessLauncher -> IO GValue
toGValue SubprocessLauncher
o = do
GType
gtype <- IO GType
c_g_subprocess_launcher_get_type
SubprocessLauncher
-> (Ptr SubprocessLauncher -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SubprocessLauncher
o (GType
-> (GValue -> Ptr SubprocessLauncher -> IO ())
-> Ptr SubprocessLauncher
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr SubprocessLauncher -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO SubprocessLauncher
fromGValue GValue
gv = do
Ptr SubprocessLauncher
ptr <- GValue -> IO (Ptr SubprocessLauncher)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr SubprocessLauncher)
(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
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]
toSubprocessLauncher :: (MonadIO m, IsSubprocessLauncher o) => o -> m SubprocessLauncher
toSubprocessLauncher :: o -> m SubprocessLauncher
toSubprocessLauncher = IO SubprocessLauncher -> m SubprocessLauncher
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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'
unsafeCastTo ManagedPtr SubprocessLauncher -> SubprocessLauncher
SubprocessLauncher
#if defined(ENABLE_OVERLOADING)
type family ResolveSubprocessLauncherMethod (t :: Symbol) (o :: *) :: * where
ResolveSubprocessLauncherMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveSubprocessLauncherMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
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.MethodInfo 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
#endif
constructSubprocessLauncherFlags :: (IsSubprocessLauncher o, MIO.MonadIO m) => [Gio.Flags.SubprocessFlags] -> m (GValueConstruct o)
constructSubprocessLauncherFlags :: [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
$ 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
#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
foreign import ccall "g_subprocess_launcher_new" g_subprocess_launcher_new ::
CUInt ->
IO (Ptr SubprocessLauncher)
subprocessLauncherNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
[Gio.Flags.SubprocessFlags]
-> m SubprocessLauncher
subprocessLauncherNew :: [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
foreign import ccall "g_subprocess_launcher_getenv" g_subprocess_launcher_getenv ::
Ptr SubprocessLauncher ->
CString ->
IO CString
subprocessLauncherGetenv ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a
-> [Char]
-> m [Char]
subprocessLauncherGetenv :: a -> String -> m String
subprocessLauncherGetenv a
self String
variable = 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 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'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"subprocessLauncherGetenv" CString
result
String
result' <- HasCallStack => CString -> IO String
CString -> IO String
cstringToString CString
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
variable'
String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
result'
#if defined(ENABLE_OVERLOADING)
data SubprocessLauncherGetenvMethodInfo
instance (signature ~ ([Char] -> m [Char]), MonadIO m, IsSubprocessLauncher a) => O.MethodInfo SubprocessLauncherGetenvMethodInfo a signature where
overloadedMethod = subprocessLauncherGetenv
#endif
foreign import ccall "g_subprocess_launcher_set_cwd" g_subprocess_launcher_set_cwd ::
Ptr SubprocessLauncher ->
CString ->
IO ()
subprocessLauncherSetCwd ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a
-> [Char]
-> m ()
subprocessLauncherSetCwd :: 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.MethodInfo SubprocessLauncherSetCwdMethodInfo a signature where
overloadedMethod = subprocessLauncherSetCwd
#endif
foreign import ccall "g_subprocess_launcher_set_environ" g_subprocess_launcher_set_environ ::
Ptr SubprocessLauncher ->
Ptr CString ->
IO ()
subprocessLauncherSetEnviron ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a
-> [[Char]]
-> m ()
subprocessLauncherSetEnviron :: 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.MethodInfo SubprocessLauncherSetEnvironMethodInfo a signature where
overloadedMethod = subprocessLauncherSetEnviron
#endif
foreign import ccall "g_subprocess_launcher_set_flags" g_subprocess_launcher_set_flags ::
Ptr SubprocessLauncher ->
CUInt ->
IO ()
subprocessLauncherSetFlags ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a
-> [Gio.Flags.SubprocessFlags]
-> m ()
subprocessLauncherSetFlags :: 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.MethodInfo SubprocessLauncherSetFlagsMethodInfo a signature where
overloadedMethod = subprocessLauncherSetFlags
#endif
foreign import ccall "g_subprocess_launcher_set_stderr_file_path" g_subprocess_launcher_set_stderr_file_path ::
Ptr SubprocessLauncher ->
CString ->
IO ()
subprocessLauncherSetStderrFilePath ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a
-> Maybe ([Char])
-> m ()
subprocessLauncherSetStderrFilePath :: 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.MethodInfo SubprocessLauncherSetStderrFilePathMethodInfo a signature where
overloadedMethod = subprocessLauncherSetStderrFilePath
#endif
foreign import ccall "g_subprocess_launcher_set_stdin_file_path" g_subprocess_launcher_set_stdin_file_path ::
Ptr SubprocessLauncher ->
CString ->
IO ()
subprocessLauncherSetStdinFilePath ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a
-> T.Text
-> m ()
subprocessLauncherSetStdinFilePath :: 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.MethodInfo SubprocessLauncherSetStdinFilePathMethodInfo a signature where
overloadedMethod = subprocessLauncherSetStdinFilePath
#endif
foreign import ccall "g_subprocess_launcher_set_stdout_file_path" g_subprocess_launcher_set_stdout_file_path ::
Ptr SubprocessLauncher ->
CString ->
IO ()
subprocessLauncherSetStdoutFilePath ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a
-> Maybe ([Char])
-> m ()
subprocessLauncherSetStdoutFilePath :: 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.MethodInfo SubprocessLauncherSetStdoutFilePathMethodInfo a signature where
overloadedMethod = subprocessLauncherSetStdoutFilePath
#endif
foreign import ccall "g_subprocess_launcher_setenv" g_subprocess_launcher_setenv ::
Ptr SubprocessLauncher ->
CString ->
CString ->
CInt ->
IO ()
subprocessLauncherSetenv ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a
-> [Char]
-> [Char]
-> Bool
-> m ()
subprocessLauncherSetenv :: 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.MethodInfo SubprocessLauncherSetenvMethodInfo a signature where
overloadedMethod = subprocessLauncherSetenv
#endif
foreign import ccall "g_subprocess_launcher_spawnv" g_subprocess_launcher_spawnv ::
Ptr SubprocessLauncher ->
Ptr CString ->
Ptr (Ptr GError) ->
IO (Ptr Gio.Subprocess.Subprocess)
subprocessLauncherSpawnv ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a
-> [[Char]]
-> m Gio.Subprocess.Subprocess
subprocessLauncherSpawnv :: 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.MethodInfo SubprocessLauncherSpawnvMethodInfo a signature where
overloadedMethod = subprocessLauncherSpawnv
#endif
foreign import ccall "g_subprocess_launcher_take_fd" g_subprocess_launcher_take_fd ::
Ptr SubprocessLauncher ->
Int32 ->
Int32 ->
IO ()
subprocessLauncherTakeFd ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a
-> Int32
-> Int32
-> m ()
subprocessLauncherTakeFd :: 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.MethodInfo SubprocessLauncherTakeFdMethodInfo a signature where
overloadedMethod = subprocessLauncherTakeFd
#endif
foreign import ccall "g_subprocess_launcher_take_stderr_fd" g_subprocess_launcher_take_stderr_fd ::
Ptr SubprocessLauncher ->
Int32 ->
IO ()
subprocessLauncherTakeStderrFd ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a
-> Int32
-> m ()
subprocessLauncherTakeStderrFd :: 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.MethodInfo SubprocessLauncherTakeStderrFdMethodInfo a signature where
overloadedMethod = subprocessLauncherTakeStderrFd
#endif
foreign import ccall "g_subprocess_launcher_take_stdin_fd" g_subprocess_launcher_take_stdin_fd ::
Ptr SubprocessLauncher ->
Int32 ->
IO ()
subprocessLauncherTakeStdinFd ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a
-> Int32
-> m ()
subprocessLauncherTakeStdinFd :: 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.MethodInfo SubprocessLauncherTakeStdinFdMethodInfo a signature where
overloadedMethod = subprocessLauncherTakeStdinFd
#endif
foreign import ccall "g_subprocess_launcher_take_stdout_fd" g_subprocess_launcher_take_stdout_fd ::
Ptr SubprocessLauncher ->
Int32 ->
IO ()
subprocessLauncherTakeStdoutFd ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a
-> Int32
-> m ()
subprocessLauncherTakeStdoutFd :: 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.MethodInfo SubprocessLauncherTakeStdoutFdMethodInfo a signature where
overloadedMethod = subprocessLauncherTakeStdoutFd
#endif
foreign import ccall "g_subprocess_launcher_unsetenv" g_subprocess_launcher_unsetenv ::
Ptr SubprocessLauncher ->
CString ->
IO ()
subprocessLauncherUnsetenv ::
(B.CallStack.HasCallStack, MonadIO m, IsSubprocessLauncher a) =>
a
-> [Char]
-> m ()
subprocessLauncherUnsetenv :: 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.MethodInfo SubprocessLauncherUnsetenvMethodInfo a signature where
overloadedMethod = subprocessLauncherUnsetenv
#endif