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