| Copyright | (c) The University of Glasgow 2002 | 
|---|---|
| License | BSD-style (see the file libraries/base/LICENSE) | 
| Maintainer | libraries@haskell.org | 
| Stability | provisional | 
| Portability | non-portable (requires POSIX) | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
System.Posix.Process.PosixString
Description
POSIX process support. See also the System.Cmd and System.Process modules in the process package.
Synopsis
- forkProcess :: IO () -> IO ProcessID
- forkProcessWithUnmask :: ((forall a. IO a -> IO a) -> IO ()) -> IO ProcessID
- executeFile :: PosixPath -> Bool -> [PosixString] -> Maybe [(PosixString, PosixString)] -> IO a
- exitImmediately :: ExitCode -> IO a
- getProcessID :: IO ProcessID
- getParentProcessID :: IO ProcessID
- getProcessGroupID :: IO ProcessGroupID
- getProcessGroupIDOf :: ProcessID -> IO ProcessGroupID
- createProcessGroupFor :: ProcessID -> IO ProcessGroupID
- joinProcessGroup :: ProcessGroupID -> IO ()
- setProcessGroupIDOf :: ProcessID -> ProcessGroupID -> IO ()
- createSession :: IO ProcessGroupID
- data ProcessTimes = ProcessTimes {}
- getProcessTimes :: IO ProcessTimes
- nice :: Int -> IO ()
- getProcessPriority :: ProcessID -> IO Int
- getProcessGroupPriority :: ProcessGroupID -> IO Int
- getUserPriority :: UserID -> IO Int
- setProcessPriority :: ProcessID -> Int -> IO ()
- setProcessGroupPriority :: ProcessGroupID -> Int -> IO ()
- setUserPriority :: UserID -> Int -> IO ()
- data ProcessStatus
- getProcessStatus :: Bool -> Bool -> ProcessID -> IO (Maybe ProcessStatus)
- getAnyProcessStatus :: Bool -> Bool -> IO (Maybe (ProcessID, ProcessStatus))
- getGroupProcessStatus :: Bool -> Bool -> ProcessGroupID -> IO (Maybe (ProcessID, ProcessStatus))
- createProcessGroup :: ProcessID -> IO ProcessGroupID
- setProcessGroupID :: ProcessID -> ProcessGroupID -> IO ()
Processes
Forking and executing
forkProcess :: IO () -> IO ProcessID Source #
forkProcess corresponds to the POSIX fork system call.
The IO action passed as an argument is executed in the child process; no other
threads will be copied to the child process.
On success, forkProcess returns the child's ProcessID to the parent process;
in case of an error, an exception is thrown.
The exception masking state of the executed action is inherited
(c.f. forkIO), see also forkProcessWithUnmask (since: 2.7.0.0).
forkProcess comes with a giant warning: since any other running
threads are not copied into the child process, it's easy to go wrong:
e.g. by accessing some shared resource that was held by another thread
in the parent.
GHC note: forkProcess is not currently very well supported when using multiple
capabilities (+RTS -N), although it is supported with -threaded as
long as only one capability is being used.
forkProcessWithUnmask :: ((forall a. IO a -> IO a) -> IO ()) -> IO ProcessID Source #
Variant of forkProcess in the style of forkIOWithUnmask.
Since: 2.7.0.0
Arguments
| :: PosixPath | Command | 
| -> Bool | Search PATH? | 
| -> [PosixString] | Arguments | 
| -> Maybe [(PosixString, PosixString)] | Environment | 
| -> IO a | 
executeFile cmd args envexecv* family, depending on whether or not the current
   PATH is to be searched for the command, and whether or not an
   environment is provided to supersede the process's current
   environment.  The basename (leading directory names suppressed) of
   the command is passed to execv* as arg[0];
   the argument list passed to executeFile therefore
   begins with arg[1].
Exiting
exitImmediately :: ExitCode -> IO a Source #
exitImmediately status_exit to terminate the process
   with the indicated exit status.
   The operation never returns. Since it does not use the Haskell exception
   system and it cannot be caught.
Note: Prior to unix-2.8.0.0 the type-signature of exitImmediately was
   ExitCode -> IO ().
Since: 2.8.0.0
Process environment
getProcessID :: IO ProcessID Source #
getProcessID calls getpid to obtain the ProcessID for
   the current process.
getParentProcessID :: IO ProcessID Source #
getParentProcessID calls getppid to obtain the ProcessID for
   the parent of the current process.
Process groups
getProcessGroupID :: IO ProcessGroupID Source #
getProcessGroupID calls getpgrp to obtain the
   ProcessGroupID for the current process.
getProcessGroupIDOf :: ProcessID -> IO ProcessGroupID Source #
getProcessGroupIDOf pidgetpgid to obtain the
   ProcessGroupID for process pid.
createProcessGroupFor :: ProcessID -> IO ProcessGroupID Source #
createProcessGroupFor pidsetpgid to make
   process pid a new process group leader.
joinProcessGroup :: ProcessGroupID -> IO () Source #
joinProcessGroup pgidsetpgid to set the
   ProcessGroupID of the current process to pgid.
setProcessGroupIDOf :: ProcessID -> ProcessGroupID -> IO () Source #
setProcessGroupIDOf pid pgidsetpgid to set the
   ProcessGroupIDOf for process pid to pgid.
Sessions
createSession :: IO ProcessGroupID Source #
createSession calls setsid to create a new session
   with the current process as session leader.
Process times
data ProcessTimes Source #
Constructors
| ProcessTimes | |
| Fields | |
getProcessTimes :: IO ProcessTimes Source #
getProcessTimes calls times to obtain time-accounting
   information for the current process and its children.
Scheduling priority
setProcessGroupPriority :: ProcessGroupID -> Int -> IO () Source #
Process status
data ProcessStatus Source #
The exit status of a process
Constructors
| Exited ExitCode | the process exited by calling
  | 
| Terminated Signal Bool | the process was terminated by a
 signal, the  Since: 2.7.0.0 | 
| Stopped Signal | the process was stopped by a signal | 
Instances
| Show ProcessStatus Source # | |
| Defined in System.Posix.Process.Internals Methods showsPrec :: Int -> ProcessStatus -> ShowS # show :: ProcessStatus -> String # showList :: [ProcessStatus] -> ShowS # | |
| Eq ProcessStatus Source # | |
| Defined in System.Posix.Process.Internals Methods (==) :: ProcessStatus -> ProcessStatus -> Bool # (/=) :: ProcessStatus -> ProcessStatus -> Bool # | |
| Ord ProcessStatus Source # | |
| Defined in System.Posix.Process.Internals Methods compare :: ProcessStatus -> ProcessStatus -> Ordering # (<) :: ProcessStatus -> ProcessStatus -> Bool # (<=) :: ProcessStatus -> ProcessStatus -> Bool # (>) :: ProcessStatus -> ProcessStatus -> Bool # (>=) :: ProcessStatus -> ProcessStatus -> Bool # max :: ProcessStatus -> ProcessStatus -> ProcessStatus # min :: ProcessStatus -> ProcessStatus -> ProcessStatus # | |
getProcessStatus :: Bool -> Bool -> ProcessID -> IO (Maybe ProcessStatus) Source #
getProcessStatus blk stopped pidwaitpid, returning
   Just tcProcessStatus for process pid if it is
   available, Nothing otherwise.  If blk is False, then
   WNOHANG is set in the options for waitpid, otherwise not.
   If stopped is True, then WUNTRACED is set in the
   options for waitpid, otherwise not.
getAnyProcessStatus :: Bool -> Bool -> IO (Maybe (ProcessID, ProcessStatus)) Source #
getAnyProcessStatus blk stoppedwaitpid, returning
   Just (pid, tc)ProcessID and ProcessStatus for any
   child process if a child process has exited, or Nothing if
   there are child processes but none have exited.  If there are no
   child processes, then getAnyProcessStatus raises an
   isDoesNotExistError exception.
If blk is False, then WNOHANG is set in the options for
   waitpid, otherwise not.  If stopped is True, then
   WUNTRACED is set in the options for waitpid, otherwise not.
getGroupProcessStatus :: Bool -> Bool -> ProcessGroupID -> IO (Maybe (ProcessID, ProcessStatus)) Source #
getGroupProcessStatus blk stopped pgidwaitpid,
   returning Just (pid, tc)ProcessID and ProcessStatus
   for any process in group pgid if one is available, or Nothing
   if there are child processes but none have exited.  If there are
   no child processes, then getGroupProcessStatus raises an
   isDoesNotExistError exception.
If blk is False, then WNOHANG is set in the options for
   waitpid, otherwise not.  If stopped is True, then
   WUNTRACED is set in the options for waitpid, otherwise not.
Deprecated
createProcessGroup :: ProcessID -> IO ProcessGroupID Source #
Deprecated: This function is scheduled to be replaced by something different in the future, we therefore recommend that you do not use this version and use createProcessGroupFor instead.
createProcessGroup pidsetpgid to make
   process pid a new process group leader.
   This function is currently deprecated,
   and might be changed to making the current
   process a new process group leader in future versions.
setProcessGroupID :: ProcessID -> ProcessGroupID -> IO () Source #
Deprecated: This function is scheduled to be replaced by something different in the future, we therefore recommend that you do not use this version and use setProcessGroupIDOf instead.
setProcessGroupID pid pgidsetpgid to set the
   ProcessGroupID for process pid to pgid.
   This function is currently deprecated,
   and might be changed to setting the ProcessGroupID
   for the current process in future versions.