Skip to content
Snippets Groups Projects
Commit 7b99b7dd authored by Robert's avatar Robert Committed by mergify-bot
Browse files

Drop various process <1.2.1.0 compatibility shims

Keep Distribution.Compat.CreatePipe as a trivial
reexport to avoid changing the published API.
parent c0080f73
No related branches found
No related tags found
No related merge requests found
......@@ -26,7 +26,6 @@ test-suite unit-tests
Test.Laws
Test.QuickCheck.Utils
UnitTests.Distribution.CabalSpecVersion
UnitTests.Distribution.Compat.CreatePipe
UnitTests.Distribution.Compat.Graph
UnitTests.Distribution.Compat.Time
UnitTests.Distribution.Described
......
......@@ -13,7 +13,6 @@ import Distribution.Simple.Utils
import Distribution.Verbosity
import Distribution.Compat.Time
import qualified UnitTests.Distribution.Compat.CreatePipe
import qualified UnitTests.Distribution.Compat.Time
import qualified UnitTests.Distribution.Compat.Graph
import qualified UnitTests.Distribution.Simple.Command
......@@ -44,9 +43,7 @@ tests mtimeChangeCalibrated =
else mtimeChangeCalibrated
in
testGroup "Unit Tests"
[ testGroup "Distribution.Compat.CreatePipe"
UnitTests.Distribution.Compat.CreatePipe.tests
, testGroup "Distribution.Compat.Time"
[ testGroup "Distribution.Compat.Time"
(UnitTests.Distribution.Compat.Time.tests mtimeChange)
, testGroup "Distribution.Compat.Graph"
UnitTests.Distribution.Compat.Graph.tests
......
module UnitTests.Distribution.Compat.CreatePipe (tests) where
import Control.Concurrent.Async (async, wait)
import Control.DeepSeq (force)
import Control.Exception (evaluate)
import System.IO (hClose, hGetContents, hPutStr, hSetEncoding, localeEncoding)
import Test.Tasty (TestTree)
import Test.Tasty.HUnit (Assertion, assertEqual, testCase)
import qualified Data.ByteString as BS
import Distribution.Compat.CreatePipe
tests :: [TestTree]
tests =
[ testCase "Locale Encoding" case_Locale_Encoding
, testCase "Binary ByteStrings are not affected" case_ByteString
]
case_Locale_Encoding :: Assertion
case_Locale_Encoding = do
let str = "\0252foobar"
(r, w) <- createPipe
hSetEncoding w localeEncoding
hSetEncoding r localeEncoding
ra <- async $ do
out <- hGetContents r
evaluate (force out)
wa <- async $ do
hPutStr w str
hClose w
out <- wait ra
wait wa
assertEqual "createPipe should support Unicode roundtripping" str out
case_ByteString :: Assertion
case_ByteString = do
let bs = BS.pack[ 1..255]
(r, w) <- createPipe
ra <- async $ do
out <- BS.hGetContents r
evaluate (force out)
wa <- async $ do
BS.hPutStr w bs
hClose w
out <- wait ra
wait wa
assertEqual "createPipe should support Unicode roundtripping" bs out
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
module Distribution.Compat.CreatePipe
{-# DEPRECATED "Use System.Process from package process directly" #-}
(createPipe) where
module Distribution.Compat.CreatePipe (createPipe) where
#if MIN_VERSION_process(1,2,1)
import System.Process (createPipe)
#else
import System.IO (Handle, hSetBinaryMode)
import Prelude ()
import Distribution.Compat.Prelude
import Distribution.Compat.Stack
-- The mingw32_HOST_OS CPP macro is GHC-specific
#ifdef mingw32_HOST_OS
import qualified Prelude
import Control.Exception (onException)
import Foreign.C.Error (throwErrnoIfMinus1_)
import Foreign.C.Types (CInt(..), CUInt(..))
import Foreign.Ptr (Ptr)
import Foreign.Marshal.Array (allocaArray)
import Foreign.Storable (peek, peekElemOff)
import GHC.IO.FD (mkFD)
import GHC.IO.Device (IODeviceType(Stream))
import GHC.IO.Handle.FD (mkHandleFromFD)
import System.IO (IOMode(ReadMode, WriteMode))
#elif defined ghcjs_HOST_OS
#else
import System.Posix.IO (fdToHandle)
import qualified System.Posix.IO as Posix
#endif
createPipe :: IO (Handle, Handle)
-- The mingw32_HOST_OS CPP macro is GHC-specific
#ifdef mingw32_HOST_OS
createPipe = do
(readfd, writefd) <- allocaArray 2 $ \ pfds -> do
throwErrnoIfMinus1_ "_pipe" $ c__pipe pfds 2 ({- _O_BINARY -} 32768)
readfd <- peek pfds
writefd <- peekElemOff pfds 1
return (readfd, writefd)
(do readh <- fdToHandle readfd ReadMode
writeh <- fdToHandle writefd WriteMode
hSetBinaryMode readh True
hSetBinaryMode writeh True
return (readh, writeh)) `onException` (close readfd >> close writefd)
where
fdToHandle :: CInt -> IOMode -> IO Handle
fdToHandle fd mode = do
(fd', deviceType) <- mkFD fd mode (Just (Stream, 0, 0)) False False
mkHandleFromFD fd' deviceType "" mode False Nothing
close :: CInt -> IO ()
close = throwErrnoIfMinus1_ "_close" . c__close
where _ = callStack -- TODO: attach call stack to exception
_ = callStack -- TODO: attach call stack to exceptions
foreign import ccall "io.h _pipe" c__pipe ::
Ptr CInt -> CUInt -> CInt -> Prelude.IO CInt
foreign import ccall "io.h _close" c__close ::
CInt -> Prelude.IO CInt
#elif defined ghcjs_HOST_OS
createPipe = error "createPipe"
where
_ = callStack
#else
createPipe = do
(readfd, writefd) <- Posix.createPipe
readh <- fdToHandle readfd
writeh <- fdToHandle writefd
hSetBinaryMode readh True
hSetBinaryMode writeh True
return (readh, writeh)
where
_ = callStack
#endif
#endif
......@@ -11,13 +11,9 @@ module Distribution.Compat.Process (
import System.Exit (ExitCode (..))
import System.IO (Handle)
import System.Process (CreateProcess, ProcessHandle)
import System.Process (CreateProcess, ProcessHandle, waitForProcess)
import qualified System.Process as Process
#if MIN_VERSION_process(1,2,0)
import System.Process (waitForProcess)
#endif
#if defined(mingw32_HOST_OS) && MIN_VERSION_process(1,6,9)
import System.IO.Unsafe (unsafePerformIO)
import System.Win32.Info.Version (dwMajorVersion, dwMinorVersion, getVersionEx)
......@@ -74,13 +70,8 @@ createProcess = Process.createProcess . enableProcessJobs
-- See 'enableProcessJobs'.
rawSystem :: String -> [String] -> IO ExitCode
rawSystem cmd args = do
#if MIN_VERSION_process(1,2,0)
(_,_,_,p) <- createProcess (Process.proc cmd args) { Process.delegate_ctlc = True }
waitForProcess p
#else
-- With very old 'process', just do its rawSystem
Process.rawSystem cmd args
#endif
-- | 'System.Process.runInteractiveProcess' with process jobs enabled when
-- appropriate. See 'enableProcessJobs'.
......
......@@ -9,7 +9,6 @@ import Prelude ()
import Distribution.Compat.Prelude
import Distribution.Types.UnqualComponentName
import Distribution.Compat.CreatePipe
import Distribution.Compat.Environment
import qualified Distribution.PackageDescription as PD
import Distribution.Simple.Build.PathsModule
......@@ -32,6 +31,7 @@ import System.Directory
, getCurrentDirectory, removeDirectoryRecursive )
import System.FilePath ( (</>), (<.>) )
import System.IO ( stdout, stderr )
import System.Process ( createPipe )
import qualified Data.ByteString.Lazy as LBS
......
......@@ -13,7 +13,6 @@ import Prelude ()
import Distribution.Compat.Prelude
import Distribution.Types.UnqualComponentName
import Distribution.Compat.CreatePipe
import Distribution.Compat.Environment
import Distribution.Compat.Internal.TempFile
import Distribution.ModuleName
......@@ -42,7 +41,7 @@ import System.Directory
, setCurrentDirectory )
import System.FilePath ( (</>), (<.>) )
import System.IO ( hClose, hPutStr )
import System.Process (StdStream(..), waitForProcess)
import System.Process (StdStream(..), createPipe, waitForProcess)
runTest :: PD.PackageDescription
-> LBI.LocalBuildInfo
......
......@@ -779,13 +779,7 @@ rawSystemExitWithEnv verbosity path args env = withFrozenCallStack $ do
hFlush stdout
(_,_,_,ph) <- createProcess $
(Process.proc path args) { Process.env = (Just env)
#ifdef MIN_VERSION_process
#if MIN_VERSION_process(1,2,0)
-- delegate_ctlc has been added in process 1.2, and we still want to be able to
-- bootstrap GHC on systems not having that version
, Process.delegate_ctlc = True
#endif
#endif
}
exitcode <- waitForProcess ph
unless (exitcode == ExitSuccess) $ do
......@@ -858,13 +852,7 @@ createProcessWithEnv verbosity path args mcwd menv inp out err = withFrozenCallS
, Process.std_in = inp
, Process.std_out = out
, Process.std_err = err
#ifdef MIN_VERSION_process
#if MIN_VERSION_process(1,2,0)
-- delegate_ctlc has been added in process 1.2, and we still want to be able to
-- bootstrap GHC on systems not having that version
, Process.delegate_ctlc = True
#endif
#endif
}
return (inp', out', err', ph)
......
......@@ -25,13 +25,7 @@ import qualified System.Clock as Clock
import System.IO
import System.FilePath
import System.Exit
import System.Process (
#if MIN_VERSION_process(1,2,0)
callProcess,
#else
proc, createProcess, waitForProcess, terminateProcess,
#endif
showCommandForUser)
import System.Process (callProcess, showCommandForUser)
#if !MIN_VERSION_base(4,12,0)
import Data.Monoid ((<>))
......@@ -288,20 +282,3 @@ getTime = do
t <- Clock.getTime Clock.Monotonic
let ns = realToFrac $ Clock.toNanoSecs t
return $ ns / 10 ^ (9 :: Int)
-------------------------------------------------------------------------------
-- compat
-------------------------------------------------------------------------------
#if !MIN_VERSION_process(1,2,0)
callProcess :: FilePath -> [String] -> IO ()
callProcess cmd args = do
exit_code <- bracket (createProcess (proc cmd args)) cleanupProcess
$ \(_, _, _, ph) -> waitForProcess ph
case exit_code of
ExitSuccess -> return ()
ExitFailure r -> fail $ "processFailedException " ++ show (cmd, args, r)
where
cleanupProcess (_, _, _, ph) = terminateProcess ph
#endif
......@@ -5,7 +5,6 @@ module Test.Cabal.Run (
Result(..)
) where
import qualified Distribution.Compat.CreatePipe as Compat
import Distribution.Simple.Program.Run
import Distribution.Verbosity
......@@ -46,7 +45,7 @@ run _verbosity mb_cwd env_overrides path0 args input = do
mb_env <- getEffectiveEnvironment env_overrides
putStrLn $ "+ " ++ showCommandForUser path args
(readh, writeh) <- Compat.createPipe
(readh, writeh) <- createPipe
hSetBuffering readh LineBuffering
hSetBuffering writeh LineBuffering
let drain = do
......
......@@ -259,15 +259,9 @@ initServer s0 = do
#else
pid <- withProcessHandle (serverProcessHandle s0) $ \ph ->
case ph of
#if MIN_VERSION_process(1,2,0)
OpenHandle x -> return (show x)
-- TODO: handle OpenExtHandle?
_ -> return (serverProcessId s0)
#else
OpenHandle x -> return (ph, show x)
-- TODO: handle OpenExtHandle?
_ -> return (ph, serverProcessId s0)
#endif
#endif
let s = s0 { serverProcessId = pid }
-- We will read/write a line at a time, including for
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment