1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE OverloadedStrings #-}
4 {-# LANGUAGE RankNTypes #-}
5 {-# LANGUAGE RecordWildCards #-}
6 {-# LANGUAGE ScopedTypeVariables #-}
8 -----------------------------------------------------------------------------
11 -- Module : Distribution.Simple.Configure
12 -- Copyright : Isaac Jones 2003-2005
15 -- Maintainer : cabal-devel@haskell.org
16 -- Portability : portable
18 -- This deals with the /configure/ phase. It provides the 'configure' action
19 -- which is given the package description and configure flags. It then tries
20 -- to: configure the compiler; resolves any conditionals in the package
21 -- description; resolve the package dependencies; check if all the extensions
22 -- used by this package are supported by the compiler; check that all the build
23 -- tools are available (including version checks if appropriate); checks for
24 -- any required @pkg-config@ packages (updating the 'BuildInfo' with the
27 -- Then based on all this it saves the info in the 'LocalBuildInfo' and writes
28 -- it out to the @dist\/setup-config@ file. It also displays various details to
29 -- the user, the amount of information displayed depending on the verbosity
31 module Distribution
.Simple
.Configure
33 , writePersistBuildConfig
35 , getPersistBuildConfig
36 , checkPersistBuildConfigOutdated
37 , tryGetPersistBuildConfig
38 , maybeGetPersistBuildConfig
40 , findDistPrefOrDefault
41 , getInternalLibraries
43 , computeCompatPackageKey
45 , getInstalledPackages
46 , getInstalledPackagesMonitorFiles
47 , getPackageDBContents
50 , computeEffectiveProfiling
51 , ccLdOptionsBuildInfo
53 , interpretPackageDbFlags
54 , ConfigStateFileError
(..)
55 , tryGetConfigStateFile
59 import Distribution
.Compat
.Prelude
62 import Distribution
.Backpack
.Configure
63 import Distribution
.Backpack
.ConfiguredComponent
(newPackageDepsBehaviour
)
64 import Distribution
.Backpack
.DescribeUnitId
65 import Distribution
.Backpack
.Id
66 import Distribution
.Backpack
.PreExistingComponent
67 import qualified Distribution
.Compat
.Graph
as Graph
68 import Distribution
.Compat
.Stack
69 import Distribution
.Compiler
70 import Distribution
.InstalledPackageInfo
(InstalledPackageInfo
)
71 import qualified Distribution
.InstalledPackageInfo
as IPI
72 import Distribution
.Package
73 import Distribution
.PackageDescription
74 import Distribution
.PackageDescription
.Check
hiding (doesFileExist)
75 import Distribution
.PackageDescription
.Configuration
76 import Distribution
.PackageDescription
.PrettyPrint
77 import Distribution
.Simple
.BuildTarget
78 import Distribution
.Simple
.BuildToolDepends
79 import Distribution
.Simple
.Compiler
80 import Distribution
.Simple
.LocalBuildInfo
81 import Distribution
.Simple
.PackageIndex
(InstalledPackageIndex
)
82 import qualified Distribution
.Simple
.PackageIndex
as PackageIndex
83 import Distribution
.Simple
.PreProcess
84 import Distribution
.Simple
.Program
85 import Distribution
.Simple
.Setup
.Common
as Setup
86 import Distribution
.Simple
.Setup
.Config
as Setup
87 import Distribution
.Simple
.Utils
88 import Distribution
.System
89 import Distribution
.Types
.ComponentRequestedSpec
90 import Distribution
.Types
.GivenComponent
91 import Distribution
.Types
.LocalBuildInfo
92 import Distribution
.Types
.PackageVersionConstraint
93 import Distribution
.Utils
.LogProgress
94 import Distribution
.Utils
.NubList
95 import Distribution
.Verbosity
96 import Distribution
.Version
98 import qualified Distribution
.Simple
.GHC
as GHC
99 import qualified Distribution
.Simple
.GHCJS
as GHCJS
100 import qualified Distribution
.Simple
.HaskellSuite
as HaskellSuite
101 import qualified Distribution
.Simple
.UHC
as UHC
103 import Control
.Exception
106 import qualified Data
.ByteString
as BS
107 import Data
.ByteString
.Lazy
(ByteString
)
108 import qualified Data
.ByteString
.Lazy
.Char8
as BLC8
114 import qualified Data
.List
.NonEmpty
as NEL
115 import qualified Data
.Map
as Map
116 import Distribution
.Compat
.Directory
120 import Distribution
.Compat
.Environment
(lookupEnv
)
121 import Distribution
.Parsec
124 import Distribution
.Pretty
129 import Distribution
.Utils
.Structured
(structuredDecodeOrFailIO
, structuredEncode
)
130 import System
.Directory
132 , createDirectoryIfMissing
134 , getTemporaryDirectory
137 import System
.FilePath
146 import qualified System
.Info
150 import Text
.PrettyPrint
160 import qualified Data
.Maybe as M
161 import qualified Data
.Set
as Set
162 import qualified Distribution
.Compat
.NonEmptySet
as NES
163 import Distribution
.Simple
.Errors
164 import Distribution
.Types
.AnnotatedId
166 type UseExternalInternalDeps
= Bool
168 -- | The errors that can be thrown when reading the @setup-config@ file.
169 data ConfigStateFileError
170 = -- | No header found.
171 ConfigStateFileNoHeader
172 |
-- | Incorrect header.
173 ConfigStateFileBadHeader
174 |
-- | Cannot parse file contents.
175 ConfigStateFileNoParse
177 ConfigStateFileMissing
178 |
-- | Mismatched version.
179 ConfigStateFileBadVersion
182 (Either ConfigStateFileError LocalBuildInfo
)
185 -- | Format a 'ConfigStateFileError' as a user-facing error message.
186 dispConfigStateFileError
:: ConfigStateFileError
-> Doc
187 dispConfigStateFileError ConfigStateFileNoHeader
=
188 text
"Saved package config file header is missing."
189 <+> text
"Re-run the 'configure' command."
190 dispConfigStateFileError ConfigStateFileBadHeader
=
191 text
"Saved package config file header is corrupt."
192 <+> text
"Re-run the 'configure' command."
193 dispConfigStateFileError ConfigStateFileNoParse
=
194 text
"Saved package config file is corrupt."
195 <+> text
"Re-run the 'configure' command."
196 dispConfigStateFileError ConfigStateFileMissing
=
197 text
"Run the 'configure' command first."
198 dispConfigStateFileError
(ConfigStateFileBadVersion oldCabal oldCompiler _
) =
199 text
"Saved package config file is outdated:"
202 $+$ text
"Re-run the 'configure' command."
205 text
"• the Cabal version changed from"
208 <+> pretty currentCabalId
210 | oldCompiler
== currentCompilerId
= mempty
212 text
"• the compiler changed from"
213 <+> pretty oldCompiler
215 <+> pretty currentCompilerId
217 instance Show ConfigStateFileError
where
218 show = renderStyle defaultStyle
. dispConfigStateFileError
220 instance Exception ConfigStateFileError
222 -- | Read the 'localBuildInfoFile'. Throw an exception if the file is
223 -- missing, if the file cannot be read, or if the file was created by an older
227 -- ^ The file path of the @setup-config@ file.
229 getConfigStateFile filename
= do
230 exists
<- doesFileExist filename
231 unless exists
$ throwIO ConfigStateFileMissing
232 -- Read the config file into a strict ByteString to avoid problems with
233 -- lazy I/O, then convert to lazy because the binary package needs that.
234 contents
<- BS
.readFile filename
235 let (header
, body
) = BLC8
.span
(/= '\n') (BLC8
.fromChunks
[contents
])
237 (cabalId
, compId
) <- parseHeader header
239 let getStoredValue
= do
240 result
<- structuredDecodeOrFailIO
(BLC8
.tail body
)
242 Left _
-> throwIO ConfigStateFileNoParse
244 deferErrorIfBadVersion act
245 | cabalId
/= currentCabalId
= do
247 throwIO
$ ConfigStateFileBadVersion cabalId compId eResult
249 deferErrorIfBadVersion getStoredValue
251 _
= callStack
-- TODO: attach call stack to exception
253 -- | Read the 'localBuildInfoFile', returning either an error or the local build
255 tryGetConfigStateFile
257 -- ^ The file path of the @setup-config@ file.
258 -> IO (Either ConfigStateFileError LocalBuildInfo
)
259 tryGetConfigStateFile
= try . getConfigStateFile
261 -- | Try to read the 'localBuildInfoFile'.
262 tryGetPersistBuildConfig
264 -- ^ The @dist@ directory path.
265 -> IO (Either ConfigStateFileError LocalBuildInfo
)
266 tryGetPersistBuildConfig
= try . getPersistBuildConfig
268 -- | Read the 'localBuildInfoFile'. Throw an exception if the file is
269 -- missing, if the file cannot be read, or if the file was created by an older
271 getPersistBuildConfig
273 -- ^ The @dist@ directory path.
275 getPersistBuildConfig
= getConfigStateFile
. localBuildInfoFile
277 -- | Try to read the 'localBuildInfoFile'.
278 maybeGetPersistBuildConfig
280 -- ^ The @dist@ directory path.
281 -> IO (Maybe LocalBuildInfo
)
282 maybeGetPersistBuildConfig
=
283 liftM (either (const Nothing
) Just
) . tryGetPersistBuildConfig
285 -- | After running configure, output the 'LocalBuildInfo' to the
286 -- 'localBuildInfoFile'.
287 writePersistBuildConfig
289 -- ^ The @dist@ directory path.
291 -- ^ The 'LocalBuildInfo' to write.
293 writePersistBuildConfig distPref lbi
= do
294 createDirectoryIfMissing
False distPref
295 writeFileAtomic
(localBuildInfoFile distPref
) $
296 BLC8
.unlines [showHeader pkgId
, structuredEncode lbi
]
298 pkgId
= localPackage lbi
300 -- | Identifier of the current Cabal package.
301 currentCabalId
:: PackageIdentifier
302 currentCabalId
= PackageIdentifier
(mkPackageName
"Cabal") cabalVersion
304 -- | Identifier of the current compiler package.
305 currentCompilerId
:: PackageIdentifier
308 (mkPackageName System
.Info
.compilerName
)
309 (mkVersion
' System
.Info
.compilerVersion
)
311 -- | Parse the @setup-config@ file header, returning the package identifiers
312 -- for Cabal and the compiler.
315 -- ^ The file contents.
316 -> IO (PackageIdentifier
, PackageIdentifier
)
317 parseHeader header
= case BLC8
.words header
of
329 maybe (throwIO ConfigStateFileBadHeader
) return $ do
330 _
<- simpleParsec
(fromUTF8LBS pkgId
) :: Maybe PackageIdentifier
331 cabalId
' <- simpleParsec
(BLC8
.unpack cabalId
)
332 compId
' <- simpleParsec
(BLC8
.unpack compId
)
333 return (cabalId
', compId
')
334 _
-> throwIO ConfigStateFileNoHeader
336 -- | Generate the @setup-config@ file header.
339 -- ^ The processed package.
347 , toUTF8LBS
$ prettyShow pkgId
350 , BLC8
.pack
$ prettyShow currentCabalId
352 , BLC8
.pack
$ prettyShow currentCompilerId
355 -- | Check that localBuildInfoFile is up-to-date with respect to the
357 checkPersistBuildConfigOutdated
:: FilePath -> FilePath -> IO Bool
358 checkPersistBuildConfigOutdated distPref pkg_descr_file
=
359 pkg_descr_file `moreRecentFile` localBuildInfoFile distPref
361 -- | Get the path of @dist\/setup-config@.
364 -- ^ The @dist@ directory path.
366 localBuildInfoFile distPref
= distPref
</> "setup-config"
368 -- -----------------------------------------------------------------------------
372 -- -----------------------------------------------------------------------------
374 -- | Return the \"dist/\" prefix, or the default prefix. The prefix is taken
375 -- from (in order of highest to lowest preference) the override prefix, the
376 -- \"CABAL_BUILDDIR\" environment variable, or the default prefix.
379 -- ^ default \"dist\" prefix
380 -> Setup
.Flag
FilePath
381 -- ^ override \"dist\" prefix
383 findDistPref defDistPref overrideDistPref
= do
384 envDistPref
<- liftM parseEnvDistPref
(lookupEnv
"CABAL_BUILDDIR")
385 return $ fromFlagOrDefault defDistPref
(mappend envDistPref overrideDistPref
)
387 parseEnvDistPref env
=
389 Just distPref |
not (null distPref
) -> toFlag distPref
392 -- | Return the \"dist/\" prefix, or the default prefix. The prefix is taken
393 -- from (in order of highest to lowest preference) the override prefix, the
394 -- \"CABAL_BUILDDIR\" environment variable, or 'defaultDistPref' is used. Call
395 -- this function to resolve a @*DistPref@ flag whenever it is not known to be
396 -- set. (The @*DistPref@ flags are always set to a definite value before
397 -- invoking 'UserHooks'.)
398 findDistPrefOrDefault
399 :: Setup
.Flag
FilePath
400 -- ^ override \"dist\" prefix
402 findDistPrefOrDefault
= findDistPref defaultDistPref
404 -- | Perform the \"@.\/setup configure@\" action.
405 -- Returns the @.setup-config@ file.
407 :: (GenericPackageDescription
, HookedBuildInfo
)
410 configure
(pkg_descr0
, pbi
) cfg
= do
411 -- Determine the component we are configuring, if a user specified
412 -- one on the command line. We use a fake, flattened version of
413 -- the package since at this point, we're not really sure what
414 -- components we *can* configure. @Nothing@ means that we should
415 -- configure everything (the old behavior).
416 (mb_cname
:: Maybe ComponentName
) <- do
417 let flat_pkg_descr
= flattenPackageDescription pkg_descr0
418 targets
<- readBuildTargets verbosity flat_pkg_descr
(configArgs cfg
)
419 -- TODO: bleat if you use the module/file syntax
420 let targets
' = [cname | BuildTargetComponent cname
<- targets
]
422 _ |
null (configArgs cfg
) -> return Nothing
423 [cname
] -> return (Just cname
)
424 [] -> dieWithException verbosity NoValidComponent
425 _
-> dieWithException verbosity ConfigureEitherSingleOrAll
427 let use_external_internal_deps
= isJust mb_cname
429 Nothing
-> setupMessage verbosity
"Configuring" (packageId pkg_descr0
)
434 (packageId pkg_descr0
)
436 (Just
(configInstantiateWith cfg
))
438 -- configCID is only valid for per-component configure
439 when (isJust (flagToMaybe
(configCID cfg
)) && isNothing mb_cname
) $
440 dieWithException verbosity ConfigCIDValidForPreComponent
442 checkDeprecatedFlags verbosity cfg
443 checkExactConfiguration verbosity pkg_descr0 cfg
445 -- Where to build the package
446 let buildDir
:: FilePath -- e.g. dist/build
447 -- fromFlag OK due to Distribution.Simple calling
448 -- findDistPrefOrDefault to fill it in
449 buildDir
= fromFlag
(configDistPref cfg
) </> "build"
450 createDirectoryIfMissingVerbose
(lessVerbose verbosity
) True buildDir
452 -- What package database(s) to use
453 let packageDbs
:: PackageDBStack
455 interpretPackageDbFlags
456 (fromFlag
(configUserInstall cfg
))
457 (configPackageDBs cfg
)
459 -- comp: the compiler we're building with
460 -- compPlatform: the platform we're building for
461 -- programDb: location and args of all programs we're
464 , compPlatform
:: Platform
465 , programDb
:: ProgramDb
468 (flagToMaybe
(configHcFlavor cfg
))
469 (flagToMaybe
(configHcPath cfg
))
470 (flagToMaybe
(configHcPkg cfg
))
471 (mkProgramDb cfg
(configPrograms cfg
))
472 (lessVerbose verbosity
)
474 -- The InstalledPackageIndex of all installed packages
475 installedPackageSet
:: InstalledPackageIndex
<-
477 (lessVerbose verbosity
)
482 -- The set of package names which are "shadowed" by internal
483 -- packages, and which component they map to
484 let internalPackageSet
:: Set LibraryName
485 internalPackageSet
= getInternalLibraries pkg_descr0
487 -- Make a data structure describing what components are enabled.
488 let enabled
:: ComponentRequestedSpec
489 enabled
= case mb_cname
of
490 Just cname
-> OneComponentRequestedSpec cname
492 ComponentRequestedSpec
493 { -- The flag name (@--enable-tests@) is a
494 -- little bit of a misnomer, because
495 -- just passing this flag won't
496 -- "enable", in our internal
497 -- nomenclature; it's just a request; a
498 -- @buildable: False@ might make it
499 -- not possible to enable.
500 testsRequested
= fromFlag
(configTests cfg
)
501 , benchmarksRequested
=
502 fromFlag
(configBenchmarks cfg
)
504 -- Some sanity checks related to enabling components.
507 && (fromFlag
(configTests cfg
) || fromFlag
(configBenchmarks cfg
))
509 $ dieWithException verbosity SanityCheckForEnableComponents
511 -- Some sanity checks related to dynamic/static linking.
512 when (fromFlag
(configDynExe cfg
) && fromFlag
(configFullyStaticExe cfg
)) $
513 dieWithException verbosity SanityCheckForDynamicStaticLinking
515 -- allConstraints: The set of all 'Dependency's we have. Used ONLY
516 -- to 'configureFinalizedPackage'.
517 -- requiredDepsMap: A map from 'PackageName' to the specifically
518 -- required 'InstalledPackageInfo', due to --dependency
520 -- NB: These constraints are to be applied to ALL components of
521 -- a package. Thus, it's not an error if allConstraints contains
522 -- more constraints than is necessary for a component (another
523 -- component might need it.)
525 -- NB: The fact that we bundle all the constraints together means
526 -- that is not possible to configure a test-suite to use one
527 -- version of a dependency, and the executable to use another.
528 ( allConstraints
:: [PackageVersionConstraint
]
529 , requiredDepsMap
:: Map
(PackageName
, ComponentName
) InstalledPackageInfo
531 either (dieWithException verbosity
) return $
533 (configConstraints cfg
)
534 (configDependencies cfg
)
537 let promisedDepsSet
= mkPromisedDepsSet
(configPromisedDependencies cfg
)
539 -- pkg_descr: The resolved package description, that does not contain any
540 -- conditionals, because we have an assignment for
541 -- every flag, either picking them ourselves using a
542 -- simple naive algorithm, or having them be passed to
543 -- us by 'configConfigurationsFlags')
544 -- flags: The 'FlagAssignment' that the conditionals were
547 -- NB: Why doesn't finalizing a package also tell us what the
548 -- dependencies are (e.g. when we run the naive algorithm,
549 -- we are checking if dependencies are satisfiable)? The
550 -- primary reason is that we may NOT have done any solving:
551 -- if the flags are all chosen for us, this step is a simple
552 -- matter of flattening according to that assignment. It's
553 -- cleaner to then configure the dependencies afterwards.
554 ( pkg_descr
:: PackageDescription
555 , flags
:: FlagAssignment
557 configureFinalizedPackage
562 ( dependencySatisfiable
563 use_external_internal_deps
564 (fromFlagOrDefault
False (configExactConfiguration cfg
))
565 (fromFlagOrDefault
False (configAllowDependingOnPrivateLibs cfg
))
566 (packageName pkg_descr0
)
577 "Finalized package description:\n"
578 ++ showPackageDescription pkg_descr
581 maybe "." takeDirectory
$
582 flagToMaybe
(configCabalFilePath cfg
)
583 checkCompilerProblems verbosity comp pkg_descr enabled
588 (updatePackageDescription pbi pkg_descr
)
590 -- The list of 'InstalledPackageInfo' recording the selected
591 -- dependencies on external packages.
593 -- Invariant: For any package name, there is at most one package
594 -- in externalPackageDeps which has that name.
596 -- NB: The dependency selection is global over ALL components
597 -- in the package (similar to how allConstraints and
598 -- requiredDepsMap are global over all components). In particular,
599 -- if *any* component (post-flag resolution) has an unsatisfiable
600 -- dependency, we will fail. This can sometimes be undesirable
601 -- for users, see #1786 (benchmark conflicts with executable),
603 -- In the presence of Backpack, these package dependencies are
604 -- NOT complete: they only ever include the INDEFINITE
605 -- dependencies. After we apply an instantiation, we'll get
606 -- definite references which constitute extra dependencies.
607 -- (Why not have cabal-install pass these in explicitly?
608 -- For one it's deterministic; for two, we need to associate
609 -- them with renamings which would require a far more complicated
610 -- input scheme than what we have today.)
611 externalPkgDeps
:: ([PreExistingComponent
], [PromisedComponent
]) <-
612 configureDependencies
614 use_external_internal_deps
622 -- Compute installation directory templates, based on user
625 -- TODO: Move this into a helper function.
626 defaultDirs
:: InstallDirTemplates
<-
628 use_external_internal_deps
629 (compilerFlavor comp
)
630 (fromFlag
(configUserInstall cfg
))
632 let installDirs
:: InstallDirTemplates
637 (configInstallDirs cfg
)
639 -- Check languages and extensions
640 -- TODO: Move this into a helper function.
646 (enabledBuildInfos pkg_descr enabled
)
647 let langs
= unsupportedLanguages comp langlist
648 when (not (null langs
)) $
649 dieWithException verbosity
$
650 UnsupportedLanguages
(packageId pkg_descr0
) (compilerId comp
) (map prettyShow langs
)
655 (enabledBuildInfos pkg_descr enabled
)
656 let exts
= unsupportedExtensions comp extlist
657 when (not (null exts
)) $
658 dieWithException verbosity
$
659 UnsupportedLanguageExtension
(packageId pkg_descr0
) (compilerId comp
) (map prettyShow exts
)
661 -- Check foreign library build requirements
662 let flibs
= [flib | CFLib flib
<- enabledComponents pkg_descr enabled
]
663 let unsupportedFLibs
= unsupportedForeignLibs comp compPlatform flibs
664 when (not (null unsupportedFLibs
)) $
665 dieWithException verbosity
$
666 CantFindForeignLibraries unsupportedFLibs
668 -- Configure certain external build tools, see below for which ones.
669 let requiredBuildTools
= do
670 bi
<- enabledBuildInfos pkg_descr enabled
671 -- First, we collect any tool dep that we know is external. This is,
674 -- 1. `build-tools` entries on the whitelist
676 -- 2. `build-tool-depends` that aren't from the current package.
677 let externBuildToolDeps
=
678 [ LegacyExeDependency
(unUnqualComponentName eName
) versionRange
679 | buildTool
@(ExeDependency _ eName versionRange
) <-
680 getAllToolDependencies pkg_descr bi
681 , not $ isInternal pkg_descr buildTool
683 -- Second, we collect any build-tools entry we don't know how to
684 -- desugar. We'll never have any idea how to build them, so we just
685 -- hope they are already on the PATH.
686 let unknownBuildTools
=
688 | buildTool
<- buildTools bi
689 , Nothing
== desugarBuildTool pkg_descr buildTool
691 externBuildToolDeps
++ unknownBuildTools
694 configureAllKnownPrograms
(lessVerbose verbosity
) programDb
695 >>= configureRequiredPrograms verbosity requiredBuildTools
697 (pkg_descr
', programDb
'') <-
698 configurePkgconfigPackages verbosity pkg_descr programDb
' enabled
700 -- Compute internal component graph
702 -- The general idea is that we take a look at all the source level
703 -- components (which may build-depends on each other) and form a graph.
704 -- From there, we build a ComponentLocalBuildInfo for each of the
705 -- components, which lets us actually build each component.
706 -- internalPackageSet
707 -- use_external_internal_deps
708 ( buildComponents
:: [ComponentLocalBuildInfo
]
709 , packageDependsIndex
:: InstalledPackageIndex
711 runLogProgress verbosity
$
712 configureComponentLocalBuildInfos
714 use_external_internal_deps
716 (fromFlagOrDefault
False (configDeterministic cfg
))
721 (configConfigurationsFlags cfg
)
722 (configInstantiateWith cfg
)
726 -- Decide if we're going to compile with split sections.
727 split_sections
:: Bool <-
728 if not (fromFlag
$ configSplitSections cfg
)
730 else case compilerFlavor comp
of
732 | compilerVersion comp
>= mkVersion
[8, 0] ->
739 ( "this compiler does not support "
740 ++ "--enable-split-sections; ignoring"
744 -- Decide if we're going to compile with split objects.
745 split_objs
:: Bool <-
746 if not (fromFlag
$ configSplitObjs cfg
)
748 else case compilerFlavor comp
of
749 _ | split_sections
->
753 ( "--enable-split-sections and "
754 ++ "--enable-split-objs are mutually "
755 ++ "exclusive; ignoring the latter"
765 ( "this compiler does not support "
766 ++ "--enable-split-objs; ignoring"
770 let compilerSupportsGhciLibs
:: Bool
771 compilerSupportsGhciLibs
=
772 case compilerId comp
of
773 CompilerId GHC version
774 | version
> mkVersion
[9, 3] && windows
->
778 CompilerId GHCJS _
->
782 windows
= case compPlatform
of
783 Platform _ Windows
-> True
784 Platform _ _
-> False
786 let ghciLibByDefault
=
787 case compilerId comp
of
789 -- If ghc is non-dynamic, then ghci needs object files,
790 -- so we build one by default.
792 -- Technically, archive files should be sufficient for ghci,
793 -- but because of GHC bug #8942, it has never been safe to
794 -- rely on them. By the time that bug was fixed, ghci had
795 -- been changed to read shared libraries instead of archive
796 -- files (see next code block).
797 not (GHC
.isDynamic comp
)
798 CompilerId GHCJS _
->
799 not (GHCJS
.isDynamic comp
)
803 case fromFlagOrDefault ghciLibByDefault
(configGHCiLib cfg
) of
804 True |
not compilerSupportsGhciLibs
-> do
806 "--enable-library-for-ghci is no longer supported on Windows with"
807 ++ " GHC 9.4 and later; ignoring..."
811 let sharedLibsByDefault
812 | fromFlag
(configDynExe cfg
) =
813 -- build a shared library if dynamically-linked
814 -- executables are requested
816 |
otherwise = case compilerId comp
of
818 -- if ghc is dynamic, then ghci needs a shared
819 -- library, so we build one by default.
821 CompilerId GHCJS _
->
825 -- build shared libraries if required by GHC or by the
826 -- executable linking mode, but allow the user to force
827 -- building only static library archives with
829 fromFlagOrDefault sharedLibsByDefault
$ configSharedLib cfg
832 -- build a static library (all dependent libraries rolled
833 -- into a huge .a archive) via GHCs -staticlib flag.
834 fromFlagOrDefault
False $ configStaticLib cfg
836 withDynExe_
= fromFlag
$ configDynExe cfg
838 withFullyStaticExe_
= fromFlag
$ configFullyStaticExe cfg
840 when (withDynExe_
&& not withSharedLib_
) $
842 "Executables will use dynamic linking, but a shared library "
843 ++ "is not being built. Linking will fail if any executables "
844 ++ "depend on the library."
846 setProfLBI
<- configureProfiling verbosity cfg comp
848 setCoverageLBI
<- configureCoverage verbosity cfg comp
850 -- Turn off library and executable stripping when `debug-info` is set
851 -- to anything other than zero.
854 let defaultStrip
= fromFlagOrDefault
True (f cfg
)
855 in case fromFlag
(configDebugInfo cfg
) of
856 NoDebugInfo
-> return defaultStrip
860 "Setting debug-info implies "
862 ++ "-stripping: False"
866 strip_lib
<- strip_libexe
"library" configStripLibs
867 strip_exe
<- strip_libexe
"executable" configStripExes
869 let reloc
= fromFlagOrDefault
False $ configRelocatable cfg
871 let buildComponentsMap
=
876 (componentLocalName clbi
)
884 (setCoverageLBI
. setProfLBI
)
887 , flagAssignment
= flags
888 , componentEnabledSpec
= enabled
889 , extraConfigArgs
= [] -- Currently configure does not
890 -- take extra args, but if it
891 -- did they would go here.
892 , installDirTemplates
= installDirs
894 , hostPlatform
= compPlatform
895 , buildDir
= buildDir
896 , cabalFilePath
= flagToMaybe
(configCabalFilePath cfg
)
897 , componentGraph
= Graph
.fromDistinctList buildComponents
898 , componentNameMap
= buildComponentsMap
899 , installedPkgs
= packageDependsIndex
900 , promisedPkgs
= promisedDepsSet
901 , pkgDescrFile
= Nothing
902 , localPkgDescr
= pkg_descr
'
903 , withPrograms
= programDb
''
904 , withVanillaLib
= fromFlag
$ configVanillaLib cfg
905 , withSharedLib
= withSharedLib_
906 , withStaticLib
= withStaticLib_
907 , withDynExe
= withDynExe_
908 , withFullyStaticExe
= withFullyStaticExe_
909 , withProfLib
= False
910 , withProfLibDetail
= ProfDetailNone
911 , withProfExe
= False
912 , withProfExeDetail
= ProfDetailNone
913 , withOptimization
= fromFlag
$ configOptimization cfg
914 , withDebugInfo
= fromFlag
$ configDebugInfo cfg
915 , withGHCiLib
= withGHCiLib_
916 , splitSections
= split_sections
917 , splitObjs
= split_objs
918 , stripExes
= strip_exe
919 , stripLibs
= strip_lib
920 , exeCoverage
= False
921 , libCoverage
= False
922 , withPackageDB
= packageDbs
923 , progPrefix
= fromFlag
$ configProgPrefix cfg
924 , progSuffix
= fromFlag
$ configProgSuffix cfg
925 , relocatable
= reloc
928 when reloc
(checkRelocatable verbosity pkg_descr lbi
)
930 -- TODO: This is not entirely correct, because the dirs may vary
931 -- across libraries/executables
932 let dirs
= absoluteInstallDirs pkg_descr lbi NoCopyDest
933 relative
= prefixRelativeInstallDirs
(packageId pkg_descr
) lbi
935 -- PKGROOT: allowing ${pkgroot} to be passed as --prefix to
936 -- cabal configure, is only a hidden option. It allows packages
937 -- to be relocatable with their package database. This however
938 -- breaks when the Paths_* or other includes are used that
939 -- contain hard coded paths. This is still an open TODO.
941 -- Allowing ${pkgroot} here, however requires less custom hooks
942 -- in scripts that *really* want ${pkgroot}. See haskell/cabal/#4872
944 ( isAbsolute
(prefix dirs
)
945 ||
"${pkgroot}" `
isPrefixOf` prefix dirs
947 $ dieWithException verbosity
948 $ ExpectedAbsoluteDirectory
(prefix dirs
)
950 when ("${pkgroot}" `
isPrefixOf` prefix dirs
) $
952 "Using ${pkgroot} in prefix "
954 ++ " will not work if you rely on the Path_* module "
955 ++ " or other hard coded paths. Cabal does not yet "
956 ++ " support fully relocatable builds! "
957 ++ " See #462 #2302 #2994 #3305 #3473 #3586 #3909"
958 ++ " #4097 #4291 #4872"
962 ++ prettyShow currentCabalId
964 ++ prettyShow currentCompilerId
965 info verbosity
$ "Using compiler: " ++ showCompilerId comp
966 info verbosity
$ "Using install prefix: " ++ prefix dirs
968 let dirinfo name dir isPrefixRelative
=
969 info verbosity
$ name
++ " installed in: " ++ dir
++ relNote
971 relNote
= case buildOS
of
973 |
not (hasLibs pkg_descr
)
974 && isNothing isPrefixRelative
->
978 dirinfo
"Executables" (bindir dirs
) (bindir relative
)
979 dirinfo
"Libraries" (libdir dirs
) (libdir relative
)
980 dirinfo
"Dynamic Libraries" (dynlibdir dirs
) (dynlibdir relative
)
981 dirinfo
"Private executables" (libexecdir dirs
) (libexecdir relative
)
982 dirinfo
"Data files" (datadir dirs
) (datadir relative
)
983 dirinfo
"Documentation" (docdir dirs
) (docdir relative
)
984 dirinfo
"Configuration files" (sysconfdir dirs
) (sysconfdir relative
)
987 [ reportProgram verbosity prog configuredProg
988 |
(prog
, configuredProg
) <- knownPrograms programDb
''
993 verbosity
= fromFlag
(configVerbosity cfg
)
995 mkPromisedDepsSet
:: [GivenComponent
] -> Map
(PackageName
, ComponentName
) ComponentId
996 mkPromisedDepsSet comps
= Map
.fromList
[((pn
, CLibName ln
), cid
) | GivenComponent pn ln cid
<- comps
]
998 mkProgramDb
:: ConfigFlags
-> ProgramDb
-> ProgramDb
999 mkProgramDb cfg initialProgramDb
= programDb
1002 userSpecifyArgss
(configProgramArgs cfg
)
1003 . userSpecifyPaths
(configProgramPaths cfg
)
1004 . setProgramSearchPath searchpath
1007 getProgramSearchPath initialProgramDb
1009 ProgramSearchPathDir
1010 (fromNubList
$ configProgramPathExtra cfg
)
1012 -- Note. We try as much as possible to _prepend_ rather than postpend the extra-prog-path
1013 -- so that we can override the system path. However, in a v2-build, at this point, the "system" path
1014 -- has already been extended by both the built-tools-depends paths, as well as the program-path-extra
1015 -- so for v2 builds adding it again is entirely unnecessary. However, it needs to get added again _anyway_
1016 -- so as to take effect for v1 builds or standalone calls to Setup.hs
1017 -- In this instance, the lesser evil is to not allow it to override the system path.
1019 -- -----------------------------------------------------------------------------
1020 -- Helper functions for configure
1022 -- | Check if the user used any deprecated flags.
1023 checkDeprecatedFlags
:: Verbosity
-> ConfigFlags
-> IO ()
1024 checkDeprecatedFlags verbosity cfg
= do
1025 unless (configProfExe cfg
== NoFlag
) $ do
1027 | fromFlag
(configProfExe cfg
) = "enable"
1028 |
otherwise = "disable"
1033 ++ "-executable-profiling is deprecated. "
1036 ++ "-profiling instead."
1039 unless (configLibCoverage cfg
== NoFlag
) $ do
1041 | fromFlag
(configLibCoverage cfg
) = "enable"
1042 |
otherwise = "disable"
1047 ++ "-library-coverage is deprecated. "
1050 ++ "-coverage instead."
1053 -- | Sanity check: if '--exact-configuration' was given, ensure that the
1054 -- complete flag assignment was specified on the command line.
1055 checkExactConfiguration
1056 :: Verbosity
-> GenericPackageDescription
-> ConfigFlags
-> IO ()
1057 checkExactConfiguration verbosity pkg_descr0 cfg
=
1058 when (fromFlagOrDefault
False (configExactConfiguration cfg
)) $ do
1059 let cmdlineFlags
= map fst (unFlagAssignment
(configConfigurationsFlags cfg
))
1060 allFlags
= map flagName
. genPackageFlags
$ pkg_descr0
1061 diffFlags
= allFlags
\\ cmdlineFlags
1062 when (not . null $ diffFlags
) $
1063 dieWithException verbosity
$
1064 FlagsNotSpecified diffFlags
1066 -- | Create a PackageIndex that makes *any libraries that might be*
1067 -- defined internally to this package look like installed packages, in
1068 -- case an executable should refer to any of them as dependencies.
1070 -- It must be *any libraries that might be* defined rather than the
1071 -- actual definitions, because these depend on conditionals in the .cabal
1072 -- file, and we haven't resolved them yet. finalizePD
1073 -- does the resolution of conditionals, and it takes internalPackageSet
1074 -- as part of its input.
1075 getInternalLibraries
1076 :: GenericPackageDescription
1078 getInternalLibraries pkg_descr0
=
1079 -- TODO: some day, executables will be fair game here too!
1080 let pkg_descr
= flattenPackageDescription pkg_descr0
1081 in Set
.fromList
(map libName
(allLibraries pkg_descr
))
1083 -- | Returns true if a dependency is satisfiable. This function may
1084 -- report a dependency satisfiable even when it is not, but not vice
1085 -- versa. This is to be passed to finalize
1086 dependencySatisfiable
1088 -- ^ use external internal deps?
1090 -- ^ exact configuration?
1092 -- ^ allow depending on private libs?
1094 -> InstalledPackageIndex
1097 -- ^ library components
1098 -> Map
(PackageName
, ComponentName
) ComponentId
1099 -> Map
(PackageName
, ComponentName
) InstalledPackageInfo
1100 -- ^ required dependencies
1101 -> (Dependency
-> Bool)
1102 dependencySatisfiable
1103 use_external_internal_deps
1111 (Dependency depName vr sublibs
)
1113 -- When we're given '--exact-configuration', we assume that all
1114 -- dependencies and flags are exactly specified on the command
1115 -- line. Thus we only consult the 'requiredDepsMap'. Note that
1116 -- we're not doing the version range check, so if there's some
1117 -- dependency that wasn't specified on the command line,
1118 -- 'finalizePD' will fail.
1119 -- TODO: mention '--exact-configuration' in the error message
1121 if isInternalDep
&& not use_external_internal_deps
1122 then -- Except for internal deps, when we're NOT per-component mode;
1123 -- those are just True.
1124 internalDepSatisfiable
1125 else -- Backward compatibility for the old sublibrary syntax
1127 ( sublibs
== mainLibSet
1132 packageNameToUnqualComponentName depName
1136 ||
all visible sublibs
1138 if use_external_internal_deps
1139 then -- When we are doing per-component configure, we now need to
1140 -- test if the internal dependency is in the index. This has
1141 -- DIFFERENT semantics from normal dependency satisfiability.
1142 internalDepSatisfiableExternally
1143 else -- If a 'PackageName' is defined by an internal component, the dep is
1144 -- satisfiable (we're going to build it ourselves)
1145 internalDepSatisfiable
1149 -- Internal dependency is when dependency is the same as package.
1150 isInternalDep
= pn
== depName
1153 not . null $ PackageIndex
.lookupDependency installedPackageSet depName vr
1155 internalDepSatisfiable
=
1156 Set
.isSubsetOf
(NES
.toSet sublibs
) packageLibraries
1157 internalDepSatisfiableExternally
=
1158 all (\ln
-> not $ null $ PackageIndex
.lookupInternalDependency installedPackageSet pn vr ln
) sublibs
1160 -- Check whether a library exists and is visible.
1161 -- We don't disambiguate between dependency on non-existent or private
1162 -- library yet, so we just return a bool and later report a generic error.
1165 False -- Does not even exist (wasn't in the depsMap)
1167 IPI
.libVisibility ipi
== LibraryVisibilityPublic
1168 -- If the override is enabled, the visibility does
1169 -- not matter (it's handled externally)
1170 || allow_private_deps
1171 -- If it's a library of the same package then it's
1173 -- This is only triggered when passing a component
1174 -- of the same package as --dependency, such as in:
1175 -- cabal-testsuite/PackageTests/ConfigureComponent/SubLib/setup-explicit.test.hs
1176 || pkgName
(IPI
.sourcePackageId ipi
) == pn
1179 -- Don't check if it's visible, we promise to build it before we need it.
1182 maybeIPI
= Map
.lookup (depName
, CLibName lib
) requiredDepsMap
1183 promised
= isJust $ Map
.lookup (depName
, CLibName lib
) promisedDeps
1185 -- | Finalize a generic package description. The workhorse is
1186 -- 'finalizePD' but there's a bit of other nattering
1189 -- TODO: what exactly is the business with @flaggedTests@ and
1190 -- @flaggedBenchmarks@?
1191 configureFinalizedPackage
1194 -> ComponentRequestedSpec
1195 -> [PackageVersionConstraint
]
1196 -> (Dependency
-> Bool)
1197 -- ^ tests if a dependency is satisfiable.
1198 -- Might say it's satisfiable even when not.
1201 -> GenericPackageDescription
1202 -> IO (PackageDescription
, FlagAssignment
)
1203 configureFinalizedPackage
1212 (pkg_descr0
', flags
) <-
1214 (configConfigurationsFlags cfg
)
1223 dieWithException verbosity
$ EncounteredMissingDependency missing
1225 -- add extra include/lib dirs as specified in cfg
1226 -- we do it here so that those get checked too
1227 let pkg_descr
= addExtraIncludeLibDirs pkg_descr0
'
1229 unless (nullFlagAssignment flags
) $
1234 [ unFlagName fn
++ "=" ++ prettyShow
value
1235 |
(fn
, value) <- unFlagAssignment flags
1238 return (pkg_descr
, flags
)
1240 addExtraIncludeLibDirs pkg_descr
=
1243 { extraLibDirs
= configExtraLibDirs cfg
1244 , extraLibDirsStatic
= configExtraLibDirsStatic cfg
1245 , extraFrameworkDirs
= configExtraFrameworkDirs cfg
1246 , includeDirs
= configExtraIncludeDirs cfg
1254 modifyExecutable e
=
1260 modifyForeignLib f
=
1262 { foreignLibBuildInfo
=
1263 foreignLibBuildInfo f
1274 { benchmarkBuildInfo
=
1275 benchmarkBuildInfo b
1279 { library
= modifyLib `
fmap` library pkg_descr
1280 , subLibraries
= modifyLib `
map` subLibraries pkg_descr
1281 , executables
= modifyExecutable `
map` executables pkg_descr
1282 , foreignLibs
= modifyForeignLib `
map` foreignLibs pkg_descr
1283 , testSuites
= modifyTestsuite `
map` testSuites pkg_descr
1284 , benchmarks
= modifyBenchmark `
map` benchmarks pkg_descr
1287 -- | Check for use of Cabal features which require compiler support
1288 checkCompilerProblems
1289 :: Verbosity
-> Compiler
-> PackageDescription
-> ComponentRequestedSpec
-> IO ()
1290 checkCompilerProblems verbosity comp pkg_descr enabled
= do
1292 ( renamingPackageFlagsSupported comp
1294 (all (isDefaultIncludeRenaming
. mixinIncludeRenaming
) . mixins
)
1295 (enabledBuildInfos pkg_descr enabled
)
1297 $ dieWithException verbosity CompilerDoesn
'tSupportThinning
1299 ( any (not . null . reexportedModules
) (allLibraries pkg_descr
)
1300 && not (reexportedModulesSupported comp
)
1302 $ dieWithException verbosity CompilerDoesn
'tSupportReexports
1304 ( any (not . null . signatures
) (allLibraries pkg_descr
)
1305 && not (backpackSupported comp
)
1307 $ dieWithException verbosity CompilerDoesn
'tSupportBackpack
1309 -- | Select dependencies for the package.
1310 configureDependencies
1312 -> UseExternalInternalDeps
1314 -> Map
(PackageName
, ComponentName
) ComponentId
1315 -> InstalledPackageIndex
1316 -- ^ installed packages
1317 -> Map
(PackageName
, ComponentName
) InstalledPackageInfo
1319 -> PackageDescription
1320 -> ComponentRequestedSpec
1321 -> IO ([PreExistingComponent
], [PromisedComponent
])
1322 configureDependencies
1324 use_external_internal_deps
1331 let failedDeps
:: [FailedDependency
]
1332 allPkgDeps
:: [ResolvedDependency
]
1333 (failedDeps
, allPkgDeps
) =
1336 [ fmap (\s
-> (dep
, s
)) <$> status
1337 | dep
<- enabledBuildDepends pkg_descr enableSpec
1345 use_external_internal_deps
1351 |
(_
, InternalDependency pkgid
) <- allPkgDeps
1353 -- NB: we have to SAVE the package name, because this is the only
1354 -- way we can be able to resolve package names in the package
1358 |
(_
, ExternalDependency pec
) <- allPkgDeps
1363 |
(_
, PromisedDependency fpec
) <- allPkgDeps
1367 ( not (null internalPkgDeps
)
1368 && not (newPackageDepsBehaviour pkg_descr
)
1370 $ dieWithException verbosity
1371 $ LibraryWithinSamePackage internalPkgDeps
1372 reportFailedDependencies verbosity failedDeps
1373 reportSelectedDependencies verbosity allPkgDeps
1375 return (externalPkgDeps
, promisedPkgDeps
)
1377 -- | Select and apply coverage settings for the build based on the
1378 -- 'ConfigFlags' and 'Compiler'.
1383 -> IO (LocalBuildInfo
-> LocalBuildInfo
)
1384 configureCoverage verbosity cfg comp
= do
1385 let tryExeCoverage
= fromFlagOrDefault
False (configCoverage cfg
)
1389 (mappend
(configCoverage cfg
) (configLibCoverage cfg
))
1390 if coverageSupported comp
1394 { libCoverage
= tryLibCoverage
1395 , exeCoverage
= tryExeCoverage
1401 { libCoverage
= False
1402 , exeCoverage
= False
1404 when (tryExeCoverage || tryLibCoverage
) $
1408 ++ showCompilerId comp
1409 ++ " does not support "
1410 ++ "program coverage. Program coverage has been disabled."
1414 -- | Compute the effective value of the profiling flags
1415 -- @--enable-library-profiling@ and @--enable-executable-profiling@
1416 -- from the specified 'ConfigFlags'. This may be useful for
1417 -- external Cabal tools which need to interact with Setup in
1418 -- a backwards-compatible way: the most predictable mechanism
1419 -- for enabling profiling across many legacy versions is to
1420 -- NOT use @--enable-profiling@ and use those two flags instead.
1422 -- Note that @--enable-executable-profiling@ also affects profiling
1423 -- of benchmarks and (non-detailed) test suites.
1424 computeEffectiveProfiling
:: ConfigFlags
-> (Bool {- lib -}, Bool {- exe -})
1425 computeEffectiveProfiling cfg
=
1426 -- The --profiling flag sets the default for both libs and exes,
1427 -- but can be overridden by --library-profiling, or the old deprecated
1428 -- --executable-profiling flag.
1430 -- The --profiling-detail and --library-profiling-detail flags behave
1432 let tryExeProfiling
=
1435 (mappend
(configProf cfg
) (configProfExe cfg
))
1439 (mappend
(configProf cfg
) (configProfLib cfg
))
1440 in (tryLibProfiling
, tryExeProfiling
)
1442 -- | Select and apply profiling settings for the build based on the
1443 -- 'ConfigFlags' and 'Compiler'.
1448 -> IO (LocalBuildInfo
-> LocalBuildInfo
)
1449 configureProfiling verbosity cfg comp
= do
1450 let (tryLibProfiling
, tryExeProfiling
) = computeEffectiveProfiling cfg
1452 tryExeProfileLevel
=
1455 (configProfDetail cfg
)
1456 tryLibProfileLevel
=
1460 (configProfDetail cfg
)
1461 (configProfLibDetail cfg
)
1464 checkProfileLevel
(ProfDetailOther other
) = do
1467 ( "Unknown profiling detail level '"
1469 ++ "', using default.\nThe profiling detail levels are: "
1472 [name |
(name
, _
, _
) <- knownProfDetailLevels
]
1474 return ProfDetailDefault
1475 checkProfileLevel other
= return other
1477 (exeProfWithoutLibProf
, applyProfiling
) <-
1478 if profilingSupported comp
1480 exeLevel
<- checkProfileLevel tryExeProfileLevel
1481 libLevel
<- checkProfileLevel tryLibProfileLevel
1484 { withProfLib
= tryLibProfiling
1485 , withProfLibDetail
= libLevel
1486 , withProfExe
= tryExeProfiling
1487 , withProfExeDetail
= exeLevel
1489 return (tryExeProfiling
&& not tryLibProfiling
, apply
)
1493 { withProfLib
= False
1494 , withProfLibDetail
= ProfDetailNone
1495 , withProfExe
= False
1496 , withProfExeDetail
= ProfDetailNone
1498 when (tryExeProfiling || tryLibProfiling
) $
1502 ++ showCompilerId comp
1503 ++ " does not support "
1504 ++ "profiling. Profiling has been disabled."
1506 return (False, apply
)
1508 when exeProfWithoutLibProf
$
1511 ( "Executables will be built with profiling, but library "
1512 ++ "profiling is disabled. Linking will fail if any executables "
1513 ++ "depend on the library."
1516 return applyProfiling
1518 -- -----------------------------------------------------------------------------
1519 -- Configuring package dependencies
1521 reportProgram
:: Verbosity
-> Program
-> Maybe ConfiguredProgram
-> IO ()
1522 reportProgram verbosity prog Nothing
=
1523 info verbosity
$ "No " ++ programName prog
++ " found"
1524 reportProgram verbosity prog
(Just configuredProg
) =
1525 info verbosity
$ "Using " ++ programName prog
++ version
++ location
1527 location
= case programLocation configuredProg
of
1528 FoundOnSystem p
-> " found on system at: " ++ p
1529 UserSpecified p
-> " given by user at: " ++ p
1530 version
= case programVersion configuredProg
of
1532 Just v
-> " version " ++ prettyShow v
1534 hackageUrl
:: String
1535 hackageUrl
= "http://hackage.haskell.org/package/"
1537 type ResolvedDependency
= (Dependency
, DependencyResolution
)
1539 data DependencyResolution
1540 = -- | An external dependency from the package database, OR an
1541 -- internal dependency which we are getting from the package
1543 ExternalDependency PreExistingComponent
1544 |
-- | A promised dependency, which doesn't yet exist, but should be provided
1545 -- at the build time.
1547 -- We have these such that we can configure components without actually
1548 -- building its dependencies, if these dependencies need to be built later
1549 -- again. For example, when launching a multi-repl,
1550 -- we need to build packages in the interactive ghci session, no matter
1551 -- whether they have been built before.
1552 -- Building them in the configure phase is then redundant and costs time.
1553 PromisedDependency PromisedComponent
1554 |
-- | An internal dependency ('PackageId' should be a library name)
1555 -- which we are going to have to build. (The
1556 -- 'PackageId' here is a hack to get a modest amount of
1557 -- polymorphism out of the 'Package' typeclass.)
1558 InternalDependency PackageId
1560 -- | Test for a package dependency and record the version we have installed.
1563 -- ^ Package id of current package
1565 -- ^ package libraries
1566 -> Map
(PackageName
, ComponentName
) ComponentId
1567 -- ^ Set of components that are promised, i.e. are not installed already. See 'PromisedDependency' for more details.
1568 -> InstalledPackageIndex
1569 -- ^ Installed packages
1570 -> Map
(PackageName
, ComponentName
) InstalledPackageInfo
1571 -- ^ Packages for which we have been given specific deps to
1573 -> UseExternalInternalDeps
1574 -- ^ Are we configuring a
1575 -- single component?
1577 -> [Either FailedDependency DependencyResolution
]
1584 use_external_internal_deps
1585 (Dependency dep_pkgname vr libs
) =
1586 -- If the dependency specification matches anything in the internal package
1587 -- index, then we prefer that match to anything in the second.
1594 -- Executable my-exec
1595 -- build-depends: MyLibrary
1597 -- We want "build-depends: MyLibrary" always to match the internal library
1598 -- even if there is a newer installed library "MyLibrary-0.2".
1599 if dep_pkgname
== pn
1601 if use_external_internal_deps
1602 then do_external_internal
<$> NES
.toList libs
1603 else do_internal
<$> NES
.toList libs
1604 else do_external_external
<$> NES
.toList libs
1606 pn
= packageName pkgid
1608 -- It's an internal library, and we're not per-component build
1610 | Set
.member lib internalIndex
=
1611 Right
$ InternalDependency
$ PackageIdentifier dep_pkgname
$ packageVersion pkgid
1613 Left
$ DependencyMissingInternal dep_pkgname lib
1615 -- We have to look it up externally
1616 do_external_external
:: LibraryName
-> Either FailedDependency DependencyResolution
1617 do_external_external lib
1618 | Just cid
<- Map
.lookup (dep_pkgname
, CLibName lib
) promisedIndex
=
1619 return $ PromisedDependency
(PromisedComponent dep_pkgname
(AnnotatedId currentCabalId
(CLibName lib
) cid
))
1620 do_external_external lib
= do
1621 ipi
<- case Map
.lookup (dep_pkgname
, CLibName lib
) requiredDepsMap
of
1622 -- If we know the exact pkg to use, then use it.
1623 Just pkginstance
-> Right pkginstance
1624 -- Otherwise we just pick an arbitrary instance of the latest version.
1625 Nothing
-> case pickLastIPI
$ PackageIndex
.lookupInternalDependency installedIndex dep_pkgname vr lib
of
1626 Nothing
-> Left
(DependencyNotExists dep_pkgname
)
1627 Just pkg
-> Right pkg
1628 return $ ExternalDependency
$ ipiToPreExistingComponent ipi
1630 do_external_internal
:: LibraryName
-> Either FailedDependency DependencyResolution
1631 do_external_internal lib
1632 | Just cid
<- Map
.lookup (dep_pkgname
, CLibName lib
) promisedIndex
=
1633 return $ PromisedDependency
(PromisedComponent dep_pkgname
(AnnotatedId currentCabalId
(CLibName lib
) cid
))
1634 do_external_internal lib
= do
1635 ipi
<- case Map
.lookup (dep_pkgname
, CLibName lib
) requiredDepsMap
of
1636 -- If we know the exact pkg to use, then use it.
1637 Just pkginstance
-> Right pkginstance
1638 Nothing
-> case pickLastIPI
$ PackageIndex
.lookupInternalDependency installedIndex pn vr lib
of
1639 -- It's an internal library, being looked up externally
1640 Nothing
-> Left
(DependencyMissingInternal dep_pkgname lib
)
1641 Just pkg
-> Right pkg
1642 return $ ExternalDependency
$ ipiToPreExistingComponent ipi
1644 pickLastIPI
:: [(Version
, [InstalledPackageInfo
])] -> Maybe InstalledPackageInfo
1645 pickLastIPI pkgs
= safeHead
. snd . last =<< nonEmpty pkgs
1647 reportSelectedDependencies
1649 -> [ResolvedDependency
]
1651 reportSelectedDependencies verbosity deps
=
1655 ++ prettyShow
(simplifyDependency dep
)
1658 |
(dep
, resolution
) <- deps
1659 , let pkgid
= case resolution
of
1660 ExternalDependency pkg
' -> packageId pkg
'
1661 InternalDependency pkgid
' -> pkgid
'
1662 PromisedDependency promisedComp
-> packageId promisedComp
1665 reportFailedDependencies
:: Verbosity
-> [FailedDependency
] -> IO ()
1666 reportFailedDependencies _
[] = return ()
1667 reportFailedDependencies verbosity failed
=
1668 dieWithException verbosity
$ ReportFailedDependencies failed hackageUrl
1670 -- | List all installed packages in the given package databases.
1671 -- Non-existent package databases do not cause errors, they just get skipped
1672 -- with a warning and treated as empty ones, since technically they do not
1673 -- contain any package.
1674 getInstalledPackages
1678 -- ^ The stack of package databases.
1680 -> IO InstalledPackageIndex
1681 getInstalledPackages verbosity comp packageDBs progdb
= do
1682 when (null packageDBs
) $
1683 dieWithException verbosity NoPackageDatabaseSpecified
1685 info verbosity
"Reading installed packages..."
1686 -- do not check empty packagedbs (ghc-pkg would error out)
1687 packageDBs
' <- filterM packageDBExists packageDBs
1688 case compilerFlavor comp
of
1689 GHC
-> GHC
.getInstalledPackages verbosity comp packageDBs
' progdb
1690 GHCJS
-> GHCJS
.getInstalledPackages verbosity packageDBs
' progdb
1691 UHC
-> UHC
.getInstalledPackages verbosity comp packageDBs
' progdb
1693 HaskellSuite
.getInstalledPackages verbosity packageDBs
' progdb
1695 dieWithException verbosity
$ HowToFindInstalledPackages flv
1697 packageDBExists
(SpecificPackageDB path
) = do
1698 exists
<- doesPathExist path
1701 "Package db " <> path
<> " does not exist yet"
1703 -- Checking the user and global package dbs is more complicated and needs
1704 -- way more data. Also ghc-pkg won't error out unless the user/global
1705 -- pkgdb is overridden with an empty one, so we just don't check for them.
1706 packageDBExists UserPackageDB
= pure
True
1707 packageDBExists GlobalPackageDB
= pure
True
1709 -- | Like 'getInstalledPackages', but for a single package DB.
1711 -- NB: Why isn't this always a fall through to 'getInstalledPackages'?
1712 -- That is because 'getInstalledPackages' performs some sanity checks
1713 -- on the package database stack in question. However, when sandboxes
1714 -- are involved these sanity checks are not desirable.
1715 getPackageDBContents
1720 -> IO InstalledPackageIndex
1721 getPackageDBContents verbosity comp packageDB progdb
= do
1722 info verbosity
"Reading installed packages..."
1723 case compilerFlavor comp
of
1724 GHC
-> GHC
.getPackageDBContents verbosity packageDB progdb
1725 GHCJS
-> GHCJS
.getPackageDBContents verbosity packageDB progdb
1726 -- For other compilers, try to fall back on 'getInstalledPackages'.
1727 _
-> getInstalledPackages verbosity comp
[packageDB
] progdb
1729 -- | A set of files (or directories) that can be monitored to detect when
1730 -- there might have been a change in the installed packages.
1731 getInstalledPackagesMonitorFiles
1738 getInstalledPackagesMonitorFiles verbosity comp packageDBs progdb platform
=
1739 case compilerFlavor comp
of
1741 GHC
.getInstalledPackagesMonitorFiles
1748 "don't know how to find change monitoring files for "
1749 ++ "the installed package databases for "
1753 -- | The user interface specifies the package dbs to use with a combination of
1754 -- @--global@, @--user@ and @--package-db=global|user|clear|$file@.
1755 -- This function combines the global/user flag and interprets the package-db
1756 -- flag into a single package db stack.
1757 interpretPackageDbFlags
:: Bool -> [Maybe PackageDB
] -> PackageDBStack
1758 interpretPackageDbFlags userInstall specificDBs
=
1759 extra initialStack specificDBs
1762 | userInstall
= [GlobalPackageDB
, UserPackageDB
]
1763 |
otherwise = [GlobalPackageDB
]
1765 extra dbs
' [] = dbs
'
1766 extra _
(Nothing
: dbs
) = extra
[] dbs
1767 extra dbs
' (Just db
: dbs
) = extra
(dbs
' ++ [db
]) dbs
1769 -- We are given both --constraint="foo < 2.0" style constraints and also
1770 -- specific packages to pick via --dependency="foo=foo-2.0-177d5cdf20962d0581".
1772 -- When finalising the package we have to take into account the specific
1773 -- installed deps we've been given, and the finalise function expects
1774 -- constraints, so we have to translate these deps into version constraints.
1776 -- But after finalising we then have to make sure we pick the right specific
1777 -- deps in the end. So we still need to remember which installed packages to
1780 :: [PackageVersionConstraint
]
1782 -- ^ installed dependencies
1783 -> InstalledPackageIndex
1786 ( [PackageVersionConstraint
]
1787 , Map
(PackageName
, ComponentName
) InstalledPackageInfo
1789 combinedConstraints constraints dependencies installedPackages
= do
1790 when (not (null badComponentIds
)) $
1792 CombinedConstraints
(dispDependencies badComponentIds
)
1794 -- TODO: we don't check that all dependencies are used!
1796 return (allConstraints
, idConstraintMap
)
1798 allConstraints
:: [PackageVersionConstraint
]
1801 ++ [ thisPackageVersionConstraint
(packageId pkg
)
1802 |
(_
, _
, _
, Just pkg
) <- dependenciesPkgInfo
1805 idConstraintMap
:: Map
(PackageName
, ComponentName
) InstalledPackageInfo
1808 -- NB: do NOT use the packageName from
1809 -- dependenciesPkgInfo!
1810 [ ((pn
, cname
), pkg
)
1811 |
(pn
, cname
, _
, Just pkg
) <- dependenciesPkgInfo
1814 -- The dependencies along with the installed package info, if it exists
1815 dependenciesPkgInfo
:: [(PackageName
, ComponentName
, ComponentId
, Maybe InstalledPackageInfo
)]
1816 dependenciesPkgInfo
=
1817 [ (pkgname
, CLibName lname
, cid
, mpkg
)
1818 | GivenComponent pkgname lname cid
<- dependencies
1820 PackageIndex
.lookupComponentId
1825 -- If we looked up a package specified by an installed package id
1826 -- (i.e. someone has written a hash) and didn't find it then it's
1829 [ (pkgname
, cname
, cid
)
1830 |
(pkgname
, cname
, cid
, Nothing
) <- dependenciesPkgInfo
1833 dispDependencies deps
=
1835 [ text
"--dependency="
1839 CLibName LMainLibName
-> ""
1840 CLibName
(LSubLibName n
) -> ":" <<>> pretty n
1841 _
-> ":" <<>> pretty cname
1845 |
(pkgname
, cname
, cid
) <- deps
1848 -- -----------------------------------------------------------------------------
1849 -- Configuring program dependencies
1851 configureRequiredPrograms
1853 -> [LegacyExeDependency
]
1856 configureRequiredPrograms verbosity deps progdb
=
1857 foldM (configureRequiredProgram verbosity
) progdb deps
1859 -- | Configure a required program, ensuring that it exists in the PATH
1860 -- (or where the user has specified the program must live) and making it
1861 -- available for use via the 'ProgramDb' interface. If the program is
1862 -- known (exists in the input 'ProgramDb'), we will make sure that the
1863 -- program matches the required version; otherwise we will accept
1864 -- any version of the program and assume that it is a simpleProgram.
1865 configureRequiredProgram
1868 -> LegacyExeDependency
1870 configureRequiredProgram
1873 (LegacyExeDependency progName verRange
) =
1874 case lookupKnownProgram progName progdb
of
1876 -- Try to configure it as a 'simpleProgram' automatically
1878 -- There's a bit of a story behind this line. In old versions
1879 -- of Cabal, there were only internal build-tools dependencies. So the
1880 -- behavior in this case was:
1882 -- - If a build-tool dependency was internal, don't do
1885 -- - If it was external, call 'configureRequiredProgram' to
1886 -- "configure" the executable. In particular, if
1887 -- the program was not "known" (present in 'ProgramDb'),
1888 -- then we would just error. This was fine, because
1889 -- the only way a program could be executed from 'ProgramDb'
1890 -- is if some library code from Cabal actually called it,
1891 -- and the pre-existing Cabal code only calls known
1892 -- programs from 'defaultProgramDb', and so if it
1893 -- is calling something else, you have a Custom setup
1894 -- script, and in that case you are expected to register
1895 -- the program you want to call in the ProgramDb.
1897 -- OK, so that was fine, until I (ezyang, in 2016) refactored
1898 -- Cabal to support per-component builds. In this case, what
1899 -- was previously an internal build-tool dependency now became
1900 -- an external one, and now previously "internal" dependencies
1901 -- are now external. But these are permitted to exist even
1902 -- when they are not previously configured (something that
1903 -- can only occur by a Custom script.)
1905 -- So, I decided, "Fine, let's just accept these in any
1906 -- case." Thus this line. The alternative would have been to
1907 -- somehow detect when a build-tools dependency was "internal" (by
1908 -- looking at the unflattened package description) but this
1909 -- would also be incompatible with future work to support
1910 -- external executable dependencies: we definitely cannot
1911 -- assume they will be preinitialized in the 'ProgramDb'.
1912 configureProgram verbosity
(simpleProgram progName
) progdb
1914 -- requireProgramVersion always requires the program have a version
1915 -- but if the user says "build-depends: foo" ie no version constraint
1916 -- then we should not fail if we cannot discover the program version.
1917 | verRange
== anyVersion
-> do
1918 (_
, progdb
') <- requireProgram verbosity prog progdb
1921 (_
, _
, progdb
') <- requireProgramVersion verbosity prog verRange progdb
1924 -- -----------------------------------------------------------------------------
1925 -- Configuring pkg-config package dependencies
1927 configurePkgconfigPackages
1929 -> PackageDescription
1931 -> ComponentRequestedSpec
1932 -> IO (PackageDescription
, ProgramDb
)
1933 configurePkgconfigPackages verbosity pkg_descr progdb enabled
1934 |
null allpkgs
= return (pkg_descr
, progdb
)
1937 requireProgramVersion
1938 (lessVerbose verbosity
)
1940 (orLaterVersion
$ mkVersion
[0, 9, 0])
1942 traverse_ requirePkg allpkgs
1943 mlib
' <- traverse addPkgConfigBILib
(library pkg_descr
)
1944 libs
' <- traverse addPkgConfigBILib
(subLibraries pkg_descr
)
1945 exes
' <- traverse addPkgConfigBIExe
(executables pkg_descr
)
1946 tests
' <- traverse addPkgConfigBITest
(testSuites pkg_descr
)
1947 benches
' <- traverse addPkgConfigBIBench
(benchmarks pkg_descr
)
1951 , subLibraries
= libs
'
1952 , executables
= exes
'
1953 , testSuites
= tests
'
1954 , benchmarks
= benches
'
1956 return (pkg_descr
', progdb
')
1958 allpkgs
= concatMap pkgconfigDepends
(enabledBuildInfos pkg_descr enabled
)
1961 (lessVerbose verbosity
)
1965 requirePkg dep
@(PkgconfigDependency pkgn
range) = do
1967 pkgconfig
["--modversion", pkg
]
1968 `catchIO`
(\_
-> dieWithException verbosity
$ PkgConfigNotFound pkg versionRequirement
)
1969 `catchExit`
(\_
-> dieWithException verbosity
$ PkgConfigNotFound pkg versionRequirement
)
1970 let trim
= dropWhile isSpace . dropWhileEnd
isSpace
1971 let v
= PkgconfigVersion
(toUTF8BS
$ trim version
)
1972 if not (withinPkgconfigVersionRange v
range)
1973 then dieWithException verbosity
$ BadVersion pkg versionRequirement v
1974 else info verbosity
(depSatisfied v
)
1979 ++ ": using version "
1983 | isAnyPkgconfigVersion
range = ""
1984 |
otherwise = " version " ++ prettyShow
range
1986 pkg
= unPkgconfigName pkgn
1988 -- Adds pkgconfig dependencies to the build info for a component
1989 addPkgConfigBI compBI setCompBI comp
= do
1990 bi
<- pkgconfigBuildInfo
(pkgconfigDepends
(compBI comp
))
1991 return $ setCompBI comp
(compBI comp `mappend` bi
)
1993 -- Adds pkgconfig dependencies to the build info for a library
1994 addPkgConfigBILib
= addPkgConfigBI libBuildInfo
$
1995 \lib bi
-> lib
{libBuildInfo
= bi
}
1997 -- Adds pkgconfig dependencies to the build info for an executable
1998 addPkgConfigBIExe
= addPkgConfigBI buildInfo
$
1999 \exe bi
-> exe
{buildInfo
= bi
}
2001 -- Adds pkgconfig dependencies to the build info for a test suite
2002 addPkgConfigBITest
= addPkgConfigBI testBuildInfo
$
2003 \test bi
-> test
{testBuildInfo
= bi
}
2005 -- Adds pkgconfig dependencies to the build info for a benchmark
2006 addPkgConfigBIBench
= addPkgConfigBI benchmarkBuildInfo
$
2007 \bench bi
-> bench
{benchmarkBuildInfo
= bi
}
2009 pkgconfigBuildInfo
:: [PkgconfigDependency
] -> IO BuildInfo
2010 pkgconfigBuildInfo
[] = return mempty
2011 pkgconfigBuildInfo pkgdeps
= do
2012 let pkgs
= nub [prettyShow pkg | PkgconfigDependency pkg _
<- pkgdeps
]
2013 ccflags
<- pkgconfig
("--cflags" : pkgs
)
2014 ldflags
<- pkgconfig
("--libs" : pkgs
)
2015 ldflags_static
<- pkgconfig
("--libs" : "--static" : pkgs
)
2016 return (ccLdOptionsBuildInfo
(words ccflags
) (words ldflags
) (words ldflags_static
))
2018 -- | Makes a 'BuildInfo' from C compiler and linker flags.
2020 -- This can be used with the output from configuration programs like pkg-config
2021 -- and similar package-specific programs like mysql-config, freealut-config etc.
2024 -- > ccflags <- getDbProgramOutput verbosity prog progdb ["--cflags"]
2025 -- > ldflags <- getDbProgramOutput verbosity prog progdb ["--libs"]
2026 -- > ldflags_static <- getDbProgramOutput verbosity prog progdb ["--libs", "--static"]
2027 -- > return (ccldOptionsBuildInfo (words ccflags) (words ldflags) (words ldflags_static))
2028 ccLdOptionsBuildInfo
:: [String] -> [String] -> [String] -> BuildInfo
2029 ccLdOptionsBuildInfo cflags ldflags ldflags_static
=
2030 let (includeDirs
', cflags
') = partition ("-I" `
isPrefixOf`
) cflags
2031 (extraLibs
', ldflags
') = partition ("-l" `
isPrefixOf`
) ldflags
2032 (extraLibDirs
', ldflags
'') = partition ("-L" `
isPrefixOf`
) ldflags
'
2033 (extraLibsStatic
') = filter ("-l" `
isPrefixOf`
) ldflags_static
2034 (extraLibDirsStatic
') = filter ("-L" `
isPrefixOf`
) ldflags_static
2036 { includeDirs
= map (drop 2) includeDirs
'
2037 , extraLibs
= map (drop 2) extraLibs
'
2038 , extraLibDirs
= map (drop 2) extraLibDirs
'
2039 , extraLibsStatic
= map (drop 2) extraLibsStatic
'
2040 , extraLibDirsStatic
= map (drop 2) extraLibDirsStatic
'
2041 , ccOptions
= cflags
'
2042 , ldOptions
= ldflags
''
2045 -- -----------------------------------------------------------------------------
2046 -- Determining the compiler details
2050 -> IO (Compiler
, Platform
, ProgramDb
)
2051 configCompilerAuxEx cfg
=
2053 (flagToMaybe
$ configHcFlavor cfg
)
2054 (flagToMaybe
$ configHcPath cfg
)
2055 (flagToMaybe
$ configHcPkg cfg
)
2057 (fromFlag
(configVerbosity cfg
))
2059 programDb
= mkProgramDb cfg defaultProgramDb
2062 :: Maybe CompilerFlavor
2067 -> IO (Compiler
, Platform
, ProgramDb
)
2068 configCompilerEx Nothing _ _ _ verbosity
= dieWithException verbosity UnknownCompilerException
2069 configCompilerEx
(Just hcFlavor
) hcPath hcPkg progdb verbosity
= do
2070 (comp
, maybePlatform
, programDb
) <- case hcFlavor
of
2071 GHC
-> GHC
.configure verbosity hcPath hcPkg progdb
2072 GHCJS
-> GHCJS
.configure verbosity hcPath hcPkg progdb
2073 UHC
-> UHC
.configure verbosity hcPath hcPkg progdb
2074 HaskellSuite
{} -> HaskellSuite
.configure verbosity hcPath hcPkg progdb
2075 _
-> dieWithException verbosity UnknownCompilerException
2076 return (comp
, fromMaybe buildPlatform maybePlatform
, programDb
)
2078 -- -----------------------------------------------------------------------------
2079 -- Testing C lib and header dependencies
2081 -- Try to build a test C program which includes every header and links every
2082 -- lib. If that fails, try to narrow it down by preprocessing (only) and linking
2083 -- with individual headers and libs. If none is the obvious culprit then give a
2084 -- generic error message.
2085 -- TODO: produce a log file from the compiler errors, if any.
2086 checkForeignDeps
:: PackageDescription
-> LocalBuildInfo
-> Verbosity
-> IO ()
2087 checkForeignDeps pkg lbi verbosity
=
2090 (commonCcArgs
++ makeLdArgs allLibs
) -- I'm feeling
2094 missingLibs
<- findMissingLibs
2095 missingHdr
<- findOffendingHdr
2096 explainErrors missingHdr missingLibs
2099 allHeaders
= collectField includes
2102 if withFullyStaticExe lbi
2103 then extraLibsStatic
2106 ifBuildsWith headers args success failure
= do
2107 checkDuplicateHeaders
2108 ok
<- builds
(makeProgram headers
) args
2109 if ok
then success
else failure
2111 -- Ensure that there is only one header with a given name
2112 -- in either the generated (most likely by `configure`)
2113 -- build directory (e.g. `dist/build`) or in the source directory.
2115 -- If it exists in both, we'll remove the one in the source
2116 -- directory, as the generated should take precedence.
2118 -- C compilers like to prefer source local relative includes,
2119 -- so the search paths provided to the compiler via -I are
2120 -- ignored if the included file can be found relative to the
2121 -- including file. As such we need to take drastic measures
2122 -- and delete the offending file in the source directory.
2123 checkDuplicateHeaders
= do
2124 let relIncDirs
= filter (not . isAbsolute
) (collectField includeDirs
)
2125 isHeader
= isSuffixOf ".h"
2126 genHeaders
<- for relIncDirs
$ \dir
->
2127 fmap (dir
</>) . filter isHeader
2128 <$> listDirectory
(buildDir lbi
</> dir
) `catchIO`
(\_
-> return [])
2129 srcHeaders
<- for relIncDirs
$ \dir
->
2130 fmap (dir
</>) . filter isHeader
2131 <$> listDirectory
(baseDir lbi
</> dir
) `catchIO`
(\_
-> return [])
2132 let commonHeaders
= concat genHeaders `
intersect`
concat srcHeaders
2133 for_ commonHeaders
$ \hdr
-> do
2135 "Duplicate header found in "
2136 ++ (buildDir lbi
</> hdr
)
2138 ++ (baseDir lbi
</> hdr
)
2140 ++ (baseDir lbi
</> hdr
)
2141 removeFile (baseDir lbi
</> hdr
)
2148 (go
. tail . NEL
.inits $ allHeaders
)
2150 go
[] = return Nothing
-- cannot happen
2151 go
(hdrs
: hdrsInits
) =
2152 -- Try just preprocessing first
2156 -- If that works, try compiling too
2161 (return . fmap Right
. safeLast
$ hdrs
)
2163 (return . fmap Left
. safeLast
$ hdrs
)
2165 cppArgs
= "-E" : commonCppArgs
-- preprocess only
2166 ccArgs
= "-c" : commonCcArgs
-- don't try to link
2170 (makeLdArgs allLibs
)
2172 (filterM (fmap not . libExists
) allLibs
)
2174 libExists lib
= builds
(makeProgram
[]) (makeLdArgs
[lib
])
2176 baseDir lbi
' = fromMaybe "." (takeDirectory
<$> cabalFilePath lbi
')
2180 -- TODO: This is a massive hack, to work around the
2181 -- fact that the test performed here should be
2182 -- PER-component (c.f. the "I'm Feeling Lucky"; we
2183 -- should NOT be glomming everything together.)
2184 ++ ["-I" ++ buildDir lbi
</> "autogen"]
2185 -- `configure' may generate headers in the build directory
2186 ++ [ "-I" ++ buildDir lbi
</> dir
2187 | dir
<- ordNub
(collectField includeDirs
)
2188 , not (isAbsolute dir
)
2190 -- we might also reference headers from the
2191 -- packages directory.
2192 ++ [ "-I" ++ baseDir lbi
</> dir
2193 | dir
<- ordNub
(collectField includeDirs
)
2194 , not (isAbsolute dir
)
2196 ++ [ "-I" ++ dir | dir
<- ordNub
(collectField includeDirs
), isAbsolute dir
2198 ++ ["-I" ++ baseDir lbi
]
2199 ++ collectField cppOptions
2200 ++ collectField ccOptions
2206 , dir
<- IPI
.includeDirs dep
2208 -- dedupe include dirs of dependencies
2209 -- to prevent quadratic blow-up
2213 , opt
<- IPI
.ccOptions dep
2218 ++ collectField ccOptions
2221 , opt
<- IPI
.ccOptions dep
2229 ( if withFullyStaticExe lbi
2230 then extraLibDirsStatic
2234 ++ collectField ldOptions
2241 if withFullyStaticExe lbi
2242 then IPI
.libraryDirsStatic dep
2243 else IPI
.libraryDirs dep
2246 -- TODO: do we also need dependent packages' ld options?
2247 makeLdArgs libs
= ["-l" ++ lib | lib
<- libs
] ++ commonLdArgs
2251 ["#include \"" ++ hdr
++ "\"" | hdr
<- hdrs
]
2252 ++ ["int main(int argc, char** argv) { return 0; }"]
2254 collectField f
= concatMap f allBi
2255 allBi
= enabledBuildInfos pkg
(componentEnabledSpec lbi
)
2256 deps
= PackageIndex
.topologicalOrder
(installedPkgs lbi
)
2258 builds program args
=
2260 tempDir
<- getTemporaryDirectory
2261 withTempFile tempDir
".c" $ \cName cHnd
->
2262 withTempFile tempDir
"" $ \oNname oHnd
-> do
2263 hPutStrLn cHnd program
2271 (cName
: "-o" : oNname
: args
)
2273 `catchIO`
(\_
-> return False)
2274 `catchExit`
(\_
-> return False)
2276 explainErrors Nothing
[] = return () -- should be impossible!
2278 |
isNothing . lookupProgram gccProgram
. withPrograms
$ lbi
=
2279 dieWithException verbosity NoWorkingGcc
2280 explainErrors hdr libs
=
2281 dieWithException verbosity
$ ExplainErrors hdr libs
2283 -- | Output package check warnings and errors. Exit if any errors.
2284 checkPackageProblems
2287 -- ^ Path to the @.cabal@ file's directory
2288 -> GenericPackageDescription
2289 -> PackageDescription
2291 checkPackageProblems verbosity dir gpkg pkg
= do
2292 ioChecks
<- checkPackageFiles verbosity pkg dir
2293 let pureChecks
= checkPackage gpkg
(Just pkg
)
2294 (errors
, warnings
) =
2295 partitionEithers
(M
.mapMaybe classEW
$ pureChecks
++ ioChecks
)
2297 then traverse_
(warn verbosity
) (map ppPackageCheck warnings
)
2298 else dieWithException verbosity
$ CheckPackageProblems
(map ppPackageCheck errors
)
2300 -- Classify error/warnings. Left: error, Right: warning.
2301 classEW
:: PackageCheck
-> Maybe (Either PackageCheck PackageCheck
)
2302 classEW e
@(PackageBuildImpossible _
) = Just
(Left e
)
2303 classEW w
@(PackageBuildWarning _
) = Just
(Right w
)
2304 classEW
(PackageDistSuspicious _
) = Nothing
2305 classEW
(PackageDistSuspiciousWarn _
) = Nothing
2306 classEW
(PackageDistInexcusable _
) = Nothing
2308 -- | Preform checks if a relocatable build is allowed
2311 -> PackageDescription
2314 checkRelocatable verbosity pkg lbi
=
2318 , packagePrefixRelative
2319 , depsPrefixRelative
2322 -- Check if the OS support relocatable builds.
2324 -- If you add new OS' to this list, and your OS supports dynamic libraries
2325 -- and RPATH, make sure you add your OS to RPATH-support list of:
2326 -- Distribution.Simple.GHC.getRPaths
2328 unless (os `
elem`
[OSX
, Linux
]) $
2329 dieWithException verbosity
$
2332 (Platform _ os
) = hostPlatform lbi
2334 -- Check if the Compiler support relocatable builds
2336 unless (compilerFlavor comp `
elem`
[GHC
]) $
2337 dieWithException verbosity
$
2338 NoCompilerSupport
(show comp
)
2342 -- Check if all the install dirs are relative to same prefix
2343 packagePrefixRelative
=
2344 unless (relativeInstallDirs installDirs
) $
2345 dieWithException verbosity
$
2346 InstallDirsNotPrefixRelative
(installDirs
)
2348 -- NB: should be good enough to check this against the default
2349 -- component ID, but if we wanted to be strictly correct we'd
2350 -- check for each ComponentId.
2351 installDirs
= absoluteInstallDirs pkg lbi NoCopyDest
2352 p
= prefix installDirs
2353 relativeInstallDirs
(InstallDirs
{..}) =
2372 -- Check if the library dirs of the dependencies that are in the package
2373 -- database to which the package is installed are relative to the
2374 -- prefix of the package
2375 depsPrefixRelative
= do
2376 pkgr
<- GHC
.pkgRoot verbosity lbi
(registrationPackageDB
(withPackageDB lbi
))
2377 traverse_
(doCheck pkgr
) ipkgs
2380 |
maybe False (== pkgr
) (IPI
.pkgRoot ipkg
) =
2381 for_
(IPI
.libraryDirs ipkg
) $ \libdir
-> do
2382 -- When @prefix@ is not under @pkgroot@,
2383 -- @shortRelativePath prefix pkgroot@ will return a path with
2384 -- @..@s and following check will fail without @canonicalizePath@.
2385 canonicalized
<- canonicalizePath libdir
2386 unless (p `
isPrefixOf` canonicalized
) $
2387 dieWithException verbosity
$
2388 LibDirDepsPrefixNotRelative libdir p
2391 -- NB: should be good enough to check this against the default
2392 -- component ID, but if we wanted to be strictly correct we'd
2393 -- check for each ComponentId.
2394 installDirs
= absoluteInstallDirs pkg lbi NoCopyDest
2395 p
= prefix installDirs
2396 ipkgs
= PackageIndex
.allPackages
(installedPkgs lbi
)
2398 -- -----------------------------------------------------------------------------
2399 -- Testing foreign library requirements
2401 unsupportedForeignLibs
:: Compiler
-> Platform
-> [ForeignLib
] -> [String]
2402 unsupportedForeignLibs comp platform
=
2403 mapMaybe (checkForeignLibSupported comp platform
)
2405 checkForeignLibSupported
:: Compiler
-> Platform
-> ForeignLib
-> Maybe String
2406 checkForeignLibSupported comp platform flib
= go
(compilerFlavor comp
)
2408 go
:: CompilerFlavor
-> Maybe String
2410 | compilerVersion comp
< mkVersion
[7, 8] =
2412 [ "Building foreign libraries is only supported with GHC >= 7.8"
2414 |
otherwise = goGhcPlatform platform
2417 [ "Building foreign libraries is currently only supported with ghc"
2420 goGhcPlatform
:: Platform
-> Maybe String
2421 goGhcPlatform
(Platform _ OSX
) = goGhcOsx
(foreignLibType flib
)
2422 goGhcPlatform
(Platform _ Linux
) = goGhcLinux
(foreignLibType flib
)
2423 goGhcPlatform
(Platform I386 Windows
) = goGhcWindows
(foreignLibType flib
)
2424 goGhcPlatform
(Platform X86_64 Windows
) = goGhcWindows
(foreignLibType flib
)
2427 [ "Building foreign libraries is currently only supported on Mac OS, "
2428 , "Linux and Windows"
2431 goGhcOsx
:: ForeignLibType
-> Maybe String
2432 goGhcOsx ForeignLibNativeShared
2433 |
not (null (foreignLibModDefFile flib
)) =
2435 [ "Module definition file not supported on OSX"
2437 |
not (null (foreignLibVersionInfo flib
)) =
2439 [ "Foreign library versioning not currently supported on OSX"
2445 [ "We can currently only build shared foreign libraries on OSX"
2448 goGhcLinux
:: ForeignLibType
-> Maybe String
2449 goGhcLinux ForeignLibNativeShared
2450 |
not (null (foreignLibModDefFile flib
)) =
2452 [ "Module definition file not supported on Linux"
2454 |
not (null (foreignLibVersionInfo flib
))
2455 && not (null (foreignLibVersionLinux flib
)) =
2457 [ "You must not specify both lib-version-info and lib-version-linux"
2463 [ "We can currently only build shared foreign libraries on Linux"
2466 goGhcWindows
:: ForeignLibType
-> Maybe String
2467 goGhcWindows ForeignLibNativeShared
2470 [ "We can currently only build standalone libraries on Windows. Use\n"
2471 , " if os(Windows)\n"
2472 , " options: standalone\n"
2473 , "in your foreign-library stanza."
2475 |
not (null (foreignLibVersionInfo flib
)) =
2477 [ "Foreign library versioning not currently supported on Windows.\n"
2478 , "You can specify module definition files in the mod-def-file field."
2484 [ "We can currently only build shared foreign libraries on Windows"
2488 standalone
= ForeignLibStandalone `
elem` foreignLibOptions flib
2490 unsupported
:: [String] -> Maybe String
2491 unsupported
= Just
. concat