Correctly provision build tools in all situations
[cabal.git] / cabal-install / src / Distribution / Client / CmdInstall.hs
bloba154eff3ce9aa70586df7972e20e190631e09497
1 {-# LANGUAGE LambdaCase #-}
2 {-# LANGUAGE NamedFieldPuns #-}
3 {-# LANGUAGE RecordWildCards #-}
4 {-# LANGUAGE ScopedTypeVariables #-}
5 {-# LANGUAGE TupleSections #-}
7 -- | cabal-install CLI command: build
8 module Distribution.Client.CmdInstall
9 ( -- * The @build@ CLI and action
10 installCommand
11 , installAction
13 -- * Internals exposed for testing
14 , selectPackageTargets
15 , selectComponentTarget
17 -- * Internals exposed for CmdRepl + CmdRun
18 , establishDummyDistDirLayout
19 , establishDummyProjectBaseContext
20 ) where
22 import Distribution.Client.Compat.Prelude
23 import Distribution.Compat.Directory
24 ( doesPathExist
26 import Prelude ()
28 import Distribution.Client.CmdErrorMessages
29 import Distribution.Client.CmdSdist
30 import Distribution.Client.ProjectOrchestration
31 import Distribution.Client.TargetProblem
32 ( TargetProblem (..)
33 , TargetProblem'
36 import Distribution.Client.CmdInstall.ClientInstallFlags
37 import Distribution.Client.CmdInstall.ClientInstallTargetSelector
39 import Distribution.Client.Config
40 ( SavedConfig (..)
41 , defaultInstallPath
42 , loadConfig
44 import Distribution.Client.DistDirLayout
45 ( CabalDirLayout (..)
46 , DistDirLayout (..)
47 , StoreDirLayout (..)
48 , cabalStoreDirLayout
49 , mkCabalDirLayout
51 import Distribution.Client.IndexUtils
52 ( getInstalledPackages
53 , getSourcePackages
55 import qualified Distribution.Client.InstallPlan as InstallPlan
56 import Distribution.Client.InstallSymlink
57 ( Symlink (..)
58 , promptRun
59 , symlinkBinary
60 , symlinkableBinary
61 , trySymlink
63 import Distribution.Client.NixStyleOptions
64 ( NixStyleFlags (..)
65 , defaultNixStyleFlags
66 , nixStyleOptions
68 import Distribution.Client.ProjectConfig
69 ( ProjectPackageLocation (..)
70 , fetchAndReadSourcePackages
71 , projectConfigWithBuilderRepoContext
72 , resolveBuildTimeSettings
73 , withGlobalConfig
74 , withProjectOrGlobalConfig
76 import Distribution.Client.ProjectConfig.Types
77 ( MapMappend (..)
78 , PackageConfig (..)
79 , ProjectConfig (..)
80 , ProjectConfigBuildOnly (..)
81 , ProjectConfigShared (..)
82 , getMapLast
83 , getMapMappend
84 , projectConfigBuildOnly
85 , projectConfigConfigFile
86 , projectConfigLogsDir
87 , projectConfigStoreDir
89 import Distribution.Client.ProjectFlags (ProjectFlags (..))
90 import Distribution.Client.ProjectPlanning
91 ( storePackageInstallDirs'
93 import Distribution.Client.ProjectPlanning.Types
94 ( ElaboratedInstallPlan
96 import Distribution.Client.RebuildMonad
97 ( runRebuild
99 import Distribution.Client.Setup
100 ( CommonSetupFlags (..)
101 , ConfigFlags (..)
102 , GlobalFlags (..)
103 , InstallFlags (..)
105 import Distribution.Client.Types
106 ( PackageLocation (..)
107 , PackageSpecifier (..)
108 , SourcePackageDb (..)
109 , UnresolvedSourcePackage
110 , mkNamedPackage
111 , pkgSpecifierTarget
113 import Distribution.Client.Types.OverwritePolicy
114 ( OverwritePolicy (..)
116 import Distribution.Package
117 ( Package (..)
118 , PackageName
119 , mkPackageName
120 , unPackageName
122 import Distribution.Simple.BuildPaths
123 ( exeExtension
125 import Distribution.Simple.Command
126 ( CommandUI (..)
127 , optionName
128 , usageAlternatives
130 import Distribution.Simple.Compiler
131 ( Compiler (..)
132 , CompilerFlavor (..)
133 , CompilerId (..)
134 , PackageDB (..)
135 , PackageDBStack
137 import Distribution.Simple.Configure
138 ( configCompilerEx
140 import Distribution.Simple.Flag
141 ( flagElim
142 , flagToMaybe
143 , fromFlagOrDefault
145 import Distribution.Simple.GHC
146 ( GhcEnvironmentFileEntry (..)
147 , GhcImplInfo (..)
148 , ParseErrorExc
149 , getGhcAppDir
150 , getImplInfo
151 , ghcPlatformAndVersionString
152 , readGhcEnvironmentFile
153 , renderGhcEnvironmentFile
155 import qualified Distribution.Simple.InstallDirs as InstallDirs
156 import qualified Distribution.Simple.PackageIndex as PI
157 import Distribution.Simple.Program.Db
158 ( defaultProgramDb
159 , prependProgramSearchPath
160 , userSpecifyArgss
161 , userSpecifyPaths
163 import Distribution.Simple.Setup
164 ( Flag (..)
165 , installDirsOptions
167 import Distribution.Simple.Utils
168 ( createDirectoryIfMissingVerbose
169 , dieWithException
170 , notice
171 , ordNub
172 , safeHead
173 , warn
174 , withTempDirectory
175 , wrapText
177 import Distribution.Solver.Types.PackageConstraint
178 ( PackageProperty (..)
180 import Distribution.Solver.Types.PackageIndex
181 ( lookupPackageName
182 , searchByName
184 import Distribution.Solver.Types.SourcePackage
185 ( SourcePackage (..)
187 import Distribution.System
188 ( OS (Windows)
189 , Platform
190 , buildOS
192 import Distribution.Types.InstalledPackageInfo
193 ( InstalledPackageInfo (..)
195 import Distribution.Types.PackageId
196 ( PackageIdentifier (..)
198 import Distribution.Types.UnitId
199 ( UnitId
201 import Distribution.Types.UnqualComponentName
202 ( UnqualComponentName
203 , unUnqualComponentName
205 import Distribution.Types.Version
206 ( Version
207 , nullVersion
209 import Distribution.Types.VersionRange
210 ( thisVersion
212 import Distribution.Utils.Generic
213 ( writeFileAtomic
215 import Distribution.Verbosity
216 ( lessVerbose
217 , normal
220 import qualified Data.ByteString.Lazy.Char8 as BS
221 import qualified Data.List.NonEmpty as NE
222 import qualified Data.Map as Map
223 import Data.Ord
224 ( Down (..)
226 import qualified Data.Set as S
227 import Distribution.Client.Errors
228 import Distribution.Utils.NubList
229 ( fromNubList
231 import Network.URI (URI)
232 import System.Directory
233 ( copyFile
234 , createDirectoryIfMissing
235 , doesDirectoryExist
236 , doesFileExist
237 , getTemporaryDirectory
238 , makeAbsolute
239 , removeDirectory
240 , removeFile
242 import System.FilePath
243 ( takeBaseName
244 , takeDirectory
245 , (<.>)
246 , (</>)
249 -- | Check or check then install an exe. The check is to see if the overwrite
250 -- policy allows installation.
251 data InstallCheck
252 = -- | Only check if install is permitted.
253 InstallCheckOnly
254 | -- | Actually install but check first if permitted.
255 InstallCheckInstall
257 type InstallAction =
258 Verbosity
259 -> OverwritePolicy
260 -> InstallExe
261 -> (UnitId, [(ComponentTarget, NonEmpty TargetSelector)])
262 -> IO ()
264 data InstallCfg = InstallCfg
265 { verbosity :: Verbosity
266 , baseCtx :: ProjectBaseContext
267 , buildCtx :: ProjectBuildContext
268 , platform :: Platform
269 , compiler :: Compiler
270 , installConfigFlags :: ConfigFlags
271 , installClientFlags :: ClientInstallFlags
274 -- | A record of install method, install directory and file path functions
275 -- needed by actions that either check if an install is possible or actually
276 -- perform an installation. This is for installation of executables only.
277 data InstallExe = InstallExe
278 { installMethod :: InstallMethod
279 , installDir :: FilePath
280 , mkSourceBinDir :: UnitId -> FilePath
281 -- ^ A function to get an UnitId's store directory.
282 , mkExeName :: UnqualComponentName -> FilePath
283 -- ^ A function to get an exe's filename.
284 , mkFinalExeName :: UnqualComponentName -> FilePath
285 -- ^ A function to get an exe's final possibly different to the name in the
286 -- store.
289 installCommand :: CommandUI (NixStyleFlags ClientInstallFlags)
290 installCommand =
291 CommandUI
292 { commandName = "v2-install"
293 , commandSynopsis = "Install packages."
294 , commandUsage =
295 usageAlternatives
296 "v2-install"
297 ["[TARGETS] [FLAGS]"]
298 , commandDescription = Just $ \_ ->
299 wrapText $
300 "Installs one or more packages. This is done by installing them "
301 ++ "in the store and symlinking or copying the executables in the directory "
302 ++ "specified by the --installdir flag (`~/.local/bin/` by default). "
303 ++ "If you want the installed executables to be available globally, "
304 ++ "make sure that the PATH environment variable contains that directory. "
305 ++ "\n\n"
306 ++ "If TARGET is a library and --lib (provisional) is used, "
307 ++ "it will be added to the global environment. "
308 ++ "When doing this, cabal will try to build a plan that includes all "
309 ++ "the previously installed libraries. This is currently not implemented."
310 , commandNotes = Just $ \pname ->
311 "Examples:\n"
312 ++ " "
313 ++ pname
314 ++ " v2-install\n"
315 ++ " Install the package in the current directory\n"
316 ++ " "
317 ++ pname
318 ++ " v2-install pkgname\n"
319 ++ " Install the package named pkgname"
320 ++ " (fetching it from hackage if necessary)\n"
321 ++ " "
322 ++ pname
323 ++ " v2-install ./pkgfoo\n"
324 ++ " Install the package in the ./pkgfoo directory\n"
325 , commandOptions = \x -> filter notInstallDirOpt $ nixStyleOptions clientInstallOptions x
326 , commandDefaultFlags = defaultNixStyleFlags defaultClientInstallFlags
328 where
329 -- install doesn't take installDirs flags, since it always installs into the store in a fixed way.
330 notInstallDirOpt x = not $ optionName x `elem` installDirOptNames
331 installDirOptNames = map optionName installDirsOptions
333 -- | The @install@ command actually serves four different needs. It installs:
334 -- * exes:
335 -- For example a program from hackage. The behavior is similar to the old
336 -- install command, except that now conflicts between separate runs of the
337 -- command are impossible thanks to the store.
338 -- Exes are installed in the store like a normal dependency, then they are
339 -- symlinked/copied in the directory specified by --installdir.
340 -- To do this we need a dummy projectBaseContext containing the targets as
341 -- extra packages and using a temporary dist directory.
342 -- * libraries
343 -- Libraries install through a similar process, but using GHC environment
344 -- files instead of symlinks. This means that 'v2-install'ing libraries
345 -- only works on GHC >= 8.0.
347 -- For more details on how this works, see the module
348 -- "Distribution.Client.ProjectOrchestration"
349 installAction :: NixStyleFlags ClientInstallFlags -> [String] -> GlobalFlags -> IO ()
350 installAction flags@NixStyleFlags{extraFlags, configFlags, installFlags, projectFlags} targetStrings globalFlags = do
351 -- Ensure there were no invalid configuration options specified.
352 verifyPreconditionsOrDie verbosity configFlags'
354 -- We cannot use establishDummyProjectBaseContext to get these flags, since
355 -- it requires one of them as an argument. Normal establishProjectBaseContext
356 -- does not, and this is why this is done only for the install command
357 clientInstallFlags <- getClientInstallFlags verbosity globalFlags extraFlags
359 installLibs = fromFlagOrDefault False (cinstInstallLibs clientInstallFlags)
361 normalisedTargetStrings = if null targetStrings then ["."] else targetStrings
363 -- Note the logic here is rather goofy. Target selectors of the form "foo:bar" also parse as uris.
364 -- However, we want install to also take uri arguments. Hence, we only parse uri arguments in the case where
365 -- no project file is present (including an implicit one derived from being in a package directory)
366 -- or where the --ignore-project flag is passed explicitly. In such a case we only parse colon-free target selectors
367 -- as selectors, and otherwise parse things as URIs.
369 -- However, in the special case where --ignore-project is passed with no selectors, we want to act as though this is
370 -- a "normal" ignore project that actually builds and installs the selected package.
372 (pkgSpecs, uris, targetSelectors, config) <-
374 with = do
375 (pkgSpecs, targetSelectors, baseConfig) <-
376 withProject verbosity cliConfig normalisedTargetStrings installLibs
377 -- No URIs in this case, see note above
378 return (pkgSpecs, [], targetSelectors, baseConfig)
380 without =
381 withGlobalConfig verbosity globalConfigFlag $ \globalConfig ->
382 withoutProject verbosity (globalConfig <> cliConfig) normalisedTargetStrings
384 -- If there's no targets it does not make sense to not be in a project.
385 if null targetStrings
386 then with
387 else withProjectOrGlobalConfig ignoreProject with without
389 -- NOTE: CmdInstall and project local packages.
391 -- CmdInstall always installs packages from a source distribution that, in case of unpackage
392 -- pacakges, is created automatically. This is implemented in getSpecsAndTargetSelectors.
394 -- This has the inconvenience that the planner will consider all packages as non-local
395 -- (see `ProjectPlanning.shouldBeLocal`) and that any project or cli configuration will
396 -- not apply to them.
398 -- We rectify this here. In the project configuration, we copy projectConfigLocalPackages to a
399 -- new projectConfigSpecificPackage entry for each package corresponding to a target selector.
401 -- See #8637 and later #7297, #8909, #7236.
404 ProjectConfig
405 { projectConfigBuildOnly =
406 ProjectConfigBuildOnly
407 { projectConfigLogsDir
409 , projectConfigShared =
410 ProjectConfigShared
411 { projectConfigHcFlavor
412 , projectConfigHcPath
413 , projectConfigHcPkg
414 , projectConfigStoreDir
415 , projectConfigProgPathExtra
416 , projectConfigPackageDBs
418 , projectConfigLocalPackages =
419 PackageConfig
420 { packageConfigProgramPaths
421 , packageConfigProgramArgs
422 , packageConfigProgramPathExtra
424 } = config
426 hcFlavor = flagToMaybe projectConfigHcFlavor
427 hcPath = flagToMaybe projectConfigHcPath
428 hcPkg = flagToMaybe projectConfigHcPkg
429 extraPath = fromNubList packageConfigProgramPathExtra ++ fromNubList projectConfigProgPathExtra
431 configProgDb <- prependProgramSearchPath verbosity extraPath [] defaultProgramDb
433 -- ProgramDb with directly user specified paths
434 preProgDb =
435 userSpecifyPaths (Map.toList (getMapLast packageConfigProgramPaths))
436 . userSpecifyArgss (Map.toList (getMapMappend packageConfigProgramArgs))
437 $ configProgDb
439 -- progDb is a program database with compiler tools configured properly
440 (compiler@Compiler{compilerId = CompilerId compilerFlavor compilerVersion}, platform, progDb) <-
441 configCompilerEx hcFlavor hcPath hcPkg preProgDb verbosity
444 GhcImplInfo{supportsPkgEnvFiles} = getImplInfo compiler
446 (usedPackageEnvFlag, envFile) <- getEnvFile clientInstallFlags platform compilerVersion
447 (usedExistingPkgEnvFile, existingEnvEntries) <-
448 getExistingEnvEntries verbosity compilerFlavor supportsPkgEnvFiles envFile
449 packageDbs <- getPackageDbStack compiler projectConfigStoreDir projectConfigLogsDir projectConfigPackageDBs
450 installedIndex <- getInstalledPackages verbosity compiler packageDbs progDb
453 (envSpecs, nonGlobalEnvEntries) =
454 getEnvSpecsAndNonGlobalEntries installedIndex existingEnvEntries installLibs
456 -- Second, we need to use a fake project to let Cabal build the
457 -- installables correctly. For that, we need a place to put a
458 -- temporary dist directory.
459 globalTmp <- getTemporaryDirectory
461 withTempDirectory verbosity globalTmp "cabal-install." $ \tmpDir -> do
462 distDirLayout <- establishDummyDistDirLayout verbosity config tmpDir
464 uriSpecs <-
465 runRebuild tmpDir $
466 fetchAndReadSourcePackages
467 verbosity
468 distDirLayout
469 (projectConfigShared config)
470 (projectConfigBuildOnly config)
471 [ProjectPackageRemoteTarball uri | uri <- uris]
473 -- check for targets already in env
474 let getPackageName :: PackageSpecifier UnresolvedSourcePackage -> PackageName
475 getPackageName = pkgSpecifierTarget
476 targetNames = S.fromList $ map getPackageName (pkgSpecs ++ uriSpecs)
477 envNames = S.fromList $ map getPackageName envSpecs
478 forceInstall = fromFlagOrDefault False $ installOverrideReinstall installFlags
479 nameIntersection = S.intersection targetNames envNames
481 -- we check for intersections in targets with the existing env
482 (envSpecs', nonGlobalEnvEntries') <-
483 if null nameIntersection
484 then pure (envSpecs, map snd nonGlobalEnvEntries)
485 else
486 if forceInstall
487 then
488 let es = filter (\e -> not $ getPackageName e `S.member` nameIntersection) envSpecs
489 nge = map snd . filter (\e -> not $ fst e `S.member` nameIntersection) $ nonGlobalEnvEntries
490 in pure (es, nge)
491 else dieWithException verbosity $ PackagesAlreadyExistInEnvfile envFile (map prettyShow $ S.toList nameIntersection)
493 -- we construct an installed index of files in the cleaned target environment (absent overwrites) so that
494 -- we can solve with regards to packages installed locally but not in the upstream repo
495 let installedPacks = PI.allPackagesByName installedIndex
496 newEnvNames = S.fromList $ map getPackageName envSpecs'
497 installedIndex' = PI.fromList . concatMap snd . filter (\p -> fst p `S.member` newEnvNames) $ installedPacks
499 baseCtx <-
500 establishDummyProjectBaseContext
501 verbosity
502 config
503 distDirLayout
504 (envSpecs' ++ pkgSpecs ++ uriSpecs)
505 InstallCommand
507 buildCtx <- constructProjectBuildContext verbosity (baseCtx{installedPackages = Just installedIndex'}) targetSelectors
509 printPlan verbosity baseCtx buildCtx
510 let installCfg = InstallCfg verbosity baseCtx buildCtx platform compiler configFlags clientInstallFlags
513 dryRun =
514 buildSettingDryRun (buildSettings baseCtx)
515 || buildSettingOnlyDownload (buildSettings baseCtx)
517 -- Before building, check if we could install any built exe by symlinking or
518 -- copying it?
519 unless
520 (dryRun || installLibs)
521 (traverseInstall (installCheckUnitExes InstallCheckOnly) installCfg)
523 buildOutcomes <- runProjectBuildPhase verbosity baseCtx buildCtx
524 runProjectPostBuildPhase verbosity baseCtx buildCtx buildOutcomes
526 -- Having built everything, do the install.
527 unless dryRun $
528 if installLibs
529 then
530 installLibraries
531 verbosity
532 buildCtx
533 installedIndex
534 compiler
535 packageDbs
536 envFile
537 nonGlobalEnvEntries'
538 (not usedExistingPkgEnvFile && not usedPackageEnvFlag)
539 else -- Install any built exe by symlinking or copying it we don't use
540 -- BuildOutcomes because we also need the component names
541 traverseInstall (installCheckUnitExes InstallCheckInstall) installCfg
542 where
543 configFlags' = disableTestsBenchsByDefault configFlags
544 verbosity = fromFlagOrDefault normal (setupVerbosity $ configCommonFlags configFlags')
545 ignoreProject = flagIgnoreProject projectFlags
546 cliConfig =
547 commandLineFlagsToProjectConfig
548 globalFlags
549 flags{configFlags = configFlags'}
550 extraFlags
552 globalConfigFlag = projectConfigConfigFile (projectConfigShared cliConfig)
554 -- Do the install action for each executable in the install configuration.
555 traverseInstall :: InstallAction -> InstallCfg -> IO ()
556 traverseInstall action cfg@InstallCfg{verbosity = v, buildCtx, installClientFlags} = do
557 let overwritePolicy = fromFlagOrDefault NeverOverwrite $ cinstOverwritePolicy installClientFlags
558 actionOnExe <- action v overwritePolicy <$> prepareExeInstall cfg
559 traverse_ actionOnExe . Map.toList $ targetsMap buildCtx
561 withProject
562 :: Verbosity
563 -> ProjectConfig
564 -> [String]
565 -> Bool
566 -> IO ([PackageSpecifier UnresolvedSourcePackage], [TargetSelector], ProjectConfig)
567 withProject verbosity cliConfig targetStrings installLibs = do
568 -- First, we need to learn about what's available to be installed.
569 baseCtx <- establishProjectBaseContext reducedVerbosity cliConfig InstallCommand
571 (pkgSpecs, targetSelectors) <-
572 -- If every target is already resolved to a package id, we can return without any further parsing.
573 if null unresolvedTargetStrings
574 then return (parsedPkgSpecs, parsedTargets)
575 else do
576 -- Anything that could not be parsed as a packageId (e.g. a package name without a version or
577 -- a target syntax using colons) must be resolved inside the project context.
578 (resolvedPkgSpecs, resolvedTargets) <-
579 resolveTargetSelectorsInProjectBaseContext verbosity baseCtx unresolvedTargetStrings targetFilter
580 return (resolvedPkgSpecs ++ parsedPkgSpecs, resolvedTargets ++ parsedTargets)
582 -- Apply the local configuration (e.g. cli flags) to all direct targets of install command, see note
583 -- in 'installAction'.
585 -- NOTE: If a target string had to be resolved inside the project context, then pkgSpecs will include
586 -- the project packages turned into source distributions (getSpecsAndTargetSelectors does this).
587 -- We want to apply the local configuration only to the actual targets.
588 let config =
589 addLocalConfigToPkgs (projectConfig baseCtx) $
590 concatMap (targetPkgNames $ localPackages baseCtx) targetSelectors
591 return (pkgSpecs, targetSelectors, config)
592 where
593 reducedVerbosity = lessVerbose verbosity
595 -- We take the targets and try to parse them as package ids (with name and version).
596 -- The ones who don't parse will have to be resolved in the project context.
597 (unresolvedTargetStrings, parsedPackageIds) =
598 partitionEithers $
599 flip map targetStrings $ \s ->
600 case eitherParsec s of
601 Right pkgId@PackageIdentifier{pkgVersion}
602 | pkgVersion /= nullVersion ->
603 pure pkgId
604 _ -> Left s
606 -- For each packageId, we output a NamedPackage specifier (i.e. a package only known by
607 -- its name) and a target selector.
608 (parsedPkgSpecs, parsedTargets) =
609 unzip
610 [ (mkNamedPackage pkgId, TargetPackageNamed (pkgName pkgId) targetFilter)
611 | pkgId <- parsedPackageIds
614 targetFilter = if installLibs then Just LibKind else Just ExeKind
616 resolveTargetSelectorsInProjectBaseContext
617 :: Verbosity
618 -> ProjectBaseContext
619 -> [String]
620 -> Maybe ComponentKindFilter
621 -> IO ([PackageSpecifier UnresolvedSourcePackage], [TargetSelector])
622 resolveTargetSelectorsInProjectBaseContext verbosity baseCtx targetStrings targetFilter = do
623 let reducedVerbosity = lessVerbose verbosity
625 sourcePkgDb <-
626 projectConfigWithBuilderRepoContext
627 reducedVerbosity
628 (buildSettings baseCtx)
629 (getSourcePackages verbosity)
631 targetSelectors <-
632 readTargetSelectors (localPackages baseCtx) Nothing targetStrings
633 >>= \case
634 Left problems -> reportTargetSelectorProblems verbosity problems
635 Right ts -> return ts
637 getSpecsAndTargetSelectors
638 verbosity
639 reducedVerbosity
640 sourcePkgDb
641 targetSelectors
642 (distDirLayout baseCtx)
643 baseCtx
644 targetFilter
646 withoutProject
647 :: Verbosity
648 -> ProjectConfig
649 -> [String]
650 -> IO ([PackageSpecifier UnresolvedSourcePackage], [URI], [TargetSelector], ProjectConfig)
651 withoutProject verbosity globalConfig targetStrings = do
652 tss <- traverse (parseWithoutProjectTargetSelector verbosity) targetStrings
654 ProjectConfigBuildOnly
655 { projectConfigLogsDir
656 } = projectConfigBuildOnly globalConfig
658 ProjectConfigShared
659 { projectConfigStoreDir
660 } = projectConfigShared globalConfig
662 mlogsDir = flagToMaybe projectConfigLogsDir
663 mstoreDir = flagToMaybe projectConfigStoreDir
665 cabalDirLayout <- mkCabalDirLayout mstoreDir mlogsDir
667 let buildSettings = resolveBuildTimeSettings verbosity cabalDirLayout globalConfig
669 SourcePackageDb{packageIndex} <-
670 projectConfigWithBuilderRepoContext
671 verbosity
672 buildSettings
673 (getSourcePackages verbosity)
675 for_ (concatMap woPackageNames tss) $ \name -> do
676 when (null (lookupPackageName packageIndex name)) $ do
677 let xs = searchByName packageIndex (unPackageName name)
678 let emptyIf True _ = []
679 emptyIf False zs = zs
680 str2 =
681 emptyIf
682 (null xs)
683 [ "Did you mean any of the following?\n"
684 , unlines (("- " ++) . unPackageName . fst <$> xs)
686 dieWithException verbosity $ WithoutProject (unPackageName name) str2
689 packageSpecifiers :: [PackageSpecifier UnresolvedSourcePackage]
690 (uris, packageSpecifiers) = partitionEithers $ map woPackageSpecifiers tss
691 packageTargets = map woPackageTargets tss
693 -- Apply the local configuration (e.g. cli flags) to all direct targets of install command,
694 -- see note in 'installAction'
695 let config = addLocalConfigToPkgs globalConfig (concatMap woPackageNames tss)
696 return (packageSpecifiers, uris, packageTargets, config)
698 addLocalConfigToPkgs :: ProjectConfig -> [PackageName] -> ProjectConfig
699 addLocalConfigToPkgs config pkgs =
700 config
701 { projectConfigSpecificPackage =
702 projectConfigSpecificPackage config
703 <> MapMappend (Map.fromList targetPackageConfigs)
705 where
706 localConfig = projectConfigLocalPackages config
707 targetPackageConfigs = map (,localConfig) pkgs
709 targetPkgNames
710 :: [PackageSpecifier UnresolvedSourcePackage]
711 -- ^ The local packages, to resolve 'TargetAllPackages' selectors
712 -> TargetSelector
713 -> [PackageName]
714 targetPkgNames localPkgs = \case
715 TargetPackage _ pkgIds _ -> map pkgName pkgIds
716 TargetPackageNamed name _ -> [name]
717 TargetAllPackages _ -> map pkgSpecifierTarget localPkgs
718 -- Note how the target may select a component only, but we will always apply
719 -- the local flags to the whole package in which that component is contained.
720 -- The reason is that our finest level of configuration is per-package, so
721 -- there is no interface to configure options to a component only. It is not
722 -- trivial to say whether we could indeed support per-component configuration
723 -- because of legacy packages which we may always have to build whole.
724 TargetComponent pkgId _ _ -> [pkgName pkgId]
725 TargetComponentUnknown name _ _ -> [name]
727 -- | Verify that invalid config options were not passed to the install command.
729 -- If an invalid configuration is found the command will @dieWithException@.
730 verifyPreconditionsOrDie :: Verbosity -> ConfigFlags -> IO ()
731 verifyPreconditionsOrDie verbosity configFlags = do
732 -- We never try to build tests/benchmarks for remote packages.
733 -- So we set them as disabled by default and error if they are explicitly
734 -- enabled.
735 when (configTests configFlags == Flag True) $
736 dieWithException verbosity ConfigTests
737 when (configBenchmarks configFlags == Flag True) $
738 dieWithException verbosity ConfigBenchmarks
740 -- | Apply the given 'ClientInstallFlags' on top of one coming from the global configuration.
741 getClientInstallFlags :: Verbosity -> GlobalFlags -> ClientInstallFlags -> IO ClientInstallFlags
742 getClientInstallFlags verbosity globalFlags existingClientInstallFlags = do
743 let configFileFlag = globalConfigFile globalFlags
744 savedConfig <- loadConfig verbosity configFileFlag
745 pure $ savedClientInstallFlags savedConfig `mappend` existingClientInstallFlags
747 getSpecsAndTargetSelectors
748 :: Verbosity
749 -> Verbosity
750 -> SourcePackageDb
751 -> [TargetSelector]
752 -> DistDirLayout
753 -> ProjectBaseContext
754 -> Maybe ComponentKindFilter
755 -> IO ([PackageSpecifier UnresolvedSourcePackage], [TargetSelector])
756 getSpecsAndTargetSelectors verbosity reducedVerbosity sourcePkgDb targetSelectors distDirLayout baseCtx targetFilter =
757 withInstallPlan reducedVerbosity baseCtx $ \elaboratedPlan _ -> do
758 -- Split into known targets and hackage packages.
759 (targetsMap, hackageNames) <-
760 partitionToKnownTargetsAndHackagePackages
761 verbosity
762 sourcePkgDb
763 elaboratedPlan
764 targetSelectors
767 planMap = InstallPlan.toMap elaboratedPlan
769 sdistize (SpecificSourcePackage spkg) =
770 SpecificSourcePackage spkg'
771 where
772 sdistPath = distSdistFile distDirLayout (packageId spkg)
773 spkg' = spkg{srcpkgSource = LocalTarballPackage sdistPath}
774 sdistize named = named
776 localPkgs = sdistize <$> localPackages baseCtx
778 gatherTargets :: UnitId -> TargetSelector
779 gatherTargets targetId = TargetPackageNamed pkgName targetFilter
780 where
781 targetUnit = Map.findWithDefault (error "cannot find target unit") targetId planMap
782 PackageIdentifier{..} = packageId targetUnit
784 localTargets = map gatherTargets (Map.keys targetsMap)
786 hackagePkgs :: [PackageSpecifier UnresolvedSourcePackage]
787 hackagePkgs = [NamedPackage pn [] | pn <- hackageNames]
789 hackageTargets :: [TargetSelector]
790 hackageTargets = [TargetPackageNamed pn targetFilter | pn <- hackageNames]
792 createDirectoryIfMissing True (distSdistDirectory distDirLayout)
794 unless (Map.null targetsMap) $ for_ (localPackages baseCtx) $ \case
795 SpecificSourcePackage pkg ->
796 packageToSdist
797 verbosity
798 (distProjectRootDirectory distDirLayout)
799 TarGzArchive
800 (distSdistFile distDirLayout (packageId pkg))
802 NamedPackage _ _ ->
803 -- This may happen if 'extra-packages' are listed in the project file.
804 -- We don't need to do extra work for NamedPackages since they will be
805 -- fetched from Hackage rather than locally 'sdistize'-d. Note how,
806 -- below, we already return the local 'sdistize'-d packages together
807 -- with the 'hackagePkgs' (which are 'NamedPackage's), and that
808 -- 'sdistize' is a no-op for 'NamedPackages', meaning the
809 -- 'NamedPackage's in 'localPkgs' will be treated just like
810 -- 'hackagePkgs' as they should.
811 pure ()
813 if null targetsMap
814 then return (hackagePkgs, hackageTargets)
815 else return (localPkgs ++ hackagePkgs, localTargets ++ hackageTargets)
817 -- | Partitions the target selectors into known local targets and hackage packages.
818 partitionToKnownTargetsAndHackagePackages
819 :: Verbosity
820 -> SourcePackageDb
821 -> ElaboratedInstallPlan
822 -> [TargetSelector]
823 -> IO (TargetsMap, [PackageName])
824 partitionToKnownTargetsAndHackagePackages verbosity pkgDb elaboratedPlan targetSelectors = do
825 let mTargets =
826 resolveTargets
827 selectPackageTargets
828 selectComponentTarget
829 elaboratedPlan
830 (Just pkgDb)
831 targetSelectors
832 case mTargets of
833 Right targets ->
834 -- Everything is a local dependency.
835 return (targets, [])
836 Left errs -> do
837 -- Not everything is local.
839 (errs', hackageNames) = partitionEithers . flip fmap errs $ \case
840 TargetAvailableInIndex name -> Right name
841 err -> Left err
843 -- report incorrect case for known package.
844 for_ errs' $ \case
845 TargetNotInProject hn ->
846 case searchByName (packageIndex pkgDb) (unPackageName hn) of
847 [] -> return ()
848 xs ->
849 dieWithException verbosity $ UnknownPackage (unPackageName hn) (("- " ++) . unPackageName . fst <$> xs)
850 _ -> return ()
852 when (not . null $ errs') $ reportBuildTargetProblems verbosity errs'
855 targetSelectors' = flip filter targetSelectors $ \case
856 TargetComponentUnknown name _ _
857 | name `elem` hackageNames -> False
858 TargetPackageNamed name _
859 | name `elem` hackageNames -> False
860 _ -> True
862 -- This can't fail, because all of the errors are
863 -- removed (or we've given up).
864 targets <-
865 either (reportBuildTargetProblems verbosity) return $
866 resolveTargets
867 selectPackageTargets
868 selectComponentTarget
869 elaboratedPlan
870 Nothing
871 targetSelectors'
873 return (targets, hackageNames)
875 constructProjectBuildContext
876 :: Verbosity
877 -> ProjectBaseContext
878 -- ^ The synthetic base context to use to produce the full build context.
879 -> [TargetSelector]
880 -> IO ProjectBuildContext
881 constructProjectBuildContext verbosity baseCtx targetSelectors = do
882 runProjectPreBuildPhase verbosity baseCtx $ \elaboratedPlan -> do
883 -- Interpret the targets on the command line as build targets
884 targets <-
885 either (reportBuildTargetProblems verbosity) return $
886 resolveTargets
887 selectPackageTargets
888 selectComponentTarget
889 elaboratedPlan
890 Nothing
891 targetSelectors
893 let prunedToTargetsElaboratedPlan =
894 pruneInstallPlanToTargets TargetActionBuild targets elaboratedPlan
895 prunedElaboratedPlan <-
896 if buildSettingOnlyDeps (buildSettings baseCtx)
897 then
898 either (reportCannotPruneDependencies verbosity) return $
899 pruneInstallPlanToDependencies
900 (Map.keysSet targets)
901 prunedToTargetsElaboratedPlan
902 else return prunedToTargetsElaboratedPlan
904 return (prunedElaboratedPlan, targets)
906 -- | From an install configuration, prepare the record needed by actions that
907 -- will either check if an install of a single executable is possible or
908 -- actually perform its installation.
909 prepareExeInstall :: InstallCfg -> IO InstallExe
910 prepareExeInstall
911 InstallCfg{verbosity, baseCtx, buildCtx, platform, compiler, installConfigFlags, installClientFlags} = do
912 installPath <- defaultInstallPath
913 let storeDirLayout = cabalStoreDirLayout $ cabalDirLayout baseCtx
915 prefix = fromFlagOrDefault "" (fmap InstallDirs.fromPathTemplate (configProgPrefix installConfigFlags))
916 suffix = fromFlagOrDefault "" (fmap InstallDirs.fromPathTemplate (configProgSuffix installConfigFlags))
918 mkUnitBinDir :: UnitId -> FilePath
919 mkUnitBinDir =
920 InstallDirs.bindir
921 . storePackageInstallDirs' storeDirLayout compiler
923 mkExeName :: UnqualComponentName -> FilePath
924 mkExeName exe = unUnqualComponentName exe <.> exeExtension platform
926 mkFinalExeName :: UnqualComponentName -> FilePath
927 mkFinalExeName exe = prefix <> unUnqualComponentName exe <> suffix <.> exeExtension platform
928 installdirUnknown =
929 "installdir is not defined. Set it in your cabal config file "
930 ++ "or use --installdir=<path>. Using default installdir: "
931 ++ show installPath
933 installdir <-
934 fromFlagOrDefault
935 (warn verbosity installdirUnknown >> pure installPath)
936 $ pure <$> cinstInstalldir installClientFlags
937 createDirectoryIfMissingVerbose verbosity True installdir
938 warnIfNoExes verbosity buildCtx
940 -- This is in IO as we will make environment checks, to decide which install
941 -- method is best.
942 let defaultMethod :: IO InstallMethod
943 defaultMethod
944 -- Try symlinking in temporary directory, if it works default to
945 -- symlinking even on windows.
946 | buildOS == Windows = do
947 symlinks <- trySymlink verbosity
948 return $ if symlinks then InstallMethodSymlink else InstallMethodCopy
949 | otherwise = return InstallMethodSymlink
951 installMethod <- flagElim defaultMethod return $ cinstInstallMethod installClientFlags
953 return $ InstallExe installMethod installdir mkUnitBinDir mkExeName mkFinalExeName
955 -- | Install any built library by adding it to the default ghc environment
956 installLibraries
957 :: Verbosity
958 -> ProjectBuildContext
959 -> PI.PackageIndex InstalledPackageInfo
960 -> Compiler
961 -> PackageDBStack
962 -> FilePath
963 -- ^ Environment file
964 -> [GhcEnvironmentFileEntry]
965 -> Bool
966 -- ^ Whether we need to show a warning (i.e. we created a new environment
967 -- file, and the user did not use --package-env)
968 -> IO ()
969 installLibraries
970 verbosity
971 buildCtx
972 installedIndex
973 compiler
974 packageDbs'
975 envFile
976 envEntries
977 showWarning = do
978 if supportsPkgEnvFiles $ getImplInfo compiler
979 then do
980 let validDb (SpecificPackageDB fp) = doesPathExist fp
981 validDb _ = pure True
982 -- if a user "installs" a global package and no existing cabal db exists, none will be created.
983 -- this ensures we don't add the "phantom" path to the file.
984 packageDbs <- filterM validDb packageDbs'
986 getLatest =
987 (=<<) (maybeToList . safeHead . snd)
988 . take 1
989 . sortBy (comparing (Down . fst))
990 . PI.lookupPackageName installedIndex
991 globalLatest = concat (getLatest <$> globalPackages)
992 globalEntries = GhcEnvFilePackageId . installedUnitId <$> globalLatest
993 baseEntries =
994 GhcEnvFileClearPackageDbStack : fmap GhcEnvFilePackageDb packageDbs
995 pkgEntries =
996 ordNub $
997 globalEntries
998 ++ envEntries
999 ++ entriesForLibraryComponents (targetsMap buildCtx)
1000 contents' = renderGhcEnvironmentFile (baseEntries ++ pkgEntries)
1001 createDirectoryIfMissing True (takeDirectory envFile)
1002 writeFileAtomic envFile (BS.pack contents')
1003 when showWarning $
1004 warn verbosity $
1005 "The libraries were installed by creating a global GHC environment file at:\n"
1006 ++ envFile
1007 ++ "\n"
1008 ++ "\n"
1009 ++ "The presence of such an environment file is likely to confuse or break other "
1010 ++ "tools because it changes GHC's behaviour: it changes the default package set in "
1011 ++ "ghc and ghci from its normal value (which is \"all boot libraries\"). GHC "
1012 ++ "environment files are little-used and often not tested for.\n"
1013 ++ "\n"
1014 ++ "Furthermore, management of these environment files is still more difficult than "
1015 ++ "it could be; see e.g. https://github.com/haskell/cabal/issues/6481 .\n"
1016 ++ "\n"
1017 ++ "Double-check that creating a global GHC environment file is really what you "
1018 ++ "wanted! You can limit the effects of the environment file by creating it in a "
1019 ++ "specific directory using the --package-env flag. For example, use:\n"
1020 ++ "\n"
1021 ++ "cabal install --lib <packages...> --package-env .\n"
1022 ++ "\n"
1023 ++ "to create the file in the current directory."
1024 else
1025 warn verbosity $
1026 "The current compiler doesn't support safely installing libraries, "
1027 ++ "so only executables will be available. (Library installation is "
1028 ++ "supported on GHC 8.0+ only)"
1030 -- See ticket #8894. This is safe to include any nonreinstallable boot pkg,
1031 -- but the particular package users will always expect to be in scope without specific installation
1032 -- is base, so that they can access prelude, regardles of if they specifically asked for it.
1033 globalPackages :: [PackageName]
1034 globalPackages = mkPackageName <$> ["base"]
1036 warnIfNoExes :: Verbosity -> ProjectBuildContext -> IO ()
1037 warnIfNoExes verbosity buildCtx =
1038 when noExes $
1039 warn verbosity $
1040 "\n"
1041 <> "@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@\n"
1042 <> "@ WARNING: Installation might not be completed as desired! @\n"
1043 <> "@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@\n"
1044 <> "The command \"cabal install [TARGETS]\" doesn't expose libraries.\n"
1045 <> "* You might have wanted to add them as dependencies to your package."
1046 <> " In this case add \""
1047 <> intercalate ", " (showTargetSelector <$> selectors)
1048 <> "\" to the build-depends field(s) of your package's .cabal file.\n"
1049 <> "* You might have wanted to add them to a GHC environment. In this case"
1050 <> " use \"cabal install --lib "
1051 <> unwords (showTargetSelector <$> selectors)
1052 <> "\". "
1053 <> " The \"--lib\" flag is provisional: see"
1054 <> " https://github.com/haskell/cabal/issues/6481 for more information."
1055 where
1056 targets = concat $ Map.elems $ targetsMap buildCtx
1057 components = fst <$> targets
1058 selectors = concatMap (NE.toList . snd) targets
1059 noExes = null $ catMaybes $ exeMaybe <$> components
1061 exeMaybe (ComponentTarget (CExeName exe) _) = Just exe
1062 exeMaybe _ = Nothing
1064 -- | Return the package specifiers and non-global environment file entries.
1065 getEnvSpecsAndNonGlobalEntries
1066 :: PI.InstalledPackageIndex
1067 -> [GhcEnvironmentFileEntry]
1068 -> Bool
1069 -> ([PackageSpecifier a], [(PackageName, GhcEnvironmentFileEntry)])
1070 getEnvSpecsAndNonGlobalEntries installedIndex entries installLibs =
1071 if installLibs
1072 then (envSpecs, envEntries')
1073 else ([], envEntries')
1074 where
1075 (envSpecs, envEntries') = environmentFileToSpecifiers installedIndex entries
1077 environmentFileToSpecifiers
1078 :: PI.InstalledPackageIndex
1079 -> [GhcEnvironmentFileEntry]
1080 -> ([PackageSpecifier a], [(PackageName, GhcEnvironmentFileEntry)])
1081 environmentFileToSpecifiers ipi = foldMap $ \case
1082 (GhcEnvFilePackageId unitId)
1083 | Just
1084 InstalledPackageInfo
1085 { sourcePackageId = PackageIdentifier{..}
1086 , installedUnitId
1087 } <-
1088 PI.lookupUnitId ipi unitId
1089 , let pkgSpec =
1090 NamedPackage
1091 pkgName
1092 [PackagePropertyVersion (thisVersion pkgVersion)] ->
1093 ([pkgSpec], [(pkgName, GhcEnvFilePackageId installedUnitId)])
1094 _ -> ([], [])
1096 -- | Disables tests and benchmarks if they weren't explicitly enabled.
1097 disableTestsBenchsByDefault :: ConfigFlags -> ConfigFlags
1098 disableTestsBenchsByDefault configFlags =
1099 configFlags
1100 { configTests = Flag False <> configTests configFlags
1101 , configBenchmarks = Flag False <> configBenchmarks configFlags
1104 -- | Prepares a record containing the information needed to either symlink or
1105 -- copy an executable.
1106 symlink :: OverwritePolicy -> InstallExe -> UnitId -> UnqualComponentName -> Symlink
1107 symlink
1108 overwritePolicy
1109 InstallExe{installDir, mkSourceBinDir, mkExeName, mkFinalExeName}
1110 unit
1111 exe =
1112 Symlink
1113 overwritePolicy
1114 installDir
1115 (mkSourceBinDir unit)
1116 (mkExeName exe)
1117 (mkFinalExeName exe)
1119 -- |
1120 -- -- * When 'InstallCheckOnly', warn if install would fail overwrite policy
1121 -- checks but don't install anything.
1122 -- -- * When 'InstallCheckInstall', try to symlink or copy every package exe
1123 -- from the store to a given location. When not permitted by the overwrite
1124 -- policy, stop with a message.
1125 installCheckUnitExes :: InstallCheck -> InstallAction
1126 installCheckUnitExes
1127 installCheck
1128 verbosity
1129 overwritePolicy
1130 installExe@InstallExe{installMethod, installDir, mkSourceBinDir, mkExeName, mkFinalExeName}
1131 (unit, components) = do
1132 symlinkables :: [Bool] <- traverse (symlinkableBinary . symlink overwritePolicy installExe unit) exes
1133 case installCheck of
1134 InstallCheckOnly -> traverse_ warnAbout (zip symlinkables exes)
1135 InstallCheckInstall ->
1136 if and symlinkables
1137 then traverse_ installAndWarn exes
1138 else traverse_ warnAbout (zip symlinkables exes)
1139 where
1140 exes = catMaybes $ (exeMaybe . fst) <$> components
1141 exeMaybe (ComponentTarget (CExeName exe) _) = Just exe
1142 exeMaybe _ = Nothing
1144 warnAbout (True, _) = return ()
1145 warnAbout (False, exe) = dieWithException verbosity $ InstallUnitExes (errorMessage installDir exe)
1147 installAndWarn exe = do
1148 success <-
1149 installBuiltExe
1150 verbosity
1151 overwritePolicy
1152 (mkSourceBinDir unit)
1153 (mkExeName exe)
1154 (mkFinalExeName exe)
1155 installDir
1156 installMethod
1157 unless success $ dieWithException verbosity $ InstallUnitExes (errorMessage installDir exe)
1159 errorMessage installdir exe = case overwritePolicy of
1160 NeverOverwrite ->
1161 "Path '"
1162 <> (installdir </> prettyShow exe)
1163 <> "' already exists. "
1164 <> "Use --overwrite-policy=always to overwrite."
1165 -- This shouldn't even be possible, but we keep it in case symlinking or
1166 -- copying logic changes.
1167 _ ->
1168 case installMethod of
1169 InstallMethodSymlink -> "Symlinking"
1170 InstallMethodCopy -> "Copying" <> " '" <> prettyShow exe <> "' failed."
1172 -- | Install a specific exe.
1173 installBuiltExe
1174 :: Verbosity
1175 -> OverwritePolicy
1176 -> FilePath
1177 -- ^ The directory where the built exe is located
1178 -> FilePath
1179 -- ^ The exe's filename
1180 -> FilePath
1181 -- ^ The exe's filename in the public install directory
1182 -> FilePath
1183 -- ^ the directory where it should be installed
1184 -> InstallMethod
1185 -> IO Bool
1186 -- ^ Whether the installation was successful
1187 installBuiltExe
1188 verbosity
1189 overwritePolicy
1190 sourceDir
1191 exeName
1192 finalExeName
1193 installdir
1194 InstallMethodSymlink = do
1195 notice verbosity $ "Symlinking '" <> exeName <> "' to '" <> destination <> "'"
1196 symlinkBinary
1197 ( Symlink
1198 overwritePolicy
1199 installdir
1200 sourceDir
1201 finalExeName
1202 exeName
1204 where
1205 destination = installdir </> finalExeName
1206 installBuiltExe
1207 verbosity
1208 overwritePolicy
1209 sourceDir
1210 exeName
1211 finalExeName
1212 installdir
1213 InstallMethodCopy = do
1214 notice verbosity $ "Copying '" <> exeName <> "' to '" <> destination <> "'"
1215 exists <- doesPathExist destination
1216 case (exists, overwritePolicy) of
1217 (True, NeverOverwrite) -> pure False
1218 (True, AlwaysOverwrite) -> overwrite
1219 (True, PromptOverwrite) -> maybeOverwrite
1220 (False, _) -> copy
1221 where
1222 source = sourceDir </> exeName
1223 destination = installdir </> finalExeName
1224 remove = do
1225 isDir <- doesDirectoryExist destination
1226 if isDir
1227 then removeDirectory destination
1228 else removeFile destination
1229 copy = copyFile source destination >> pure True
1230 overwrite :: IO Bool
1231 overwrite = remove >> copy
1232 maybeOverwrite :: IO Bool
1233 maybeOverwrite =
1234 promptRun
1235 "Existing file found while installing executable. Do you want to overwrite that file? (y/n)"
1236 overwrite
1238 -- | Create 'GhcEnvironmentFileEntry's for packages with exposed libraries.
1239 entriesForLibraryComponents :: TargetsMap -> [GhcEnvironmentFileEntry]
1240 entriesForLibraryComponents = Map.foldrWithKey' (\k v -> mappend (go k v)) []
1241 where
1242 hasLib :: (ComponentTarget, NonEmpty TargetSelector) -> Bool
1243 hasLib (ComponentTarget (CLibName _) _, _) = True
1244 hasLib _ = False
1247 :: UnitId
1248 -> [(ComponentTarget, NonEmpty TargetSelector)]
1249 -> [GhcEnvironmentFileEntry]
1250 go unitId targets
1251 | any hasLib targets = [GhcEnvFilePackageId unitId]
1252 | otherwise = []
1254 -- | Gets the file path to the request environment file. The @Bool@ is @True@
1255 -- if we got an explicit instruction using @--package-env@, @False@ if we used
1256 -- the default.
1257 getEnvFile :: ClientInstallFlags -> Platform -> Version -> IO (Bool, FilePath)
1258 getEnvFile clientInstallFlags platform compilerVersion = do
1259 appDir <- getGhcAppDir
1260 case flagToMaybe (cinstEnvironmentPath clientInstallFlags) of
1261 Just spec
1262 -- Is spec a bare word without any "pathy" content, then it refers to
1263 -- a named global environment.
1264 | takeBaseName spec == spec ->
1265 return (True, getGlobalEnv appDir platform compilerVersion spec)
1266 | otherwise -> do
1267 spec' <- makeAbsolute spec
1268 isDir <- doesDirectoryExist spec'
1269 if isDir
1270 then -- If spec is a directory, then make an ambient environment inside
1271 -- that directory.
1272 return (True, getLocalEnv spec' platform compilerVersion)
1273 else -- Otherwise, treat it like a literal file path.
1274 return (True, spec')
1275 Nothing ->
1276 return (False, getGlobalEnv appDir platform compilerVersion "default")
1278 -- | Returns the list of @GhcEnvFilePackageId@ values already existing in the
1279 -- environment being operated on. The @Bool@ is @True@ if we took settings
1280 -- from an existing file, @False@ otherwise.
1281 getExistingEnvEntries :: Verbosity -> CompilerFlavor -> Bool -> FilePath -> IO (Bool, [GhcEnvironmentFileEntry])
1282 getExistingEnvEntries verbosity compilerFlavor supportsPkgEnvFiles envFile = do
1283 envFileExists <- doesFileExist envFile
1284 (usedExisting, allEntries) <-
1285 if (compilerFlavor == GHC || compilerFlavor == GHCJS)
1286 && supportsPkgEnvFiles
1287 && envFileExists
1288 then catch ((True,) <$> readGhcEnvironmentFile envFile) $ \(_ :: ParseErrorExc) ->
1289 warn
1290 verbosity
1291 ( "The environment file "
1292 ++ envFile
1293 ++ " is unparsable. Libraries cannot be installed."
1295 >> return (False, [])
1296 else return (False, [])
1297 return (usedExisting, filterEnvEntries allEntries)
1298 where
1299 -- Why? We know what the first part will be, we only care about the packages.
1300 filterEnvEntries = filter $ \case
1301 GhcEnvFilePackageId _ -> True
1302 _ -> False
1304 -- | Constructs the path to the global GHC environment file.
1306 -- TODO(m-renaud): Create PkgEnvName newtype wrapper.
1307 getGlobalEnv :: FilePath -> Platform -> Version -> String -> FilePath
1308 getGlobalEnv appDir platform compilerVersion name =
1309 appDir
1310 </> ghcPlatformAndVersionString platform compilerVersion
1311 </> "environments"
1312 </> name
1314 -- | Constructs the path to a local GHC environment file.
1315 getLocalEnv :: FilePath -> Platform -> Version -> FilePath
1316 getLocalEnv dir platform compilerVersion =
1318 </> ".ghc.environment."
1319 <> ghcPlatformAndVersionString platform compilerVersion
1321 getPackageDbStack
1322 :: Compiler
1323 -> Flag FilePath
1324 -> Flag FilePath
1325 -> [Maybe PackageDB]
1326 -> IO PackageDBStack
1327 getPackageDbStack compiler storeDirFlag logsDirFlag packageDbs = do
1328 mstoreDir <- traverse makeAbsolute $ flagToMaybe storeDirFlag
1330 mlogsDir = flagToMaybe logsDirFlag
1331 cabalLayout <- mkCabalDirLayout mstoreDir mlogsDir
1332 pure $ storePackageDBStack (cabalStoreDirLayout cabalLayout) compiler packageDbs
1334 -- | This defines what a 'TargetSelector' means for the @bench@ command.
1335 -- It selects the 'AvailableTarget's that the 'TargetSelector' refers to,
1336 -- or otherwise classifies the problem.
1338 -- For the @build@ command select all components except non-buildable
1339 -- and disabled tests\/benchmarks, fail if there are no such
1340 -- components
1341 selectPackageTargets
1342 :: TargetSelector
1343 -> [AvailableTarget k]
1344 -> Either TargetProblem' [k]
1345 selectPackageTargets targetSelector targets
1346 -- If there are any buildable targets then we select those
1347 | not (null targetsBuildable) =
1348 Right targetsBuildable
1349 -- If there are targets but none are buildable then we report those
1350 | not (null targets) =
1351 Left (TargetProblemNoneEnabled targetSelector targets')
1352 -- If there are no targets at all then we report that
1353 | otherwise =
1354 Left (TargetProblemNoTargets targetSelector)
1355 where
1356 targets' = forgetTargetsDetail targets
1357 targetsBuildable =
1358 selectBuildableTargetsWith
1359 (buildable targetSelector)
1360 targets
1362 -- When there's a target filter like "pkg:tests" then we do select tests,
1363 -- but if it's just a target like "pkg" then we don't build tests unless
1364 -- they are requested by default (i.e. by using --enable-tests)
1365 buildable (TargetPackage _ _ Nothing) TargetNotRequestedByDefault = False
1366 buildable (TargetAllPackages Nothing) TargetNotRequestedByDefault = False
1367 buildable _ _ = True
1369 -- | For a 'TargetComponent' 'TargetSelector', check if the component can be
1370 -- selected.
1372 -- For the @build@ command we just need the basic checks on being buildable etc.
1373 selectComponentTarget
1374 :: SubComponentTarget
1375 -> AvailableTarget k
1376 -> Either TargetProblem' k
1377 selectComponentTarget = selectComponentTargetBasic
1379 reportBuildTargetProblems :: Verbosity -> [TargetProblem'] -> IO a
1380 reportBuildTargetProblems verbosity problems = reportTargetProblems verbosity "build" problems
1382 reportCannotPruneDependencies :: Verbosity -> CannotPruneDependencies -> IO a
1383 reportCannotPruneDependencies verbosity =
1384 dieWithException verbosity . SelectComponentTargetError . renderCannotPruneDependencies