1{-# LANGUAGE LambdaCase          #-}
2{-# LANGUAGE NamedFieldPuns      #-}
3{-# LANGUAGE RecordWildCards     #-}
4{-# LANGUAGE ScopedTypeVariables #-}
5{-# LANGUAGE ViewPatterns        #-}
6
7-- | cabal-install CLI command: build
8--
9module Distribution.Client.CmdInstall (
10    -- * The @build@ CLI and action
11    installCommand,
12    installAction,
13
14    -- * Internals exposed for testing
15    selectPackageTargets,
16    selectComponentTarget,
17    -- * Internals exposed for CmdRepl + CmdRun
18    establishDummyDistDirLayout,
19    establishDummyProjectBaseContext
20  ) where
21
22import Prelude ()
23import Distribution.Client.Compat.Prelude
24import Distribution.Compat.Directory
25         ( doesPathExist )
26
27import Distribution.Client.ProjectOrchestration
28import Distribution.Client.CmdErrorMessages
29import Distribution.Client.CmdSdist
30import Distribution.Client.TargetProblem
31         ( TargetProblem', TargetProblem (..) )
32
33import Distribution.Client.CmdInstall.ClientInstallFlags
34import Distribution.Client.CmdInstall.ClientInstallTargetSelector
35
36import Distribution.Client.Setup
37         ( GlobalFlags(..), ConfigFlags(..) )
38import Distribution.Client.Types
39         ( PackageSpecifier(..), PackageLocation(..), UnresolvedSourcePackage
40         , SourcePackageDb(..) )
41import qualified Distribution.Client.InstallPlan as InstallPlan
42import Distribution.Package
43         ( Package(..), PackageName, mkPackageName, unPackageName )
44import Distribution.Types.PackageId
45         ( PackageIdentifier(..) )
46import Distribution.Client.ProjectConfig
47         ( ProjectPackageLocation(..)
48         , fetchAndReadSourcePackages
49         )
50import Distribution.Client.NixStyleOptions
51         ( NixStyleFlags (..), nixStyleOptions, defaultNixStyleFlags )
52import Distribution.Client.ProjectFlags (ProjectFlags (..))
53import Distribution.Client.ProjectConfig.Types
54         ( ProjectConfig(..), ProjectConfigShared(..)
55         , ProjectConfigBuildOnly(..), PackageConfig(..)
56         , getMapLast, getMapMappend, projectConfigLogsDir
57         , projectConfigStoreDir, projectConfigBuildOnly
58         , projectConfigConfigFile )
59import Distribution.Simple.Program.Db
60         ( userSpecifyPaths, userSpecifyArgss, defaultProgramDb
61         , modifyProgramSearchPath, ProgramDb )
62import Distribution.Simple.BuildPaths
63         ( exeExtension )
64import Distribution.Simple.Program.Find
65         ( ProgramSearchPathEntry(..) )
66import Distribution.Client.Config
67         ( defaultInstallPath, getCabalDir, loadConfig, SavedConfig(..) )
68import qualified Distribution.Simple.PackageIndex as PI
69import Distribution.Solver.Types.PackageIndex
70         ( lookupPackageName, searchByName )
71import Distribution.Types.InstalledPackageInfo
72         ( InstalledPackageInfo(..) )
73import Distribution.Types.Version
74         ( Version, nullVersion )
75import Distribution.Types.VersionRange
76         ( thisVersion )
77import Distribution.Solver.Types.PackageConstraint
78         ( PackageProperty(..) )
79import Distribution.Client.IndexUtils
80         ( getSourcePackages, getInstalledPackages )
81import Distribution.Client.ProjectConfig
82         ( projectConfigWithBuilderRepoContext
83         , resolveBuildTimeSettings, withProjectOrGlobalConfig )
84import Distribution.Client.ProjectPlanning
85         ( storePackageInstallDirs' )
86import Distribution.Client.ProjectPlanning.Types
87         ( ElaboratedInstallPlan )
88import qualified Distribution.Simple.InstallDirs as InstallDirs
89import Distribution.Client.DistDirLayout
90         ( DistDirLayout(..), mkCabalDirLayout
91         , cabalStoreDirLayout
92         , CabalDirLayout(..), StoreDirLayout(..) )
93import Distribution.Client.RebuildMonad
94         ( runRebuild )
95import Distribution.Client.InstallSymlink
96         ( symlinkBinary, trySymlink )
97import Distribution.Client.Types.OverwritePolicy
98         ( OverwritePolicy (..) )
99import Distribution.Simple.Flag
100         ( fromFlagOrDefault, flagToMaybe, flagElim )
101import Distribution.Simple.Setup
102         ( Flag(..) )
103import Distribution.Solver.Types.SourcePackage
104         ( SourcePackage(..) )
105import Distribution.Simple.Command
106         ( CommandUI(..), usageAlternatives )
107import Distribution.Simple.Configure
108         ( configCompilerEx )
109import Distribution.Simple.Compiler
110         ( Compiler(..), CompilerId(..), CompilerFlavor(..)
111         , PackageDBStack )
112import Distribution.Simple.GHC
113         ( ghcPlatformAndVersionString, getGhcAppDir
114         , GhcImplInfo(..), getImplInfo
115         , GhcEnvironmentFileEntry(..)
116         , renderGhcEnvironmentFile, readGhcEnvironmentFile, ParseErrorExc )
117import Distribution.System
118         ( Platform , buildOS, OS (Windows) )
119import Distribution.Types.UnitId
120         ( UnitId )
121import Distribution.Types.UnqualComponentName
122         ( UnqualComponentName, unUnqualComponentName )
123import Distribution.Verbosity
124         ( normal, lessVerbose )
125import Distribution.Simple.Utils
126         ( wrapText, die', notice, warn
127         , withTempDirectory, createDirectoryIfMissingVerbose
128         , ordNub )
129import Distribution.Utils.Generic
130         ( safeHead, writeFileAtomic )
131
132import qualified Data.ByteString.Lazy.Char8 as BS
133import Data.Ord
134         ( Down(..) )
135import qualified Data.Map as Map
136import Distribution.Utils.NubList
137         ( fromNubList )
138import Network.URI (URI)
139import System.Directory
140         ( doesFileExist, createDirectoryIfMissing
141         , getTemporaryDirectory, makeAbsolute, doesDirectoryExist
142         , removeFile, removeDirectory, copyFile )
143import System.FilePath
144         ( (</>), (<.>), takeDirectory, takeBaseName )
145
146installCommand :: CommandUI (NixStyleFlags ClientInstallFlags)
147installCommand = CommandUI
148  { commandName         = "v2-install"
149  , commandSynopsis     = "Install packages."
150  , commandUsage        = usageAlternatives
151                          "v2-install" [ "[TARGETS] [FLAGS]" ]
152  , commandDescription  = Just $ \_ -> wrapText $
153    "Installs one or more packages. This is done by installing them "
154    ++ "in the store and symlinking/copying the executables in the directory "
155    ++ "specified by the --installdir flag (`~/.cabal/bin/` by default). "
156    ++ "If you want the installed executables to be available globally, "
157    ++ "make sure that the PATH environment variable contains that directory. "
158    ++ "\n\n"
159    ++ "If TARGET is a library, it will be added to the global environment. "
160    ++ "When doing this, cabal will try to build a plan that includes all "
161    ++ "the previously installed libraries. This is currently not implemented."
162  , commandNotes        = Just $ \pname ->
163      "Examples:\n"
164      ++ "  " ++ pname ++ " v2-install\n"
165      ++ "    Install the package in the current directory\n"
166      ++ "  " ++ pname ++ " v2-install pkgname\n"
167      ++ "    Install the package named pkgname"
168      ++ " (fetching it from hackage if necessary)\n"
169      ++ "  " ++ pname ++ " v2-install ./pkgfoo\n"
170      ++ "    Install the package in the ./pkgfoo directory\n"
171
172  , commandOptions      = nixStyleOptions clientInstallOptions
173  , commandDefaultFlags = defaultNixStyleFlags defaultClientInstallFlags
174  }
175
176-- | The @install@ command actually serves four different needs. It installs:
177-- * exes:
178--   For example a program from hackage. The behavior is similar to the old
179--   install command, except that now conflicts between separate runs of the
180--   command are impossible thanks to the store.
181--   Exes are installed in the store like a normal dependency, then they are
182--   symlinked/copied in the directory specified by --installdir.
183--   To do this we need a dummy projectBaseContext containing the targets as
184--   estra packages and using a temporary dist directory.
185-- * libraries
186--   Libraries install through a similar process, but using GHC environment
187--   files instead of symlinks. This means that 'v2-install'ing libraries
188--   only works on GHC >= 8.0.
189--
190-- For more details on how this works, see the module
191-- "Distribution.Client.ProjectOrchestration"
192--
193installAction :: NixStyleFlags ClientInstallFlags -> [String] -> GlobalFlags -> IO ()
194installAction flags@NixStyleFlags { extraFlags = clientInstallFlags', .. } targetStrings globalFlags = do
195  -- Ensure there were no invalid configuration options specified.
196  verifyPreconditionsOrDie verbosity configFlags'
197
198  -- We cannot use establishDummyProjectBaseContext to get these flags, since
199  -- it requires one of them as an argument. Normal establishProjectBaseContext
200  -- does not, and this is why this is done only for the install command
201  clientInstallFlags <- getClientInstallFlags verbosity globalFlags clientInstallFlags'
202
203  let
204    installLibs    = fromFlagOrDefault False (cinstInstallLibs clientInstallFlags)
205    targetFilter   = if installLibs then Just LibKind else Just ExeKind
206    targetStrings' = if null targetStrings then ["."] else targetStrings
207
208    withProject :: IO ([PackageSpecifier UnresolvedSourcePackage], [URI], [TargetSelector], ProjectConfig)
209    withProject = do
210      let reducedVerbosity = lessVerbose verbosity
211
212      -- First, we need to learn about what's available to be installed.
213      localBaseCtx <-
214        establishProjectBaseContext reducedVerbosity cliConfig InstallCommand
215      let localDistDirLayout = distDirLayout localBaseCtx
216      pkgDb <- projectConfigWithBuilderRepoContext reducedVerbosity
217               (buildSettings localBaseCtx) (getSourcePackages verbosity)
218
219      let
220        (targetStrings'', packageIds) =
221          partitionEithers .
222          flip fmap targetStrings' $
223          \str -> case simpleParsec str of
224            Just (pkgId :: PackageId)
225              | pkgVersion pkgId /= nullVersion -> Right pkgId
226            _                                   -> Left str
227        packageSpecifiers =
228          flip fmap packageIds $ \case
229          PackageIdentifier{..}
230            | pkgVersion == nullVersion -> NamedPackage pkgName []
231            | otherwise                 -> NamedPackage pkgName
232                                           [PackagePropertyVersion
233                                            (thisVersion pkgVersion)]
234        packageTargets =
235          flip TargetPackageNamed targetFilter . pkgName <$> packageIds
236
237      if null targetStrings'
238        then return (packageSpecifiers, [], packageTargets, projectConfig localBaseCtx)
239        else do
240          targetSelectors <-
241            either (reportTargetSelectorProblems verbosity) return
242            =<< readTargetSelectors (localPackages localBaseCtx)
243                                    Nothing targetStrings''
244
245          (specs, selectors) <-
246            getSpecsAndTargetSelectors
247              verbosity reducedVerbosity pkgDb targetSelectors localDistDirLayout localBaseCtx targetFilter
248
249          return ( specs ++ packageSpecifiers
250                 , []
251                 , selectors ++ packageTargets
252                 , projectConfig localBaseCtx )
253
254    withoutProject :: ProjectConfig -> IO ([PackageSpecifier pkg], [URI], [TargetSelector], ProjectConfig)
255    withoutProject globalConfig = do
256      tss <- traverse (parseWithoutProjectTargetSelector verbosity) targetStrings'
257
258      cabalDir <- getCabalDir
259      let
260        projectConfig = globalConfig <> cliConfig
261
262        ProjectConfigBuildOnly {
263          projectConfigLogsDir
264        } = projectConfigBuildOnly projectConfig
265
266        ProjectConfigShared {
267          projectConfigStoreDir
268        } = projectConfigShared projectConfig
269
270        mlogsDir = flagToMaybe projectConfigLogsDir
271        mstoreDir = flagToMaybe projectConfigStoreDir
272        cabalDirLayout = mkCabalDirLayout cabalDir mstoreDir mlogsDir
273
274        buildSettings = resolveBuildTimeSettings
275                          verbosity cabalDirLayout
276                          projectConfig
277
278      SourcePackageDb { packageIndex } <- projectConfigWithBuilderRepoContext
279                                            verbosity buildSettings
280                                            (getSourcePackages verbosity)
281
282      for_ (concatMap woPackageNames tss) $ \name -> do
283        when (null (lookupPackageName packageIndex name)) $ do
284          let xs = searchByName packageIndex (unPackageName name)
285          let emptyIf True  _  = []
286              emptyIf False zs = zs
287          die' verbosity $ concat $
288            [ "Unknown package \"", unPackageName name, "\". "
289            ] ++ emptyIf (null xs)
290            [ "Did you mean any of the following?\n"
291            , unlines (("- " ++) . unPackageName . fst <$> xs)
292            ]
293
294      let
295        (uris, packageSpecifiers) = partitionEithers $ map woPackageSpecifiers tss
296        packageTargets            = map woPackageTargets tss
297
298      return (packageSpecifiers, uris, packageTargets, projectConfig)
299
300  (specs, uris, targetSelectors, config) <-
301     withProjectOrGlobalConfig verbosity ignoreProject globalConfigFlag withProject withoutProject
302
303  let
304    ProjectConfig {
305      projectConfigBuildOnly = ProjectConfigBuildOnly {
306        projectConfigLogsDir
307      },
308      projectConfigShared = ProjectConfigShared {
309        projectConfigHcFlavor,
310        projectConfigHcPath,
311        projectConfigHcPkg,
312        projectConfigStoreDir
313      },
314      projectConfigLocalPackages = PackageConfig {
315        packageConfigProgramPaths,
316        packageConfigProgramArgs,
317        packageConfigProgramPathExtra
318      }
319    } = config
320
321    hcFlavor = flagToMaybe projectConfigHcFlavor
322    hcPath   = flagToMaybe projectConfigHcPath
323    hcPkg    = flagToMaybe projectConfigHcPkg
324
325    -- ProgramDb with directly user specified paths
326    preProgDb =
327        userSpecifyPaths (Map.toList (getMapLast packageConfigProgramPaths))
328      . userSpecifyArgss (Map.toList (getMapMappend packageConfigProgramArgs))
329      . modifyProgramSearchPath
330          (++ [ ProgramSearchPathDir dir
331              | dir <- fromNubList packageConfigProgramPathExtra ])
332      $ defaultProgramDb
333
334  -- progDb is a program database with compiler tools configured properly
335  (compiler@Compiler { compilerId =
336    compilerId@(CompilerId compilerFlavor compilerVersion) }, platform, progDb) <-
337      configCompilerEx hcFlavor hcPath hcPkg preProgDb verbosity
338
339  let
340    GhcImplInfo{ supportsPkgEnvFiles } = getImplInfo compiler
341
342  envFile <- getEnvFile clientInstallFlags platform compilerVersion
343  existingEnvEntries <-
344    getExistingEnvEntries verbosity compilerFlavor supportsPkgEnvFiles envFile
345  packageDbs <- getPackageDbStack compilerId projectConfigStoreDir projectConfigLogsDir
346  installedIndex <- getInstalledPackages verbosity compiler packageDbs progDb
347
348  let
349    (envSpecs, nonGlobalEnvEntries) =
350      getEnvSpecsAndNonGlobalEntries installedIndex existingEnvEntries installLibs
351
352  -- Second, we need to use a fake project to let Cabal build the
353  -- installables correctly. For that, we need a place to put a
354  -- temporary dist directory.
355  globalTmp <- getTemporaryDirectory
356
357  withTempDirectory verbosity globalTmp "cabal-install." $ \tmpDir -> do
358    distDirLayout <- establishDummyDistDirLayout verbosity config tmpDir
359
360    uriSpecs <- runRebuild tmpDir $ fetchAndReadSourcePackages
361      verbosity
362      distDirLayout
363      (projectConfigShared config)
364      (projectConfigBuildOnly config)
365      [ ProjectPackageRemoteTarball uri | uri <- uris ]
366
367    baseCtx <- establishDummyProjectBaseContext
368                 verbosity
369                 config
370                 distDirLayout
371                 (envSpecs ++ specs ++ uriSpecs)
372                 InstallCommand
373
374    buildCtx <- constructProjectBuildContext verbosity baseCtx targetSelectors
375
376    printPlan verbosity baseCtx buildCtx
377
378    buildOutcomes <- runProjectBuildPhase verbosity baseCtx buildCtx
379    runProjectPostBuildPhase verbosity baseCtx buildCtx buildOutcomes
380
381    -- Now that we built everything we can do the installation part.
382    -- First, figure out if / what parts we want to install:
383    let
384      dryRun = buildSettingDryRun $ buildSettings baseCtx
385
386    -- Then, install!
387    when (not dryRun) $
388      if installLibs
389      then installLibraries verbosity
390           buildCtx compiler packageDbs progDb envFile nonGlobalEnvEntries
391      else installExes verbosity
392           baseCtx buildCtx platform compiler configFlags clientInstallFlags
393  where
394    configFlags' = disableTestsBenchsByDefault configFlags
395    verbosity = fromFlagOrDefault normal (configVerbosity configFlags')
396    ignoreProject = flagIgnoreProject projectFlags
397    cliConfig = commandLineFlagsToProjectConfig
398                  globalFlags
399                  flags { configFlags = configFlags' }
400                  clientInstallFlags'
401    globalConfigFlag = projectConfigConfigFile (projectConfigShared cliConfig)
402
403-- | Verify that invalid config options were not passed to the install command.
404--
405-- If an invalid configuration is found the command will @die'@.
406verifyPreconditionsOrDie :: Verbosity -> ConfigFlags -> IO ()
407verifyPreconditionsOrDie verbosity configFlags = do
408  -- We never try to build tests/benchmarks for remote packages.
409  -- So we set them as disabled by default and error if they are explicitly
410  -- enabled.
411  when (configTests configFlags == Flag True) $
412    die' verbosity $ "--enable-tests was specified, but tests can't "
413                  ++ "be enabled in a remote package"
414  when (configBenchmarks configFlags == Flag True) $
415    die' verbosity $ "--enable-benchmarks was specified, but benchmarks can't "
416                  ++ "be enabled in a remote package"
417
418getClientInstallFlags :: Verbosity -> GlobalFlags -> ClientInstallFlags -> IO ClientInstallFlags
419getClientInstallFlags verbosity globalFlags existingClientInstallFlags = do
420  let configFileFlag = globalConfigFile globalFlags
421  savedConfig <- loadConfig verbosity configFileFlag
422  pure $ savedClientInstallFlags savedConfig `mappend` existingClientInstallFlags
423
424
425getSpecsAndTargetSelectors
426  :: Verbosity
427  -> Verbosity
428  -> SourcePackageDb
429  -> [TargetSelector]
430  -> DistDirLayout
431  -> ProjectBaseContext
432  -> Maybe ComponentKindFilter
433  -> IO ([PackageSpecifier UnresolvedSourcePackage], [TargetSelector])
434getSpecsAndTargetSelectors verbosity reducedVerbosity pkgDb targetSelectors localDistDirLayout localBaseCtx targetFilter =
435  withInstallPlan reducedVerbosity localBaseCtx $ \elaboratedPlan _ -> do
436  -- Split into known targets and hackage packages.
437  (targets, hackageNames) <-
438    partitionToKnownTargetsAndHackagePackages
439      verbosity pkgDb elaboratedPlan targetSelectors
440
441  let
442    planMap = InstallPlan.toMap elaboratedPlan
443    targetIds = Map.keys targets
444
445    sdistize (SpecificSourcePackage spkg) =
446      SpecificSourcePackage spkg'
447      where
448        sdistPath = distSdistFile localDistDirLayout (packageId spkg)
449        spkg' = spkg { srcpkgSource = LocalTarballPackage sdistPath }
450    sdistize named = named
451
452    local = sdistize <$> localPackages localBaseCtx
453
454    gatherTargets :: UnitId -> TargetSelector
455    gatherTargets targetId = TargetPackageNamed pkgName targetFilter
456      where
457        targetUnit = Map.findWithDefault (error "cannot find target unit") targetId planMap
458        PackageIdentifier{..} = packageId targetUnit
459
460    targets' = fmap gatherTargets targetIds
461
462    hackagePkgs :: [PackageSpecifier UnresolvedSourcePackage]
463    hackagePkgs = flip NamedPackage [] <$> hackageNames
464
465    hackageTargets :: [TargetSelector]
466    hackageTargets =
467      flip TargetPackageNamed targetFilter <$> hackageNames
468
469  createDirectoryIfMissing True (distSdistDirectory localDistDirLayout)
470
471  unless (Map.null targets) $ for_ (localPackages localBaseCtx) $ \lpkg -> case lpkg of
472      SpecificSourcePackage pkg -> packageToSdist verbosity
473        (distProjectRootDirectory localDistDirLayout) TarGzArchive
474        (distSdistFile localDistDirLayout (packageId pkg)) pkg
475      NamedPackage pkgName _ -> error $ "Got NamedPackage " ++ prettyShow pkgName
476
477  if null targets
478    then return (hackagePkgs, hackageTargets)
479    else return (local ++ hackagePkgs, targets' ++ hackageTargets)
480
481-- | Partitions the target selectors into known local targets and hackage packages.
482partitionToKnownTargetsAndHackagePackages
483  :: Verbosity
484  -> SourcePackageDb
485  -> ElaboratedInstallPlan
486  -> [TargetSelector]
487  -> IO (Map UnitId [(ComponentTarget,[TargetSelector])], [PackageName])
488partitionToKnownTargetsAndHackagePackages verbosity pkgDb elaboratedPlan targetSelectors = do
489  let mTargets = resolveTargets
490        selectPackageTargets
491        selectComponentTarget
492        elaboratedPlan
493        (Just pkgDb)
494        targetSelectors
495  case mTargets of
496    Right targets ->
497      -- Everything is a local dependency.
498      return (targets, [])
499    Left errs     -> do
500      -- Not everything is local.
501      let
502        (errs', hackageNames) = partitionEithers . flip fmap errs $ \case
503          TargetAvailableInIndex name -> Right name
504          err                         -> Left err
505
506      -- report incorrect case for known package.
507      for_ errs' $ \case
508        TargetNotInProject hn ->
509          case searchByName (packageIndex pkgDb) (unPackageName hn) of
510            [] -> return ()
511            xs -> die' verbosity . concat $
512              [ "Unknown package \"", unPackageName hn, "\". "
513              , "Did you mean any of the following?\n"
514              , unlines (("- " ++) . unPackageName . fst <$> xs)
515              ]
516        _ -> return ()
517
518      when (not . null $ errs') $ reportBuildTargetProblems verbosity errs'
519
520      let
521        targetSelectors' = flip filter targetSelectors $ \case
522          TargetComponentUnknown name _ _
523            | name `elem` hackageNames -> False
524          TargetPackageNamed name _
525            | name `elem` hackageNames -> False
526          _                            -> True
527
528      -- This can't fail, because all of the errors are
529      -- removed (or we've given up).
530      targets <-
531        either (reportBuildTargetProblems verbosity) return $
532        resolveTargets
533          selectPackageTargets
534          selectComponentTarget
535          elaboratedPlan
536          Nothing
537          targetSelectors'
538
539      return (targets, hackageNames)
540
541
542
543constructProjectBuildContext
544  :: Verbosity
545  -> ProjectBaseContext
546     -- ^ The synthetic base context to use to produce the full build context.
547  -> [TargetSelector]
548  -> IO ProjectBuildContext
549constructProjectBuildContext verbosity baseCtx targetSelectors = do
550  runProjectPreBuildPhase verbosity baseCtx $ \elaboratedPlan -> do
551    -- Interpret the targets on the command line as build targets
552    targets <- either (reportBuildTargetProblems verbosity) return $
553      resolveTargets
554        selectPackageTargets
555        selectComponentTarget
556        elaboratedPlan
557        Nothing
558        targetSelectors
559
560    let prunedToTargetsElaboratedPlan =
561          pruneInstallPlanToTargets TargetActionBuild targets elaboratedPlan
562    prunedElaboratedPlan <-
563      if buildSettingOnlyDeps (buildSettings baseCtx)
564      then either (reportCannotPruneDependencies verbosity) return $
565           pruneInstallPlanToDependencies (Map.keysSet targets)
566                                          prunedToTargetsElaboratedPlan
567      else return prunedToTargetsElaboratedPlan
568
569    return (prunedElaboratedPlan, targets)
570
571
572-- | Install any built exe by symlinking/copying it
573-- we don't use BuildOutcomes because we also need the component names
574installExes
575  :: Verbosity
576  -> ProjectBaseContext
577  -> ProjectBuildContext
578  -> Platform
579  -> Compiler
580  -> ConfigFlags
581  -> ClientInstallFlags
582  -> IO ()
583installExes verbosity baseCtx buildCtx platform compiler
584            configFlags clientInstallFlags = do
585  installPath <- defaultInstallPath
586  let storeDirLayout = cabalStoreDirLayout $ cabalDirLayout baseCtx
587
588      prefix = fromFlagOrDefault "" (fmap InstallDirs.fromPathTemplate (configProgPrefix configFlags))
589      suffix = fromFlagOrDefault "" (fmap InstallDirs.fromPathTemplate (configProgSuffix configFlags))
590
591      mkUnitBinDir :: UnitId -> FilePath
592      mkUnitBinDir =
593        InstallDirs.bindir .
594        storePackageInstallDirs' storeDirLayout (compilerId compiler)
595
596      mkExeName :: UnqualComponentName -> FilePath
597      mkExeName exe = unUnqualComponentName exe <.> exeExtension platform
598
599      mkFinalExeName :: UnqualComponentName -> FilePath
600      mkFinalExeName exe = prefix <> unUnqualComponentName exe <> suffix <.> exeExtension platform
601      installdirUnknown =
602        "installdir is not defined. Set it in your cabal config file "
603        ++ "or use --installdir=<path>. Using default installdir: " ++ show installPath
604
605  installdir <- fromFlagOrDefault
606                (warn verbosity installdirUnknown >> pure installPath) $
607                pure <$> cinstInstalldir clientInstallFlags
608  createDirectoryIfMissingVerbose verbosity False installdir
609  warnIfNoExes verbosity buildCtx
610
611  installMethod <- flagElim defaultMethod return $
612    cinstInstallMethod clientInstallFlags
613
614  let
615    doInstall = installUnitExes
616                  verbosity
617                  overwritePolicy
618                  mkUnitBinDir mkExeName mkFinalExeName
619                  installdir installMethod
620    in traverse_ doInstall $ Map.toList $ targetsMap buildCtx
621  where
622    overwritePolicy = fromFlagOrDefault NeverOverwrite $
623                      cinstOverwritePolicy clientInstallFlags
624    isWindows = buildOS == Windows
625
626    -- This is in IO as we will make environment checks,
627    -- to decide which method is best
628    defaultMethod :: IO InstallMethod
629    defaultMethod
630      -- Try symlinking in temporary directory, if it works default to
631      -- symlinking even on windows
632      | isWindows = do
633        symlinks <- trySymlink verbosity
634        return $ if symlinks then InstallMethodSymlink else InstallMethodCopy
635      | otherwise = return InstallMethodSymlink
636
637-- | Install any built library by adding it to the default ghc environment
638installLibraries
639  :: Verbosity
640  -> ProjectBuildContext
641  -> Compiler
642  -> PackageDBStack
643  -> ProgramDb
644  -> FilePath -- ^ Environment file
645  -> [GhcEnvironmentFileEntry]
646  -> IO ()
647installLibraries verbosity buildCtx compiler
648                 packageDbs programDb envFile envEntries = do
649  -- Why do we get it again? If we updated a globalPackage then we need
650  -- the new version.
651  installedIndex <- getInstalledPackages verbosity compiler packageDbs programDb
652  if supportsPkgEnvFiles $ getImplInfo compiler
653    then do
654      let
655        getLatest :: PackageName -> [InstalledPackageInfo]
656        getLatest = (=<<) (maybeToList . safeHead . snd) . take 1 . sortBy (comparing (Down . fst))
657                  . PI.lookupPackageName installedIndex
658        globalLatest = concat (getLatest <$> globalPackages)
659
660        baseEntries =
661          GhcEnvFileClearPackageDbStack : fmap GhcEnvFilePackageDb packageDbs
662        globalEntries = GhcEnvFilePackageId . installedUnitId <$> globalLatest
663        pkgEntries = ordNub $
664              globalEntries
665          ++ envEntries
666          ++ entriesForLibraryComponents (targetsMap buildCtx)
667        contents' = renderGhcEnvironmentFile (baseEntries ++ pkgEntries)
668      createDirectoryIfMissing True (takeDirectory envFile)
669      writeFileAtomic envFile (BS.pack contents')
670    else
671      warn verbosity $
672          "The current compiler doesn't support safely installing libraries, "
673        ++ "so only executables will be available. (Library installation is "
674        ++ "supported on GHC 8.0+ only)"
675
676warnIfNoExes :: Verbosity -> ProjectBuildContext -> IO ()
677warnIfNoExes verbosity buildCtx =
678  when noExes $
679    warn verbosity $
680    "\n" <>
681    "@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@\n" <>
682    "@ WARNING: Installation might not be completed as desired! @\n" <>
683    "@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@\n" <>
684    "Without flags, the command \"cabal install\" doesn't expose" <>
685    " libraries in a usable manner.  You might have wanted to run" <>
686    " \"cabal install --lib " <>
687    unwords (showTargetSelector <$> selectors) <> "\". "
688  where
689    targets    = concat $ Map.elems $ targetsMap buildCtx
690    components = fst <$> targets
691    selectors  = concatMap snd targets
692    noExes     = null $ catMaybes $ exeMaybe <$> components
693
694    exeMaybe (ComponentTarget (CExeName exe) _) = Just exe
695    exeMaybe _                                  = Nothing
696
697globalPackages :: [PackageName]
698globalPackages = mkPackageName <$>
699  [ "ghc", "hoopl", "bytestring", "unix", "base", "time", "hpc", "filepath"
700  , "process", "array", "integer-gmp", "containers", "ghc-boot", "binary"
701  , "ghc-prim", "ghci", "rts", "terminfo", "transformers", "deepseq"
702  , "ghc-boot-th", "pretty", "template-haskell", "directory", "text"
703  , "bin-package-db"
704  ]
705
706-- | Return the package specifiers and non-global environment file entries.
707getEnvSpecsAndNonGlobalEntries
708  :: PI.InstalledPackageIndex
709  -> [GhcEnvironmentFileEntry]
710  -> Bool
711  -> ([PackageSpecifier a], [GhcEnvironmentFileEntry])
712getEnvSpecsAndNonGlobalEntries installedIndex entries installLibs =
713  if installLibs
714  then (envSpecs, envEntries')
715  else ([], envEntries')
716  where
717    (envSpecs, envEntries') = environmentFileToSpecifiers installedIndex entries
718
719environmentFileToSpecifiers
720  :: PI.InstalledPackageIndex -> [GhcEnvironmentFileEntry]
721  -> ([PackageSpecifier a], [GhcEnvironmentFileEntry])
722environmentFileToSpecifiers ipi = foldMap $ \case
723    (GhcEnvFilePackageId unitId)
724        | Just InstalledPackageInfo
725          { sourcePackageId = PackageIdentifier{..}, installedUnitId }
726          <- PI.lookupUnitId ipi unitId
727        , let pkgSpec = NamedPackage pkgName
728                        [PackagePropertyVersion (thisVersion pkgVersion)]
729        -> if pkgName `elem` globalPackages
730          then ([pkgSpec], [])
731          else ([pkgSpec], [GhcEnvFilePackageId installedUnitId])
732    _ -> ([], [])
733
734
735-- | Disables tests and benchmarks if they weren't explicitly enabled.
736disableTestsBenchsByDefault :: ConfigFlags -> ConfigFlags
737disableTestsBenchsByDefault configFlags =
738  configFlags { configTests = Flag False <> configTests configFlags
739              , configBenchmarks = Flag False <> configBenchmarks configFlags }
740
741-- | Symlink/copy every exe from a package from the store to a given location
742installUnitExes
743  :: Verbosity
744  -> OverwritePolicy -- ^ Whether to overwrite existing files
745  -> (UnitId -> FilePath) -- ^ A function to get an UnitId's
746                          -- ^ store directory
747  -> (UnqualComponentName -> FilePath) -- ^ A function to get an
748                                       -- ^ exe's filename
749  -> (UnqualComponentName -> FilePath) -- ^ A function to get an
750                                       -- ^ exe's final possibly
751                                       -- ^ different to the name in the store.
752  -> FilePath
753  -> InstallMethod
754  -> ( UnitId
755     , [(ComponentTarget, [TargetSelector])] )
756  -> IO ()
757installUnitExes verbosity overwritePolicy
758                mkSourceBinDir mkExeName mkFinalExeName
759                installdir installMethod
760                (unit, components) =
761  traverse_ installAndWarn exes
762  where
763    exes = catMaybes $ (exeMaybe . fst) <$> components
764    exeMaybe (ComponentTarget (CExeName exe) _) = Just exe
765    exeMaybe _ = Nothing
766    installAndWarn exe = do
767      success <- installBuiltExe
768                   verbosity overwritePolicy
769                   (mkSourceBinDir unit) (mkExeName exe)
770                   (mkFinalExeName exe)
771                   installdir installMethod
772      let errorMessage = case overwritePolicy of
773            NeverOverwrite ->
774              "Path '" <> (installdir </> prettyShow exe) <> "' already exists. "
775              <> "Use --overwrite-policy=always to overwrite."
776            -- This shouldn't even be possible, but we keep it in case
777            -- symlinking/copying logic changes
778            AlwaysOverwrite ->
779              case installMethod of
780                InstallMethodSymlink -> "Symlinking"
781                InstallMethodCopy    ->
782                  "Copying" <> " '" <> prettyShow exe <> "' failed."
783      unless success $ die' verbosity errorMessage
784
785-- | Install a specific exe.
786installBuiltExe
787  :: Verbosity -> OverwritePolicy
788  -> FilePath -- ^ The directory where the built exe is located
789  -> FilePath -- ^ The exe's filename
790  -> FilePath -- ^ The exe's filename in the public install directory
791  -> FilePath -- ^ the directory where it should be installed
792  -> InstallMethod
793  -> IO Bool -- ^ Whether the installation was successful
794installBuiltExe verbosity overwritePolicy
795                sourceDir exeName finalExeName
796                installdir InstallMethodSymlink = do
797  notice verbosity $ "Symlinking '" <> exeName <> "' to '" <> destination <> "'"
798  symlinkBinary
799    overwritePolicy
800    installdir
801    sourceDir
802    finalExeName
803    exeName
804  where
805    destination = installdir </> finalExeName
806installBuiltExe verbosity overwritePolicy
807                sourceDir exeName finalExeName
808                installdir InstallMethodCopy = do
809  notice verbosity $ "Copying '" <> exeName <> "' to '" <> destination <> "'"
810  exists <- doesPathExist destination
811  case (exists, overwritePolicy) of
812    (True , NeverOverwrite ) -> pure False
813    (True , AlwaysOverwrite) -> remove >> copy
814    (False, _              ) -> copy
815  where
816    source      = sourceDir </> exeName
817    destination = installdir </> finalExeName
818    remove = do
819      isDir <- doesDirectoryExist destination
820      if isDir
821      then removeDirectory destination
822      else removeFile      destination
823    copy = copyFile source destination >> pure True
824
825-- | Create 'GhcEnvironmentFileEntry's for packages with exposed libraries.
826entriesForLibraryComponents :: TargetsMap -> [GhcEnvironmentFileEntry]
827entriesForLibraryComponents = Map.foldrWithKey' (\k v -> mappend (go k v)) []
828  where
829    hasLib :: (ComponentTarget, [TargetSelector]) -> Bool
830    hasLib (ComponentTarget (CLibName _) _, _) = True
831    hasLib _                                   = False
832
833    go :: UnitId
834       -> [(ComponentTarget, [TargetSelector])]
835       -> [GhcEnvironmentFileEntry]
836    go unitId targets
837      | any hasLib targets = [GhcEnvFilePackageId unitId]
838      | otherwise          = []
839
840
841-- | Gets the file path to the request environment file.
842getEnvFile :: ClientInstallFlags -> Platform -> Version -> IO FilePath
843getEnvFile clientInstallFlags platform compilerVersion = do
844  appDir <- getGhcAppDir
845  case flagToMaybe (cinstEnvironmentPath clientInstallFlags) of
846    Just spec
847      -- Is spec a bare word without any "pathy" content, then it refers to
848      -- a named global environment.
849      | takeBaseName spec == spec ->
850          return (getGlobalEnv appDir platform compilerVersion spec)
851      | otherwise                 -> do
852        spec' <- makeAbsolute spec
853        isDir <- doesDirectoryExist spec'
854        if isDir
855          -- If spec is a directory, then make an ambient environment inside
856          -- that directory.
857          then return (getLocalEnv spec' platform compilerVersion)
858          -- Otherwise, treat it like a literal file path.
859          else return spec'
860    Nothing                       ->
861      return (getGlobalEnv appDir platform compilerVersion "default")
862
863-- | Returns the list of @GhcEnvFilePackageIj@ values already existing in the
864--   environment being operated on.
865getExistingEnvEntries :: Verbosity -> CompilerFlavor -> Bool -> FilePath -> IO [GhcEnvironmentFileEntry]
866getExistingEnvEntries verbosity compilerFlavor supportsPkgEnvFiles envFile = do
867  envFileExists <- doesFileExist envFile
868  filterEnvEntries <$> if
869    (compilerFlavor == GHC || compilerFlavor == GHCJS)
870      && supportsPkgEnvFiles && envFileExists
871    then catch (readGhcEnvironmentFile envFile) $ \(_ :: ParseErrorExc) ->
872      warn verbosity ("The environment file " ++ envFile ++
873        " is unparsable. Libraries cannot be installed.") >> return []
874    else return []
875  where
876    -- Why? We know what the first part will be, we only care about the packages.
877    filterEnvEntries = filter $ \case
878      GhcEnvFilePackageId _ -> True
879      _                     -> False
880
881-- | Constructs the path to the global GHC environment file.
882--
883-- TODO(m-renaud): Create PkgEnvName newtype wrapper.
884getGlobalEnv :: FilePath -> Platform -> Version -> String -> FilePath
885getGlobalEnv appDir platform compilerVersion name =
886  appDir </> ghcPlatformAndVersionString platform compilerVersion
887  </> "environments" </> name
888
889-- | Constructs the path to a local GHC environment file.
890getLocalEnv :: FilePath -> Platform -> Version -> FilePath
891getLocalEnv dir platform compilerVersion  =
892  dir </>
893  ".ghc.environment." <> ghcPlatformAndVersionString platform compilerVersion
894
895getPackageDbStack
896  :: CompilerId
897  -> Flag FilePath
898  -> Flag FilePath
899  -> IO PackageDBStack
900getPackageDbStack compilerId storeDirFlag logsDirFlag = do
901  cabalDir <- getCabalDir
902  mstoreDir <- traverse makeAbsolute $ flagToMaybe storeDirFlag
903  let
904    mlogsDir    = flagToMaybe logsDirFlag
905    cabalLayout = mkCabalDirLayout cabalDir mstoreDir mlogsDir
906  pure $ storePackageDBStack (cabalStoreDirLayout cabalLayout) compilerId
907
908-- | This defines what a 'TargetSelector' means for the @bench@ command.
909-- It selects the 'AvailableTarget's that the 'TargetSelector' refers to,
910-- or otherwise classifies the problem.
911--
912-- For the @build@ command select all components except non-buildable
913-- and disabled tests\/benchmarks, fail if there are no such
914-- components
915--
916selectPackageTargets
917  :: TargetSelector
918  -> [AvailableTarget k] -> Either TargetProblem' [k]
919selectPackageTargets targetSelector targets
920
921    -- If there are any buildable targets then we select those
922  | not (null targetsBuildable)
923  = Right targetsBuildable
924
925    -- If there are targets but none are buildable then we report those
926  | not (null targets)
927  = Left (TargetProblemNoneEnabled targetSelector targets')
928
929    -- If there are no targets at all then we report that
930  | otherwise
931  = Left (TargetProblemNoTargets targetSelector)
932  where
933    targets'         = forgetTargetsDetail targets
934    targetsBuildable = selectBuildableTargetsWith
935                         (buildable targetSelector)
936                         targets
937
938    -- When there's a target filter like "pkg:tests" then we do select tests,
939    -- but if it's just a target like "pkg" then we don't build tests unless
940    -- they are requested by default (i.e. by using --enable-tests)
941    buildable (TargetPackage _ _  Nothing) TargetNotRequestedByDefault = False
942    buildable (TargetAllPackages  Nothing) TargetNotRequestedByDefault = False
943    buildable _ _ = True
944
945-- | For a 'TargetComponent' 'TargetSelector', check if the component can be
946-- selected.
947--
948-- For the @build@ command we just need the basic checks on being buildable etc.
949--
950selectComponentTarget
951  :: SubComponentTarget
952  -> AvailableTarget k -> Either TargetProblem' k
953selectComponentTarget = selectComponentTargetBasic
954
955reportBuildTargetProblems :: Verbosity -> [TargetProblem'] -> IO a
956reportBuildTargetProblems verbosity problems = reportTargetProblems verbosity "build" problems
957
958reportCannotPruneDependencies :: Verbosity -> CannotPruneDependencies -> IO a
959reportCannotPruneDependencies verbosity =
960    die' verbosity . renderCannotPruneDependencies
961