Correctly provision build tools in all situations
[cabal.git] / Cabal / src / Distribution / Simple / Configure.hs
blob9e561e791c69b009ba2138525b93742a57df4024
1 {-# LANGUAGE DataKinds #-}
2 {-# LANGUAGE DeriveDataTypeable #-}
3 {-# LANGUAGE FlexibleContexts #-}
4 {-# LANGUAGE NamedFieldPuns #-}
5 {-# LANGUAGE OverloadedStrings #-}
6 {-# LANGUAGE RankNTypes #-}
7 {-# LANGUAGE RecordWildCards #-}
8 {-# LANGUAGE ScopedTypeVariables #-}
10 -----------------------------------------------------------------------------
12 -- |
13 -- Module : Distribution.Simple.Configure
14 -- Copyright : Isaac Jones 2003-2005
15 -- License : BSD3
17 -- Maintainer : cabal-devel@haskell.org
18 -- Portability : portable
20 -- This deals with the /configure/ phase. It provides the 'configure' action
21 -- which is given the package description and configure flags. It then tries
22 -- to: configure the compiler; resolves any conditionals in the package
23 -- description; resolve the package dependencies; check if all the extensions
24 -- used by this package are supported by the compiler; check that all the build
25 -- tools are available (including version checks if appropriate); checks for
26 -- any required @pkg-config@ packages (updating the 'BuildInfo' with the
27 -- results)
29 -- Then based on all this it saves the info in the 'LocalBuildInfo' and writes
30 -- it out to the @dist\/setup-config@ file. It also displays various details to
31 -- the user, the amount of information displayed depending on the verbosity
32 -- level.
33 module Distribution.Simple.Configure
34 ( configure
35 , configure_setupHooks
36 , writePersistBuildConfig
37 , getConfigStateFile
38 , getPersistBuildConfig
39 , checkPersistBuildConfigOutdated
40 , tryGetPersistBuildConfig
41 , maybeGetPersistBuildConfig
42 , findDistPref
43 , findDistPrefOrDefault
44 , getInternalLibraries
45 , computeComponentId
46 , computeCompatPackageKey
47 , localBuildInfoFile
48 , getInstalledPackages
49 , getInstalledPackagesMonitorFiles
50 , getInstalledPackagesById
51 , getPackageDBContents
52 , configCompilerEx
53 , configCompilerAuxEx
54 , computeEffectiveProfiling
55 , ccLdOptionsBuildInfo
56 , checkForeignDeps
57 , interpretPackageDbFlags
58 , ConfigStateFileError (..)
59 , tryGetConfigStateFile
60 , platformDefines
61 ) where
63 import Control.Monad
64 import Distribution.Compat.Prelude
65 import Prelude ()
67 import Distribution.Backpack.Configure
68 import Distribution.Backpack.ConfiguredComponent (newPackageDepsBehaviour)
69 import Distribution.Backpack.DescribeUnitId
70 import Distribution.Backpack.Id
71 import Distribution.Backpack.PreExistingComponent
72 import qualified Distribution.Compat.Graph as Graph
73 import Distribution.Compat.Stack
74 import Distribution.Compiler
75 import Distribution.InstalledPackageInfo (InstalledPackageInfo)
76 import qualified Distribution.InstalledPackageInfo as IPI
77 import Distribution.Package
78 import Distribution.PackageDescription
79 import Distribution.PackageDescription.Check hiding (doesFileExist)
80 import Distribution.PackageDescription.Configuration
81 import Distribution.PackageDescription.PrettyPrint
82 import Distribution.Simple.BuildTarget
83 import Distribution.Simple.BuildToolDepends
84 import Distribution.Simple.Compiler
85 import Distribution.Simple.LocalBuildInfo
86 import Distribution.Simple.PackageIndex (InstalledPackageIndex, lookupUnitId)
87 import qualified Distribution.Simple.PackageIndex as PackageIndex
88 import Distribution.Simple.PreProcess
89 import Distribution.Simple.Program
90 import Distribution.Simple.Program.Db
91 ( ProgramDb (..)
92 , lookupProgramByName
93 , modifyProgramSearchPath
94 , prependProgramSearchPath
95 , updateConfiguredProgs
97 import Distribution.Simple.Setup.Common as Setup
98 import Distribution.Simple.Setup.Config as Setup
99 import Distribution.Simple.SetupHooks.Internal
100 ( ConfigureHooks (..)
101 , applyComponentDiffs
102 , noConfigureHooks
104 import qualified Distribution.Simple.SetupHooks.Internal as SetupHooks
105 import Distribution.Simple.Utils
106 import Distribution.System
107 import Distribution.Types.ComponentRequestedSpec
108 import Distribution.Types.GivenComponent
109 import qualified Distribution.Types.LocalBuildConfig as LBC
110 import Distribution.Types.LocalBuildInfo
111 import Distribution.Types.PackageVersionConstraint
112 import Distribution.Utils.LogProgress
113 import Distribution.Utils.NubList
114 import Distribution.Verbosity
115 import Distribution.Version
117 import qualified Distribution.Simple.GHC as GHC
118 import qualified Distribution.Simple.GHCJS as GHCJS
119 import qualified Distribution.Simple.HaskellSuite as HaskellSuite
120 import qualified Distribution.Simple.UHC as UHC
122 import Control.Exception
123 ( try
125 import qualified Data.ByteString as BS
126 import Data.ByteString.Lazy (ByteString)
127 import qualified Data.ByteString.Lazy.Char8 as BLC8
128 import Data.List
129 ( intersect
130 , stripPrefix
131 , (\\)
133 import qualified Data.List.NonEmpty as NEL
134 import qualified Data.Map as Map
135 import Distribution.Compat.Directory
136 ( doesPathExist
137 , listDirectory
139 import Distribution.Compat.Environment (lookupEnv)
140 import Distribution.Parsec
141 ( simpleParsec
143 import Distribution.Pretty
144 ( defaultStyle
145 , pretty
146 , prettyShow
148 import Distribution.Simple.Errors
149 import Distribution.Types.AnnotatedId
150 import Distribution.Utils.Path
151 import Distribution.Utils.Structured (structuredDecodeOrFailIO, structuredEncode)
152 import System.Directory
153 ( canonicalizePath
154 , createDirectoryIfMissing
155 , doesFileExist
156 , getTemporaryDirectory
157 , removeFile
159 import System.FilePath
160 ( isAbsolute
162 import System.IO
163 ( hClose
164 , hPutStrLn
166 import qualified System.Info
167 ( compilerName
168 , compilerVersion
170 import Text.PrettyPrint
171 ( Doc
172 , char
173 , hsep
174 , quotes
175 , renderStyle
176 , text
177 , ($+$)
180 import qualified Data.Maybe as M
181 import qualified Data.Set as Set
182 import qualified Distribution.Compat.NonEmptySet as NES
184 type UseExternalInternalDeps = Bool
186 -- | The errors that can be thrown when reading the @setup-config@ file.
187 data ConfigStateFileError
188 = -- | No header found.
189 ConfigStateFileNoHeader
190 | -- | Incorrect header.
191 ConfigStateFileBadHeader
192 | -- | Cannot parse file contents.
193 ConfigStateFileNoParse
194 | -- | No file!
195 ConfigStateFileMissing
196 { cfgStateFileErrorCwd :: Maybe (SymbolicPath CWD (Dir Pkg))
197 , cfgStateFileErrorFile :: SymbolicPath Pkg File
199 | -- | Mismatched version.
200 ConfigStateFileBadVersion
201 PackageIdentifier
202 PackageIdentifier
203 (Either ConfigStateFileError LocalBuildInfo)
204 deriving (Typeable)
206 -- | Format a 'ConfigStateFileError' as a user-facing error message.
207 dispConfigStateFileError :: ConfigStateFileError -> Doc
208 dispConfigStateFileError ConfigStateFileNoHeader =
209 text "Saved package config file header is missing."
210 <+> text "Re-run the 'configure' command."
211 dispConfigStateFileError ConfigStateFileBadHeader =
212 text "Saved package config file header is corrupt."
213 <+> text "Re-run the 'configure' command."
214 dispConfigStateFileError ConfigStateFileNoParse =
215 text "Saved package config file is corrupt."
216 <+> text "Re-run the 'configure' command."
217 dispConfigStateFileError ConfigStateFileMissing{} =
218 text "Run the 'configure' command first."
219 dispConfigStateFileError (ConfigStateFileBadVersion oldCabal oldCompiler _) =
220 text "Saved package config file is outdated:"
221 $+$ badCabal
222 $+$ badCompiler
223 $+$ text "Re-run the 'configure' command."
224 where
225 badCabal =
226 text "• the Cabal version changed from"
227 <+> pretty oldCabal
228 <+> "to"
229 <+> pretty currentCabalId
230 badCompiler
231 | oldCompiler == currentCompilerId = mempty
232 | otherwise =
233 text "• the compiler changed from"
234 <+> pretty oldCompiler
235 <+> "to"
236 <+> pretty currentCompilerId
238 instance Show ConfigStateFileError where
239 show = renderStyle defaultStyle . dispConfigStateFileError
241 instance Exception ConfigStateFileError
243 -- | Read the 'localBuildInfoFile'. Throw an exception if the file is
244 -- missing, if the file cannot be read, or if the file was created by an older
245 -- version of Cabal.
246 getConfigStateFile
247 :: Maybe (SymbolicPath CWD (Dir Pkg))
248 -> SymbolicPath Pkg File
249 -- ^ The file path of the @setup-config@ file.
250 -> IO LocalBuildInfo
251 getConfigStateFile mbWorkDir setupConfigFile = do
252 let filename = interpretSymbolicPath mbWorkDir setupConfigFile
253 exists <- doesFileExist filename
254 unless exists $ throwIO $ ConfigStateFileMissing mbWorkDir setupConfigFile
255 -- Read the config file into a strict ByteString to avoid problems with
256 -- lazy I/O, then convert to lazy because the binary package needs that.
257 contents <- BS.readFile filename
258 let (header, body) = BLC8.span (/= '\n') (BLC8.fromChunks [contents])
260 (cabalId, compId) <- parseHeader header
262 let getStoredValue = do
263 result <- structuredDecodeOrFailIO (BLC8.tail body)
264 case result of
265 Left _ -> throwIO ConfigStateFileNoParse
266 Right x -> return x
267 deferErrorIfBadVersion act
268 | cabalId /= currentCabalId = do
269 eResult <- try act
270 throwIO $ ConfigStateFileBadVersion cabalId compId eResult
271 | otherwise = act
272 deferErrorIfBadVersion getStoredValue
273 where
274 _ = callStack -- TODO: attach call stack to exception
276 -- | Read the 'localBuildInfoFile', returning either an error or the local build
277 -- info.
278 tryGetConfigStateFile
279 :: Maybe (SymbolicPath CWD (Dir Pkg))
280 -- ^ Working directory.
281 -> SymbolicPath Pkg File
282 -- ^ The file path of the @setup-config@ file.
283 -> IO (Either ConfigStateFileError LocalBuildInfo)
284 tryGetConfigStateFile mbWorkDir = try . getConfigStateFile mbWorkDir
286 -- | Try to read the 'localBuildInfoFile'.
287 tryGetPersistBuildConfig
288 :: Maybe (SymbolicPath CWD (Dir Pkg))
289 -- ^ Working directory.
290 -> SymbolicPath Pkg (Dir Dist)
291 -- ^ The @dist@ directory path.
292 -> IO (Either ConfigStateFileError LocalBuildInfo)
293 tryGetPersistBuildConfig mbWorkDir = try . getPersistBuildConfig mbWorkDir
295 -- | Read the 'localBuildInfoFile'. Throw an exception if the file is
296 -- missing, if the file cannot be read, or if the file was created by an older
297 -- version of Cabal.
298 getPersistBuildConfig
299 :: Maybe (SymbolicPath CWD (Dir Pkg))
300 -- ^ Working directory.
301 -> SymbolicPath Pkg (Dir Dist)
302 -- ^ The @dist@ directory path.
303 -> IO LocalBuildInfo
304 getPersistBuildConfig mbWorkDir distPref =
305 getConfigStateFile mbWorkDir $ localBuildInfoFile distPref
307 -- | Try to read the 'localBuildInfoFile'.
308 maybeGetPersistBuildConfig
309 :: Maybe (SymbolicPath CWD (Dir Pkg))
310 -- ^ Working directory.
311 -> SymbolicPath Pkg (Dir Dist)
312 -- ^ The @dist@ directory path.
313 -> IO (Maybe LocalBuildInfo)
314 maybeGetPersistBuildConfig mbWorkDir =
315 liftM (either (const Nothing) Just) . tryGetPersistBuildConfig mbWorkDir
317 -- | After running configure, output the 'LocalBuildInfo' to the
318 -- 'localBuildInfoFile'.
319 writePersistBuildConfig
320 :: Maybe (SymbolicPath CWD (Dir Pkg))
321 -- ^ Working directory
322 -> SymbolicPath Pkg (Dir Dist)
323 -- ^ The @dist@ directory path.
324 -> LocalBuildInfo
325 -- ^ The 'LocalBuildInfo' to write.
326 -> IO ()
327 writePersistBuildConfig mbWorkDir distPref lbi = do
328 createDirectoryIfMissing False (i distPref)
329 writeFileAtomic (i $ localBuildInfoFile distPref) $
330 BLC8.unlines [showHeader pkgId, structuredEncode lbi]
331 where
332 i = interpretSymbolicPath mbWorkDir -- See Note [Symbolic paths] in Distribution.Utils.Path
333 pkgId = localPackage lbi
335 -- | Identifier of the current Cabal package.
336 currentCabalId :: PackageIdentifier
337 currentCabalId = PackageIdentifier (mkPackageName "Cabal") cabalVersion
339 -- | Identifier of the current compiler package.
340 currentCompilerId :: PackageIdentifier
341 currentCompilerId =
342 PackageIdentifier
343 (mkPackageName System.Info.compilerName)
344 (mkVersion' System.Info.compilerVersion)
346 -- | Parse the @setup-config@ file header, returning the package identifiers
347 -- for Cabal and the compiler.
348 parseHeader
349 :: ByteString
350 -- ^ The file contents.
351 -> IO (PackageIdentifier, PackageIdentifier)
352 parseHeader header = case BLC8.words header of
353 [ "Saved"
354 , "package"
355 , "config"
356 , "for"
357 , pkgId
358 , "written"
359 , "by"
360 , cabalId
361 , "using"
362 , compId
363 ] ->
364 maybe (throwIO ConfigStateFileBadHeader) return $ do
365 _ <- simpleParsec (fromUTF8LBS pkgId) :: Maybe PackageIdentifier
366 cabalId' <- simpleParsec (BLC8.unpack cabalId)
367 compId' <- simpleParsec (BLC8.unpack compId)
368 return (cabalId', compId')
369 _ -> throwIO ConfigStateFileNoHeader
371 -- | Generate the @setup-config@ file header.
372 showHeader
373 :: PackageIdentifier
374 -- ^ The processed package.
375 -> ByteString
376 showHeader pkgId =
377 BLC8.unwords
378 [ "Saved"
379 , "package"
380 , "config"
381 , "for"
382 , toUTF8LBS $ prettyShow pkgId
383 , "written"
384 , "by"
385 , BLC8.pack $ prettyShow currentCabalId
386 , "using"
387 , BLC8.pack $ prettyShow currentCompilerId
390 -- | Check that localBuildInfoFile is up-to-date with respect to the
391 -- .cabal file.
392 checkPersistBuildConfigOutdated
393 :: Maybe (SymbolicPath CWD (Dir Pkg))
394 -> SymbolicPath Pkg (Dir Dist)
395 -> SymbolicPath Pkg File
396 -> IO Bool
397 checkPersistBuildConfigOutdated mbWorkDir distPref pkg_descr_file =
398 i pkg_descr_file `moreRecentFile` i (localBuildInfoFile distPref)
399 where
400 i = interpretSymbolicPath mbWorkDir -- See Note [Symbolic paths] in Distribution.Utils.Path
402 -- | Get the path of @dist\/setup-config@.
403 localBuildInfoFile
404 :: SymbolicPath Pkg (Dir Dist)
405 -- ^ The @dist@ directory path.
406 -> SymbolicPath Pkg File
407 localBuildInfoFile distPref = distPref </> makeRelativePathEx "setup-config"
409 -- -----------------------------------------------------------------------------
411 -- * Configuration
413 -- -----------------------------------------------------------------------------
415 -- | Return the \"dist/\" prefix, or the default prefix. The prefix is taken
416 -- from (in order of highest to lowest preference) the override prefix, the
417 -- \"CABAL_BUILDDIR\" environment variable, or the default prefix.
418 findDistPref
419 :: SymbolicPath Pkg (Dir Dist)
420 -- ^ default \"dist\" prefix
421 -> Setup.Flag (SymbolicPath Pkg (Dir Dist))
422 -- ^ override \"dist\" prefix
423 -> IO (SymbolicPath Pkg (Dir Dist))
424 findDistPref defDistPref overrideDistPref = do
425 envDistPref <- liftM parseEnvDistPref (lookupEnv "CABAL_BUILDDIR")
426 return $ fromFlagOrDefault defDistPref (mappend envDistPref overrideDistPref)
427 where
428 parseEnvDistPref env =
429 case env of
430 Just distPref | not (null distPref) -> toFlag $ makeSymbolicPath distPref
431 _ -> NoFlag
433 -- | Return the \"dist/\" prefix, or the default prefix. The prefix is taken
434 -- from (in order of highest to lowest preference) the override prefix, the
435 -- \"CABAL_BUILDDIR\" environment variable, or 'defaultDistPref' is used. Call
436 -- this function to resolve a @*DistPref@ flag whenever it is not known to be
437 -- set. (The @*DistPref@ flags are always set to a definite value before
438 -- invoking 'UserHooks'.)
439 findDistPrefOrDefault
440 :: Setup.Flag (SymbolicPath Pkg (Dir Dist))
441 -- ^ override \"dist\" prefix
442 -> IO (SymbolicPath Pkg (Dir Dist))
443 findDistPrefOrDefault = findDistPref defaultDistPref
445 -- | Perform the \"@.\/setup configure@\" action.
446 -- Returns the @.setup-config@ file.
447 configure
448 :: (GenericPackageDescription, HookedBuildInfo)
449 -> ConfigFlags
450 -> IO LocalBuildInfo
451 configure = configure_setupHooks noConfigureHooks
453 configure_setupHooks
454 :: ConfigureHooks
455 -> (GenericPackageDescription, HookedBuildInfo)
456 -> ConfigFlags
457 -> IO LocalBuildInfo
458 configure_setupHooks
459 (ConfigureHooks{preConfPackageHook, postConfPackageHook, preConfComponentHook})
460 (g_pkg_descr, hookedBuildInfo)
461 cfg = do
462 -- Cabal pre-configure
463 let verbosity = fromFlag (configVerbosity cfg)
464 distPref = fromFlag $ configDistPref cfg
465 mbWorkDir = flagToMaybe $ configWorkingDir cfg
466 (lbc0, comp, platform, enabledComps) <- preConfigurePackage cfg g_pkg_descr
468 -- Package-wide pre-configure hook
469 lbc1 <-
470 case preConfPackageHook of
471 Nothing -> return lbc0
472 Just pre_conf -> do
473 let programDb0 = LBC.withPrograms lbc0
474 programDb0' = programDb0{unconfiguredProgs = Map.empty}
475 input =
476 SetupHooks.PreConfPackageInputs
477 { SetupHooks.configFlags = cfg
478 , SetupHooks.localBuildConfig = lbc0{LBC.withPrograms = programDb0'}
479 , -- Unconfigured programs are not supplied to the hook,
480 -- as these cannot be passed over a serialisation boundary
481 -- (see the "Binary ProgramDb" instance).
482 SetupHooks.compiler = comp
483 , SetupHooks.platform = platform
485 SetupHooks.PreConfPackageOutputs
486 { SetupHooks.buildOptions = opts1
487 , SetupHooks.extraConfiguredProgs = progs1
488 } <-
489 pre_conf input
490 -- The package-wide pre-configure hook returns BuildOptions that
491 -- overrides the one it was passed in, as well as an update to
492 -- the ProgramDb in the form of new configured programs to add
493 -- to the program database.
494 return $
495 lbc0
496 { LBC.withBuildOptions = opts1
497 , LBC.withPrograms =
498 updateConfiguredProgs
499 (`Map.union` progs1)
500 programDb0
503 -- Cabal package-wide configure
504 (lbc2, pbd2, pkg_info) <-
505 finalizeAndConfigurePackage cfg lbc1 g_pkg_descr comp platform enabledComps
507 -- Package-wide post-configure hook
508 for_ postConfPackageHook $ \postConfPkg -> do
509 let input =
510 SetupHooks.PostConfPackageInputs
511 { SetupHooks.localBuildConfig = lbc2
512 , SetupHooks.packageBuildDescr = pbd2
514 postConfPkg input
516 -- Per-component pre-configure hook
517 pkg_descr <- do
518 let pkg_descr2 = LBC.localPkgDescr pbd2
519 applyComponentDiffs
520 verbosity
521 ( \c -> for preConfComponentHook $ \computeDiff -> do
522 let input =
523 SetupHooks.PreConfComponentInputs
524 { SetupHooks.localBuildConfig = lbc2
525 , SetupHooks.packageBuildDescr = pbd2
526 , SetupHooks.component = c
528 SetupHooks.PreConfComponentOutputs
529 { SetupHooks.componentDiff = diff
530 } <-
531 computeDiff input
532 return diff
534 pkg_descr2
535 let pbd3 = pbd2{LBC.localPkgDescr = pkg_descr}
537 -- Cabal per-component configure
538 externalPkgDeps <- finalCheckPackage g_pkg_descr pbd3 hookedBuildInfo pkg_info
539 lbi <- configureComponents lbc2 pbd3 pkg_info externalPkgDeps
541 writePersistBuildConfig mbWorkDir distPref lbi
543 return lbi
545 preConfigurePackage
546 :: ConfigFlags
547 -> GenericPackageDescription
548 -> IO (LBC.LocalBuildConfig, Compiler, Platform, ComponentRequestedSpec)
549 preConfigurePackage cfg g_pkg_descr = do
550 let verbosity = fromFlag $ configVerbosity cfg
552 -- Determine the component we are configuring, if a user specified
553 -- one on the command line. We use a fake, flattened version of
554 -- the package since at this point, we're not really sure what
555 -- components we *can* configure. @Nothing@ means that we should
556 -- configure everything (the old behavior).
557 (mb_cname :: Maybe ComponentName) <- do
558 let flat_pkg_descr = flattenPackageDescription g_pkg_descr
559 targets0 = configTargets cfg
560 targets <- readBuildTargets verbosity flat_pkg_descr targets0
561 -- TODO: bleat if you use the module/file syntax
562 let targets' = [cname | BuildTargetComponent cname <- targets]
563 case targets' of
564 _ | null targets0 -> return Nothing
565 [cname] -> return (Just cname)
566 [] -> dieWithException verbosity NoValidComponent
567 _ -> dieWithException verbosity ConfigureEitherSingleOrAll
569 case mb_cname of
570 Nothing -> setupMessage verbosity "Configuring" (packageId g_pkg_descr)
571 Just cname ->
572 setupMessage'
573 verbosity
574 "Configuring"
575 (packageId g_pkg_descr)
576 cname
577 (Just (configInstantiateWith cfg))
579 -- configCID is only valid for per-component configure
580 when (isJust (flagToMaybe (configCID cfg)) && isNothing mb_cname) $
581 dieWithException verbosity ConfigCIDValidForPreComponent
583 -- Make a data structure describing what components are enabled.
584 let enabled :: ComponentRequestedSpec
585 enabled = case mb_cname of
586 Just cname -> OneComponentRequestedSpec cname
587 Nothing ->
588 ComponentRequestedSpec
589 { -- The flag name (@--enable-tests@) is a
590 -- little bit of a misnomer, because
591 -- just passing this flag won't
592 -- "enable", in our internal
593 -- nomenclature; it's just a request; a
594 -- @buildable: False@ might make it
595 -- not possible to enable.
596 testsRequested = fromFlag (configTests cfg)
597 , benchmarksRequested =
598 fromFlag (configBenchmarks cfg)
600 -- Some sanity checks related to enabling components.
601 when
602 ( isJust mb_cname
603 && (fromFlag (configTests cfg) || fromFlag (configBenchmarks cfg))
605 $ dieWithException verbosity SanityCheckForEnableComponents
607 checkDeprecatedFlags verbosity cfg
608 checkExactConfiguration verbosity g_pkg_descr cfg
610 programDbPre <- mkProgramDb cfg (configPrograms cfg)
611 -- comp: the compiler we're building with
612 -- compPlatform: the platform we're building for
613 -- programDb: location and args of all programs we're
614 -- building with
615 ( comp :: Compiler
616 , compPlatform :: Platform
617 , programDb00 :: ProgramDb
618 ) <-
619 configCompilerEx
620 (flagToMaybe (configHcFlavor cfg))
621 (flagToMaybe (configHcPath cfg))
622 (flagToMaybe (configHcPkg cfg))
623 programDbPre
624 (lessVerbose verbosity)
626 -- Where to build the package
627 let builddir :: SymbolicPath Pkg (Dir Build) -- e.g. dist/build
628 builddir = setupFlagsBuildDir $ configCommonFlags cfg
629 mbWorkDir = flagToMaybe $ configWorkingDir cfg
630 -- NB: create this directory now so that all configure hooks get
631 -- to see it. (In practice, the Configure build-type needs it before
632 -- the postConfPackageHook runs.)
633 createDirectoryIfMissingVerbose (lessVerbose verbosity) True $
634 interpretSymbolicPath mbWorkDir builddir
636 lbc <- computeLocalBuildConfig cfg comp programDb00
637 return (lbc, comp, compPlatform, enabled)
639 computeLocalBuildConfig
640 :: ConfigFlags
641 -> Compiler
642 -> ProgramDb
643 -> IO LBC.LocalBuildConfig
644 computeLocalBuildConfig cfg comp programDb = do
645 let common = configCommonFlags cfg
646 verbosity = fromFlag $ setupVerbosity common
647 -- Decide if we're going to compile with split sections.
648 split_sections :: Bool <-
649 if not (fromFlag $ configSplitSections cfg)
650 then return False
651 else case compilerFlavor comp of
653 | compilerVersion comp >= mkVersion [8, 0] ->
654 return True
655 GHCJS ->
656 return True
657 _ -> do
658 warn
659 verbosity
660 ( "this compiler does not support "
661 ++ "--enable-split-sections; ignoring"
663 return False
665 -- Decide if we're going to compile with split objects.
666 split_objs :: Bool <-
667 if not (fromFlag $ configSplitObjs cfg)
668 then return False
669 else case compilerFlavor comp of
670 _ | split_sections ->
672 warn
673 verbosity
674 ( "--enable-split-sections and "
675 ++ "--enable-split-objs are mutually "
676 ++ "exclusive; ignoring the latter"
678 return False
679 GHC ->
680 return True
681 GHCJS ->
682 return True
683 _ -> do
684 warn
685 verbosity
686 ( "this compiler does not support "
687 ++ "--enable-split-objs; ignoring"
689 return False
691 -- Basically yes/no/unknown.
692 let linkerSupportsRelocations :: Maybe Bool
693 linkerSupportsRelocations =
694 case lookupProgramByName "ld" programDb of
695 Nothing -> Nothing
696 Just ld ->
697 case Map.lookup "Supports relocatable output" $ programProperties ld of
698 Just "YES" -> Just True
699 Just "NO" -> Just False
700 _other -> Nothing
701 let ghciLibByDefault =
702 case compilerId comp of
703 CompilerId GHC _ ->
704 -- If ghc is non-dynamic, then ghci needs object files,
705 -- so we build one by default.
707 -- Technically, archive files should be sufficient for ghci,
708 -- but because of GHC bug #8942, it has never been safe to
709 -- rely on them. By the time that bug was fixed, ghci had
710 -- been changed to read shared libraries instead of archive
711 -- files (see next code block).
712 not (GHC.isDynamic comp)
713 CompilerId GHCJS _ ->
714 not (GHCJS.isDynamic comp)
715 _ -> False
717 withGHCiLib_ <-
718 case fromFlagOrDefault ghciLibByDefault (configGHCiLib cfg) of
719 -- NOTE: If linkerSupportsRelocations is Nothing this may still fail if the
720 -- linker does not support -r.
721 True | not (fromMaybe True linkerSupportsRelocations) -> do
722 warn verbosity $
723 "--enable-library-for-ghci is not supported with the current"
724 ++ " linker; ignoring..."
725 return False
726 v -> return v
728 let sharedLibsByDefault
729 | fromFlag (configDynExe cfg) =
730 -- build a shared library if dynamically-linked
731 -- executables are requested
732 True
733 | otherwise = case compilerId comp of
734 CompilerId GHC _ ->
735 -- if ghc is dynamic, then ghci needs a shared
736 -- library, so we build one by default.
737 GHC.isDynamic comp
738 CompilerId GHCJS _ ->
739 GHCJS.isDynamic comp
740 _ -> False
741 withSharedLib_ =
742 -- build shared libraries if required by GHC or by the
743 -- executable linking mode, but allow the user to force
744 -- building only static library archives with
745 -- --disable-shared.
746 fromFlagOrDefault sharedLibsByDefault $ configSharedLib cfg
748 withStaticLib_ =
749 -- build a static library (all dependent libraries rolled
750 -- into a huge .a archive) via GHCs -staticlib flag.
751 fromFlagOrDefault False $ configStaticLib cfg
753 withDynExe_ = fromFlag $ configDynExe cfg
755 withFullyStaticExe_ = fromFlag $ configFullyStaticExe cfg
757 when (withDynExe_ && not withSharedLib_) $
758 warn verbosity $
759 "Executables will use dynamic linking, but a shared library "
760 ++ "is not being built. Linking will fail if any executables "
761 ++ "depend on the library."
763 setProfiling <- configureProfiling verbosity cfg comp
765 setCoverage <- configureCoverage verbosity cfg comp
767 -- Turn off library and executable stripping when `debug-info` is set
768 -- to anything other than zero.
770 strip_libexe s f =
771 let defaultStrip = fromFlagOrDefault True (f cfg)
772 in case fromFlag (configDebugInfo cfg) of
773 NoDebugInfo -> return defaultStrip
774 _ -> case f cfg of
775 Flag True -> do
776 warn verbosity $
777 "Setting debug-info implies "
778 ++ s
779 ++ "-stripping: False"
780 return False
781 _ -> return False
783 strip_lib <- strip_libexe "library" configStripLibs
784 strip_exe <- strip_libexe "executable" configStripExes
786 let buildOptions =
787 setCoverage . setProfiling $
788 LBC.BuildOptions
789 { withVanillaLib = fromFlag $ configVanillaLib cfg
790 , withSharedLib = withSharedLib_
791 , withStaticLib = withStaticLib_
792 , withDynExe = withDynExe_
793 , withFullyStaticExe = withFullyStaticExe_
794 , withProfLib = False
795 , withProfLibDetail = ProfDetailNone
796 , withProfExe = False
797 , withProfExeDetail = ProfDetailNone
798 , withOptimization = fromFlag $ configOptimization cfg
799 , withDebugInfo = fromFlag $ configDebugInfo cfg
800 , withGHCiLib = withGHCiLib_
801 , splitSections = split_sections
802 , splitObjs = split_objs
803 , stripExes = strip_exe
804 , stripLibs = strip_lib
805 , exeCoverage = False
806 , libCoverage = False
807 , relocatable = fromFlagOrDefault False $ configRelocatable cfg
810 return $
811 LBC.LocalBuildConfig
812 { extraConfigArgs = [] -- Currently configure does not
813 -- take extra args, but if it
814 -- did they would go here.
815 , withPrograms = programDb
816 , withBuildOptions = buildOptions
819 data PackageInfo = PackageInfo
820 { internalPackageSet :: Set LibraryName
821 , promisedDepsSet :: Map (PackageName, ComponentName) ComponentId
822 , installedPackageSet :: InstalledPackageIndex
823 , requiredDepsMap :: Map (PackageName, ComponentName) InstalledPackageInfo
826 configurePackage
827 :: ConfigFlags
828 -> LBC.LocalBuildConfig
829 -> PackageDescription
830 -> FlagAssignment
831 -> ComponentRequestedSpec
832 -> Compiler
833 -> Platform
834 -> ProgramDb
835 -> PackageDBStack
836 -> IO (LBC.LocalBuildConfig, LBC.PackageBuildDescr)
837 configurePackage cfg lbc0 pkg_descr00 flags enabled comp platform programDb0 packageDbs = do
838 let common = configCommonFlags cfg
839 verbosity = fromFlag $ setupVerbosity common
841 -- add extra include/lib dirs as specified in cfg
842 pkg_descr0 = addExtraIncludeLibDirsFromConfigFlags pkg_descr00 cfg
843 -- TODO: it is not clear whether this adding these dirs is necessary
844 -- when we are directly stating from a PackageDescription (e.g. when
845 -- cabal-install has determined a PackageDescription, instead of rediscovering
846 -- when working with a GenericPackageDescription).
847 -- Could this function call be moved to the end of finalizeAndConfigurePackage
848 -- right before calling configurePackage?
850 -- Configure certain external build tools, see below for which ones.
851 let requiredBuildTools = do
852 bi <- enabledBuildInfos pkg_descr0 enabled
853 -- First, we collect any tool dep that we know is external. This is,
854 -- in practice:
856 -- 1. `build-tools` entries on the whitelist
858 -- 2. `build-tool-depends` that aren't from the current package.
859 let externBuildToolDeps =
860 [ LegacyExeDependency (unUnqualComponentName eName) versionRange
861 | buildTool@(ExeDependency _ eName versionRange) <-
862 getAllToolDependencies pkg_descr0 bi
863 , not $ isInternal pkg_descr0 buildTool
865 -- Second, we collect any build-tools entry we don't know how to
866 -- desugar. We'll never have any idea how to build them, so we just
867 -- hope they are already on the PATH.
868 let unknownBuildTools =
869 [ buildTool
870 | buildTool <- buildTools bi
871 , Nothing == desugarBuildTool pkg_descr0 buildTool
873 externBuildToolDeps ++ unknownBuildTools
875 programDb1 <-
876 configureAllKnownPrograms (lessVerbose verbosity) programDb0
877 >>= configureRequiredPrograms verbosity requiredBuildTools
879 (pkg_descr2, programDb2) <-
880 configurePkgconfigPackages verbosity pkg_descr0 programDb1 enabled
882 let use_external_internal_deps =
883 case enabled of
884 OneComponentRequestedSpec{} -> True
885 ComponentRequestedSpec{} -> False
887 -- Compute installation directory templates, based on user
888 -- configuration.
890 -- TODO: Move this into a helper function.
891 defaultDirs :: InstallDirTemplates <-
892 defaultInstallDirs'
893 use_external_internal_deps
894 (compilerFlavor comp)
895 (fromFlag (configUserInstall cfg))
896 (hasLibs pkg_descr2)
898 installDirs =
899 combineInstallDirs
900 fromFlagOrDefault
901 defaultDirs
902 (configInstallDirs cfg)
903 lbc = lbc0{LBC.withPrograms = programDb2}
904 pbd =
905 LBC.PackageBuildDescr
906 { configFlags = cfg
907 , flagAssignment = flags
908 , componentEnabledSpec = enabled
909 , compiler = comp
910 , hostPlatform = platform
911 , localPkgDescr = pkg_descr2
912 , installDirTemplates = installDirs
913 , withPackageDB = packageDbs
914 , pkgDescrFile = Nothing
915 , extraCoverageFor = []
918 debug verbosity $
919 "Finalized package description:\n"
920 ++ showPackageDescription pkg_descr2
922 return (lbc, pbd)
924 finalizeAndConfigurePackage
925 :: ConfigFlags
926 -> LBC.LocalBuildConfig
927 -> GenericPackageDescription
928 -> Compiler
929 -> Platform
930 -> ComponentRequestedSpec
931 -> IO (LBC.LocalBuildConfig, LBC.PackageBuildDescr, PackageInfo)
932 finalizeAndConfigurePackage cfg lbc0 g_pkg_descr comp platform enabled = do
933 let common = configCommonFlags cfg
934 verbosity = fromFlag $ setupVerbosity common
935 mbWorkDir = flagToMaybe $ setupWorkingDir common
937 let programDb0 = LBC.withPrograms lbc0
938 -- What package database(s) to use
939 packageDbs :: PackageDBStack
940 packageDbs =
941 interpretPackageDbFlags
942 (fromFlag (configUserInstall cfg))
943 (configPackageDBs cfg)
945 -- The InstalledPackageIndex of all installed packages
946 installedPackageSet :: InstalledPackageIndex <-
947 getInstalledPackages
948 (lessVerbose verbosity)
949 comp
950 mbWorkDir
951 packageDbs
952 programDb0
954 -- The set of package names which are "shadowed" by internal
955 -- packages, and which component they map to
956 let internalPackageSet :: Set LibraryName
957 internalPackageSet = getInternalLibraries g_pkg_descr
959 -- Some sanity checks related to dynamic/static linking.
960 when (fromFlag (configDynExe cfg) && fromFlag (configFullyStaticExe cfg)) $
961 dieWithException verbosity SanityCheckForDynamicStaticLinking
963 -- allConstraints: The set of all 'Dependency's we have. Used ONLY
964 -- to 'configureFinalizedPackage'.
965 -- requiredDepsMap: A map from 'PackageName' to the specifically
966 -- required 'InstalledPackageInfo', due to --dependency
968 -- NB: These constraints are to be applied to ALL components of
969 -- a package. Thus, it's not an error if allConstraints contains
970 -- more constraints than is necessary for a component (another
971 -- component might need it.)
973 -- NB: The fact that we bundle all the constraints together means
974 -- that is not possible to configure a test-suite to use one
975 -- version of a dependency, and the executable to use another.
976 ( allConstraints :: [PackageVersionConstraint]
977 , requiredDepsMap :: Map (PackageName, ComponentName) InstalledPackageInfo
978 ) <-
979 either (dieWithException verbosity) return $
980 combinedConstraints
981 (configConstraints cfg)
982 (configDependencies cfg)
983 installedPackageSet
986 promisedDepsSet = mkPromisedDepsSet (configPromisedDependencies cfg)
987 pkg_info =
988 PackageInfo
989 { internalPackageSet
990 , promisedDepsSet
991 , installedPackageSet
992 , requiredDepsMap
995 -- pkg_descr: The resolved package description, that does not contain any
996 -- conditionals, because we have an assignment for
997 -- every flag, either picking them ourselves using a
998 -- simple naive algorithm, or having them be passed to
999 -- us by 'configConfigurationsFlags')
1000 -- flags: The 'FlagAssignment' that the conditionals were
1001 -- resolved with.
1003 -- NB: Why doesn't finalizing a package also tell us what the
1004 -- dependencies are (e.g. when we run the naive algorithm,
1005 -- we are checking if dependencies are satisfiable)? The
1006 -- primary reason is that we may NOT have done any solving:
1007 -- if the flags are all chosen for us, this step is a simple
1008 -- matter of flattening according to that assignment. It's
1009 -- cleaner to then configure the dependencies afterwards.
1010 let use_external_internal_deps = case enabled of
1011 OneComponentRequestedSpec{} -> True
1012 ComponentRequestedSpec{} -> False
1013 ( pkg_descr0 :: PackageDescription
1014 , flags :: FlagAssignment
1015 ) <-
1016 configureFinalizedPackage
1017 verbosity
1019 enabled
1020 allConstraints
1021 ( dependencySatisfiable
1022 use_external_internal_deps
1023 (fromFlagOrDefault False (configExactConfiguration cfg))
1024 (fromFlagOrDefault False (configAllowDependingOnPrivateLibs cfg))
1025 (packageName g_pkg_descr)
1026 installedPackageSet
1027 internalPackageSet
1028 promisedDepsSet
1029 requiredDepsMap
1031 comp
1032 platform
1033 g_pkg_descr
1035 (lbc, pbd) <-
1036 configurePackage
1038 lbc0
1039 pkg_descr0
1040 flags
1041 enabled
1042 comp
1043 platform
1044 programDb0
1045 packageDbs
1046 return (lbc, pbd, pkg_info)
1048 addExtraIncludeLibDirsFromConfigFlags
1049 :: PackageDescription -> ConfigFlags -> PackageDescription
1050 addExtraIncludeLibDirsFromConfigFlags pkg_descr cfg =
1051 let extraBi =
1052 mempty
1053 { extraLibDirs = configExtraLibDirs cfg
1054 , extraLibDirsStatic = configExtraLibDirsStatic cfg
1055 , extraFrameworkDirs = configExtraFrameworkDirs cfg
1056 , includeDirs = configExtraIncludeDirs cfg
1058 modifyLib l =
1060 { libBuildInfo =
1061 libBuildInfo l
1062 `mappend` extraBi
1064 modifyExecutable e =
1066 { buildInfo =
1067 buildInfo e
1068 `mappend` extraBi
1070 modifyForeignLib f =
1072 { foreignLibBuildInfo =
1073 foreignLibBuildInfo f
1074 `mappend` extraBi
1076 modifyTestsuite t =
1078 { testBuildInfo =
1079 testBuildInfo t
1080 `mappend` extraBi
1082 modifyBenchmark b =
1084 { benchmarkBuildInfo =
1085 benchmarkBuildInfo b
1086 `mappend` extraBi
1088 in pkg_descr
1089 { library = modifyLib `fmap` library pkg_descr
1090 , subLibraries = modifyLib `map` subLibraries pkg_descr
1091 , executables = modifyExecutable `map` executables pkg_descr
1092 , foreignLibs = modifyForeignLib `map` foreignLibs pkg_descr
1093 , testSuites = modifyTestsuite `map` testSuites pkg_descr
1094 , benchmarks = modifyBenchmark `map` benchmarks pkg_descr
1097 finalCheckPackage
1098 :: GenericPackageDescription
1099 -> LBC.PackageBuildDescr
1100 -> HookedBuildInfo
1101 -> PackageInfo
1102 -> IO ([PreExistingComponent], [PromisedComponent])
1103 finalCheckPackage
1104 g_pkg_descr
1105 ( LBC.PackageBuildDescr
1106 { configFlags = cfg
1107 , localPkgDescr = pkg_descr
1108 , compiler = comp
1109 , hostPlatform = compPlatform
1110 , componentEnabledSpec = enabled
1113 hookedBuildInfo
1114 (PackageInfo{internalPackageSet, promisedDepsSet, installedPackageSet, requiredDepsMap}) =
1116 let common = configCommonFlags cfg
1117 verbosity = fromFlag $ setupVerbosity common
1118 cabalFileDir = packageRoot common
1119 use_external_internal_deps =
1120 case enabled of
1121 OneComponentRequestedSpec{} -> True
1122 ComponentRequestedSpec{} -> False
1124 checkCompilerProblems verbosity comp pkg_descr enabled
1125 checkPackageProblems
1126 verbosity
1127 cabalFileDir
1128 g_pkg_descr
1129 (updatePackageDescription hookedBuildInfo pkg_descr)
1130 -- NB: we apply the HookedBuildInfo to check it is valid,
1131 -- but we don't propagate it.
1132 -- Other UserHooks must separately return it again, and we
1133 -- will re-apply it each time.
1135 -- Check languages and extensions
1136 -- TODO: Move this into a helper function.
1137 let langlist =
1138 nub $
1139 catMaybes $
1141 defaultLanguage
1142 (enabledBuildInfos pkg_descr enabled)
1143 let langs = unsupportedLanguages comp langlist
1144 when (not (null langs)) $
1145 dieWithException verbosity $
1146 UnsupportedLanguages (packageId g_pkg_descr) (compilerId comp) (map prettyShow langs)
1147 let extlist =
1148 nub $
1149 concatMap
1150 allExtensions
1151 (enabledBuildInfos pkg_descr enabled)
1152 let exts = unsupportedExtensions comp extlist
1153 when (not (null exts)) $
1154 dieWithException verbosity $
1155 UnsupportedLanguageExtension (packageId g_pkg_descr) (compilerId comp) (map prettyShow exts)
1157 -- Check foreign library build requirements
1158 let flibs = [flib | CFLib flib <- enabledComponents pkg_descr enabled]
1159 let unsupportedFLibs = unsupportedForeignLibs comp compPlatform flibs
1160 when (not (null unsupportedFLibs)) $
1161 dieWithException verbosity $
1162 CantFindForeignLibraries unsupportedFLibs
1164 -- The list of 'InstalledPackageInfo' recording the selected
1165 -- dependencies on external packages.
1167 -- Invariant: For any package name, there is at most one package
1168 -- in externalPackageDeps which has that name.
1170 -- NB: The dependency selection is global over ALL components
1171 -- in the package (similar to how allConstraints and
1172 -- requiredDepsMap are global over all components). In particular,
1173 -- if *any* component (post-flag resolution) has an unsatisfiable
1174 -- dependency, we will fail. This can sometimes be undesirable
1175 -- for users, see #1786 (benchmark conflicts with executable),
1177 -- In the presence of Backpack, these package dependencies are
1178 -- NOT complete: they only ever include the INDEFINITE
1179 -- dependencies. After we apply an instantiation, we'll get
1180 -- definite references which constitute extra dependencies.
1181 -- (Why not have cabal-install pass these in explicitly?
1182 -- For one it's deterministic; for two, we need to associate
1183 -- them with renamings which would require a far more complicated
1184 -- input scheme than what we have today.)
1185 configureDependencies
1186 verbosity
1187 use_external_internal_deps
1188 internalPackageSet
1189 promisedDepsSet
1190 installedPackageSet
1191 requiredDepsMap
1192 pkg_descr
1193 enabled
1195 configureComponents
1196 :: LBC.LocalBuildConfig
1197 -> LBC.PackageBuildDescr
1198 -> PackageInfo
1199 -> ([PreExistingComponent], [PromisedComponent])
1200 -> IO LocalBuildInfo
1201 configureComponents
1202 lbc@(LBC.LocalBuildConfig{withPrograms = programDb})
1203 pbd0@( LBC.PackageBuildDescr
1204 { configFlags = cfg
1205 , localPkgDescr = pkg_descr
1206 , compiler = comp
1207 , componentEnabledSpec = enabled
1210 (PackageInfo{promisedDepsSet, installedPackageSet})
1211 externalPkgDeps =
1213 let common = configCommonFlags cfg
1214 verbosity = fromFlag $ setupVerbosity common
1215 use_external_internal_deps =
1216 case enabled of
1217 OneComponentRequestedSpec{} -> True
1218 ComponentRequestedSpec{} -> False
1220 -- Compute internal component graph
1222 -- The general idea is that we take a look at all the source level
1223 -- components (which may build-depends on each other) and form a graph.
1224 -- From there, we build a ComponentLocalBuildInfo for each of the
1225 -- components, which lets us actually build each component.
1226 ( buildComponents :: [ComponentLocalBuildInfo]
1227 , packageDependsIndex :: InstalledPackageIndex
1228 ) <-
1229 runLogProgress verbosity $
1230 configureComponentLocalBuildInfos
1231 verbosity
1232 use_external_internal_deps
1233 enabled
1234 (fromFlagOrDefault False (configDeterministic cfg))
1235 (configIPID cfg)
1236 (configCID cfg)
1237 pkg_descr
1238 externalPkgDeps
1239 (configConfigurationsFlags cfg)
1240 (configInstantiateWith cfg)
1241 installedPackageSet
1242 comp
1244 let buildComponentsMap =
1245 foldl'
1246 ( \m clbi ->
1247 Map.insertWith
1248 (++)
1249 (componentLocalName clbi)
1250 [clbi]
1253 Map.empty
1254 buildComponents
1256 let cbd =
1257 LBC.ComponentBuildDescr
1258 { componentGraph = Graph.fromDistinctList buildComponents
1259 , componentNameMap = buildComponentsMap
1260 , promisedPkgs = promisedDepsSet
1261 , installedPkgs = packageDependsIndex
1264 -- For whole-package configure, we determine the
1265 -- extraCoverageFor of the main lib and sub libs here.
1266 extraCoverageUnitIds = case enabled of
1267 -- Whole package configure, add package libs
1268 ComponentRequestedSpec{} -> mapMaybe mbCompUnitId buildComponents
1269 -- Component configure, no need to do anything
1270 OneComponentRequestedSpec{} -> []
1271 mbCompUnitId LibComponentLocalBuildInfo{componentUnitId} = Just componentUnitId
1272 mbCompUnitId _ = Nothing
1274 pbd =
1275 pbd0
1276 { LBC.extraCoverageFor = extraCoverageUnitIds
1279 lbd =
1280 LBC.LocalBuildDescr
1281 { packageBuildDescr = pbd
1282 , componentBuildDescr = cbd
1285 lbi =
1286 NewLocalBuildInfo
1287 { localBuildDescr = lbd
1288 , localBuildConfig = lbc
1291 when (LBC.relocatable $ LBC.withBuildOptions lbc) $
1292 checkRelocatable verbosity pkg_descr lbi
1294 -- TODO: This is not entirely correct, because the dirs may vary
1295 -- across libraries/executables
1296 let dirs = absoluteInstallDirs pkg_descr lbi NoCopyDest
1297 relative = prefixRelativeInstallDirs (packageId pkg_descr) lbi
1299 -- PKGROOT: allowing ${pkgroot} to be passed as --prefix to
1300 -- cabal configure, is only a hidden option. It allows packages
1301 -- to be relocatable with their package database. This however
1302 -- breaks when the Paths_* or other includes are used that
1303 -- contain hard coded paths. This is still an open TODO.
1305 -- Allowing ${pkgroot} here, however requires less custom hooks
1306 -- in scripts that *really* want ${pkgroot}. See haskell/cabal/#4872
1307 unless
1308 ( isAbsolute (prefix dirs)
1309 || "${pkgroot}" `isPrefixOf` prefix dirs
1311 $ dieWithException verbosity
1312 $ ExpectedAbsoluteDirectory (prefix dirs)
1314 when ("${pkgroot}" `isPrefixOf` prefix dirs) $
1315 warn verbosity $
1316 "Using ${pkgroot} in prefix "
1317 ++ prefix dirs
1318 ++ " will not work if you rely on the Path_* module "
1319 ++ " or other hard coded paths. Cabal does not yet "
1320 ++ " support fully relocatable builds! "
1321 ++ " See #462 #2302 #2994 #3305 #3473 #3586 #3909"
1322 ++ " #4097 #4291 #4872"
1324 info verbosity $
1325 "Using "
1326 ++ prettyShow currentCabalId
1327 ++ " compiled by "
1328 ++ prettyShow currentCompilerId
1329 info verbosity $ "Using compiler: " ++ showCompilerId comp
1330 info verbosity $ "Using install prefix: " ++ prefix dirs
1332 let dirinfo name dir isPrefixRelative =
1333 info verbosity $ name ++ " installed in: " ++ dir ++ relNote
1334 where
1335 relNote = case buildOS of
1336 Windows
1337 | not (hasLibs pkg_descr)
1338 && isNothing isPrefixRelative ->
1339 " (fixed location)"
1340 _ -> ""
1342 dirinfo "Executables" (bindir dirs) (bindir relative)
1343 dirinfo "Libraries" (libdir dirs) (libdir relative)
1344 dirinfo "Dynamic Libraries" (dynlibdir dirs) (dynlibdir relative)
1345 dirinfo "Private executables" (libexecdir dirs) (libexecdir relative)
1346 dirinfo "Data files" (datadir dirs) (datadir relative)
1347 dirinfo "Documentation" (docdir dirs) (docdir relative)
1348 dirinfo "Configuration files" (sysconfdir dirs) (sysconfdir relative)
1350 sequence_
1351 [ reportProgram verbosity prog configuredProg
1352 | (prog, configuredProg) <- knownPrograms programDb
1355 return lbi
1357 mkPromisedDepsSet :: [GivenComponent] -> Map (PackageName, ComponentName) ComponentId
1358 mkPromisedDepsSet comps = Map.fromList [((pn, CLibName ln), cid) | GivenComponent pn ln cid <- comps]
1360 -- | Adds the extra program paths from the flags provided to @configure@ as
1361 -- well as specified locations for certain known programs and their default
1362 -- arguments.
1363 mkProgramDb :: ConfigFlags -> ProgramDb -> IO ProgramDb
1364 mkProgramDb cfg initialProgramDb = do
1365 programDb <-
1366 modifyProgramSearchPath (getProgramSearchPath initialProgramDb ++) -- We need to have the paths to programs installed by build-tool-depends before all other paths
1367 <$> prependProgramSearchPath (fromFlagOrDefault normal (configVerbosity cfg)) searchpath [] initialProgramDb
1368 pure
1369 . userSpecifyArgss (configProgramArgs cfg)
1370 . userSpecifyPaths (configProgramPaths cfg)
1371 $ programDb
1372 where
1373 searchpath = fromNubList (configProgramPathExtra cfg)
1375 -- Note. We try as much as possible to _prepend_ rather than postpend the extra-prog-path
1376 -- so that we can override the system path. However, in a v2-build, at this point, the "system" path
1377 -- has already been extended by both the built-tools-depends paths, as well as the program-path-extra
1378 -- so for v2 builds adding it again is entirely unnecessary. However, it needs to get added again _anyway_
1379 -- so as to take effect for v1 builds or standalone calls to Setup.hs
1380 -- In this instance, the lesser evil is to not allow it to override the system path.
1382 -- -----------------------------------------------------------------------------
1383 -- Helper functions for configure
1385 -- | Check if the user used any deprecated flags.
1386 checkDeprecatedFlags :: Verbosity -> ConfigFlags -> IO ()
1387 checkDeprecatedFlags verbosity cfg = do
1388 unless (configProfExe cfg == NoFlag) $ do
1389 let enable
1390 | fromFlag (configProfExe cfg) = "enable"
1391 | otherwise = "disable"
1392 warn
1393 verbosity
1394 ( "The flag --"
1395 ++ enable
1396 ++ "-executable-profiling is deprecated. "
1397 ++ "Please use --"
1398 ++ enable
1399 ++ "-profiling instead."
1402 unless (configLibCoverage cfg == NoFlag) $ do
1403 let enable
1404 | fromFlag (configLibCoverage cfg) = "enable"
1405 | otherwise = "disable"
1406 warn
1407 verbosity
1408 ( "The flag --"
1409 ++ enable
1410 ++ "-library-coverage is deprecated. "
1411 ++ "Please use --"
1412 ++ enable
1413 ++ "-coverage instead."
1416 -- | Sanity check: if '--exact-configuration' was given, ensure that the
1417 -- complete flag assignment was specified on the command line.
1418 checkExactConfiguration
1419 :: Verbosity -> GenericPackageDescription -> ConfigFlags -> IO ()
1420 checkExactConfiguration verbosity pkg_descr0 cfg =
1421 when (fromFlagOrDefault False (configExactConfiguration cfg)) $ do
1422 let cmdlineFlags = map fst (unFlagAssignment (configConfigurationsFlags cfg))
1423 allFlags = map flagName . genPackageFlags $ pkg_descr0
1424 diffFlags = allFlags \\ cmdlineFlags
1425 when (not . null $ diffFlags) $
1426 dieWithException verbosity $
1427 FlagsNotSpecified diffFlags
1429 -- | Create a PackageIndex that makes *any libraries that might be*
1430 -- defined internally to this package look like installed packages, in
1431 -- case an executable should refer to any of them as dependencies.
1433 -- It must be *any libraries that might be* defined rather than the
1434 -- actual definitions, because these depend on conditionals in the .cabal
1435 -- file, and we haven't resolved them yet. finalizePD
1436 -- does the resolution of conditionals, and it takes internalPackageSet
1437 -- as part of its input.
1438 getInternalLibraries
1439 :: GenericPackageDescription
1440 -> Set LibraryName
1441 getInternalLibraries pkg_descr0 =
1442 -- TODO: some day, executables will be fair game here too!
1443 let pkg_descr = flattenPackageDescription pkg_descr0
1444 in Set.fromList (map libName (allLibraries pkg_descr))
1446 -- | Returns true if a dependency is satisfiable. This function may
1447 -- report a dependency satisfiable even when it is not, but not vice
1448 -- versa. This is to be passed to finalize
1449 dependencySatisfiable
1450 :: Bool
1451 -- ^ use external internal deps?
1452 -> Bool
1453 -- ^ exact configuration?
1454 -> Bool
1455 -- ^ allow depending on private libs?
1456 -> PackageName
1457 -> InstalledPackageIndex
1458 -- ^ installed set
1459 -> Set LibraryName
1460 -- ^ library components
1461 -> Map (PackageName, ComponentName) ComponentId
1462 -> Map (PackageName, ComponentName) InstalledPackageInfo
1463 -- ^ required dependencies
1464 -> (Dependency -> Bool)
1465 dependencySatisfiable
1466 use_external_internal_deps
1467 exact_config
1468 allow_private_deps
1470 installedPackageSet
1471 packageLibraries
1472 promisedDeps
1473 requiredDepsMap
1474 (Dependency depName vr sublibs)
1475 | exact_config =
1476 -- When we're given '--exact-configuration', we assume that all
1477 -- dependencies and flags are exactly specified on the command
1478 -- line. Thus we only consult the 'requiredDepsMap'. Note that
1479 -- we're not doing the version range check, so if there's some
1480 -- dependency that wasn't specified on the command line,
1481 -- 'finalizePD' will fail.
1482 -- TODO: mention '--exact-configuration' in the error message
1483 -- when this fails?
1484 if isInternalDep && not use_external_internal_deps
1485 then -- Except for internal deps, when we're NOT per-component mode;
1486 -- those are just True.
1487 internalDepSatisfiable
1488 else -- Backward compatibility for the old sublibrary syntax
1490 ( sublibs == mainLibSet
1491 && Map.member
1492 ( pn
1493 , CLibName $
1494 LSubLibName $
1495 packageNameToUnqualComponentName depName
1497 requiredDepsMap
1499 || all visible sublibs
1500 | isInternalDep =
1501 if use_external_internal_deps
1502 then -- When we are doing per-component configure, we now need to
1503 -- test if the internal dependency is in the index. This has
1504 -- DIFFERENT semantics from normal dependency satisfiability.
1505 internalDepSatisfiableExternally
1506 else -- If a 'PackageName' is defined by an internal component, the dep is
1507 -- satisfiable (we're going to build it ourselves)
1508 internalDepSatisfiable
1509 | otherwise =
1510 depSatisfiable
1511 where
1512 -- Internal dependency is when dependency is the same as package.
1513 isInternalDep = pn == depName
1515 depSatisfiable =
1516 not . null $ PackageIndex.lookupDependency installedPackageSet depName vr
1518 internalDepSatisfiable =
1519 Set.isSubsetOf (NES.toSet sublibs) packageLibraries
1520 internalDepSatisfiableExternally =
1521 all (\ln -> not $ null $ PackageIndex.lookupInternalDependency installedPackageSet pn vr ln) sublibs
1523 -- Check whether a library exists and is visible.
1524 -- We don't disambiguate between dependency on non-existent or private
1525 -- library yet, so we just return a bool and later report a generic error.
1526 visible lib =
1527 maybe
1528 False -- Does not even exist (wasn't in the depsMap)
1529 ( \ipi ->
1530 IPI.libVisibility ipi == LibraryVisibilityPublic
1531 -- If the override is enabled, the visibility does
1532 -- not matter (it's handled externally)
1533 || allow_private_deps
1534 -- If it's a library of the same package then it's
1535 -- always visible.
1536 -- This is only triggered when passing a component
1537 -- of the same package as --dependency, such as in:
1538 -- cabal-testsuite/PackageTests/ConfigureComponent/SubLib/setup-explicit.test.hs
1539 || pkgName (IPI.sourcePackageId ipi) == pn
1541 maybeIPI
1542 -- Don't check if it's visible, we promise to build it before we need it.
1543 || promised
1544 where
1545 maybeIPI = Map.lookup (depName, CLibName lib) requiredDepsMap
1546 promised = isJust $ Map.lookup (depName, CLibName lib) promisedDeps
1548 -- | Finalize a generic package description.
1550 -- The workhorse is 'finalizePD'.
1551 configureFinalizedPackage
1552 :: Verbosity
1553 -> ConfigFlags
1554 -> ComponentRequestedSpec
1555 -> [PackageVersionConstraint]
1556 -> (Dependency -> Bool)
1557 -- ^ tests if a dependency is satisfiable.
1558 -- Might say it's satisfiable even when not.
1559 -> Compiler
1560 -> Platform
1561 -> GenericPackageDescription
1562 -> IO (PackageDescription, FlagAssignment)
1563 configureFinalizedPackage
1564 verbosity
1566 enabled
1567 allConstraints
1568 satisfies
1569 comp
1570 compPlatform
1571 pkg_descr0 = do
1572 (pkg_descr, flags) <-
1573 case finalizePD
1574 (configConfigurationsFlags cfg)
1575 enabled
1576 satisfies
1577 compPlatform
1578 (compilerInfo comp)
1579 allConstraints
1580 pkg_descr0 of
1581 Right r -> return r
1582 Left missing ->
1583 dieWithException verbosity $ EncounteredMissingDependency missing
1585 unless (nullFlagAssignment flags) $
1586 info verbosity $
1587 "Flags chosen: "
1588 ++ intercalate
1589 ", "
1590 [ unFlagName fn ++ "=" ++ prettyShow value
1591 | (fn, value) <- unFlagAssignment flags
1594 return (pkg_descr, flags)
1596 -- | Check for use of Cabal features which require compiler support
1597 checkCompilerProblems
1598 :: Verbosity -> Compiler -> PackageDescription -> ComponentRequestedSpec -> IO ()
1599 checkCompilerProblems verbosity comp pkg_descr enabled = do
1600 unless
1601 ( renamingPackageFlagsSupported comp
1602 || all
1603 (all (isDefaultIncludeRenaming . mixinIncludeRenaming) . mixins)
1604 (enabledBuildInfos pkg_descr enabled)
1606 $ dieWithException verbosity CompilerDoesn'tSupportThinning
1607 when
1608 ( any (not . null . reexportedModules) (allLibraries pkg_descr)
1609 && not (reexportedModulesSupported comp)
1611 $ dieWithException verbosity CompilerDoesn'tSupportReexports
1612 when
1613 ( any (not . null . signatures) (allLibraries pkg_descr)
1614 && not (backpackSupported comp)
1616 $ dieWithException verbosity CompilerDoesn'tSupportBackpack
1618 -- | Select dependencies for the package.
1619 configureDependencies
1620 :: Verbosity
1621 -> UseExternalInternalDeps
1622 -> Set LibraryName
1623 -> Map (PackageName, ComponentName) ComponentId
1624 -> InstalledPackageIndex
1625 -- ^ installed packages
1626 -> Map (PackageName, ComponentName) InstalledPackageInfo
1627 -- ^ required deps
1628 -> PackageDescription
1629 -> ComponentRequestedSpec
1630 -> IO ([PreExistingComponent], [PromisedComponent])
1631 configureDependencies
1632 verbosity
1633 use_external_internal_deps
1634 packageLibraries
1635 promisedDeps
1636 installedPackageSet
1637 requiredDepsMap
1638 pkg_descr
1639 enableSpec = do
1640 let failedDeps :: [FailedDependency]
1641 allPkgDeps :: [ResolvedDependency]
1642 (failedDeps, allPkgDeps) =
1643 partitionEithers $
1644 concat
1645 [ fmap (\s -> (dep, s)) <$> status
1646 | dep <- enabledBuildDepends pkg_descr enableSpec
1647 , let status =
1648 selectDependency
1649 (package pkg_descr)
1650 packageLibraries
1651 promisedDeps
1652 installedPackageSet
1653 requiredDepsMap
1654 use_external_internal_deps
1658 internalPkgDeps =
1659 [ pkgid
1660 | (_, InternalDependency pkgid) <- allPkgDeps
1662 -- NB: we have to SAVE the package name, because this is the only
1663 -- way we can be able to resolve package names in the package
1664 -- description.
1665 externalPkgDeps =
1666 [ pec
1667 | (_, ExternalDependency pec) <- allPkgDeps
1670 promisedPkgDeps =
1671 [ fpec
1672 | (_, PromisedDependency fpec) <- allPkgDeps
1675 when
1676 ( not (null internalPkgDeps)
1677 && not (newPackageDepsBehaviour pkg_descr)
1679 $ dieWithException verbosity
1680 $ LibraryWithinSamePackage internalPkgDeps
1681 reportFailedDependencies verbosity failedDeps
1682 reportSelectedDependencies verbosity allPkgDeps
1684 return (externalPkgDeps, promisedPkgDeps)
1686 -- | Select and apply coverage settings for the build based on the
1687 -- 'ConfigFlags' and 'Compiler'.
1688 configureCoverage
1689 :: Verbosity
1690 -> ConfigFlags
1691 -> Compiler
1692 -> IO (LBC.BuildOptions -> LBC.BuildOptions)
1693 configureCoverage verbosity cfg comp = do
1694 let tryExeCoverage = fromFlagOrDefault False (configCoverage cfg)
1695 tryLibCoverage =
1696 fromFlagOrDefault
1697 tryExeCoverage
1698 (mappend (configCoverage cfg) (configLibCoverage cfg))
1699 -- TODO: Should we also enforce something here on that --coverage-for cannot
1700 -- include indefinite components or instantiations?
1701 if coverageSupported comp
1702 then do
1703 let apply buildOptions =
1704 buildOptions
1705 { LBC.libCoverage = tryLibCoverage
1706 , LBC.exeCoverage = tryExeCoverage
1708 return apply
1709 else do
1710 let apply buildOptions =
1711 buildOptions
1712 { LBC.libCoverage = False
1713 , LBC.exeCoverage = False
1715 when (tryExeCoverage || tryLibCoverage) $
1716 warn
1717 verbosity
1718 ( "The compiler "
1719 ++ showCompilerId comp
1720 ++ " does not support "
1721 ++ "program coverage. Program coverage has been disabled."
1723 return apply
1725 -- | Compute the effective value of the profiling flags
1726 -- @--enable-library-profiling@ and @--enable-executable-profiling@
1727 -- from the specified 'ConfigFlags'. This may be useful for
1728 -- external Cabal tools which need to interact with Setup in
1729 -- a backwards-compatible way: the most predictable mechanism
1730 -- for enabling profiling across many legacy versions is to
1731 -- NOT use @--enable-profiling@ and use those two flags instead.
1733 -- Note that @--enable-executable-profiling@ also affects profiling
1734 -- of benchmarks and (non-detailed) test suites.
1735 computeEffectiveProfiling :: ConfigFlags -> (Bool {- lib -}, Bool {- exe -})
1736 computeEffectiveProfiling cfg =
1737 -- The --profiling flag sets the default for both libs and exes,
1738 -- but can be overridden by --library-profiling, or the old deprecated
1739 -- --executable-profiling flag.
1741 -- The --profiling-detail and --library-profiling-detail flags behave
1742 -- similarly
1743 let tryExeProfiling =
1744 fromFlagOrDefault
1745 False
1746 (mappend (configProf cfg) (configProfExe cfg))
1747 tryLibProfiling =
1748 fromFlagOrDefault
1749 tryExeProfiling
1750 (mappend (configProf cfg) (configProfLib cfg))
1751 in (tryLibProfiling, tryExeProfiling)
1753 -- | Select and apply profiling settings for the build based on the
1754 -- 'ConfigFlags' and 'Compiler'.
1755 configureProfiling
1756 :: Verbosity
1757 -> ConfigFlags
1758 -> Compiler
1759 -> IO (LBC.BuildOptions -> LBC.BuildOptions)
1760 configureProfiling verbosity cfg comp = do
1761 let (tryLibProfiling, tryExeProfiling) = computeEffectiveProfiling cfg
1763 tryExeProfileLevel =
1764 fromFlagOrDefault
1765 ProfDetailDefault
1766 (configProfDetail cfg)
1767 tryLibProfileLevel =
1768 fromFlagOrDefault
1769 ProfDetailDefault
1770 ( mappend
1771 (configProfDetail cfg)
1772 (configProfLibDetail cfg)
1775 checkProfileLevel (ProfDetailOther other) = do
1776 warn
1777 verbosity
1778 ( "Unknown profiling detail level '"
1779 ++ other
1780 ++ "', using default.\nThe profiling detail levels are: "
1781 ++ intercalate
1782 ", "
1783 [name | (name, _, _) <- knownProfDetailLevels]
1785 return ProfDetailDefault
1786 checkProfileLevel other = return other
1788 (exeProfWithoutLibProf, applyProfiling) <-
1789 if profilingSupported comp
1790 then do
1791 exeLevel <- checkProfileLevel tryExeProfileLevel
1792 libLevel <- checkProfileLevel tryLibProfileLevel
1793 let apply buildOptions =
1794 buildOptions
1795 { LBC.withProfLib = tryLibProfiling
1796 , LBC.withProfLibDetail = libLevel
1797 , LBC.withProfExe = tryExeProfiling
1798 , LBC.withProfExeDetail = exeLevel
1800 return (tryExeProfiling && not tryLibProfiling, apply)
1801 else do
1802 let apply buildOptions =
1803 buildOptions
1804 { LBC.withProfLib = False
1805 , LBC.withProfLibDetail = ProfDetailNone
1806 , LBC.withProfExe = False
1807 , LBC.withProfExeDetail = ProfDetailNone
1809 when (tryExeProfiling || tryLibProfiling) $
1810 warn
1811 verbosity
1812 ( "The compiler "
1813 ++ showCompilerId comp
1814 ++ " does not support "
1815 ++ "profiling. Profiling has been disabled."
1817 return (False, apply)
1819 when exeProfWithoutLibProf $
1820 warn
1821 verbosity
1822 ( "Executables will be built with profiling, but library "
1823 ++ "profiling is disabled. Linking will fail if any executables "
1824 ++ "depend on the library."
1827 return applyProfiling
1829 -- -----------------------------------------------------------------------------
1830 -- Configuring package dependencies
1832 reportProgram :: Verbosity -> Program -> Maybe ConfiguredProgram -> IO ()
1833 reportProgram verbosity prog Nothing =
1834 info verbosity $ "No " ++ programName prog ++ " found"
1835 reportProgram verbosity prog (Just configuredProg) =
1836 info verbosity $ "Using " ++ programName prog ++ version ++ location
1837 where
1838 location = case programLocation configuredProg of
1839 FoundOnSystem p -> " found on system at: " ++ p
1840 UserSpecified p -> " given by user at: " ++ p
1841 version = case programVersion configuredProg of
1842 Nothing -> ""
1843 Just v -> " version " ++ prettyShow v
1845 hackageUrl :: String
1846 hackageUrl = "http://hackage.haskell.org/package/"
1848 type ResolvedDependency = (Dependency, DependencyResolution)
1850 data DependencyResolution
1851 = -- | An external dependency from the package database, OR an
1852 -- internal dependency which we are getting from the package
1853 -- database.
1854 ExternalDependency PreExistingComponent
1855 | -- | A promised dependency, which doesn't yet exist, but should be provided
1856 -- at the build time.
1858 -- We have these such that we can configure components without actually
1859 -- building its dependencies, if these dependencies need to be built later
1860 -- again. For example, when launching a multi-repl,
1861 -- we need to build packages in the interactive ghci session, no matter
1862 -- whether they have been built before.
1863 -- Building them in the configure phase is then redundant and costs time.
1864 PromisedDependency PromisedComponent
1865 | -- | An internal dependency ('PackageId' should be a library name)
1866 -- which we are going to have to build. (The
1867 -- 'PackageId' here is a hack to get a modest amount of
1868 -- polymorphism out of the Pkg' typeclass.)
1869 InternalDependency PackageId
1871 -- | Test for a package dependency and record the version we have installed.
1872 selectDependency
1873 :: PackageId
1874 -- ^ Package id of current package
1875 -> Set LibraryName
1876 -- ^ package libraries
1877 -> Map (PackageName, ComponentName) ComponentId
1878 -- ^ Set of components that are promised, i.e. are not installed already. See 'PromisedDependency' for more details.
1879 -> InstalledPackageIndex
1880 -- ^ Installed packages
1881 -> Map (PackageName, ComponentName) InstalledPackageInfo
1882 -- ^ Packages for which we have been given specific deps to
1883 -- use
1884 -> UseExternalInternalDeps
1885 -- ^ Are we configuring a
1886 -- single component?
1887 -> Dependency
1888 -> [Either FailedDependency DependencyResolution]
1889 selectDependency
1890 pkgid
1891 internalIndex
1892 promisedIndex
1893 installedIndex
1894 requiredDepsMap
1895 use_external_internal_deps
1896 (Dependency dep_pkgname vr libs) =
1897 -- If the dependency specification matches anything in the internal package
1898 -- index, then we prefer that match to anything in the second.
1899 -- For example:
1901 -- Name: MyLibrary
1902 -- Version: 0.1
1903 -- Library
1904 -- ..
1905 -- Executable my-exec
1906 -- build-depends: MyLibrary
1908 -- We want "build-depends: MyLibrary" always to match the internal library
1909 -- even if there is a newer installed library "MyLibrary-0.2".
1910 if dep_pkgname == pn
1911 then
1912 if use_external_internal_deps
1913 then do_external_internal <$> NES.toList libs
1914 else do_internal <$> NES.toList libs
1915 else do_external_external <$> NES.toList libs
1916 where
1917 pn = packageName pkgid
1919 -- It's an internal library, and we're not per-component build
1920 do_internal lib
1921 | Set.member lib internalIndex =
1922 Right $ InternalDependency $ PackageIdentifier dep_pkgname $ packageVersion pkgid
1923 | otherwise =
1924 Left $ DependencyMissingInternal dep_pkgname lib
1926 -- We have to look it up externally
1927 do_external_external :: LibraryName -> Either FailedDependency DependencyResolution
1928 do_external_external lib
1929 | Just cid <- Map.lookup (dep_pkgname, CLibName lib) promisedIndex =
1930 return $ PromisedDependency (PromisedComponent dep_pkgname (AnnotatedId currentCabalId (CLibName lib) cid))
1931 do_external_external lib = do
1932 ipi <- case Map.lookup (dep_pkgname, CLibName lib) requiredDepsMap of
1933 -- If we know the exact pkg to use, then use it.
1934 Just pkginstance -> Right pkginstance
1935 -- Otherwise we just pick an arbitrary instance of the latest version.
1936 Nothing -> case pickLastIPI $ PackageIndex.lookupInternalDependency installedIndex dep_pkgname vr lib of
1937 Nothing -> Left (DependencyNotExists dep_pkgname)
1938 Just pkg -> Right pkg
1939 return $ ExternalDependency $ ipiToPreExistingComponent ipi
1941 do_external_internal :: LibraryName -> Either FailedDependency DependencyResolution
1942 do_external_internal lib
1943 | Just cid <- Map.lookup (dep_pkgname, CLibName lib) promisedIndex =
1944 return $ PromisedDependency (PromisedComponent dep_pkgname (AnnotatedId currentCabalId (CLibName lib) cid))
1945 do_external_internal lib = do
1946 ipi <- case Map.lookup (dep_pkgname, CLibName lib) requiredDepsMap of
1947 -- If we know the exact pkg to use, then use it.
1948 Just pkginstance -> Right pkginstance
1949 Nothing -> case pickLastIPI $ PackageIndex.lookupInternalDependency installedIndex pn vr lib of
1950 -- It's an internal library, being looked up externally
1951 Nothing -> Left (DependencyMissingInternal dep_pkgname lib)
1952 Just pkg -> Right pkg
1953 return $ ExternalDependency $ ipiToPreExistingComponent ipi
1955 pickLastIPI :: [(Version, [InstalledPackageInfo])] -> Maybe InstalledPackageInfo
1956 pickLastIPI pkgs = safeHead . snd . last =<< nonEmpty pkgs
1958 reportSelectedDependencies
1959 :: Verbosity
1960 -> [ResolvedDependency]
1961 -> IO ()
1962 reportSelectedDependencies verbosity deps =
1963 info verbosity $
1964 unlines
1965 [ "Dependency "
1966 ++ prettyShow (simplifyDependency dep)
1967 ++ ": using "
1968 ++ prettyShow pkgid
1969 | (dep, resolution) <- deps
1970 , let pkgid = case resolution of
1971 ExternalDependency pkg' -> packageId pkg'
1972 InternalDependency pkgid' -> pkgid'
1973 PromisedDependency promisedComp -> packageId promisedComp
1976 reportFailedDependencies :: Verbosity -> [FailedDependency] -> IO ()
1977 reportFailedDependencies _ [] = return ()
1978 reportFailedDependencies verbosity failed =
1979 dieWithException verbosity $ ReportFailedDependencies failed hackageUrl
1981 -- | List all installed packages in the given package databases.
1982 -- Non-existent package databases do not cause errors, they just get skipped
1983 -- with a warning and treated as empty ones, since technically they do not
1984 -- contain any package.
1985 getInstalledPackages
1986 :: Verbosity
1987 -> Compiler
1988 -> Maybe (SymbolicPath CWD (Dir Pkg))
1989 -> PackageDBStack
1990 -- ^ The stack of package databases.
1991 -> ProgramDb
1992 -> IO InstalledPackageIndex
1993 getInstalledPackages verbosity comp mbWorkDir packageDBs progdb = do
1994 when (null packageDBs) $
1995 dieWithException verbosity NoPackageDatabaseSpecified
1997 info verbosity "Reading installed packages..."
1998 -- do not check empty packagedbs (ghc-pkg would error out)
1999 packageDBs' <- filterM packageDBExists packageDBs
2000 case compilerFlavor comp of
2001 GHC -> GHC.getInstalledPackages verbosity comp mbWorkDir packageDBs' progdb
2002 GHCJS -> GHCJS.getInstalledPackages verbosity mbWorkDir packageDBs' progdb
2003 UHC -> UHC.getInstalledPackages verbosity comp packageDBs' progdb
2004 HaskellSuite{} ->
2005 HaskellSuite.getInstalledPackages verbosity packageDBs' progdb
2006 flv ->
2007 dieWithException verbosity $ HowToFindInstalledPackages flv
2008 where
2009 packageDBExists (SpecificPackageDB path0) = do
2010 let path = interpretSymbolicPath mbWorkDir $ makeSymbolicPath path0
2011 exists <- doesPathExist path
2012 unless exists $
2013 warn verbosity $
2014 "Package db " <> path <> " does not exist yet"
2015 return exists
2016 -- Checking the user and global package dbs is more complicated and needs
2017 -- way more data. Also ghc-pkg won't error out unless the user/global
2018 -- pkgdb is overridden with an empty one, so we just don't check for them.
2019 packageDBExists UserPackageDB = pure True
2020 packageDBExists GlobalPackageDB = pure True
2022 -- | Like 'getInstalledPackages', but for a single package DB.
2024 -- NB: Why isn't this always a fall through to 'getInstalledPackages'?
2025 -- That is because 'getInstalledPackages' performs some sanity checks
2026 -- on the package database stack in question. However, when sandboxes
2027 -- are involved these sanity checks are not desirable.
2028 getPackageDBContents
2029 :: Verbosity
2030 -> Compiler
2031 -> Maybe (SymbolicPath CWD (Dir Pkg))
2032 -> PackageDB
2033 -> ProgramDb
2034 -> IO InstalledPackageIndex
2035 getPackageDBContents verbosity comp mbWorkDir packageDB progdb = do
2036 info verbosity "Reading installed packages..."
2037 case compilerFlavor comp of
2038 GHC -> GHC.getPackageDBContents verbosity mbWorkDir packageDB progdb
2039 GHCJS -> GHCJS.getPackageDBContents verbosity mbWorkDir packageDB progdb
2040 -- For other compilers, try to fall back on 'getInstalledPackages'.
2041 _ -> getInstalledPackages verbosity comp mbWorkDir [packageDB] progdb
2043 -- | A set of files (or directories) that can be monitored to detect when
2044 -- there might have been a change in the installed packages.
2045 getInstalledPackagesMonitorFiles
2046 :: Verbosity
2047 -> Compiler
2048 -> Maybe (SymbolicPath CWD ('Dir Pkg))
2049 -> PackageDBStack
2050 -> ProgramDb
2051 -> Platform
2052 -> IO [FilePath]
2053 getInstalledPackagesMonitorFiles verbosity comp mbWorkDir packageDBs progdb platform =
2054 case compilerFlavor comp of
2055 GHC ->
2056 GHC.getInstalledPackagesMonitorFiles
2057 verbosity
2058 mbWorkDir
2059 platform
2060 progdb
2061 packageDBs
2062 other -> do
2063 warn verbosity $
2064 "don't know how to find change monitoring files for "
2065 ++ "the installed package databases for "
2066 ++ prettyShow other
2067 return []
2069 -- | Looks up the 'InstalledPackageInfo' of the given 'UnitId's from the
2070 -- 'PackageDBStack' in the 'LocalBuildInfo'.
2071 getInstalledPackagesById
2072 :: (Exception (VerboseException exception), Show exception, Typeable exception)
2073 => Verbosity
2074 -> LocalBuildInfo
2075 -> (UnitId -> exception)
2076 -- ^ Construct an exception that is thrown if a
2077 -- unit-id is not found in the installed packages,
2078 -- from the unit-id that is missing.
2079 -> [UnitId]
2080 -- ^ The unit ids to lookup in the installed packages
2081 -> IO [InstalledPackageInfo]
2082 getInstalledPackagesById verbosity lbi@LocalBuildInfo{compiler = comp, withPackageDB = pkgDb, withPrograms = progDb} mkException unitids = do
2083 let mbWorkDir = mbWorkDirLBI lbi
2084 ipindex <- getInstalledPackages verbosity comp mbWorkDir pkgDb progDb
2085 mapM
2086 ( \uid -> case lookupUnitId ipindex uid of
2087 Nothing -> dieWithException verbosity (mkException uid)
2088 Just ipkg -> return ipkg
2090 unitids
2092 -- | The user interface specifies the package dbs to use with a combination of
2093 -- @--global@, @--user@ and @--package-db=global|user|clear|$file@.
2094 -- This function combines the global/user flag and interprets the package-db
2095 -- flag into a single package db stack.
2096 interpretPackageDbFlags :: Bool -> [Maybe PackageDB] -> PackageDBStack
2097 interpretPackageDbFlags userInstall specificDBs =
2098 extra initialStack specificDBs
2099 where
2100 initialStack
2101 | userInstall = [GlobalPackageDB, UserPackageDB]
2102 | otherwise = [GlobalPackageDB]
2104 extra dbs' [] = dbs'
2105 extra _ (Nothing : dbs) = extra [] dbs
2106 extra dbs' (Just db : dbs) = extra (dbs' ++ [db]) dbs
2108 -- We are given both --constraint="foo < 2.0" style constraints and also
2109 -- specific packages to pick via --dependency="foo=foo-2.0-177d5cdf20962d0581".
2111 -- When finalising the package we have to take into account the specific
2112 -- installed deps we've been given, and the finalise function expects
2113 -- constraints, so we have to translate these deps into version constraints.
2115 -- But after finalising we then have to make sure we pick the right specific
2116 -- deps in the end. So we still need to remember which installed packages to
2117 -- pick.
2118 combinedConstraints
2119 :: [PackageVersionConstraint]
2120 -> [GivenComponent]
2121 -- ^ installed dependencies
2122 -> InstalledPackageIndex
2123 -> Either
2124 CabalException
2125 ( [PackageVersionConstraint]
2126 , Map (PackageName, ComponentName) InstalledPackageInfo
2128 combinedConstraints constraints dependencies installedPackages = do
2129 when (not (null badComponentIds)) $
2130 Left $
2131 CombinedConstraints (dispDependencies badComponentIds)
2133 -- TODO: we don't check that all dependencies are used!
2135 return (allConstraints, idConstraintMap)
2136 where
2137 allConstraints :: [PackageVersionConstraint]
2138 allConstraints =
2139 constraints
2140 ++ [ thisPackageVersionConstraint (packageId pkg)
2141 | (_, _, _, Just pkg) <- dependenciesPkgInfo
2144 idConstraintMap :: Map (PackageName, ComponentName) InstalledPackageInfo
2145 idConstraintMap =
2146 Map.fromList
2147 -- NB: do NOT use the packageName from
2148 -- dependenciesPkgInfo!
2149 [ ((pn, cname), pkg)
2150 | (pn, cname, _, Just pkg) <- dependenciesPkgInfo
2153 -- The dependencies along with the installed package info, if it exists
2154 dependenciesPkgInfo :: [(PackageName, ComponentName, ComponentId, Maybe InstalledPackageInfo)]
2155 dependenciesPkgInfo =
2156 [ (pkgname, CLibName lname, cid, mpkg)
2157 | GivenComponent pkgname lname cid <- dependencies
2158 , let mpkg =
2159 PackageIndex.lookupComponentId
2160 installedPackages
2164 -- If we looked up a package specified by an installed package id
2165 -- (i.e. someone has written a hash) and didn't find it then it's
2166 -- an error.
2167 badComponentIds =
2168 [ (pkgname, cname, cid)
2169 | (pkgname, cname, cid, Nothing) <- dependenciesPkgInfo
2172 dispDependencies deps =
2173 hsep
2174 [ text "--dependency="
2175 <<>> quotes
2176 ( pretty pkgname
2177 <<>> case cname of
2178 CLibName LMainLibName -> ""
2179 CLibName (LSubLibName n) -> ":" <<>> pretty n
2180 _ -> ":" <<>> pretty cname
2181 <<>> char '='
2182 <<>> pretty cid
2184 | (pkgname, cname, cid) <- deps
2187 -- -----------------------------------------------------------------------------
2188 -- Configuring program dependencies
2190 configureRequiredPrograms
2191 :: Verbosity
2192 -> [LegacyExeDependency]
2193 -> ProgramDb
2194 -> IO ProgramDb
2195 configureRequiredPrograms verbosity deps progdb =
2196 foldM (configureRequiredProgram verbosity) progdb deps
2198 -- | Configure a required program, ensuring that it exists in the PATH
2199 -- (or where the user has specified the program must live) and making it
2200 -- available for use via the 'ProgramDb' interface. If the program is
2201 -- known (exists in the input 'ProgramDb'), we will make sure that the
2202 -- program matches the required version; otherwise we will accept
2203 -- any version of the program and assume that it is a simpleProgram.
2204 configureRequiredProgram
2205 :: Verbosity
2206 -> ProgramDb
2207 -> LegacyExeDependency
2208 -> IO ProgramDb
2209 configureRequiredProgram
2210 verbosity
2211 progdb
2212 (LegacyExeDependency progName verRange) =
2213 case lookupKnownProgram progName progdb of
2214 Nothing ->
2215 -- Try to configure it as a 'simpleProgram' automatically
2217 -- There's a bit of a story behind this line. In old versions
2218 -- of Cabal, there were only internal build-tools dependencies. So the
2219 -- behavior in this case was:
2221 -- - If a build-tool dependency was internal, don't do
2222 -- any checking.
2224 -- - If it was external, call 'configureRequiredProgram' to
2225 -- "configure" the executable. In particular, if
2226 -- the program was not "known" (present in 'ProgramDb'),
2227 -- then we would just error. This was fine, because
2228 -- the only way a program could be executed from 'ProgramDb'
2229 -- is if some library code from Cabal actually called it,
2230 -- and the pre-existing Cabal code only calls known
2231 -- programs from 'defaultProgramDb', and so if it
2232 -- is calling something else, you have a Custom setup
2233 -- script, and in that case you are expected to register
2234 -- the program you want to call in the ProgramDb.
2236 -- OK, so that was fine, until I (ezyang, in 2016) refactored
2237 -- Cabal to support per-component builds. In this case, what
2238 -- was previously an internal build-tool dependency now became
2239 -- an external one, and now previously "internal" dependencies
2240 -- are now external. But these are permitted to exist even
2241 -- when they are not previously configured (something that
2242 -- can only occur by a Custom script.)
2244 -- So, I decided, "Fine, let's just accept these in any
2245 -- case." Thus this line. The alternative would have been to
2246 -- somehow detect when a build-tools dependency was "internal" (by
2247 -- looking at the unflattened package description) but this
2248 -- would also be incompatible with future work to support
2249 -- external executable dependencies: we definitely cannot
2250 -- assume they will be preinitialized in the 'ProgramDb'.
2251 configureProgram verbosity (simpleProgram progName) progdb
2252 Just prog
2253 -- requireProgramVersion always requires the program have a version
2254 -- but if the user says "build-depends: foo" ie no version constraint
2255 -- then we should not fail if we cannot discover the program version.
2256 | verRange == anyVersion -> do
2257 (_, progdb') <- requireProgram verbosity prog progdb
2258 return progdb'
2259 | otherwise -> do
2260 (_, _, progdb') <- requireProgramVersion verbosity prog verRange progdb
2261 return progdb'
2263 -- -----------------------------------------------------------------------------
2264 -- Configuring pkg-config package dependencies
2266 configurePkgconfigPackages
2267 :: Verbosity
2268 -> PackageDescription
2269 -> ProgramDb
2270 -> ComponentRequestedSpec
2271 -> IO (PackageDescription, ProgramDb)
2272 configurePkgconfigPackages verbosity pkg_descr progdb enabled
2273 | null allpkgs = return (pkg_descr, progdb)
2274 | otherwise = do
2275 (_, _, progdb') <-
2276 requireProgramVersion
2277 (lessVerbose verbosity)
2278 pkgConfigProgram
2279 (orLaterVersion $ mkVersion [0, 9, 0])
2280 progdb
2281 traverse_ requirePkg allpkgs
2282 mlib' <- traverse addPkgConfigBILib (library pkg_descr)
2283 libs' <- traverse addPkgConfigBILib (subLibraries pkg_descr)
2284 exes' <- traverse addPkgConfigBIExe (executables pkg_descr)
2285 tests' <- traverse addPkgConfigBITest (testSuites pkg_descr)
2286 benches' <- traverse addPkgConfigBIBench (benchmarks pkg_descr)
2287 let pkg_descr' =
2288 pkg_descr
2289 { library = mlib'
2290 , subLibraries = libs'
2291 , executables = exes'
2292 , testSuites = tests'
2293 , benchmarks = benches'
2295 return (pkg_descr', progdb')
2296 where
2297 allpkgs = concatMap pkgconfigDepends (enabledBuildInfos pkg_descr enabled)
2298 pkgconfig =
2299 getDbProgramOutput
2300 (lessVerbose verbosity)
2301 pkgConfigProgram
2302 progdb
2304 requirePkg dep@(PkgconfigDependency pkgn range) = do
2305 version <-
2306 pkgconfig ["--modversion", pkg]
2307 `catchIO` (\_ -> dieWithException verbosity $ PkgConfigNotFound pkg versionRequirement)
2308 `catchExit` (\_ -> dieWithException verbosity $ PkgConfigNotFound pkg versionRequirement)
2309 let trim = dropWhile isSpace . dropWhileEnd isSpace
2310 let v = PkgconfigVersion (toUTF8BS $ trim version)
2311 if not (withinPkgconfigVersionRange v range)
2312 then dieWithException verbosity $ BadVersion pkg versionRequirement v
2313 else info verbosity (depSatisfied v)
2314 where
2315 depSatisfied v =
2316 "Dependency "
2317 ++ prettyShow dep
2318 ++ ": using version "
2319 ++ prettyShow v
2321 versionRequirement
2322 | isAnyPkgconfigVersion range = ""
2323 | otherwise = " version " ++ prettyShow range
2325 pkg = unPkgconfigName pkgn
2327 -- Adds pkgconfig dependencies to the build info for a component
2328 addPkgConfigBI compBI setCompBI comp = do
2329 bi <- pkgconfigBuildInfo (pkgconfigDepends (compBI comp))
2330 return $ setCompBI comp (compBI comp `mappend` bi)
2332 -- Adds pkgconfig dependencies to the build info for a library
2333 addPkgConfigBILib = addPkgConfigBI libBuildInfo $
2334 \lib bi -> lib{libBuildInfo = bi}
2336 -- Adds pkgconfig dependencies to the build info for an executable
2337 addPkgConfigBIExe = addPkgConfigBI buildInfo $
2338 \exe bi -> exe{buildInfo = bi}
2340 -- Adds pkgconfig dependencies to the build info for a test suite
2341 addPkgConfigBITest = addPkgConfigBI testBuildInfo $
2342 \test bi -> test{testBuildInfo = bi}
2344 -- Adds pkgconfig dependencies to the build info for a benchmark
2345 addPkgConfigBIBench = addPkgConfigBI benchmarkBuildInfo $
2346 \bench bi -> bench{benchmarkBuildInfo = bi}
2348 pkgconfigBuildInfo :: [PkgconfigDependency] -> IO BuildInfo
2349 pkgconfigBuildInfo [] = return mempty
2350 pkgconfigBuildInfo pkgdeps = do
2351 let pkgs = nub [prettyShow pkg | PkgconfigDependency pkg _ <- pkgdeps]
2352 ccflags <- pkgconfig ("--cflags" : pkgs)
2353 ldflags <- pkgconfig ("--libs" : pkgs)
2354 ldflags_static <- pkgconfig ("--libs" : "--static" : pkgs)
2355 return (ccLdOptionsBuildInfo (words ccflags) (words ldflags) (words ldflags_static))
2357 -- | Makes a 'BuildInfo' from C compiler and linker flags.
2359 -- This can be used with the output from configuration programs like pkg-config
2360 -- and similar package-specific programs like mysql-config, freealut-config etc.
2361 -- For example:
2363 -- > ccflags <- getDbProgramOutput verbosity prog progdb ["--cflags"]
2364 -- > ldflags <- getDbProgramOutput verbosity prog progdb ["--libs"]
2365 -- > ldflags_static <- getDbProgramOutput verbosity prog progdb ["--libs", "--static"]
2366 -- > return (ccldOptionsBuildInfo (words ccflags) (words ldflags) (words ldflags_static))
2367 ccLdOptionsBuildInfo :: [String] -> [String] -> [String] -> BuildInfo
2368 ccLdOptionsBuildInfo cflags ldflags ldflags_static =
2369 let (includeDirs', cflags') = partition ("-I" `isPrefixOf`) cflags
2370 (extraLibs', ldflags') = partition ("-l" `isPrefixOf`) ldflags
2371 (extraLibDirs', ldflags'') = partition ("-L" `isPrefixOf`) ldflags'
2372 (extraLibsStatic') = filter ("-l" `isPrefixOf`) ldflags_static
2373 (extraLibDirsStatic') = filter ("-L" `isPrefixOf`) ldflags_static
2374 in mempty
2375 { includeDirs = map (makeSymbolicPath . drop 2) includeDirs'
2376 , extraLibs = map (drop 2) extraLibs'
2377 , extraLibDirs = map (makeSymbolicPath . drop 2) extraLibDirs'
2378 , extraLibsStatic = map (drop 2) extraLibsStatic'
2379 , extraLibDirsStatic = map (makeSymbolicPath . drop 2) extraLibDirsStatic'
2380 , ccOptions = cflags'
2381 , ldOptions = ldflags''
2384 -- -----------------------------------------------------------------------------
2385 -- Determining the compiler details
2387 configCompilerAuxEx
2388 :: ConfigFlags
2389 -> IO (Compiler, Platform, ProgramDb)
2390 configCompilerAuxEx cfg = do
2391 programDb <- mkProgramDb cfg defaultProgramDb
2392 let common = configCommonFlags cfg
2393 verbosity = fromFlag $ setupVerbosity common
2394 configCompilerEx
2395 (flagToMaybe $ configHcFlavor cfg)
2396 (flagToMaybe $ configHcPath cfg)
2397 (flagToMaybe $ configHcPkg cfg)
2398 programDb
2399 verbosity
2401 configCompilerEx
2402 :: Maybe CompilerFlavor
2403 -> Maybe FilePath
2404 -> Maybe FilePath
2405 -> ProgramDb
2406 -> Verbosity
2407 -> IO (Compiler, Platform, ProgramDb)
2408 configCompilerEx Nothing _ _ _ verbosity = dieWithException verbosity UnknownCompilerException
2409 configCompilerEx (Just hcFlavor) hcPath hcPkg progdb verbosity = do
2410 (comp, maybePlatform, programDb) <- case hcFlavor of
2411 GHC -> GHC.configure verbosity hcPath hcPkg progdb
2412 GHCJS -> GHCJS.configure verbosity hcPath hcPkg progdb
2413 UHC -> UHC.configure verbosity hcPath hcPkg progdb
2414 HaskellSuite{} -> HaskellSuite.configure verbosity hcPath hcPkg progdb
2415 _ -> dieWithException verbosity UnknownCompilerException
2416 return (comp, fromMaybe buildPlatform maybePlatform, programDb)
2418 -- -----------------------------------------------------------------------------
2419 -- Testing C lib and header dependencies
2421 -- Try to build a test C program which includes every header and links every
2422 -- lib. If that fails, try to narrow it down by preprocessing (only) and linking
2423 -- with individual headers and libs. If none is the obvious culprit then give a
2424 -- generic error message.
2425 -- TODO: produce a log file from the compiler errors, if any.
2426 checkForeignDeps :: PackageDescription -> LocalBuildInfo -> Verbosity -> IO ()
2427 checkForeignDeps pkg lbi verbosity =
2428 ifBuildsWith
2429 allHeaders
2430 (commonCcArgs ++ makeLdArgs allLibs) -- I'm feeling lucky
2431 (return ())
2432 ( do
2433 missingLibs <- findMissingLibs
2434 missingHdr <- findOffendingHdr
2435 explainErrors missingHdr missingLibs
2437 where
2438 allHeaders = collectField (fmap getSymbolicPath . includes)
2439 allLibs =
2440 collectField $
2441 if withFullyStaticExe lbi
2442 then extraLibsStatic
2443 else extraLibs
2445 ifBuildsWith headers args success failure = do
2446 checkDuplicateHeaders
2447 ok <- builds (makeProgram headers) args
2448 if ok then success else failure
2450 -- Ensure that there is only one header with a given name
2451 -- in either the generated (most likely by `configure`)
2452 -- build directory (e.g. `dist/build`) or in the source directory.
2454 -- If it exists in both, we'll remove the one in the source
2455 -- directory, as the generated should take precedence.
2457 -- C compilers like to prefer source local relative includes,
2458 -- so the search paths provided to the compiler via -I are
2459 -- ignored if the included file can be found relative to the
2460 -- including file. As such we need to take drastic measures
2461 -- and delete the offending file in the source directory.
2462 checkDuplicateHeaders = do
2463 let relIncDirs = filter (not . isAbsolute) (collectField (fmap getSymbolicPath . includeDirs))
2464 isHeader = isSuffixOf ".h"
2465 genHeaders <- for relIncDirs $ \dir ->
2466 fmap (dir </>) . filter isHeader
2467 <$> listDirectory (i (buildDir lbi) </> dir) `catchIO` (\_ -> return [])
2468 srcHeaders <- for relIncDirs $ \dir ->
2469 fmap (dir </>) . filter isHeader
2470 <$> listDirectory (baseDir </> dir) `catchIO` (\_ -> return [])
2471 let commonHeaders = concat genHeaders `intersect` concat srcHeaders
2472 for_ commonHeaders $ \hdr -> do
2473 warn verbosity $
2474 "Duplicate header found in "
2475 ++ (getSymbolicPath (buildDir lbi) </> hdr)
2476 ++ " and "
2477 ++ (baseDir </> hdr)
2478 ++ "; removing "
2479 ++ (baseDir </> hdr)
2480 removeFile (baseDir </> hdr)
2482 findOffendingHdr =
2483 ifBuildsWith
2484 allHeaders
2485 ccArgs
2486 (return Nothing)
2487 (go . tail . NEL.inits $ allHeaders)
2488 where
2489 go [] = return Nothing -- cannot happen
2490 go (hdrs : hdrsInits) =
2491 -- Try just preprocessing first
2492 ifBuildsWith
2493 hdrs
2494 cppArgs
2495 -- If that works, try compiling too
2496 ( ifBuildsWith
2497 hdrs
2498 ccArgs
2499 (go hdrsInits)
2500 (return . fmap Right . safeLast $ hdrs)
2502 (return . fmap Left . safeLast $ hdrs)
2504 cppArgs = "-E" : commonCppArgs -- preprocess only
2505 ccArgs = "-c" : commonCcArgs -- don't try to link
2506 findMissingLibs =
2507 ifBuildsWith
2509 (makeLdArgs allLibs)
2510 (return [])
2511 (filterM (fmap not . libExists) allLibs)
2513 libExists lib = builds (makeProgram []) (makeLdArgs [lib])
2515 common = configCommonFlags $ configFlags lbi
2516 baseDir = packageRoot common
2518 -- See Note [Symbolic paths] in Distribution.Utils.Path
2519 i = interpretSymbolicPathLBI lbi
2520 mbWorkDir = mbWorkDirLBI lbi
2522 commonCppArgs =
2523 platformDefines lbi
2524 -- TODO: This is a massive hack, to work around the
2525 -- fact that the test performed here should be
2526 -- PER-component (c.f. the "I'm Feeling Lucky"; we
2527 -- should NOT be glomming everything together.)
2528 ++ ["-I" ++ i (buildDir lbi </> makeRelativePathEx "autogen")]
2529 -- `configure' may generate headers in the build directory
2530 ++ [ "-I" ++ i (buildDir lbi </> unsafeCoerceSymbolicPath dir)
2531 | dir <- mapMaybe symbolicPathRelative_maybe $ ordNub (collectField includeDirs)
2533 -- we might also reference headers from the
2534 -- packages directory.
2535 ++ [ "-I" ++ baseDir </> getSymbolicPath dir
2536 | dir <- mapMaybe symbolicPathRelative_maybe $ ordNub (collectField includeDirs)
2538 ++ [ "-I" ++ dir
2539 | dir <- ordNub (collectField (fmap getSymbolicPath . includeDirs))
2540 , isAbsolute dir
2542 ++ ["-I" ++ baseDir]
2543 ++ collectField cppOptions
2544 ++ collectField ccOptions
2545 ++ [ "-I" ++ dir
2546 | dir <-
2547 ordNub
2548 [ dir
2549 | dep <- deps
2550 , dir <- IPI.includeDirs dep
2552 -- dedupe include dirs of dependencies
2553 -- to prevent quadratic blow-up
2555 ++ [ opt
2556 | dep <- deps
2557 , opt <- IPI.ccOptions dep
2560 commonCcArgs =
2561 commonCppArgs
2562 ++ collectField ccOptions
2563 ++ [ opt
2564 | dep <- deps
2565 , opt <- IPI.ccOptions dep
2568 commonLdArgs =
2569 [ "-L" ++ getSymbolicPath dir
2570 | dir <-
2571 ordNub $
2572 collectField
2573 ( if withFullyStaticExe lbi
2574 then extraLibDirsStatic
2575 else extraLibDirs
2578 ++ collectField ldOptions
2579 ++ [ "-L" ++ dir
2580 | dir <-
2581 ordNub
2582 [ dir
2583 | dep <- deps
2584 , dir <-
2585 if withFullyStaticExe lbi
2586 then IPI.libraryDirsStatic dep
2587 else IPI.libraryDirs dep
2590 -- TODO: do we also need dependent packages' ld options?
2591 makeLdArgs libs = ["-l" ++ lib | lib <- libs] ++ commonLdArgs
2593 makeProgram hdrs =
2594 unlines $
2595 ["#include \"" ++ hdr ++ "\"" | hdr <- hdrs]
2596 ++ ["int main(int argc, char** argv) { return 0; }"]
2598 collectField f = concatMap f allBi
2599 allBi = enabledBuildInfos pkg (componentEnabledSpec lbi)
2600 deps = PackageIndex.topologicalOrder (installedPkgs lbi)
2602 builds :: String -> [ProgArg] -> IO Bool
2603 builds program args =
2605 tempDir <- makeSymbolicPath <$> getTemporaryDirectory
2606 withTempFileCwd mbWorkDir tempDir ".c" $ \cName cHnd ->
2607 withTempFileCwd mbWorkDir tempDir "" $ \oNname oHnd -> do
2608 hPutStrLn cHnd program
2609 hClose cHnd
2610 hClose oHnd
2611 _ <-
2612 getDbProgramOutputCwd
2613 verbosity
2614 mbWorkDir
2615 gccProgram
2616 (withPrograms lbi)
2617 (getSymbolicPath cName : "-o" : getSymbolicPath oNname : args)
2618 return True
2619 `catchIO` (\_ -> return False)
2620 `catchExit` (\_ -> return False)
2622 explainErrors Nothing [] = return () -- should be impossible!
2623 explainErrors _ _
2624 | isNothing . lookupProgram gccProgram . withPrograms $ lbi =
2625 dieWithException verbosity NoWorkingGcc
2626 explainErrors hdr libs =
2627 dieWithException verbosity $ ExplainErrors hdr libs
2629 -- | Output package check warnings and errors. Exit if any errors.
2630 checkPackageProblems
2631 :: Verbosity
2632 -> FilePath
2633 -- ^ Path to the @.cabal@ file's directory
2634 -> GenericPackageDescription
2635 -> PackageDescription
2636 -> IO ()
2637 checkPackageProblems verbosity dir gpkg pkg = do
2638 ioChecks <- checkPackageFiles verbosity pkg dir
2639 let pureChecks = checkPackage gpkg
2640 (errors, warnings) =
2641 partitionEithers (M.mapMaybe classEW $ pureChecks ++ ioChecks)
2642 if null errors
2643 then traverse_ (warn verbosity) (map ppPackageCheck warnings)
2644 else dieWithException verbosity $ CheckPackageProblems (map ppPackageCheck errors)
2645 where
2646 -- Classify error/warnings. Left: error, Right: warning.
2647 classEW :: PackageCheck -> Maybe (Either PackageCheck PackageCheck)
2648 classEW e@(PackageBuildImpossible _) = Just (Left e)
2649 classEW w@(PackageBuildWarning _) = Just (Right w)
2650 classEW (PackageDistSuspicious _) = Nothing
2651 classEW (PackageDistSuspiciousWarn _) = Nothing
2652 classEW (PackageDistInexcusable _) = Nothing
2654 -- | Preform checks if a relocatable build is allowed
2655 checkRelocatable
2656 :: Verbosity
2657 -> PackageDescription
2658 -> LocalBuildInfo
2659 -> IO ()
2660 checkRelocatable verbosity pkg lbi =
2661 sequence_
2662 [ checkOS
2663 , checkCompiler
2664 , packagePrefixRelative
2665 , depsPrefixRelative
2667 where
2668 -- Check if the OS support relocatable builds.
2670 -- If you add new OS' to this list, and your OS supports dynamic libraries
2671 -- and RPATH, make sure you add your OS to RPATH-support list of:
2672 -- Distribution.Simple.GHC.getRPaths
2673 checkOS =
2674 unless (os `elem` [OSX, Linux]) $
2675 dieWithException verbosity $
2676 NoOSSupport os
2677 where
2678 (Platform _ os) = hostPlatform lbi
2680 -- Check if the Compiler support relocatable builds
2681 checkCompiler =
2682 unless (compilerFlavor comp `elem` [GHC]) $
2683 dieWithException verbosity $
2684 NoCompilerSupport (show comp)
2685 where
2686 comp = compiler lbi
2688 -- Check if all the install dirs are relative to same prefix
2689 packagePrefixRelative =
2690 unless (relativeInstallDirs installDirs) $
2691 dieWithException verbosity $
2692 InstallDirsNotPrefixRelative (installDirs)
2693 where
2694 -- NB: should be good enough to check this against the default
2695 -- component ID, but if we wanted to be strictly correct we'd
2696 -- check for each ComponentId.
2697 installDirs = absoluteInstallDirs pkg lbi NoCopyDest
2698 p = prefix installDirs
2699 relativeInstallDirs (InstallDirs{..}) =
2701 isJust
2702 ( fmap
2703 (stripPrefix p)
2704 [ bindir
2705 , libdir
2706 , dynlibdir
2707 , libexecdir
2708 , includedir
2709 , datadir
2710 , docdir
2711 , mandir
2712 , htmldir
2713 , haddockdir
2714 , sysconfdir
2718 -- Check if the library dirs of the dependencies that are in the package
2719 -- database to which the package is installed are relative to the
2720 -- prefix of the package
2721 depsPrefixRelative = do
2722 pkgr <- GHC.pkgRoot verbosity lbi (registrationPackageDB (withPackageDB lbi))
2723 traverse_ (doCheck $ getSymbolicPath pkgr) ipkgs
2724 where
2725 doCheck pkgr ipkg
2726 | maybe False (== pkgr) (IPI.pkgRoot ipkg) =
2727 for_ (IPI.libraryDirs ipkg) $ \libdir -> do
2728 -- When @prefix@ is not under @pkgroot@,
2729 -- @shortRelativePath prefix pkgroot@ will return a path with
2730 -- @..@s and following check will fail without @canonicalizePath@.
2731 canonicalized <- canonicalizePath libdir
2732 -- The @prefix@ itself must also be canonicalized because
2733 -- canonicalizing @libdir@ may expand symlinks which would make
2734 -- @prefix@ no longer being a prefix of @canonical libdir@,
2735 -- while @canonical p@ could be a prefix of @canonical libdir@
2736 p' <- canonicalizePath p
2737 unless (p' `isPrefixOf` canonicalized) $
2738 dieWithException verbosity $
2739 LibDirDepsPrefixNotRelative libdir p
2740 | otherwise =
2741 return ()
2742 -- NB: should be good enough to check this against the default
2743 -- component ID, but if we wanted to be strictly correct we'd
2744 -- check for each ComponentId.
2745 installDirs = absoluteInstallDirs pkg lbi NoCopyDest
2746 p = prefix installDirs
2747 ipkgs = PackageIndex.allPackages (installedPkgs lbi)
2749 -- -----------------------------------------------------------------------------
2750 -- Testing foreign library requirements
2752 unsupportedForeignLibs :: Compiler -> Platform -> [ForeignLib] -> [String]
2753 unsupportedForeignLibs comp platform =
2754 mapMaybe (checkForeignLibSupported comp platform)
2756 checkForeignLibSupported :: Compiler -> Platform -> ForeignLib -> Maybe String
2757 checkForeignLibSupported comp platform flib = go (compilerFlavor comp)
2758 where
2759 go :: CompilerFlavor -> Maybe String
2760 go GHC
2761 | compilerVersion comp < mkVersion [7, 8] =
2762 unsupported
2763 [ "Building foreign libraries is only supported with GHC >= 7.8"
2765 | otherwise = goGhcPlatform platform
2766 go _ =
2767 unsupported
2768 [ "Building foreign libraries is currently only supported with ghc"
2771 goGhcPlatform :: Platform -> Maybe String
2772 goGhcPlatform (Platform _ OSX) = goGhcOsx (foreignLibType flib)
2773 goGhcPlatform (Platform _ Linux) = goGhcLinux (foreignLibType flib)
2774 goGhcPlatform (Platform I386 Windows) = goGhcWindows (foreignLibType flib)
2775 goGhcPlatform (Platform X86_64 Windows) = goGhcWindows (foreignLibType flib)
2776 goGhcPlatform _ =
2777 unsupported
2778 [ "Building foreign libraries is currently only supported on Mac OS, "
2779 , "Linux and Windows"
2782 goGhcOsx :: ForeignLibType -> Maybe String
2783 goGhcOsx ForeignLibNativeShared
2784 | not (null (foreignLibModDefFile flib)) =
2785 unsupported
2786 [ "Module definition file not supported on OSX"
2788 | not (null (foreignLibVersionInfo flib)) =
2789 unsupported
2790 [ "Foreign library versioning not currently supported on OSX"
2792 | otherwise =
2793 Nothing
2794 goGhcOsx _ =
2795 unsupported
2796 [ "We can currently only build shared foreign libraries on OSX"
2799 goGhcLinux :: ForeignLibType -> Maybe String
2800 goGhcLinux ForeignLibNativeShared
2801 | not (null (foreignLibModDefFile flib)) =
2802 unsupported
2803 [ "Module definition file not supported on Linux"
2805 | not (null (foreignLibVersionInfo flib))
2806 && not (null (foreignLibVersionLinux flib)) =
2807 unsupported
2808 [ "You must not specify both lib-version-info and lib-version-linux"
2810 | otherwise =
2811 Nothing
2812 goGhcLinux _ =
2813 unsupported
2814 [ "We can currently only build shared foreign libraries on Linux"
2817 goGhcWindows :: ForeignLibType -> Maybe String
2818 goGhcWindows ForeignLibNativeShared
2819 | not standalone =
2820 unsupported
2821 [ "We can currently only build standalone libraries on Windows. Use\n"
2822 , " if os(Windows)\n"
2823 , " options: standalone\n"
2824 , "in your foreign-library stanza."
2826 | not (null (foreignLibVersionInfo flib)) =
2827 unsupported
2828 [ "Foreign library versioning not currently supported on Windows.\n"
2829 , "You can specify module definition files in the mod-def-file field."
2831 | otherwise =
2832 Nothing
2833 goGhcWindows _ =
2834 unsupported
2835 [ "We can currently only build shared foreign libraries on Windows"
2838 standalone :: Bool
2839 standalone = ForeignLibStandalone `elem` foreignLibOptions flib
2841 unsupported :: [String] -> Maybe String
2842 unsupported = Just . concat