[commit: packages/process] master: Rename runGenProcess_ and leave a deprecated stub (3d8f9bb)

git at git.haskell.org git at git.haskell.org
Wed Nov 20 21:09:03 UTC 2013


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

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

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

commit 3d8f9bb7f84c1fbb5efa62dd46daae44110ddb18
Author: Duncan Coutts <duncan at well-typed.com>
Date:   Fri Nov 15 14:19:48 2013 +0000

    Rename runGenProcess_ and leave a deprecated stub
    
    At least Cabal was using runGenProcess_, and the previous patches
    addressing #2301 changed its type already. So this adds a deprecated
    stub with the original type and the real function gets to have a less
    odd name.
    
    Authored-by: Duncan Coutts <duncan at well-typed.com>
    Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org>


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

3d8f9bb7f84c1fbb5efa62dd46daae44110ddb18
 System/Process.hs           |   12 ++++++------
 System/Process/Internals.hs |   27 +++++++++++++++++++++++----
 2 files changed, 29 insertions(+), 10 deletions(-)

diff --git a/System/Process.hs b/System/Process.hs
index ce36ccd..224074f 100644
--- a/System/Process.hs
+++ b/System/Process.hs
@@ -116,7 +116,7 @@ runCommand
   -> IO ProcessHandle
 
 runCommand string = do
-  (_,_,_,ph) <- runGenProcess_ "runCommand" (shell string)
+  (_,_,_,ph) <- createProcess_ "runCommand" (shell string)
   return ph
 
 -- ----------------------------------------------------------------------------
@@ -145,7 +145,7 @@ runProcess
 
 runProcess cmd args mb_cwd mb_env mb_stdin mb_stdout mb_stderr = do
   (_,_,_,ph) <-
-      runGenProcess_ "runProcess"
+      createProcess_ "runProcess"
          (proc cmd args){ cwd = mb_cwd,
                           env = mb_env,
                           std_in  = mbToStd mb_stdin,
@@ -255,7 +255,7 @@ createProcess
   :: CreateProcess
   -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
 createProcess cp = do
-  r <- runGenProcess_ "createProcess" cp
+  r <- createProcess_ "createProcess" cp
   maybeCloseStd (std_in  cp)
   maybeCloseStd (std_out cp)
   maybeCloseStd (std_err cp)
@@ -356,7 +356,7 @@ runInteractiveProcess1
   -> IO (Handle,Handle,Handle,ProcessHandle)
 runInteractiveProcess1 fun cmd = do
   (mb_in, mb_out, mb_err, p) <-
-      runGenProcess_ fun
+      createProcess_ fun
            cmd{ std_in  = CreatePipe,
                 std_out = CreatePipe,
                 std_err = CreatePipe }
@@ -582,7 +582,7 @@ when the process died as the result of a signal.
 system :: String -> IO ExitCode
 system "" = ioException (ioeSetErrorString (mkIOError InvalidArgument "system" Nothing Nothing) "null command")
 system str = do
-  (_,_,_,p) <- runGenProcess_ "system" (shell str) { delegate_ctlc = True }
+  (_,_,_,p) <- createProcess_ "system" (shell str) { delegate_ctlc = True }
   waitForProcess p
 #endif  /* __GLASGOW_HASKELL__ */
 
@@ -597,7 +597,7 @@ The return codes and possible failures are the same as for 'system'.
 rawSystem :: String -> [String] -> IO ExitCode
 #ifdef __GLASGOW_HASKELL__
 rawSystem cmd args = do
-  (_,_,_,p) <- runGenProcess_ "rawSystem" (proc cmd args) { delegate_ctlc = True }
+  (_,_,_,p) <- createProcess_ "rawSystem" (proc cmd args) { delegate_ctlc = True }
   waitForProcess p
 #elif !mingw32_HOST_OS
 -- crude fallback implementation: could do much better than this under Unix
diff --git a/System/Process/Internals.hs b/System/Process/Internals.hs
index daceed7..54a7d06 100644
--- a/System/Process/Internals.hs
+++ b/System/Process/Internals.hs
@@ -26,7 +26,8 @@ module System.Process.Internals (
 #ifdef __GLASGOW_HASKELL__
         CreateProcess(..),
         CmdSpec(..), StdStream(..),
-        runGenProcess_,
+        createProcess_,
+        runGenProcess_, --deprecated
 #endif
         startDelegateControlC,
         endDelegateControlC,
@@ -193,7 +194,7 @@ data StdStream
                              -- and newline translation mode (just
                              -- like @Handle at s created by @openFile@).
 
-runGenProcess_
+createProcess_
   :: String                     -- ^ function name (for error messages)
   -> CreateProcess
   -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
@@ -205,7 +206,7 @@ runGenProcess_
 -- -----------------------------------------------------------------------------
 -- POSIX runProcess with signal handling in the child
 
-runGenProcess_ fun CreateProcess{ cmdspec = cmdsp,
+createProcess_ fun CreateProcess{ cmdspec = cmdsp,
                                   cwd = mb_cwd,
                                   env = mb_env,
                                   std_in = mb_stdin,
@@ -364,7 +365,7 @@ defaultSignal = CONST_SIG_DFL
 
 #ifdef __GLASGOW_HASKELL__
 
-runGenProcess_ fun CreateProcess{ cmdspec = cmdsp,
+createProcess_ fun CreateProcess{ cmdspec = cmdsp,
                                   cwd = mb_cwd,
                                   env = mb_env,
                                   std_in = mb_stdin,
@@ -659,3 +660,21 @@ withCEnvironment envir act =
   let env' = foldr (\(name, val) env -> name ++ ('=':val)++'\0':env) "\0" envir
   in withCWString env' (act . castPtr)
 #endif
+
+
+-- ----------------------------------------------------------------------------
+-- Deprecated / compat
+
+#ifdef __GLASGOW_HASKELL__
+{-# DEPRECATED runGenProcess_
+      "Please do not use this anymore, use the ordinary 'System.Process.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)." #-}
+runGenProcess_
+ :: String                     -- ^ function name (for error messages)
+ -> CreateProcess
+ -> Maybe CLong                -- ^ handler for SIGINT
+ -> Maybe CLong                -- ^ handler for SIGQUIT
+ -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
+runGenProcess_ fun c (Just sig) (Just sig') | sig == defaultSignal && sig == sig'
+                         = createProcess_ fun c { delegate_ctlc = True }
+runGenProcess_ fun c _ _ = createProcess_ fun c
+#endif



More information about the ghc-commits mailing list