[commit: packages/process] master: Added child_user and child_group to CreateProcess for unix. (bc4e5e6)

git at git.haskell.org git at git.haskell.org
Mon Nov 2 06:24:15 UTC 2015


Repository : ssh://git@git.haskell.org/process

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/bc4e5e6c2ec3d23020d977117a70717f543674e8/process

>---------------------------------------------------------------

commit bc4e5e6c2ec3d23020d977117a70717f543674e8
Author: jprider63 <jp at jamesparker.me>
Date:   Tue Oct 13 22:43:21 2015 -0400

    Added child_user and child_group to CreateProcess for unix.


>---------------------------------------------------------------

bc4e5e6c2ec3d23020d977117a70717f543674e8
 System/Process.hsc          |  8 ++++++--
 System/Process/Internals.hs | 21 +++++++++++++++++++--
 cbits/runProcess.c          | 24 ++++++++++++++++++++++++
 include/runProcess.h        |  2 ++
 4 files changed, 51 insertions(+), 4 deletions(-)

diff --git a/System/Process.hsc b/System/Process.hsc
index 4de9a26..a390c74 100644
--- a/System/Process.hsc
+++ b/System/Process.hsc
@@ -126,7 +126,9 @@ proc cmd args = CreateProcess { cmdspec = RawCommand cmd args,
                                 delegate_ctlc = False,
                                 detach_console = False,
                                 create_new_console = False,
-                                new_session = False }
+                                new_session = False,
+                                child_group = Nothing,
+                                child_user = Nothing }
 
 -- | Construct a 'CreateProcess' record for passing to 'createProcess',
 -- representing a command to be passed to the shell.
@@ -142,7 +144,9 @@ shell str = CreateProcess { cmdspec = ShellCommand str,
                             delegate_ctlc = False,
                             detach_console = False,
                             create_new_console = False,
-                            new_session = False }
+                            new_session = False,
+                            child_group = Nothing,
+                            child_user = Nothing }
 
 {- |
 This is the most general way to spawn an external process.  The
diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs
index 40f2f92..7d65546 100644
--- a/System/Process/Internals.hs
+++ b/System/Process/Internals.hs
@@ -190,9 +190,19 @@ data CreateProcess = CreateProcess{
                                            --   Default: @False@
                                            --
                                            --   @since 1.3.0.0
-  new_session :: Bool                      -- ^ Use posix setsid to start the new process in a new session; does nothing on other platforms.
+  new_session :: Bool,                     -- ^ Use posix setsid to start the new process in a new session; does nothing on other platforms.
                                            --
                                            --   @since 1.3.0.0
+  child_group :: Maybe GroupID,            -- ^ Use posix setgid to set child process's group id; does nothing on other platforms.
+                                           --
+                                           --   Default: @Nothing@
+                                           --
+                                           --   @since X.X.X.X
+  child_user :: Maybe UserID               -- ^ Use posix setuid to set child process's user id; does nothing on other platforms.
+                                           --
+                                           --   Default: @Nothing@
+                                           --
+                                           --   @since X.X.X.X
  }
 
 data CmdSpec
@@ -273,7 +283,9 @@ createProcess_ fun CreateProcess{ cmdspec = cmdsp,
                                   delegate_ctlc = mb_delegate_ctlc,
                                   detach_console = mb_detach_console,
                                   create_new_console = mb_create_new_console,
-                                  new_session = mb_new_session }
+                                  new_session = mb_new_session,
+                                  child_group = mb_child_group,
+                                  child_user = mb_child_user }
  = do
   let (cmd,args) = commandToProcess cmdsp
   withFilePathException cmd $
@@ -283,6 +295,8 @@ createProcess_ fun CreateProcess{ cmdspec = cmdsp,
    alloca $ \ pFailedDoing ->
    maybeWith withCEnvironment mb_env $ \pEnv ->
    maybeWith withFilePath mb_cwd $ \pWorkDir ->
+   maybeWith with mb_child_group $ \pChildGroup ->
+   maybeWith with mb_child_user $ \pChildUser ->
    withMany withFilePath (cmd:args) $ \cstrs ->
    withArray0 nullPtr cstrs $ \pargs -> do
 
@@ -301,6 +315,7 @@ createProcess_ fun CreateProcess{ cmdspec = cmdsp,
                          c_runInteractiveProcess pargs pWorkDir pEnv
                                 fdin fdout fderr
                                 pfdStdInput pfdStdOutput pfdStdError
+                                pChildGroup pChildUser
                                 (if mb_delegate_ctlc then 1 else 0)
                                 ((if mb_close_fds then RUN_PROCESS_IN_CLOSE_FDS else 0)
                                 .|.(if mb_create_group then RUN_PROCESS_IN_NEW_GROUP else 0)
@@ -414,6 +429,8 @@ foreign import ccall unsafe "runInteractiveProcess"
         -> Ptr FD
         -> Ptr FD
         -> Ptr FD
+        -> Ptr CGid
+        -> Ptr CUid
         -> CInt                         -- reset child's SIGINT & SIGQUIT handlers
         -> CInt                         -- flags
         -> Ptr CString
diff --git a/cbits/runProcess.c b/cbits/runProcess.c
index 8019605..950635d 100644
--- a/cbits/runProcess.c
+++ b/cbits/runProcess.c
@@ -40,6 +40,10 @@ extern void unblockUserSignals(void);
 #define forkChdirFailed 126
 #define forkExecFailed  127
 
+// These are arbitrarily chosen -- JP
+#define forkSetgidFailed 124
+#define forkSetuidFailed 125
+
 __attribute__((__noreturn__))
 static void childFailed(int pipe, int failCode) {
     int err;
@@ -57,6 +61,7 @@ runInteractiveProcess (char *const args[],
                        char *workingDirectory, char **environment,
                        int fdStdIn, int fdStdOut, int fdStdErr,
                        int *pfdStdInput, int *pfdStdOutput, int *pfdStdError,
+                       gid_t *childGroup, uid_t *childUser,
                        int reset_int_quit_handlers,
                        int flags,
                        char **failed_doing)
@@ -145,6 +150,20 @@ runInteractiveProcess (char *const args[],
             setpgid(0, 0);
         }
         
+        if ( childGroup) {
+            if ( setgid( *childGroup) != 0) {
+                // ERROR
+                childFailed(forkCommunicationFds[1], forkSetgidFailed);
+            }
+        }
+
+        if ( childUser) {
+            if ( setuid( *childUser) != 0) {
+                // ERROR
+                childFailed(forkCommunicationFds[1], forkSetuidFailed);
+            }
+        }
+
         unblockUserSignals();
 
         if (workingDirectory) {
@@ -281,6 +300,11 @@ runInteractiveProcess (char *const args[],
         case forkExecFailed:
             *failed_doing = "runInteractiveProcess: exec";
             break;
+        case forkSetgidFailed:
+            *failed_doing = "runInteractiveProcess: setgid";
+            break;
+        case forkSetuidFailed:
+            *failed_doing = "runInteractiveProcess: setuid";
         default:
             *failed_doing = "runInteractiveProcess: unknown";
             break;
diff --git a/include/runProcess.h b/include/runProcess.h
index 63f1f23..d35e3e4 100644
--- a/include/runProcess.h
+++ b/include/runProcess.h
@@ -62,6 +62,8 @@ extern ProcHandle runInteractiveProcess( char *const args[],
                                          int *pfdStdInput, 
                                          int *pfdStdOutput, 
                                          int *pfdStdError,
+                                         gid_t *childGroup,
+                                         uid_t *childUser,
                                          int reset_int_quit_handlers,
                                          int flags,
                                          char **failed_doing);



More information about the ghc-commits mailing list