From 97f2c7b38df470f53b4c200bc23a2fcd14b1c72e Mon Sep 17 00:00:00 2001
From: Robert Vollmert <rob@vllmrt.net>
Date: Wed, 23 Feb 2022 00:38:20 +0100
Subject: [PATCH] Remove newly deprecated functions

---
 Cabal/src/Distribution/Compat/Process.hs | 45 +-----------------------
 Cabal/src/Distribution/Simple/Utils.hs   | 44 -----------------------
 2 files changed, 1 insertion(+), 88 deletions(-)

diff --git a/Cabal/src/Distribution/Compat/Process.hs b/Cabal/src/Distribution/Compat/Process.hs
index bb66e145ce..18a1d9f53d 100644
--- a/Cabal/src/Distribution/Compat/Process.hs
+++ b/Cabal/src/Distribution/Compat/Process.hs
@@ -4,16 +4,9 @@ module Distribution.Compat.Process (
     proc,
     -- * Additions
     enableProcessJobs,
-    -- * Deprecated
-    createProcess,
-    runInteractiveProcess,
-    rawSystem,
     ) where
 
-import System.Exit (ExitCode (..))
-import System.IO   (Handle)
-
-import           System.Process (CreateProcess, ProcessHandle)
+import           System.Process (CreateProcess)
 import qualified System.Process as Process
 
 #if defined(mingw32_HOST_OS) && MIN_VERSION_process(1,6,9)
@@ -66,39 +59,3 @@ enableProcessJobs cp = cp
 -- and defaulting 'delegate_ctlc' to 'True'.
 proc :: FilePath -> [String] -> CreateProcess
 proc path args = enableProcessJobs (Process.proc path args) { Process.delegate_ctlc = True }
-
--- | 'System.Process.createProcess' with process jobs enabled when appropriate.
--- See 'enableProcessJobs'.
-{-# DEPRECATED createProcess "use proc with System.Process.createProcess instead" #-}
-createProcess :: CreateProcess
-              -> IO (Maybe Handle, Maybe Handle, Maybe Handle, ProcessHandle)
-createProcess = Process.createProcess . enableProcessJobs
-
--- | 'System.Process.rawSystem' with process jobs enabled when appropriate.
--- See 'enableProcessJobs'.
-{-# DEPRECATED rawSystem "use one of the functions exported by Distribution.Simple.Utils instead" #-}
-rawSystem :: FilePath -> [String] -> IO ExitCode
-rawSystem path args = do
-  (_,_,_,p) <- Process.createProcess (proc path args)
-  Process.waitForProcess p
-
--- | 'System.Process.runInteractiveProcess' with process jobs enabled when
--- appropriate. See 'enableProcessJobs'.
-{-# DEPRECATED runInteractiveProcess "use one of the functions exported by Distribution.Simple.Utils instead" #-}
-runInteractiveProcess
-  :: FilePath                   -- ^ Filename of the executable (see 'RawCommand' for details)
-  -> [String]                   -- ^ Arguments to pass to the executable
-  -> Maybe FilePath             -- ^ Optional path to the working directory
-  -> Maybe [(String,String)]    -- ^ Optional environment (otherwise inherit)
-  -> IO (Handle,Handle,Handle,ProcessHandle)
-runInteractiveProcess path args mb_cwd mb_env = do
-  (mb_in, mb_out, mb_err, p) <-
-      Process.createProcess (proc path args)
-              { Process.std_in  = Process.CreatePipe,
-                Process.std_out = Process.CreatePipe,
-                Process.std_err = Process.CreatePipe,
-                Process.env     = mb_env,
-                Process.cwd     = mb_cwd }
-  return (fromJust mb_in, fromJust mb_out, fromJust mb_err, p)
-  where
-    fromJust = maybe (error "runInteractiveProcess: fromJust") id
diff --git a/Cabal/src/Distribution/Simple/Utils.hs b/Cabal/src/Distribution/Simple/Utils.hs
index 76dca142aa..1772bfac09 100644
--- a/Cabal/src/Distribution/Simple/Utils.hs
+++ b/Cabal/src/Distribution/Simple/Utils.hs
@@ -38,7 +38,6 @@ module Distribution.Simple.Utils (
         debug, debugNoWrap,
         chattyTry,
         annotateIO,
-        logCommand,
         withOutputMarker,
 
         -- * exceptions
@@ -174,10 +173,6 @@ module Distribution.Simple.Utils (
         -- * FilePath stuff
         isAbsoluteOnAnyPlatform,
         isRelativeOnAnyPlatform,
-
-        -- * Deprecated
-        printRawCommandAndArgs, printRawCommandAndArgsAndEnv,
-        createProcessWithEnv,
   ) where
 
 import Prelude ()
@@ -241,7 +236,6 @@ import Foreign.C.Error (Errno (..), ePIPE)
 import Data.Time.Clock.POSIX (getPOSIXTime, POSIXTime)
 import Numeric (showFFloat)
 import Distribution.Compat.Process (proc)
-import System.Process (ProcessHandle)
 import qualified System.Process as Process
 import qualified GHC.IO.Exception as GHC
 
@@ -738,21 +732,6 @@ maybeExit cmd = do
   exitcode <- cmd
   unless (exitcode == ExitSuccess) $ exitWith exitcode
 
-{-# DEPRECATED printRawCommandAndArgs "use logCommand" #-}
-printRawCommandAndArgs :: Verbosity -> FilePath -> [String] -> IO ()
-printRawCommandAndArgs verbosity path args = withFrozenCallStack $ do
-    logCommand verbosity (proc path args)
-
-{-# DEPRECATED printRawCommandAndArgsAndEnv "use logCommand" #-}
-printRawCommandAndArgsAndEnv :: Verbosity
-                             -> FilePath
-                             -> [String]
-                             -> Maybe FilePath
-                             -> Maybe [(String, String)]
-                             -> IO ()
-printRawCommandAndArgsAndEnv verbosity path args mcwd menv = withFrozenCallStack $ do
-    logCommand verbosity (proc path args) { Process.cwd = mcwd, Process.env = menv }
-
 -- | Log a command execution (that's typically about to happen)
 -- at info level, and log working directory and environment overrides
 -- at debug level if specified.
@@ -893,29 +872,6 @@ rawSystemIOWithEnvAndAction verbosity path args mcwd menv action inp out err = w
     mbToStd :: Maybe Handle -> Process.StdStream
     mbToStd = maybe Process.Inherit Process.UseHandle
 
-{-# DEPRECATED createProcessWithEnv "use System.Process.createProcess with Distribution.Compat.Process.proc instead" #-}
-createProcessWithEnv ::
-     Verbosity
-  -> FilePath
-  -> [String]
-  -> Maybe FilePath           -- ^ New working dir or inherit
-  -> Maybe [(String, String)] -- ^ New environment or inherit
-  -> Process.StdStream  -- ^ stdin
-  -> Process.StdStream  -- ^ stdout
-  -> Process.StdStream  -- ^ stderr
-  -> IO (Maybe Handle, Maybe Handle, Maybe Handle,ProcessHandle)
-  -- ^ Any handles created for stdin, stdout, or stderr
-  -- with 'CreateProcess', and a handle to the process.
-createProcessWithEnv verbosity path args mcwd menv inp out err = withFrozenCallStack $ do
-  let cp = (proc path args) { Process.cwd           = mcwd
-                            , Process.env           = menv
-                            , Process.std_in        = inp
-                            , Process.std_out       = out
-                            , Process.std_err       = err
-                            }
-  logCommand verbosity cp
-  Process.createProcess cp
-
 -- | Execute the given command with the given arguments, returning
 -- the command's output. Exits if the command exits with error.
 --
-- 
GitLab