Skip to content
Snippets Groups Projects
Commit 802a326f authored by Rodrigo Mesquita's avatar Rodrigo Mesquita :seedling:
Browse files

Apply local configuration to install targets

The target of `cabal install` is not considered to be a local package,
which means local configuration (e.g. in cabal.project, or flags like
--enable-profiling) does not apply to it.

In 76670ebd, we changed the behaviour to
applying the local flags to cabal install targets, but it used the
literal target string as a package name to which the flags were
additionally applied.

However, `cabal install` targets are NOT necessarily package names, so,
e.g., if we did `cabal install exe:mycomp`, the local flags would not
apply since "exe:mycomp" is not a recognized /package/.

The solution is to parse the target selectors first, and apply the local
flags to the package of the resolved targets.

Fixes #7297, #8909, the install part of #7236, #8529, #7832
parent 0e66a4b7
No related branches found
No related tags found
No related merge requests found
...@@ -2,6 +2,7 @@ ...@@ -2,6 +2,7 @@
{-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
-- | cabal-install CLI command: build -- | cabal-install CLI command: build
module Distribution.Client.CmdInstall module Distribution.Client.CmdInstall
...@@ -104,6 +105,7 @@ import Distribution.Client.Types ...@@ -104,6 +105,7 @@ import Distribution.Client.Types
, PackageSpecifier (..) , PackageSpecifier (..)
, SourcePackageDb (..) , SourcePackageDb (..)
, UnresolvedSourcePackage , UnresolvedSourcePackage
, pkgSpecifierTarget
) )
import Distribution.Client.Types.OverwritePolicy import Distribution.Client.Types.OverwritePolicy
( OverwritePolicy (..) ( OverwritePolicy (..)
...@@ -371,7 +373,7 @@ installAction flags@NixStyleFlags{extraFlags = clientInstallFlags', ..} targetSt ...@@ -371,7 +373,7 @@ installAction flags@NixStyleFlags{extraFlags = clientInstallFlags', ..} targetSt
-- First, we need to learn about what's available to be installed. -- First, we need to learn about what's available to be installed.
localBaseCtx <- localBaseCtx <-
establishProjectBaseContext reducedVerbosity cliConfig InstallCommand establishProjectBaseContext reducedVerbosity baseCliConfig InstallCommand
let localDistDirLayout = distDirLayout localBaseCtx let localDistDirLayout = distDirLayout localBaseCtx
pkgDb <- pkgDb <-
projectConfigWithBuilderRepoContext projectConfigWithBuilderRepoContext
...@@ -432,7 +434,7 @@ installAction flags@NixStyleFlags{extraFlags = clientInstallFlags', ..} targetSt ...@@ -432,7 +434,7 @@ installAction flags@NixStyleFlags{extraFlags = clientInstallFlags', ..} targetSt
withoutProject globalConfig = do withoutProject globalConfig = do
tss <- traverse (parseWithoutProjectTargetSelector verbosity) targetStrings' tss <- traverse (parseWithoutProjectTargetSelector verbosity) targetStrings'
let let
projectConfig = globalConfig <> cliConfig projectConfig = globalConfig <> baseCliConfig
ProjectConfigBuildOnly ProjectConfigBuildOnly
{ projectConfigLogsDir { projectConfigLogsDir
...@@ -478,10 +480,17 @@ installAction flags@NixStyleFlags{extraFlags = clientInstallFlags', ..} targetSt ...@@ -478,10 +480,17 @@ installAction flags@NixStyleFlags{extraFlags = clientInstallFlags', ..} targetSt
return (packageSpecifiers, uris, packageTargets, projectConfig) return (packageSpecifiers, uris, packageTargets, projectConfig)
(specs, uris, targetSelectors, config) <- (specs, uris, targetSelectors, baseConfig) <-
withProjectOrGlobalConfig verbosity ignoreProject globalConfigFlag withProject withoutProject withProjectOrGlobalConfig verbosity ignoreProject globalConfigFlag withProject withoutProject
-- We compute the base context again to determine packages available in the
-- project to be installed, so we can list the available package names when
-- the "all:..." variants of the target selectors are used.
localPkgs <- localPackages <$> establishProjectBaseContext verbosity baseConfig InstallCommand
let let
config = addLocalConfigToPkgs baseConfig (map pkgSpecifierTarget specs ++ concatMap (targetPkgNames localPkgs) targetSelectors)
ProjectConfig ProjectConfig
{ projectConfigBuildOnly = { projectConfigBuildOnly =
ProjectConfigBuildOnly ProjectConfigBuildOnly
...@@ -631,8 +640,7 @@ installAction flags@NixStyleFlags{extraFlags = clientInstallFlags', ..} targetSt ...@@ -631,8 +640,7 @@ installAction flags@NixStyleFlags{extraFlags = clientInstallFlags', ..} targetSt
globalFlags globalFlags
flags{configFlags = configFlags'} flags{configFlags = configFlags'}
clientInstallFlags' clientInstallFlags'
cliConfig = addLocalConfigToTargets baseCliConfig targetStrings globalConfigFlag = projectConfigConfigFile (projectConfigShared baseCliConfig)
globalConfigFlag = projectConfigConfigFile (projectConfigShared cliConfig)
-- Do the install action for each executable in the install configuration. -- Do the install action for each executable in the install configuration.
traverseInstall :: InstallAction -> InstallCfg -> IO () traverseInstall :: InstallAction -> InstallCfg -> IO ()
...@@ -641,9 +649,9 @@ installAction flags@NixStyleFlags{extraFlags = clientInstallFlags', ..} targetSt ...@@ -641,9 +649,9 @@ installAction flags@NixStyleFlags{extraFlags = clientInstallFlags', ..} targetSt
actionOnExe <- action v overwritePolicy <$> prepareExeInstall cfg actionOnExe <- action v overwritePolicy <$> prepareExeInstall cfg
traverse_ actionOnExe . Map.toList $ targetsMap buildCtx traverse_ actionOnExe . Map.toList $ targetsMap buildCtx
-- | Treat all direct targets of install command as local packages: #8637 -- | Treat all direct targets of install command as local packages: #8637 and later #7297, #8909, #7236.
addLocalConfigToTargets :: ProjectConfig -> [String] -> ProjectConfig addLocalConfigToPkgs :: ProjectConfig -> [PackageName] -> ProjectConfig
addLocalConfigToTargets config targetStrings = addLocalConfigToPkgs config pkgs =
config config
{ projectConfigSpecificPackage = { projectConfigSpecificPackage =
projectConfigSpecificPackage config projectConfigSpecificPackage config
...@@ -651,7 +659,25 @@ addLocalConfigToTargets config targetStrings = ...@@ -651,7 +659,25 @@ addLocalConfigToTargets config targetStrings =
} }
where where
localConfig = projectConfigLocalPackages config localConfig = projectConfigLocalPackages config
targetPackageConfigs = map (\x -> (mkPackageName x, localConfig)) targetStrings targetPackageConfigs = map (,localConfig) pkgs
targetPkgNames
:: [PackageSpecifier UnresolvedSourcePackage]
-- ^ The local packages, to resolve 'TargetAllPackages' selectors
-> TargetSelector
-> [PackageName]
targetPkgNames localPkgs = \case
TargetPackage _ pkgIds _ -> map pkgName pkgIds
TargetPackageNamed name _ -> [name]
TargetAllPackages _ -> map pkgSpecifierTarget localPkgs
-- Note how the target may select a component only, but we will always apply
-- the local flags to the whole package in which that component is contained.
-- The reason is that our finest level of configuration is per-package, so
-- there is no interface to configure options to a component only. It is not
-- trivial to say whether we could indeed support per-component configuration
-- because of legacy packages which we may always have to build whole.
TargetComponent pkgId _ _ -> [pkgName pkgId]
TargetComponentUnknown name _ _ -> [name]
-- | Verify that invalid config options were not passed to the install command. -- | Verify that invalid config options were not passed to the install command.
-- --
......
{-# LANGUAGE CPP #-}
#ifdef TEST1
main = putStrLn "hi1"
#endif
#ifdef TEST2
main = putStrLn "hi2"
#endif
#ifdef TEST3
main = putStrLn "hi3"
#endif
#ifdef TEST4
main = putStrLn "hi4"
#endif
#ifdef TEST5
main = putStrLn "hi5"
#endif
#ifdef TEST6
main = putStrLn "hi6"
#endif
packages: .
import Test.Cabal.Prelude
main = cabalTest $ do
env <- getTestEnv
recordMode DoNotRecord $ do
let
installdir = testPrefixDir env </> "bin"
commonOpts v = ["--ghc-options=-DTEST" ++ show v, "--overwrite-policy=always", "--installdir=" ++ installdir]
installWithTgt tgt v = do
cabal "install" (tgt:commonOpts v)
runInstalledExe' "my-exe" []
>>= assertOutputContains ("hi" ++ show v)
cabal "install" (commonOpts 1) -- no target
runInstalledExe' "my-exe" []
>>= assertOutputContains "hi1"
installWithTgt "t7297-89097236a" 2
installWithTgt "exe:my-exe" 3
installWithTgt "my-exe" 4
installWithTgt "all" 5
installWithTgt "all:exes" 6
name: t7297-89097236a
version: 1.0
build-type: Simple
cabal-version: >= 1.2
executable my-exe
main-is: Main.hs
build-depends: base
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