Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Unlifted System.Process.
Since: unliftio-0.2.5.0
Synopsis
- data CreateProcess = CreateProcess {
- cmdspec :: CmdSpec
- cwd :: Maybe FilePath
- env :: Maybe [(String, String)]
- std_in :: StdStream
- std_out :: StdStream
- std_err :: StdStream
- close_fds :: Bool
- create_group :: Bool
- delegate_ctlc :: Bool
- detach_console :: Bool
- create_new_console :: Bool
- new_session :: Bool
- child_group :: Maybe GroupID
- child_user :: Maybe UserID
- use_process_jobs :: Bool
- data CmdSpec
- data StdStream
- data ProcessHandle
- createProcess :: MonadIO m => CreateProcess -> m (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
- createProcess_ :: MonadIO m => String -> CreateProcess -> m (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
- shell :: String -> CreateProcess
- proc :: FilePath -> [String] -> CreateProcess
- callProcess :: MonadIO m => FilePath -> [String] -> m ()
- callCommand :: MonadIO m => String -> m ()
- spawnProcess :: MonadIO m => FilePath -> [String] -> m ProcessHandle
- spawnCommand :: MonadIO m => String -> m ProcessHandle
- readCreateProcess :: MonadIO m => CreateProcess -> String -> m String
- readProcess :: MonadIO m => FilePath -> [String] -> String -> m String
- readCreateProcessWithExitCode :: MonadIO m => CreateProcess -> String -> m (ExitCode, String, String)
- readProcessWithExitCode :: MonadIO m => FilePath -> [String] -> String -> m (ExitCode, String, String)
- withCreateProcess :: MonadUnliftIO m => CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> m a) -> m a
- showCommandForUser :: FilePath -> [String] -> String
- waitForProcess :: MonadIO m => ProcessHandle -> m ExitCode
- getProcessExitCode :: MonadIO m => ProcessHandle -> m (Maybe ExitCode)
- terminateProcess :: MonadIO m => ProcessHandle -> m ()
- interruptProcessGroupOf :: MonadIO m => ProcessHandle -> m ()
- createPipe :: MonadIO m => m (Handle, Handle)
- createPipeFd :: MonadIO m => m (FD, FD)
Running sub-processes
data CreateProcess #
CreateProcess | |
|
Instances
Eq CreateProcess | |
Defined in System.Process.Common (==) :: CreateProcess -> CreateProcess -> Bool # (/=) :: CreateProcess -> CreateProcess -> Bool # | |
Show CreateProcess | |
Defined in System.Process.Common showsPrec :: Int -> CreateProcess -> ShowS # show :: CreateProcess -> String # showList :: [CreateProcess] -> ShowS # |
ShellCommand String | A command line to execute using the shell |
RawCommand FilePath [String] | The name of an executable with a list of arguments The
|
Instances
Eq CmdSpec | |
Show CmdSpec | |
IsString CmdSpec | construct a Since: process-1.2.1.0 |
Defined in System.Process.Common fromString :: String -> CmdSpec # |
Inherit | Inherit Handle from parent |
UseHandle Handle | Use the supplied Handle |
CreatePipe | Create a new pipe. The returned
|
NoStream | No stream handle will be passed |
data ProcessHandle #
createProcess :: MonadIO m => CreateProcess -> m (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) Source #
Lifted createProcess
.
Since: unliftio-0.2.5.0
createProcess_ :: MonadIO m => String -> CreateProcess -> m (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) Source #
Lifted createProcess_
.
Since: unliftio-0.2.5.0
shell :: String -> CreateProcess #
Construct a CreateProcess
record for passing to createProcess
,
representing a command to be passed to the shell.
proc :: FilePath -> [String] -> CreateProcess #
Construct a CreateProcess
record for passing to createProcess
,
representing a raw command with arguments.
See RawCommand
for precise semantics of the specified FilePath
.
Simpler functions for common tasks
callProcess :: MonadIO m => FilePath -> [String] -> m () Source #
Lifted callProcess
.
Since: unliftio-0.2.5.0
callCommand :: MonadIO m => String -> m () Source #
Lifted callCommand
.
Since: unliftio-0.2.5.0
spawnProcess :: MonadIO m => FilePath -> [String] -> m ProcessHandle Source #
Lifted spawnProcess
.
Since: unliftio-0.2.5.0
spawnCommand :: MonadIO m => String -> m ProcessHandle Source #
Lifted spawnCommand
.
Since: unliftio-0.2.5.0
readCreateProcess :: MonadIO m => CreateProcess -> String -> m String Source #
Lifted readCreateProcess
.
Since: unliftio-0.2.5.0
readProcess :: MonadIO m => FilePath -> [String] -> String -> m String Source #
Lifted readProcess
.
Since: unliftio-0.2.5.0
readCreateProcessWithExitCode :: MonadIO m => CreateProcess -> String -> m (ExitCode, String, String) Source #
Lifted readCreateProcessWithExitCode
.
Since: unliftio-0.2.5.0
readProcessWithExitCode :: MonadIO m => FilePath -> [String] -> String -> m (ExitCode, String, String) Source #
Lifted readProcessWithExitCode
.
Since: unliftio-0.2.5.0
withCreateProcess :: MonadUnliftIO m => CreateProcess -> (Maybe Handle -> Maybe Handle -> Maybe Handle -> ProcessHandle -> m a) -> m a Source #
Unlifted withCreateProcess
.
Since: unliftio-0.2.5.0
Related utilities
showCommandForUser :: FilePath -> [String] -> String #
Given a program p
and arguments args
,
showCommandForUser p args
returns a string suitable for pasting
into /bin/sh
(on Unix systems) or CMD.EXE
(on Windows).
Process completion
waitForProcess :: MonadIO m => ProcessHandle -> m ExitCode Source #
Lifted waitForProcess
.
Since: unliftio-0.2.5.0
getProcessExitCode :: MonadIO m => ProcessHandle -> m (Maybe ExitCode) Source #
Lifted getProcessExitCode
.
Since: unliftio-0.2.5.0
terminateProcess :: MonadIO m => ProcessHandle -> m () Source #
Lifted terminateProcess
.
Since: unliftio-0.2.5.0
interruptProcessGroupOf :: MonadIO m => ProcessHandle -> m () Source #
Lifted interruptProcessGroupOf
.
Since: unliftio-0.2.5.0
Interprocess communication
createPipe :: MonadIO m => m (Handle, Handle) Source #
Lifted createPipe
.
Since: unliftio-0.2.5.0
createPipeFd :: MonadIO m => m (FD, FD) Source #
Lifted createPipeFd
.
Since: unliftio-0.2.5.0