| Copyright | (c) The University of Glasgow 2004 |
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) |
| Maintainer | libraries@haskell.org |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
System.Process.Internals
Description
Note: This module exports internal implementation details that may change anytime. If you want a more stable API, use System.Process instead.
Synopsis
- data ProcessHandle = ProcessHandle {
- phandle :: !(MVar ProcessHandle__)
- mb_delegate_ctlc :: !Bool
- waitpidLock :: !(MVar ())
- data ProcessHandle__
- = OpenHandle { }
- | OpenExtHandle { }
- | ClosedHandle ExitCode
- type PHANDLE = CPid
- closePHANDLE :: PHANDLE -> IO ()
- mkProcessHandle :: PHANDLE -> Bool -> IO ProcessHandle
- data CGid
- type GroupID = CGid
- type UserID = CUid
- modifyProcessHandle :: ProcessHandle -> (ProcessHandle__ -> IO (ProcessHandle__, a)) -> IO a
- withProcessHandle :: ProcessHandle -> (ProcessHandle__ -> IO a) -> IO a
- 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
- = Inherit
- | UseHandle Handle
- | CreatePipe
- | NoStream
- data ProcRetHandles = ProcRetHandles {
- hStdInput :: Maybe Handle
- hStdOutput :: Maybe Handle
- hStdError :: Maybe Handle
- procHandle :: ProcessHandle
- createProcess_ :: String -> CreateProcess -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
- runGenProcess_ :: String -> CreateProcess -> Maybe CLong -> Maybe CLong -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
- fdToHandle :: FD -> IO Handle
- startDelegateControlC :: IO ()
- endDelegateControlC :: ExitCode -> IO ()
- stopDelegateControlC :: IO ()
- unwrapHandles :: ProcRetHandles -> (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
- pPrPr_disableITimers :: IO ()
- c_execvpe :: CString -> Ptr CString -> Ptr CString -> IO CInt
- runInteractiveProcess_lock :: MVar ()
- ignoreSignal :: CLong
- defaultSignal :: CLong
- withFilePathException :: FilePath -> IO a -> IO a
- withCEnvironment :: [(String, String)] -> (Ptr CString -> IO a) -> IO a
- translate :: String -> String
- createPipe :: IO (Handle, Handle)
- createPipeFd :: IO (FD, FD)
- interruptProcessGroupOf :: ProcessHandle -> IO ()
- withForkWait :: IO () -> (IO () -> IO a) -> IO a
- ignoreSigPipe :: IO () -> IO ()
Documentation
data ProcessHandle Source #
A handle to a process, which can be used to wait for termination
of the process using waitForProcess .
None of the process-creation functions in this library wait for
termination: they all return a ProcessHandle which may be used
to wait for the process later.
On Windows a second wait method can be used to block for event completion. This requires two handles. A process job handle and a events handle to monitor.
Constructors
Fields
- phandle :: !(MVar ProcessHandle__)
- mb_delegate_ctlc :: !Bool
- waitpidLock :: !(MVar ())
data ProcessHandle__ Source #
Constructors
Fields
- phdlProcessHandle :: PHANDLE
the process
OpenExtHandle is only applicable for
Windows platform. It represents Job
Objects.
Fields
- phdlProcessHandle :: PHANDLE
the process
- phdlJobHandle :: PHANDLE
the job containing the process and its subprocesses
closePHANDLE :: PHANDLE -> IO () Source #
mkProcessHandle :: PHANDLE -> Bool -> IO ProcessHandle Source #
Instances
Instances details
Instance details
Defined in System.Posix.Types
Methods
(.&.) :: CGid -> CGid -> CGid #
(.|.) :: CGid -> CGid -> CGid #
complement :: CGid -> CGid #
shift :: CGid -> Int -> CGid #
rotate :: CGid -> Int -> CGid #
setBit :: CGid -> Int -> CGid #
clearBit :: CGid -> Int -> CGid #
complementBit :: CGid -> Int -> CGid #
testBit :: CGid -> Int -> Bool #
bitSizeMaybe :: CGid -> Maybe Int #
shiftL :: CGid -> Int -> CGid #
unsafeShiftL :: CGid -> Int -> CGid #
shiftR :: CGid -> Int -> CGid #
unsafeShiftR :: CGid -> Int -> CGid #
rotateL :: CGid -> Int -> CGid #
Instance details
Defined in System.Posix.Types
Methods
finiteBitSize :: CGid -> Int #
countLeadingZeros :: CGid -> Int #
countTrailingZeros :: CGid -> Int #
Instance details
Defined in System.Posix.Types
modifyProcessHandle :: ProcessHandle -> (ProcessHandle__ -> IO (ProcessHandle__, a)) -> IO a Source #
withProcessHandle :: ProcessHandle -> (ProcessHandle__ -> IO a) -> IO a Source #
data CreateProcess Source #
Constructors
Fields
- cmdspec :: CmdSpec
Executable & arguments, or shell command. If
cwdisNothing, relative paths are resolved with respect to the current working directory. Ifcwdis provided, it is implementation-dependent whether relative paths are resolved with respect tocwdor the current working directory, so absolute paths should be used to ensure portability. - cwd :: Maybe FilePath
Optional path to the working directory for the new process
- env :: Maybe [(String, String)]
Optional environment (otherwise inherit from the current process)
- std_in :: StdStream
How to determine stdin
- std_out :: StdStream
How to determine stdout
- std_err :: StdStream
How to determine stderr XXX verify what happens with fds in nodejs child processes
- close_fds :: Bool
Close all file descriptors except stdin, stdout and stderr in the new process (on Windows, only works if std_in, std_out, and std_err are all Inherit). This implementation will call close on every fd from 3 to the maximum of open files, which can be slow for high maximum of open files.
- create_group :: Bool
Create a new process group. On JavaScript this also creates a new session.
- delegate_ctlc :: Bool
Delegate control-C handling. Use this for interactive console processes to let them handle control-C themselves (see below for details).
Since: 1.2.0.0
- detach_console :: Bool
Use the windows DETACHED_PROCESS flag when creating the process; does nothing on other platforms.
Since: 1.3.0.0
- create_new_console :: Bool
Use the windows CREATE_NEW_CONSOLE flag when creating the process; does nothing on other platforms.
Default:
FalseSince: 1.3.0.0
- new_session :: Bool
Use posix setsid to start the new process in a new session; starts process in a new session on JavaScript; does nothing on other platforms.
Since: 1.3.0.0
- child_group :: Maybe GroupID
Use posix setgid to set child process's group id; works for JavaScript when system running nodejs is posix. does nothing on other platforms.
Default:
NothingSince: 1.4.0.0
- child_user :: Maybe UserID
Use posix setuid to set child process's user id; works for JavaScript when system running nodejs is posix. does nothing on other platforms.
Default:
NothingSince: 1.4.0.0
- use_process_jobs :: Bool
On Windows systems this flag indicates that we should wait for the entire process tree to finish before unblocking. On POSIX systems this flag is ignored. See $exec-on-windows for details.
Default:
FalseSince: 1.5.0.0
Instances
Instances details
Instance details
Defined in System.Process.Common
Methods
showsPrec :: Int -> CreateProcess -> ShowS #
show :: CreateProcess -> String #
showList :: [CreateProcess] -> ShowS #
Instance details
Defined in System.Process.Common
Methods
(==) :: CreateProcess -> CreateProcess -> Bool #
(/=) :: CreateProcess -> CreateProcess -> Bool #
Constructors
The name of an executable with a list of arguments
The FilePath argument names the executable, and is interpreted
according to the platform's standard policy for searching for
executables. Specifically:
- on Unix systems the
execvp(3)
semantics is used, where if the executable filename does not
contain a slash (
/) then thePATHenvironment variable is searched for the executable. - on Windows systems the Win32
CreateProcesssemantics is used. Briefly: if the filename does not contain a path, then the directory containing the parent executable is searched, followed by the current directory, then some standard locations, and finally the currentPATH. An.exeextension is added if the filename does not already have an extension. For full details see the documentation for the WindowsSearchPathAPI.
Windows does not have a mechanism for passing multiple arguments.
When using RawCommand on Windows, the command line is serialised
into a string, with arguments quoted separately. Command line
parsing is up individual programs, so the default behaviour may
not work for some programs. If you are not getting the desired
results, construct the command line yourself and use ShellCommand .
Instances
Instances details
Constructors
Inherit Handle from parent
Create a new pipe. The returned
Handle will use the default encoding
and newline translation mode (just
like Handles created by openFile).
Close the stream's file descriptor without
passing a Handle. On POSIX systems this may
lead to strange behavior in the child process
because attempting to read or write after the
file has been closed throws an error. This
should only be used with child processes that
don't use the file descriptor at all. If you
wish to ignore the child process's output you
should either create a pipe and drain it
manually or pass a Handle that writes to
/dev/null.
Instances
Instances details
data ProcRetHandles Source #
contains the handles returned by a call to createProcess_Internal
Constructors
Fields
- hStdInput :: Maybe Handle
- hStdOutput :: Maybe Handle
- hStdError :: Maybe Handle
- procHandle :: ProcessHandle
Arguments
Function name (for error messages).
This can be any String , but will typically be the name of the caller.
E.g., spawnProcess passes "spawnProcess" here when calling
createProcess_ .
This function is almost identical to
createProcess . The only differences are:
Handles provided viaUseHandleare not closed automatically.- This function takes an extra
Stringargument to be used in creating error messages.
This function has been available from the System.Process.Internals module for some time, and is part of the System.Process module since version 1.2.1.0.
Since: 1.2.1.0
Arguments
function name (for error messages)
Deprecated: Please do not use this anymore, use the ordinary createProcess . If you need the SIGINT handling, use delegate_ctlc = True (runGenProcess_ is now just an imperfectly emulated stub that probably duplicates or overrides your own signal handling).
fdToHandle :: FD -> IO Handle #
Turn an existing file descriptor into a Handle. This is used by various external libraries to make Handles.
Makes a binary Handle. This is for historical reasons; it should probably be a text Handle with the default encoding and newline translation instead.
startDelegateControlC :: IO () Source #
endDelegateControlC :: ExitCode -> IO () Source #
stopDelegateControlC :: IO () Source #
unwrapHandles :: ProcRetHandles -> (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle) Source #
pPrPr_disableITimers :: IO () #
runInteractiveProcess_lock :: MVar () Source #
runInteractiveProcess blocks signals around the fork().
Since blocking/unblocking of signals is a global state operation, we need to
ensure mutual exclusion of calls to runInteractiveProcess.
This lock is exported so that other libraries which also need to fork()
(and also need to make the same global state changes) can protect their changes
with the same lock.
See https://github.com/haskell/process/pull/154.
Since: 1.6.6.0
ignoreSignal :: CLong Source #
createPipe :: IO (Handle, Handle) Source #
Create a pipe for interprocess communication and return a
(readEnd, writeEnd) Handle pair.
- WinIO Support
When this function is used with WinIO enabled it's the caller's responsibility to register the handles with the I/O manager. If this is not done the operation will deadlock. Association can be done as follows:
#if defined(IO_MANAGER_WINIO)
import GHC.IO.SubSystem ((<!>))
import GHC.IO.Handle.Windows (handleToHANDLE)
import GHC.Event.Windows (associateHandle')
#endif
...
#if defined(IO_MANAGER_WINIO)
return () <!> do
associateHandle' =<< handleToHANDLE readEnd
#endif
Only associate handles that you are in charge of read/writing to. Do not associate handles passed to another process. It's the process's responsibility to register the handle if it supports async access.
Since: 1.2.1.0
createPipeFd :: IO (FD, FD) Source #
Create a pipe for interprocess communication and return a
(readEnd, writeEnd) FD pair.
Since: 1.4.2.0
interruptProcessGroupOf Source #
Sends an interrupt signal to the process group of the given process.
On Unix systems, it sends the group the SIGINT signal.
On Windows systems, it generates a CTRL_BREAK_EVENT and will only work for
processes created using createProcess and setting the create_group flag
withForkWait :: IO () -> (IO () -> IO a) -> IO a Source #
Fork a thread while doing something else, but kill it if there's an exception.
This is important in the cases above because we want to kill the thread that is holding the Handle lock, because when we clean up the process we try to close that handle, which could otherwise deadlock.
Since: 1.6.20.0
ignoreSigPipe :: IO () -> IO () Source #
Handle any SIGPIPE errors in the given computation.
Since: 1.6.20.0