Skip to content

Commit 5aac988

Browse files
committed
Add Distribution.Compat.Process module
1 parent 6e88f4a commit 5aac988

File tree

5 files changed

+90
-56
lines changed

5 files changed

+90
-56
lines changed

Cabal/Cabal.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -334,6 +334,7 @@ library
334334
Distribution.Compat.Newtype
335335
Distribution.Compat.ResponseFile
336336
Distribution.Compat.Prelude.Internal
337+
Distribution.Compat.Process
337338
Distribution.Compat.Semigroup
338339
Distribution.Compat.Stack
339340
Distribution.Compat.Time

Cabal/ChangeLog.md

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@
1919
* Add `unsnoc` and `unsnocNE` to `Distribution.Utils.Generic`
2020
* Add `Set'` modifier to `Distribution.Parsec.Newtypes`
2121
* Add `Distribution.Compat.Async`
22+
* Add `Distribution.Compat.Process` with `enableProcessJobs`
2223

2324
# 3.0.1.0 TBW
2425
* Add GHC-8.8 flags to normaliseGhcFlags

Cabal/Distribution/Compat/Process.hs

Lines changed: 82 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,82 @@
1+
{-# LANGUAGE CPP #-}
2+
module Distribution.Compat.Process (
3+
-- * Redefined functions
4+
createProcess,
5+
runInteractiveProcess,
6+
rawSystem,
7+
-- * Additions
8+
enableProcessJobs,
9+
) where
10+
11+
import System.Exit (ExitCode (..))
12+
import System.IO (Handle)
13+
14+
import System.Process (CreateProcess, ProcessHandle)
15+
import qualified System.Process as Process
16+
17+
#if MIN_VERSION_process(1,2,0)
18+
import System.Process (waitForProcess)
19+
#endif
20+
21+
-------------------------------------------------------------------------------
22+
-- enableProcessJobs
23+
-------------------------------------------------------------------------------
24+
25+
-- | Enable process jobs to ensure accurate determination of process completion
26+
-- in the presence of @exec(3)@ on Windows.
27+
--
28+
-- Unfortunately the process job support is badly broken in @process@ releases
29+
-- prior to 1.6.8, so we disable it in these versions, despite the fact that
30+
-- this means we may see sporatic build failures without jobs.
31+
enableProcessJobs :: CreateProcess -> CreateProcess
32+
#ifdef MIN_VERSION_process
33+
#if MIN_VERSION_process(1,6,8)
34+
enableProcessJobs cp = cp {Process.use_process_jobs = True}
35+
#else
36+
enableProcessJobs cp = cp
37+
#endif
38+
#else
39+
enableProcessJobs cp = cp
40+
#endif
41+
42+
-------------------------------------------------------------------------------
43+
-- process redefinitions
44+
-------------------------------------------------------------------------------
45+
46+
-- | 'System.Process.createProcess' with process jobs enabled when appropriate.
47+
-- See 'enableProcessJobs'.
48+
createProcess :: CreateProcess
49+
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
50+
createProcess = Process.createProcess . enableProcessJobs
51+
52+
-- | 'System.Process.rawSystem' with process jobs enabled when appropriate.
53+
-- See 'enableProcessJobs'.
54+
rawSystem :: String -> [String] -> IO ExitCode
55+
rawSystem cmd args = do
56+
#if MIN_VERSION_process(1,2,0)
57+
(_,_,_,p) <- createProcess (Process.proc cmd args) { Process.delegate_ctlc = True }
58+
waitForProcess p
59+
#else
60+
-- With very old 'process', just do its rawSystem
61+
Process.rawSystem cmd args
62+
#endif
63+
64+
-- | 'System.Process.runInteractiveProcess' with process jobs enabled when
65+
-- appropriate. See 'enableProcessJobs'.
66+
runInteractiveProcess
67+
:: FilePath -- ^ Filename of the executable (see 'RawCommand' for details)
68+
-> [String] -- ^ Arguments to pass to the executable
69+
-> Maybe FilePath -- ^ Optional path to the working directory
70+
-> Maybe [(String,String)] -- ^ Optional environment (otherwise inherit)
71+
-> IO (Handle,Handle,Handle,ProcessHandle)
72+
runInteractiveProcess cmd args mb_cwd mb_env = do
73+
(mb_in, mb_out, mb_err, p) <-
74+
createProcess (Process.proc cmd args)
75+
{ Process.std_in = Process.CreatePipe,
76+
Process.std_out = Process.CreatePipe,
77+
Process.std_err = Process.CreatePipe,
78+
Process.env = mb_env,
79+
Process.cwd = mb_cwd }
80+
return (fromJust mb_in, fromJust mb_out, fromJust mb_err, p)
81+
where
82+
fromJust = maybe (error "runInteractiveProcess: fromJust") id

Cabal/Distribution/Simple/Utils.hs

Lines changed: 3 additions & 55 deletions
Original file line numberDiff line numberDiff line change
@@ -230,15 +230,14 @@ import System.IO.Unsafe
230230
import qualified Control.Exception as Exception
231231

232232
import Foreign.C.Error (Errno (..), ePIPE)
233-
import Data.Maybe (fromJust)
234233
import Data.Time.Clock.POSIX (getPOSIXTime, POSIXTime)
235234
import Control.Exception (IOException, evaluate, throwIO, fromException)
236235
import Numeric (showFFloat)
237-
import qualified System.Process as Process
236+
import Distribution.Compat.Process (createProcess, rawSystem, runInteractiveProcess)
238237
import System.Process
239-
( CreateProcess, ProcessHandle
238+
( ProcessHandle
240239
, showCommandForUser, waitForProcess)
241-
240+
import qualified System.Process as Process
242241
import qualified GHC.IO.Exception as GHC
243242

244243
import qualified Text.PrettyPrint as Disp
@@ -680,58 +679,7 @@ maybeExit cmd = do
680679
res <- cmd
681680
unless (res == ExitSuccess) $ exitWith res
682681

683-
-- | Enable process jobs to ensure accurate determination of process completion
684-
-- in the presence of @exec(3)@ on Windows.
685-
--
686-
-- Unfortunately the process job support is badly broken in @process@ releases
687-
-- prior to 1.6.8, so we disable it in these versions, despite the fact that
688-
-- this means we may see sporatic build failures without jobs.
689-
enableProcessJobs :: CreateProcess -> CreateProcess
690-
#ifdef MIN_VERSION_process
691-
#if MIN_VERSION_process(1,6,8)
692-
enableProcessJobs cp = cp {Process.use_process_jobs = True}
693-
#else
694-
enableProcessJobs cp = cp
695-
#endif
696-
#else
697-
enableProcessJobs cp = cp
698-
#endif
699-
700-
-- | 'System.Process.createProcess' with process jobs enabled when appropriate.
701-
-- See 'enableProcessJobs'.
702-
createProcess :: CreateProcess
703-
-> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
704-
createProcess = Process.createProcess . enableProcessJobs
705-
706-
-- | 'System.Process.rawSystem' with process jobs enabled when appropriate.
707-
-- See 'enableProcessJobs'.
708-
rawSystem :: String -> [String] -> IO ExitCode
709-
rawSystem cmd args = do
710-
#if MIN_VERSION_process(1,2,0)
711-
(_,_,_,p) <- createProcess (Process.proc cmd args) { Process.delegate_ctlc = True }
712-
waitForProcess p
713-
#else
714-
-- With very old 'process', just do its rawSystem
715-
Process.rawSystem cmd args
716-
#endif
717682

718-
-- | 'System.Process.runInteractiveProcess' with process jobs enabled when
719-
-- appropriate. See 'enableProcessJobs'.
720-
runInteractiveProcess
721-
:: FilePath -- ^ Filename of the executable (see 'RawCommand' for details)
722-
-> [String] -- ^ Arguments to pass to the executable
723-
-> Maybe FilePath -- ^ Optional path to the working directory
724-
-> Maybe [(String,String)] -- ^ Optional environment (otherwise inherit)
725-
-> IO (Handle,Handle,Handle,ProcessHandle)
726-
runInteractiveProcess cmd args mb_cwd mb_env = do
727-
(mb_in, mb_out, mb_err, p) <-
728-
createProcess (Process.proc cmd args)
729-
{ Process.std_in = Process.CreatePipe,
730-
Process.std_out = Process.CreatePipe,
731-
Process.std_err = Process.CreatePipe,
732-
Process.env = mb_env,
733-
Process.cwd = mb_cwd }
734-
return (fromJust mb_in, fromJust mb_out, fromJust mb_err, p)
735683

736684
printRawCommandAndArgs :: Verbosity -> FilePath -> [String] -> IO ()
737685
printRawCommandAndArgs verbosity path args = withFrozenCallStack $

cabal-install/Distribution/Client/SetupWrapper.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -111,7 +111,8 @@ import System.Directory ( doesFileExist )
111111
import System.FilePath ( (</>), (<.>) )
112112
import System.IO ( Handle, hPutStr )
113113
import System.Exit ( ExitCode(..), exitWith )
114-
import System.Process ( createProcess, StdStream(..), proc, waitForProcess
114+
import Distribution.Compat.Process (createProcess)
115+
import System.Process ( StdStream(..), proc, waitForProcess
115116
, ProcessHandle )
116117
import qualified System.Process as Process
117118
import Data.List ( foldl1' )
@@ -464,6 +465,7 @@ runProcess' cmd args mb_cwd mb_env mb_stdin mb_stdout mb_stderr _delegate = do
464465
mbToStd :: Maybe Handle -> StdStream
465466
mbToStd Nothing = Inherit
466467
mbToStd (Just hdl) = UseHandle hdl
468+
467469
-- ------------------------------------------------------------
468470
-- * Self-Exec SetupMethod
469471
-- ------------------------------------------------------------

0 commit comments

Comments
 (0)