Skip to content

Commit

Permalink
Fix extra-prog-path propagation in the codebase.
Browse files Browse the repository at this point in the history
This allows finding system executables in:
- `cabal exec`
- `cabal build` (configure steps for example)
- `cabal get`

In particular this fixes PATH issues when running MinGW cabal in
PowerShell.
  • Loading branch information
jasagredo committed Dec 15, 2023
1 parent 7ba955f commit 9993cbd
Show file tree
Hide file tree
Showing 7 changed files with 56 additions and 21 deletions.
14 changes: 13 additions & 1 deletion cabal-install/src/Distribution/Client/CmdExec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,10 @@ import Distribution.Client.NixStyleOptions
, defaultNixStyleFlags
, nixStyleOptions
)
import Distribution.Client.ProjectConfig.Types
( ProjectConfig (projectConfigShared)
, ProjectConfigShared (projectConfigProgPathExtra)
)
import Distribution.Client.ProjectFlags
( removeIgnoreProjectOption
)
Expand Down Expand Up @@ -91,6 +95,8 @@ import Distribution.Simple.Utils
, withTempDirectory
, wrapText
)
import Distribution.Utils.NubList
( fromNubList )
import Distribution.Verbosity
( normal
)
Expand Down Expand Up @@ -163,9 +169,15 @@ execAction flags@NixStyleFlags{..} extraArgs globalFlags = do

-- Some dependencies may have executables. Let's put those on the PATH.
extraPaths <- pathAdditions verbosity baseCtx buildCtx
let configProgPathExtras =
fromNubList
. projectConfigProgPathExtra
. projectConfigShared
. projectConfig
$ baseCtx
let programDb =
modifyProgramSearchPath
(map ProgramSearchPathDir extraPaths ++)
(map ProgramSearchPathDir (configProgPathExtras ++ extraPaths) ++)
. pkgConfigCompilerProgs
. elaboratedShared
$ buildCtx
Expand Down
7 changes: 7 additions & 0 deletions cabal-install/src/Distribution/Client/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1539,6 +1539,13 @@ parseConfig src initial = \str -> do
splitMultiPath
(configConfigureArgs scf)
}
, savedGlobalFlags =
let sgf = savedGlobalFlags conf
in sgf { globalProgPathExtra =
toNubList $
splitMultiPath
(fromNubList $ globalProgPathExtra sgf)
}
}

parse =
Expand Down
12 changes: 9 additions & 3 deletions cabal-install/src/Distribution/Client/Get.hs
Original file line number Diff line number Diff line change
Expand Up @@ -78,6 +78,8 @@ import Distribution.Solver.Types.SourcePackage
import Control.Monad (mapM_)
import qualified Data.Map as Map
import Distribution.Client.Errors
import Distribution.Utils.NubList
(fromNubList)
import System.Directory
( createDirectoryIfMissing
, doesDirectoryExist
Expand All @@ -99,7 +101,7 @@ get
-> IO ()
get verbosity _ _ _ [] =
notice verbosity "No packages requested. Nothing to do."
get verbosity repoCtxt _ getFlags userTargets = do
get verbosity repoCtxt globalFlags getFlags userTargets = do
let useSourceRepo = case getSourceRepository getFlags of
NoFlag -> False
_ -> True
Expand Down Expand Up @@ -154,7 +156,7 @@ get verbosity repoCtxt _ getFlags userTargets = do

clone :: [UnresolvedSourcePackage] -> IO ()
clone =
clonePackagesFromSourceRepo verbosity prefix kind
clonePackagesFromSourceRepo verbosity prefix kind (fromNubList $ globalProgPathExtra globalFlags)
. map (\pkg -> (packageId pkg, packageSourceRepos pkg))
where
kind :: Maybe RepoKind
Expand Down Expand Up @@ -337,6 +339,8 @@ clonePackagesFromSourceRepo
-- ^ destination dir prefix
-> Maybe RepoKind
-- ^ preferred 'RepoKind'
-> [FilePath]
-- ^ Extra prog paths
-> [(PackageId, [PD.SourceRepo])]
-- ^ the packages and their
-- available 'SourceRepo's
Expand All @@ -345,13 +349,15 @@ clonePackagesFromSourceRepo
verbosity
destDirPrefix
preferredRepoKind
progPaths
pkgrepos = do
-- Do a bunch of checks and collect the required info
pkgrepos' <- traverse preCloneChecks pkgrepos

-- Configure the VCS drivers for all the repository types we may need
vcss <-
configureVCSs verbosity $
-- TODO: the empty list below should have the config prog paths
configureVCSs verbosity progPaths $
Map.fromList
[ (vcsRepoType vcs, vcs)
| (_, _, vcs, _) <- pkgrepos'
Expand Down
5 changes: 2 additions & 3 deletions cabal-install/src/Distribution/Client/ProjectConfig.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1351,11 +1351,10 @@ syncAndReadSourcePackagesRemoteRepos
| (repo, rloc, rtype, vcs) <- repos'
]

-- TODO: pass progPathExtra on to 'configureVCS'
let _progPathExtra = fromNubList projectConfigProgPathExtra
let progPathExtra = fromNubList projectConfigProgPathExtra
getConfiguredVCS <- delayInitSharedResources $ \repoType ->
let vcs = Map.findWithDefault (error $ "Unknown VCS: " ++ prettyShow repoType) repoType knownVCSs
in configureVCS verbosity {-progPathExtra-} vcs
in configureVCS verbosity progPathExtra vcs

concat
<$> sequenceA
Expand Down
14 changes: 11 additions & 3 deletions cabal-install/src/Distribution/Client/VCS.hs
Original file line number Diff line number Diff line change
Expand Up @@ -61,6 +61,10 @@ import Distribution.Simple.Program
, runProgramInvocation
, simpleProgram
)
import Distribution.Simple.Program.Db
( modifyProgramSearchPath )
import Distribution.Simple.Program.Find
( ProgramSearchPathEntry (ProgramSearchPathDir) )
import Distribution.Types.SourceRepo
( KnownRepoType (..)
, RepoType (..)
Expand Down Expand Up @@ -198,18 +202,22 @@ validateSourceRepos rs =

configureVCS
:: Verbosity
-> [FilePath]
-> VCS Program
-- ^ Extra prog paths
-> IO (VCS ConfiguredProgram)
configureVCS verbosity vcs@VCS{vcsProgram = prog} =
asVcsConfigured <$> requireProgram verbosity prog emptyProgramDb
configureVCS verbosity progPaths vcs@VCS{vcsProgram = prog} =
asVcsConfigured <$> requireProgram verbosity prog (modifyProgramSearchPath (map ProgramSearchPathDir progPaths ++) emptyProgramDb )
where
asVcsConfigured (prog', _) = vcs{vcsProgram = prog'}

configureVCSs
:: Verbosity
-> [FilePath]
-> Map RepoType (VCS Program)
-- ^ Extra prog paths
-> IO (Map RepoType (VCS ConfiguredProgram))
configureVCSs verbosity = traverse (configureVCS verbosity)
configureVCSs verbosity progPaths = traverse (configureVCS verbosity progPaths)

-- ------------------------------------------------------------

Expand Down
21 changes: 12 additions & 9 deletions cabal-install/tests/UnitTests/Distribution/Client/Get.hs
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,7 @@ testNoRepos :: Assertion
testNoRepos = do
e <-
assertException $
clonePackagesFromSourceRepo verbosity "." Nothing pkgrepos
clonePackagesFromSourceRepo verbosity "." Nothing [] pkgrepos
e @?= ClonePackageNoSourceRepos pkgidfoo
where
pkgrepos = [(pkgidfoo, [])]
Expand All @@ -73,7 +73,7 @@ testNoReposOfKind :: Assertion
testNoReposOfKind = do
e <-
assertException $
clonePackagesFromSourceRepo verbosity "." repokind pkgrepos
clonePackagesFromSourceRepo verbosity "." repokind [] pkgrepos
e @?= ClonePackageNoSourceReposOfKind pkgidfoo repokind
where
pkgrepos = [(pkgidfoo, [repo])]
Expand All @@ -84,7 +84,7 @@ testNoRepoType :: Assertion
testNoRepoType = do
e <-
assertException $
clonePackagesFromSourceRepo verbosity "." Nothing pkgrepos
clonePackagesFromSourceRepo verbosity "." Nothing [] pkgrepos
e @?= ClonePackageNoRepoType pkgidfoo repo
where
pkgrepos = [(pkgidfoo, [repo])]
Expand All @@ -94,7 +94,7 @@ testUnsupportedRepoType :: Assertion
testUnsupportedRepoType = do
e <-
assertException $
clonePackagesFromSourceRepo verbosity "." Nothing pkgrepos
clonePackagesFromSourceRepo verbosity "." Nothing [] pkgrepos
e @?= ClonePackageUnsupportedRepoType pkgidfoo repo' repotype
where
pkgrepos = [(pkgidfoo, [repo])]
Expand All @@ -118,7 +118,7 @@ testNoRepoLocation :: Assertion
testNoRepoLocation = do
e <-
assertException $
clonePackagesFromSourceRepo verbosity "." Nothing pkgrepos
clonePackagesFromSourceRepo verbosity "." Nothing [] pkgrepos
e @?= ClonePackageNoRepoLocation pkgidfoo repo
where
pkgrepos = [(pkgidfoo, [repo])]
Expand All @@ -139,7 +139,7 @@ testSelectRepoKind =
e' @?= ClonePackageNoRepoType pkgidfoo expectedRepo
| let test rt rs =
assertException $
clonePackagesFromSourceRepo verbosity "." rt rs
clonePackagesFromSourceRepo verbosity "." rt [] rs
, (requestedRepoType, expectedRepo) <- cases
]
where
Expand All @@ -161,14 +161,14 @@ testRepoDestinationExists =
createDirectory pkgdir
e1 <-
assertException $
clonePackagesFromSourceRepo verbosity tmpdir Nothing pkgrepos
clonePackagesFromSourceRepo verbosity tmpdir Nothing [] pkgrepos
e1 @?= ClonePackageDestinationExists pkgidfoo pkgdir True {- isdir -}
removeDirectory pkgdir

writeFile pkgdir ""
e2 <-
assertException $
clonePackagesFromSourceRepo verbosity tmpdir Nothing pkgrepos
clonePackagesFromSourceRepo verbosity tmpdir Nothing [] pkgrepos
e2 @?= ClonePackageDestinationExists pkgidfoo pkgdir False {- isfile -}
where
pkgrepos = [(pkgidfoo, [repo])]
Expand Down Expand Up @@ -199,7 +199,7 @@ testGitFetchFailed =
pkgrepos = [(pkgidfoo, [repo])]
e1 <-
assertException $
clonePackagesFromSourceRepo verbosity tmpdir Nothing pkgrepos
clonePackagesFromSourceRepo verbosity tmpdir Nothing [] pkgrepos
e1 @?= ClonePackageFailedWithExitCode pkgidfoo repo' "git" (ExitFailure 128)

testNetworkGitClone :: Assertion
Expand All @@ -214,6 +214,7 @@ testNetworkGitClone =
verbosity
tmpdir
Nothing
[]
[(mkpkgid "zlib1", [repo1])]
assertFileContains (tmpdir </> "zlib1/zlib.cabal") ["name:", "zlib"]

Expand All @@ -226,6 +227,7 @@ testNetworkGitClone =
verbosity
tmpdir
Nothing
[]
[(mkpkgid "zlib2", [repo2])]
assertFileContains (tmpdir </> "zlib2/zlib.cabal") ["name:", "zlib"]

Expand All @@ -239,6 +241,7 @@ testNetworkGitClone =
verbosity
tmpdir
Nothing
[]
[(mkpkgid "zlib3", [repo3])]
assertFileContains (tmpdir </> "zlib3/zlib.cabal") ["version:", "0.5.0.0"]
where
Expand Down
4 changes: 2 additions & 2 deletions cabal-install/tests/UnitTests/Distribution/Client/VCS.hs
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,7 @@ tests :: MTimeChange -> [TestTree]
tests mtimeChange =
map
(localOption $ QuickCheckTests 10)
[ ignoreInWindows "See issue #8048" $
[ ignoreInWindows "See issue #8048 and #9519" $
testGroup
"git"
[ testProperty "check VCS test framework" prop_framework_git
Expand Down Expand Up @@ -227,7 +227,7 @@ testSetup
-> IO a
testSetup vcs mkVCSTestDriver repoRecipe theTest = do
-- test setup
vcs' <- configureVCS verbosity vcs
vcs' <- configureVCS verbosity [] vcs
withTestDir verbosity "vcstest" $ \tmpdir -> do
let srcRepoPath = tmpdir </> "src"
submodulesPath = tmpdir </> "submodules"
Expand Down

0 comments on commit 9993cbd

Please sign in to comment.