Skip to content
Snippets Groups Projects
Commit d5ae20cf authored by Robert's avatar Robert
Browse files

Deprecate obsolete functions

parent 9d33338c
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE CPP #-}
module Distribution.Compat.Process (
-- * Redefined functions
createProcess,
proc,
runInteractiveProcess,
rawSystem,
-- * Additions
enableProcessJobs,
-- * Deprecated
createProcess,
runInteractiveProcess,
rawSystem,
) where
import System.Exit (ExitCode (..))
......@@ -68,12 +69,14 @@ proc path args = enableProcessJobs (Process.proc path args) { Process.delegate_c
-- | '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)
......@@ -81,6 +84,7 @@ rawSystem path args = do
-- | '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
......
......@@ -38,7 +38,7 @@ module Distribution.Simple.Utils (
debug, debugNoWrap,
chattyTry,
annotateIO,
printRawCommandAndArgs, printRawCommandAndArgsAndEnv,
logCommand,
withOutputMarker,
-- * exceptions
......@@ -55,7 +55,6 @@ module Distribution.Simple.Utils (
rawSystemStdInOut,
rawSystemIOWithEnv,
rawSystemIOWithEnvAndAction,
createProcessWithEnv,
fromCreatePipe,
maybeExit,
xargs,
......@@ -175,6 +174,10 @@ module Distribution.Simple.Utils (
-- * FilePath stuff
isAbsoluteOnAnyPlatform,
isRelativeOnAnyPlatform,
-- * Deprecated
printRawCommandAndArgs, printRawCommandAndArgsAndEnv,
createProcessWithEnv,
) where
import Prelude ()
......@@ -735,10 +738,12 @@ 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]
......@@ -888,6 +893,7 @@ 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
......
......@@ -226,7 +226,6 @@ startServer chan senv = do
std_out = CreatePipe,
std_err = CreatePipe
}
-- printRawCommandAndArgsAndEnv (runnerVerbosity senv) (programPath prog) ghc_args Nothing
when (verbosity >= verbose) $
writeChan chan (ServerLogMsg AllServers (showCommandForUser (programPath prog) ghc_args))
(Just hin, Just hout, Just herr, proch) <- createProcess proc_spec
......
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