Skip to content

Commit

Permalink
Fix extra-prog-path propagation in the codebase.
Browse files Browse the repository at this point in the history
Extra prog paths were being handled in many different ways all thorugh
the codebase. This PR introduces a unified way to look at them.

Aiming for traceability, the addition of extra paths is now traced via
`logExtraProgramSearchPath`. All appearances of
`modifyProgramSearchPath` are replaced with `appendProgramSearchPath`
which traces the added paths.

`progInvokePathEnv` was only being set by GHC for some paths to
executables in components and only under certain circumstances. Now
every `ghcInvocation` sets the extra paths directly into `pkgInvokeEnv`.

In particular this fixes PATH issues when running MinGW cabal in
PowerShell, as usually for other OSes the system path contains most of
the expected directories.
  • Loading branch information
jasagredo committed Dec 27, 2023
1 parent 52d1fb6 commit 4cf508f
Show file tree
Hide file tree
Showing 23 changed files with 222 additions and 135 deletions.
33 changes: 16 additions & 17 deletions Cabal/src/Distribution/Simple/Configure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -86,7 +86,7 @@ import Distribution.Simple.PackageIndex (InstalledPackageIndex, lookupUnitId)
import qualified Distribution.Simple.PackageIndex as PackageIndex
import Distribution.Simple.PreProcess
import Distribution.Simple.Program
import Distribution.Simple.Program.Db (lookupProgramByName)
import Distribution.Simple.Program.Db (appendProgramSearchPath, lookupProgramByName)
import Distribution.Simple.Setup.Common as Setup
import Distribution.Simple.Setup.Config as Setup
import Distribution.Simple.Utils
Expand Down Expand Up @@ -462,6 +462,7 @@ configure (pkg_descr0, pbi) cfg = do
(fromFlag (configUserInstall cfg))
(configPackageDBs cfg)

programDbPre <- mkProgramDb cfg (configPrograms cfg)
-- comp: the compiler we're building with
-- compPlatform: the platform we're building for
-- programDb: location and args of all programs we're
Expand All @@ -474,7 +475,7 @@ configure (pkg_descr0, pbi) cfg = do
(flagToMaybe (configHcFlavor cfg))
(flagToMaybe (configHcPath cfg))
(flagToMaybe (configHcPkg cfg))
(mkProgramDb cfg (configPrograms cfg))
programDbPre
(lessVerbose verbosity)

-- The InstalledPackageIndex of all installed packages
Expand Down Expand Up @@ -1008,19 +1009,18 @@ configure (pkg_descr0, pbi) cfg = do
mkPromisedDepsSet :: [GivenComponent] -> Map (PackageName, ComponentName) ComponentId
mkPromisedDepsSet comps = Map.fromList [((pn, CLibName ln), cid) | GivenComponent pn ln cid <- comps]

mkProgramDb :: ConfigFlags -> ProgramDb -> ProgramDb
mkProgramDb cfg initialProgramDb = programDb
-- | Adds the extra program paths from the flags provided to @configure@ as
-- well as specified locations for certain known programs and their default
-- arguments.
mkProgramDb :: ConfigFlags -> ProgramDb -> IO ProgramDb
mkProgramDb cfg initialProgramDb = do
programDb <- appendProgramSearchPath (fromFlagOrDefault normal (configVerbosity cfg)) searchpath initialProgramDb
pure
. userSpecifyArgss (configProgramArgs cfg)
. userSpecifyPaths (configProgramPaths cfg)
$ programDb
where
programDb =
userSpecifyArgss (configProgramArgs cfg)
. userSpecifyPaths (configProgramPaths cfg)
. setProgramSearchPath searchpath
$ initialProgramDb
searchpath =
getProgramSearchPath initialProgramDb
++ map
ProgramSearchPathDir
(fromNubList $ configProgramPathExtra cfg)
searchpath = fromNubList $ configProgramPathExtra cfg

-- Note. We try as much as possible to _prepend_ rather than postpend the extra-prog-path
-- so that we can override the system path. However, in a v2-build, at this point, the "system" path
Expand Down Expand Up @@ -2083,15 +2083,14 @@ ccLdOptionsBuildInfo cflags ldflags ldflags_static =
configCompilerAuxEx
:: ConfigFlags
-> IO (Compiler, Platform, ProgramDb)
configCompilerAuxEx cfg =
configCompilerAuxEx cfg = do
programDb <- mkProgramDb cfg defaultProgramDb
configCompilerEx
(flagToMaybe $ configHcFlavor cfg)
(flagToMaybe $ configHcPath cfg)
(flagToMaybe $ configHcPkg cfg)
programDb
(fromFlag (configVerbosity cfg))
where
programDb = mkProgramDb cfg defaultProgramDb

configCompilerEx
:: Maybe CompilerFlavor
Expand Down
5 changes: 1 addition & 4 deletions Cabal/src/Distribution/Simple/ConfigureScript.hs
Original file line number Diff line number Diff line change
Expand Up @@ -169,10 +169,7 @@ runConfigureScript verbosity flags lbi = do
maybeHostFlag = if hp == buildPlatform then [] else ["--host=" ++ show (pretty hp)]
args' = configureFile' : args ++ ["CC=" ++ ccProgShort] ++ maybeHostFlag
shProg = simpleProgram "sh"
progDb =
modifyProgramSearchPath
(\p -> map ProgramSearchPathDir extraPath ++ p)
emptyProgramDb
progDb <- appendProgramSearchPath verbosity extraPath emptyProgramDb
shConfiguredProg <-
lookupProgram shProg
`fmap` configureProgram verbosity shProg progDb
Expand Down
4 changes: 3 additions & 1 deletion Cabal/src/Distribution/Simple/GHC.hs
Original file line number Diff line number Diff line change
Expand Up @@ -697,10 +697,12 @@ libAbiHash verbosity _pkg_descr lbi lib clbi = do
| otherwise = error "libAbiHash: Can't find an enabled library way"

(ghcProg, _) <- requireProgram verbosity ghcProgram (withPrograms lbi)

hash <-
getProgramInvocationOutput
verbosity
(ghcInvocation ghcProg comp platform ghcArgs)
=<< ghcInvocation verbosity ghcProg comp platform ghcArgs

return (takeWhile (not . isSpace) hash)

componentCcGhcOptions
Expand Down
2 changes: 1 addition & 1 deletion Cabal/src/Distribution/Simple/GHCJS.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1769,7 +1769,7 @@ libAbiHash verbosity _pkg_descr lbi lib clbi = do
hash <-
getProgramInvocationOutput
verbosity
(ghcInvocation ghcjsProg comp platform ghcArgs)
=<< ghcInvocation verbosity ghcjsProg comp platform ghcArgs
return (takeWhile (not . isSpace) hash)

componentGhcOptions
Expand Down
13 changes: 13 additions & 0 deletions Cabal/src/Distribution/Simple/Program/Db.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,7 @@ module Distribution.Simple.Program.Db
-- ** Query and manipulate the program db
, addKnownProgram
, addKnownPrograms
, appendProgramSearchPath
, lookupKnownProgram
, knownPrograms
, getProgramSearchPath
Expand Down Expand Up @@ -221,6 +222,18 @@ modifyProgramSearchPath
modifyProgramSearchPath f db =
setProgramSearchPath (f $ getProgramSearchPath db) db

-- | Modify the current 'ProgramSearchPath' used by the 'ProgramDb'
-- by appending the provided extra paths. Also logs the added paths
-- in info verbosity.
appendProgramSearchPath
:: Verbosity
-> [FilePath]
-> ProgramDb
-> IO ProgramDb
appendProgramSearchPath verbosity extraPaths db = do
logExtraProgramSearchPath verbosity extraPaths
pure $ modifyProgramSearchPath (map ProgramSearchPathDir extraPaths ++) db

-- | User-specify this path. Basically override any path information
-- for this program in the configuration. If it's not a known
-- program ignore it.
Expand Down
30 changes: 30 additions & 0 deletions Cabal/src/Distribution/Simple/Program/Find.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,9 @@ module Distribution.Simple.Program.Find
, defaultProgramSearchPath
, findProgramOnSearchPath
, programSearchPathAsPATHVar
, logExtraProgramSearchPath
, getSystemSearchPath
, getExtraPathEnv
, simpleProgram
) where

Expand Down Expand Up @@ -63,6 +65,15 @@ import qualified System.Win32 as Win32
defaultProgramSearchPath :: ProgramSearchPath
defaultProgramSearchPath = [ProgramSearchPathDefault]

logExtraProgramSearchPath
:: Verbosity
-> [FilePath]
-> IO ()
logExtraProgramSearchPath verbosity extraPaths =
info verbosity . unlines $
"Including the following directories in PATH:"
: map ("- " ++) extraPaths

findProgramOnSearchPath
:: Verbosity
-> ProgramSearchPath
Expand Down Expand Up @@ -133,6 +144,25 @@ findProgramOnSearchPath verbosity searchpath prog = do
Just _ -> return a
Nothing -> firstJustM mas

-- | Adds some paths to the "PATH" entry in the key-value environment provided
-- or if there is none, looks up @$PATH@ in the real environment.
getExtraPathEnv
:: Verbosity
-> [(String, Maybe String)]
-> [FilePath]
-> IO [(String, Maybe String)]
getExtraPathEnv _ _ [] = return []
getExtraPathEnv verbosity env extras = do
mb_path <- case lookup "PATH" env of
Just x -> return x
Nothing -> lookupEnv "PATH"
logExtraProgramSearchPath verbosity extras
let extra = intercalate [searchPathSeparator] extras
path' = case mb_path of
Nothing -> extra
Just path -> extra ++ searchPathSeparator : path
return [("PATH", Just path')]

-- | Interpret a 'ProgramSearchPath' to construct a new @$PATH@ env var.
-- Note that this is close but not perfect because on Windows the search
-- algorithm looks at more than just the @%PATH%@.
Expand Down
23 changes: 14 additions & 9 deletions Cabal/src/Distribution/Simple/Program/GHC.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ import Distribution.Pretty
import Distribution.Simple.Compiler
import Distribution.Simple.Flag
import Distribution.Simple.GHC.ImplInfo
import Distribution.Simple.Program.Find (getExtraPathEnv)
import Distribution.Simple.Program.Run
import Distribution.Simple.Program.Types
import Distribution.System
Expand Down Expand Up @@ -554,8 +555,6 @@ data GhcOptions = GhcOptions
, ghcOptExtraPath :: NubListR FilePath
-- ^ Put the extra folders in the PATH environment variable we invoke
-- GHC with
-- | Put the extra folders in the PATH environment variable we invoke
-- GHC with
, ghcOptCabal :: Flag Bool
-- ^ Let GHC know that it is Cabal that's calling it.
-- Modifies some of the GHC error messages.
Expand Down Expand Up @@ -616,18 +615,24 @@ runGHC
-> GhcOptions
-> IO ()
runGHC verbosity ghcProg comp platform opts = do
runProgramInvocation verbosity (ghcInvocation ghcProg comp platform opts)
runProgramInvocation verbosity =<< ghcInvocation verbosity ghcProg comp platform opts

ghcInvocation
:: ConfiguredProgram
:: Verbosity
-> ConfiguredProgram
-> Compiler
-> Platform
-> GhcOptions
-> ProgramInvocation
ghcInvocation prog comp platform opts =
(programInvocation prog (renderGhcOptions comp platform opts))
{ progInvokePathEnv = fromNubListR (ghcOptExtraPath opts)
}
-> IO ProgramInvocation
ghcInvocation verbosity ghcProg comp platform opts = do
-- NOTE: GHC is the only program whose path we modify with more values than
-- the standard @extra-prog-path@, namely the folders of the executables in
-- the components, see @componentGhcOptions@.
let envOverrides = programOverrideEnv ghcProg
extraPath <- getExtraPathEnv verbosity envOverrides (fromNubListR (ghcOptExtraPath opts))
let ghcProg' = ghcProg{programOverrideEnv = envOverrides ++ extraPath}

pure $ programInvocation ghcProg' (renderGhcOptions comp platform opts)

renderGhcOptions :: Compiler -> Platform -> GhcOptions -> [String]
renderGhcOptions comp _platform@(Platform _arch os) opts
Expand Down
29 changes: 3 additions & 26 deletions Cabal/src/Distribution/Simple/Program/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,6 @@ import Distribution.Simple.Program.Types
import Distribution.Simple.Utils
import Distribution.Utils.Generic
import Distribution.Verbosity
import System.FilePath (searchPathSeparator)

import qualified Data.ByteString.Lazy as LBS
import qualified Data.Map as Map
Expand All @@ -51,8 +50,6 @@ data ProgramInvocation = ProgramInvocation
{ progInvokePath :: FilePath
, progInvokeArgs :: [String]
, progInvokeEnv :: [(String, Maybe String)]
, -- Extra paths to add to PATH
progInvokePathEnv :: [FilePath]
, progInvokeCwd :: Maybe FilePath
, progInvokeInput :: Maybe IOData
, progInvokeInputEncoding :: IOEncoding
Expand All @@ -75,7 +72,6 @@ emptyProgramInvocation =
{ progInvokePath = ""
, progInvokeArgs = []
, progInvokeEnv = []
, progInvokePathEnv = []
, progInvokeCwd = Nothing
, progInvokeInput = Nothing
, progInvokeInputEncoding = IOEncodingText
Expand Down Expand Up @@ -107,7 +103,6 @@ runProgramInvocation
{ progInvokePath = path
, progInvokeArgs = args
, progInvokeEnv = []
, progInvokePathEnv = []
, progInvokeCwd = Nothing
, progInvokeInput = Nothing
} =
Expand All @@ -118,12 +113,10 @@ runProgramInvocation
{ progInvokePath = path
, progInvokeArgs = args
, progInvokeEnv = envOverrides
, progInvokePathEnv = extraPath
, progInvokeCwd = mcwd
, progInvokeInput = Nothing
} = do
pathOverride <- getExtraPathEnv envOverrides extraPath
menv <- getEffectiveEnvironment (envOverrides ++ pathOverride)
menv <- getEffectiveEnvironment envOverrides
maybeExit $
rawSystemIOWithEnv
verbosity
Expand All @@ -140,13 +133,11 @@ runProgramInvocation
{ progInvokePath = path
, progInvokeArgs = args
, progInvokeEnv = envOverrides
, progInvokePathEnv = extraPath
, progInvokeCwd = mcwd
, progInvokeInput = Just inputStr
, progInvokeInputEncoding = encoding
} = do
pathOverride <- getExtraPathEnv envOverrides extraPath
menv <- getEffectiveEnvironment (envOverrides ++ pathOverride)
menv <- getEffectiveEnvironment envOverrides
(_, errors, exitCode) <-
rawSystemStdInOut
verbosity
Expand Down Expand Up @@ -202,30 +193,16 @@ getProgramInvocationIODataAndErrors
{ progInvokePath = path
, progInvokeArgs = args
, progInvokeEnv = envOverrides
, progInvokePathEnv = extraPath
, progInvokeCwd = mcwd
, progInvokeInput = minputStr
, progInvokeInputEncoding = encoding
}
mode = do
pathOverride <- getExtraPathEnv envOverrides extraPath
menv <- getEffectiveEnvironment (envOverrides ++ pathOverride)
menv <- getEffectiveEnvironment envOverrides
rawSystemStdInOut verbosity path args mcwd menv input mode
where
input = encodeToIOData encoding <$> minputStr

getExtraPathEnv :: [(String, Maybe String)] -> [FilePath] -> IO [(String, Maybe String)]
getExtraPathEnv _ [] = return []
getExtraPathEnv env extras = do
mb_path <- case lookup "PATH" env of
Just x -> return x
Nothing -> lookupEnv "PATH"
let extra = intercalate [searchPathSeparator] extras
path' = case mb_path of
Nothing -> extra
Just path -> extra ++ searchPathSeparator : path
return [("PATH", Just path')]

-- | Return the current environment extended with the given overrides.
-- If an entry is specified twice in @overrides@, the second entry takes
-- precedence.
Expand Down
7 changes: 7 additions & 0 deletions Cabal/src/Distribution/Simple/Program/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -93,6 +93,13 @@ type ProgArg = String
-- dir to search after the usual ones.
--
-- > ['ProgramSearchPathDefault', 'ProgramSearchPathDir' dir]
--
-- We also use this path to set the environment when running child processes.
--
-- The @ProgramDb@ is created with a @ProgramSearchPath@ to which we
-- @appendProgramSearchPath@ to add the ones that come from cli flags and from
-- configurations. Then each of the programs that are configured in the db
-- inherits the same path as part of @configureProgram@.
type ProgramSearchPath = [ProgramSearchPathEntry]

data ProgramSearchPathEntry
Expand Down
Loading

0 comments on commit 4cf508f

Please sign in to comment.