1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE OverloadedStrings #-}
4 {-# LANGUAGE RankNTypes #-}
5 {-# LANGUAGE RecordWildCards #-}
6 {-# LANGUAGE ScopedTypeVariables #-}
8 -----------------------------------------------------------------------------
10 -- Module : Distribution.Simple.Configure
11 -- Copyright : Isaac Jones 2003-2005
14 -- Maintainer : cabal-devel@haskell.org
15 -- Portability : portable
17 -- This deals with the /configure/ phase. It provides the 'configure' action
18 -- which is given the package description and configure flags. It then tries
19 -- to: configure the compiler; resolves any conditionals in the package
20 -- description; resolve the package dependencies; check if all the extensions
21 -- used by this package are supported by the compiler; check that all the build
22 -- tools are available (including version checks if appropriate); checks for
23 -- any required @pkg-config@ packages (updating the 'BuildInfo' with the
26 -- Then based on all this it saves the info in the 'LocalBuildInfo' and writes
27 -- it out to the @dist\/setup-config@ file. It also displays various details to
28 -- the user, the amount of information displayed depending on the verbosity
31 module Distribution
.Simple
.Configure
(configure
,
32 writePersistBuildConfig
,
34 getPersistBuildConfig
,
35 checkPersistBuildConfigOutdated
,
36 tryGetPersistBuildConfig
,
37 maybeGetPersistBuildConfig
,
38 findDistPref
, findDistPrefOrDefault
,
41 computeCompatPackageKey
,
42 computeCompatPackageName
,
45 getInstalledPackagesMonitorFiles
,
47 configCompiler
, configCompilerAux
,
48 configCompilerEx
, configCompilerAuxEx
,
49 computeEffectiveProfiling
,
52 interpretPackageDbFlags
,
53 ConfigStateFileError
(..),
54 tryGetConfigStateFile
,
60 import Distribution
.Compat
.Prelude
62 import Distribution
.Compiler
63 import Distribution
.Types
.IncludeRenaming
64 import Distribution
.Utils
.NubList
65 import Distribution
.Simple
.Compiler
hiding (Flag
)
66 import Distribution
.Simple
.PreProcess
67 import Distribution
.Package
68 import qualified Distribution
.InstalledPackageInfo
as Installed
69 import Distribution
.InstalledPackageInfo
(InstalledPackageInfo
)
70 import qualified Distribution
.Simple
.PackageIndex
as PackageIndex
71 import Distribution
.Simple
.PackageIndex
(InstalledPackageIndex
)
72 import Distribution
.PackageDescription
as PD
hiding (Flag
)
73 import Distribution
.Types
.PackageDescription
as PD
74 import Distribution
.PackageDescription
.PrettyPrint
75 import Distribution
.PackageDescription
.Configuration
76 import Distribution
.PackageDescription
.Check
hiding (doesFileExist)
77 import Distribution
.Simple
.BuildToolDepends
78 import Distribution
.Simple
.Program
79 import Distribution
.Simple
.Setup
as Setup
80 import Distribution
.Simple
.BuildTarget
81 import Distribution
.Simple
.LocalBuildInfo
82 import Distribution
.Types
.ExeDependency
83 import Distribution
.Types
.LegacyExeDependency
84 import Distribution
.Types
.PkgconfigDependency
85 import Distribution
.Types
.MungedPackageName
86 import Distribution
.Types
.LocalBuildInfo
87 import Distribution
.Types
.ComponentRequestedSpec
88 import Distribution
.Types
.ForeignLib
89 import Distribution
.Types
.ForeignLibType
90 import Distribution
.Types
.ForeignLibOption
91 import Distribution
.Types
.Mixin
92 import Distribution
.Types
.UnqualComponentName
93 import Distribution
.Simple
.Utils
94 import Distribution
.System
95 import Distribution
.Version
96 import Distribution
.Verbosity
97 import qualified Distribution
.Compat
.Graph
as Graph
98 import Distribution
.Compat
.Stack
99 import Distribution
.Backpack
.Configure
100 import Distribution
.Backpack
.DescribeUnitId
101 import Distribution
.Backpack
.PreExistingComponent
102 import Distribution
.Backpack
.ConfiguredComponent
(newPackageDepsBehaviour
)
103 import Distribution
.Backpack
.Id
104 import Distribution
.Utils
.LogProgress
106 import qualified Distribution
.Simple
.GHC
as GHC
107 import qualified Distribution
.Simple
.GHCJS
as GHCJS
108 import qualified Distribution
.Simple
.UHC
as UHC
109 import qualified Distribution
.Simple
.HaskellSuite
as HaskellSuite
111 import Control
.Exception
112 ( ErrorCall
, Exception
, evaluate
, throw
, throwIO
, try )
113 import Control
.Monad
( forM
, forM_
)
114 import Distribution
.Compat
.Binary
( decodeOrFailIO
, encode
)
115 import Distribution
.Compat
.Directory
( listDirectory
)
116 import Data
.ByteString
.Lazy
( ByteString
)
117 import qualified Data
.ByteString
as BS
118 import qualified Data
.ByteString
.Lazy
.Char8
as BLC8
120 ( (\\), partition, inits, stripPrefix
, intersect )
123 import qualified Data
.Map
as Map
124 import System
.Directory
125 ( doesFileExist, createDirectoryIfMissing
, getTemporaryDirectory
127 import System
.FilePath
128 ( (</>), isAbsolute
, takeDirectory
)
129 import qualified System
.Info
130 ( compilerName
, compilerVersion
)
132 ( hPutStrLn, hClose )
133 import Distribution
.Text
134 ( Text
(disp
), defaultStyle
, display
, simpleParse
)
135 import Text
.PrettyPrint
136 ( Doc
, (<+>), ($+$), char
, comma
, hsep
, nest
137 , punctuate
, quotes
, render
, renderStyle
, sep
, text
)
138 import Distribution
.Compat
.Environment
( lookupEnv
)
139 import Distribution
.Compat
.Exception
( catchExit
, catchIO
)
142 type UseExternalInternalDeps
= Bool
144 -- | The errors that can be thrown when reading the @setup-config@ file.
145 data ConfigStateFileError
146 = ConfigStateFileNoHeader
-- ^ No header found.
147 | ConfigStateFileBadHeader
-- ^ Incorrect header.
148 | ConfigStateFileNoParse
-- ^ Cannot parse file contents.
149 | ConfigStateFileMissing
-- ^ No file!
150 | ConfigStateFileBadVersion PackageIdentifier PackageIdentifier
151 (Either ConfigStateFileError LocalBuildInfo
) -- ^ Mismatched version.
154 -- | Format a 'ConfigStateFileError' as a user-facing error message.
155 dispConfigStateFileError
:: ConfigStateFileError
-> Doc
156 dispConfigStateFileError ConfigStateFileNoHeader
=
157 text
"Saved package config file header is missing."
158 <+> text
"Re-run the 'configure' command."
159 dispConfigStateFileError ConfigStateFileBadHeader
=
160 text
"Saved package config file header is corrupt."
161 <+> text
"Re-run the 'configure' command."
162 dispConfigStateFileError ConfigStateFileNoParse
=
163 text
"Saved package config file is corrupt."
164 <+> text
"Re-run the 'configure' command."
165 dispConfigStateFileError ConfigStateFileMissing
=
166 text
"Run the 'configure' command first."
167 dispConfigStateFileError
(ConfigStateFileBadVersion oldCabal oldCompiler _
) =
168 text
"Saved package config file is outdated:"
169 $+$ badCabal
$+$ badCompiler
170 $+$ text
"Re-run the 'configure' command."
173 text
"• the Cabal version changed from"
174 <+> disp oldCabal
<+> "to" <+> disp currentCabalId
176 | oldCompiler
== currentCompilerId
= mempty
178 text
"• the compiler changed from"
179 <+> disp oldCompiler
<+> "to" <+> disp currentCompilerId
181 instance Show ConfigStateFileError
where
182 show = renderStyle defaultStyle
. dispConfigStateFileError
184 instance Exception ConfigStateFileError
186 -- | Read the 'localBuildInfoFile'. Throw an exception if the file is
187 -- missing, if the file cannot be read, or if the file was created by an older
189 getConfigStateFile
:: FilePath -- ^ The file path of the @setup-config@ file.
191 getConfigStateFile filename
= do
192 exists
<- doesFileExist filename
193 unless exists
$ throwIO ConfigStateFileMissing
194 -- Read the config file into a strict ByteString to avoid problems with
195 -- lazy I/O, then convert to lazy because the binary package needs that.
196 contents
<- BS
.readFile filename
197 let (header
, body
) = BLC8
.span
(/='\n') (BLC8
.fromChunks
[contents
])
199 headerParseResult
<- try $ evaluate
$ parseHeader header
200 let (cabalId
, compId
) =
201 case headerParseResult
of
202 Left
(_
:: ErrorCall
) -> throw ConfigStateFileBadHeader
205 let getStoredValue
= do
206 result
<- decodeOrFailIO
(BLC8
.tail body
)
208 Left _
-> throw ConfigStateFileNoParse
210 deferErrorIfBadVersion act
211 | cabalId
/= currentCabalId
= do
213 throw
$ ConfigStateFileBadVersion cabalId compId eResult
215 deferErrorIfBadVersion getStoredValue
217 _
= callStack
-- TODO: attach call stack to exception
219 -- | Read the 'localBuildInfoFile', returning either an error or the local build
221 tryGetConfigStateFile
:: FilePath -- ^ The file path of the @setup-config@ file.
222 -> IO (Either ConfigStateFileError LocalBuildInfo
)
223 tryGetConfigStateFile
= try . getConfigStateFile
225 -- | Try to read the 'localBuildInfoFile'.
226 tryGetPersistBuildConfig
:: FilePath -- ^ The @dist@ directory path.
227 -> IO (Either ConfigStateFileError LocalBuildInfo
)
228 tryGetPersistBuildConfig
= try . getPersistBuildConfig
230 -- | Read the 'localBuildInfoFile'. Throw an exception if the file is
231 -- missing, if the file cannot be read, or if the file was created by an older
233 getPersistBuildConfig
:: FilePath -- ^ The @dist@ directory path.
235 getPersistBuildConfig
= getConfigStateFile
. localBuildInfoFile
237 -- | Try to read the 'localBuildInfoFile'.
238 maybeGetPersistBuildConfig
:: FilePath -- ^ The @dist@ directory path.
239 -> IO (Maybe LocalBuildInfo
)
240 maybeGetPersistBuildConfig
=
241 liftM (either (const Nothing
) Just
) . tryGetPersistBuildConfig
243 -- | After running configure, output the 'LocalBuildInfo' to the
244 -- 'localBuildInfoFile'.
245 writePersistBuildConfig
:: FilePath -- ^ The @dist@ directory path.
246 -> LocalBuildInfo
-- ^ The 'LocalBuildInfo' to write.
248 writePersistBuildConfig distPref lbi
= do
249 createDirectoryIfMissing
False distPref
250 writeFileAtomic
(localBuildInfoFile distPref
) $
251 BLC8
.unlines [showHeader pkgId
, encode lbi
]
253 pkgId
= localPackage lbi
255 -- | Identifier of the current Cabal package.
256 currentCabalId
:: PackageIdentifier
257 currentCabalId
= PackageIdentifier
(mkPackageName
"Cabal") cabalVersion
259 -- | Identifier of the current compiler package.
260 currentCompilerId
:: PackageIdentifier
261 currentCompilerId
= PackageIdentifier
(mkPackageName System
.Info
.compilerName
)
262 (mkVersion
' System
.Info
.compilerVersion
)
264 -- | Parse the @setup-config@ file header, returning the package identifiers
265 -- for Cabal and the compiler.
266 parseHeader
:: ByteString
-- ^ The file contents.
267 -> (PackageIdentifier
, PackageIdentifier
)
268 parseHeader header
= case BLC8
.words header
of
269 ["Saved", "package", "config", "for", pkgId
, "written", "by", cabalId
,
271 fromMaybe (throw ConfigStateFileBadHeader
) $ do
272 _
<- simpleParse
(BLC8
.unpack pkgId
) :: Maybe PackageIdentifier
273 cabalId
' <- simpleParse
(BLC8
.unpack cabalId
)
274 compId
' <- simpleParse
(BLC8
.unpack compId
)
275 return (cabalId
', compId
')
276 _
-> throw ConfigStateFileNoHeader
278 -- | Generate the @setup-config@ file header.
279 showHeader
:: PackageIdentifier
-- ^ The processed package.
281 showHeader pkgId
= BLC8
.unwords
282 [ "Saved", "package", "config", "for"
283 , BLC8
.pack
$ display pkgId
285 , BLC8
.pack
$ display currentCabalId
287 , BLC8
.pack
$ display currentCompilerId
290 -- | Check that localBuildInfoFile is up-to-date with respect to the
292 checkPersistBuildConfigOutdated
:: FilePath -> FilePath -> NoCallStackIO
Bool
293 checkPersistBuildConfigOutdated distPref pkg_descr_file
=
294 pkg_descr_file `moreRecentFile` localBuildInfoFile distPref
296 -- | Get the path of @dist\/setup-config@.
297 localBuildInfoFile
:: FilePath -- ^ The @dist@ directory path.
299 localBuildInfoFile distPref
= distPref
</> "setup-config"
301 -- -----------------------------------------------------------------------------
303 -- -----------------------------------------------------------------------------
305 -- | Return the \"dist/\" prefix, or the default prefix. The prefix is taken
306 -- from (in order of highest to lowest preference) the override prefix, the
307 -- \"CABAL_BUILDDIR\" environment variable, or the default prefix.
308 findDistPref
:: FilePath -- ^ default \"dist\" prefix
309 -> Setup
.Flag
FilePath -- ^ override \"dist\" prefix
310 -> NoCallStackIO
FilePath
311 findDistPref defDistPref overrideDistPref
= do
312 envDistPref
<- liftM parseEnvDistPref
(lookupEnv
"CABAL_BUILDDIR")
313 return $ fromFlagOrDefault defDistPref
(mappend envDistPref overrideDistPref
)
315 parseEnvDistPref env
=
317 Just distPref |
not (null distPref
) -> toFlag distPref
320 -- | Return the \"dist/\" prefix, or the default prefix. The prefix is taken
321 -- from (in order of highest to lowest preference) the override prefix, the
322 -- \"CABAL_BUILDDIR\" environment variable, or 'defaultDistPref' is used. Call
323 -- this function to resolve a @*DistPref@ flag whenever it is not known to be
324 -- set. (The @*DistPref@ flags are always set to a definite value before
325 -- invoking 'UserHooks'.)
326 findDistPrefOrDefault
:: Setup
.Flag
FilePath -- ^ override \"dist\" prefix
327 -> NoCallStackIO
FilePath
328 findDistPrefOrDefault
= findDistPref defaultDistPref
330 -- |Perform the \"@.\/setup configure@\" action.
331 -- Returns the @.setup-config@ file.
332 configure
:: (GenericPackageDescription
, HookedBuildInfo
)
333 -> ConfigFlags
-> IO LocalBuildInfo
334 configure
(pkg_descr0
, pbi
) cfg
= do
335 -- Determine the component we are configuring, if a user specified
336 -- one on the command line. We use a fake, flattened version of
337 -- the package since at this point, we're not really sure what
338 -- components we *can* configure. @Nothing@ means that we should
339 -- configure everything (the old behavior).
340 (mb_cname
:: Maybe ComponentName
) <- do
341 let flat_pkg_descr
= flattenPackageDescription pkg_descr0
342 targets
<- readBuildTargets verbosity flat_pkg_descr
(configArgs cfg
)
343 -- TODO: bleat if you use the module/file syntax
344 let targets
' = [ cname | BuildTargetComponent cname
<- targets
]
346 _ |
null (configArgs cfg
) -> return Nothing
347 [cname
] -> return (Just cname
)
348 [] -> die
' verbosity
"No valid component targets found"
349 _
-> die
' verbosity
"Can only configure either single component or all of them"
351 let use_external_internal_deps
= isJust mb_cname
353 Nothing
-> setupMessage verbosity
"Configuring" (packageId pkg_descr0
)
354 Just cname
-> setupMessage
' verbosity
"Configuring" (packageId pkg_descr0
)
355 cname
(Just
(configInstantiateWith cfg
))
357 -- configCID is only valid for per-component configure
358 when (isJust (flagToMaybe
(configCID cfg
)) && isNothing mb_cname
) $
359 die
' verbosity
"--cid is only supported for per-component configure"
361 checkDeprecatedFlags verbosity cfg
362 checkExactConfiguration verbosity pkg_descr0 cfg
364 -- Where to build the package
365 let buildDir
:: FilePath -- e.g. dist/build
366 -- fromFlag OK due to Distribution.Simple calling
367 -- findDistPrefOrDefault to fill it in
368 buildDir
= fromFlag
(configDistPref cfg
) </> "build"
369 createDirectoryIfMissingVerbose
(lessVerbose verbosity
) True buildDir
371 -- What package database(s) to use
372 let packageDbs
:: PackageDBStack
374 = interpretPackageDbFlags
375 (fromFlag
(configUserInstall cfg
))
376 (configPackageDBs cfg
)
378 -- comp: the compiler we're building with
379 -- compPlatform: the platform we're building for
380 -- programDb: location and args of all programs we're
383 compPlatform
:: Platform
,
384 programDb
:: ProgramDb
)
386 (flagToMaybe
(configHcFlavor cfg
))
387 (flagToMaybe
(configHcPath cfg
))
388 (flagToMaybe
(configHcPkg cfg
))
389 (mkProgramDb cfg
(configPrograms cfg
))
390 (lessVerbose verbosity
)
392 -- The InstalledPackageIndex of all installed packages
393 installedPackageSet
:: InstalledPackageIndex
394 <- getInstalledPackages
(lessVerbose verbosity
) comp
397 -- The set of package names which are "shadowed" by internal
398 -- packages, and which component they map to
399 let internalPackageSet
:: Map PackageName
(Maybe UnqualComponentName
)
400 internalPackageSet
= getInternalPackages pkg_descr0
402 -- Make a data structure describing what components are enabled.
403 let enabled
:: ComponentRequestedSpec
404 enabled
= case mb_cname
of
405 Just cname
-> OneComponentRequestedSpec cname
406 Nothing
-> ComponentRequestedSpec
407 -- The flag name (@--enable-tests@) is a
408 -- little bit of a misnomer, because
409 -- just passing this flag won't
410 -- "enable", in our internal
411 -- nomenclature; it's just a request; a
412 -- @buildable: False@ might make it
413 -- not possible to enable.
414 { testsRequested
= fromFlag
(configTests cfg
)
415 , benchmarksRequested
=
416 fromFlag
(configBenchmarks cfg
) }
417 -- Some sanity checks related to enabling components.
418 when (isJust mb_cname
419 && (fromFlag
(configTests cfg
) || fromFlag
(configBenchmarks cfg
))) $
420 die
' verbosity
$ "--enable-tests/--enable-benchmarks are incompatible with" ++
421 " explicitly specifying a component to configure."
423 -- allConstraints: The set of all 'Dependency's we have. Used ONLY
424 -- to 'configureFinalizedPackage'.
425 -- requiredDepsMap: A map from 'PackageName' to the specifically
426 -- required 'InstalledPackageInfo', due to --dependency
428 -- NB: These constraints are to be applied to ALL components of
429 -- a package. Thus, it's not an error if allConstraints contains
430 -- more constraints than is necessary for a component (another
431 -- component might need it.)
433 -- NB: The fact that we bundle all the constraints together means
434 -- that is not possible to configure a test-suite to use one
435 -- version of a dependency, and the executable to use another.
436 (allConstraints
:: [Dependency
],
437 requiredDepsMap
:: Map PackageName InstalledPackageInfo
)
438 <- either (die
' verbosity
) return $
439 combinedConstraints
(configConstraints cfg
)
440 (configDependencies cfg
)
443 -- pkg_descr: The resolved package description, that does not contain any
444 -- conditionals, because we have have an assignment for
445 -- every flag, either picking them ourselves using a
446 -- simple naive algorithm, or having them be passed to
447 -- us by 'configConfigurationsFlags')
448 -- flags: The 'FlagAssignment' that the conditionals were
451 -- NB: Why doesn't finalizing a package also tell us what the
452 -- dependencies are (e.g. when we run the naive algorithm,
453 -- we are checking if dependencies are satisfiable)? The
454 -- primary reason is that we may NOT have done any solving:
455 -- if the flags are all chosen for us, this step is a simple
456 -- matter of flattening according to that assignment. It's
457 -- cleaner to then configure the dependencies afterwards.
458 (pkg_descr
:: PackageDescription
,
459 flags
:: FlagAssignment
)
460 <- configureFinalizedPackage verbosity cfg enabled
462 (dependencySatisfiable
463 use_external_internal_deps
464 (fromFlagOrDefault
False (configExactConfiguration cfg
))
465 (packageName pkg_descr0
)
473 debug verbosity
$ "Finalized package description:\n"
474 ++ showPackageDescription pkg_descr
476 let cabalFileDir
= maybe "." takeDirectory
$
477 flagToMaybe
(configCabalFilePath cfg
)
478 checkCompilerProblems verbosity comp pkg_descr enabled
479 checkPackageProblems verbosity cabalFileDir pkg_descr0
480 (updatePackageDescription pbi pkg_descr
)
482 -- The list of 'InstalledPackageInfo' recording the selected
483 -- dependencies on external packages.
485 -- Invariant: For any package name, there is at most one package
486 -- in externalPackageDeps which has that name.
488 -- NB: The dependency selection is global over ALL components
489 -- in the package (similar to how allConstraints and
490 -- requiredDepsMap are global over all components). In particular,
491 -- if *any* component (post-flag resolution) has an unsatisfiable
492 -- dependency, we will fail. This can sometimes be undesirable
493 -- for users, see #1786 (benchmark conflicts with executable),
495 -- In the presence of Backpack, these package dependencies are
496 -- NOT complete: they only ever include the INDEFINITE
497 -- dependencies. After we apply an instantiation, we'll get
498 -- definite references which constitute extra dependencies.
499 -- (Why not have cabal-install pass these in explicitly?
500 -- For one it's deterministic; for two, we need to associate
501 -- them with renamings which would require a far more complicated
502 -- input scheme than what we have today.)
503 externalPkgDeps
:: [PreExistingComponent
]
504 <- configureDependencies
506 use_external_internal_deps
513 -- Compute installation directory templates, based on user
516 -- TODO: Move this into a helper function.
517 defaultDirs
:: InstallDirTemplates
518 <- defaultInstallDirs
' use_external_internal_deps
519 (compilerFlavor comp
)
520 (fromFlag
(configUserInstall cfg
))
522 let installDirs
:: InstallDirTemplates
523 installDirs
= combineInstallDirs fromFlagOrDefault
524 defaultDirs
(configInstallDirs cfg
)
526 -- Check languages and extensions
527 -- TODO: Move this into a helper function.
528 let langlist
= nub $ catMaybes $ map defaultLanguage
529 (enabledBuildInfos pkg_descr enabled
)
530 let langs
= unsupportedLanguages comp langlist
531 when (not (null langs
)) $
532 die
' verbosity
$ "The package " ++ display
(packageId pkg_descr0
)
533 ++ " requires the following languages which are not "
534 ++ "supported by " ++ display
(compilerId comp
) ++ ": "
535 ++ intercalate
", " (map display langs
)
536 let extlist
= nub $ concatMap allExtensions
(enabledBuildInfos pkg_descr enabled
)
537 let exts
= unsupportedExtensions comp extlist
538 when (not (null exts
)) $
539 die
' verbosity
$ "The package " ++ display
(packageId pkg_descr0
)
540 ++ " requires the following language extensions which are not "
541 ++ "supported by " ++ display
(compilerId comp
) ++ ": "
542 ++ intercalate
", " (map display exts
)
544 -- Check foreign library build requirements
545 let flibs
= [flib | CFLib flib
<- enabledComponents pkg_descr enabled
]
546 let unsupportedFLibs
= unsupportedForeignLibs comp compPlatform flibs
547 when (not (null unsupportedFLibs
)) $
548 die
' verbosity
$ "Cannot build some foreign libraries: "
549 ++ intercalate
"," unsupportedFLibs
551 -- Configure certain external build tools, see below for which ones.
552 let requiredBuildTools
= do
553 bi
<- enabledBuildInfos pkg_descr enabled
554 -- First, we collect any tool dep that we know is external. This is,
557 -- 1. `build-tools` entries on the whitelist
559 -- 2. `build-tool-depends` that aren't from the current package.
560 let externBuildToolDeps
=
561 [ LegacyExeDependency
(unUnqualComponentName eName
) versionRange
562 | buildTool
@(ExeDependency _ eName versionRange
)
563 <- getAllToolDependencies pkg_descr bi
564 , not $ isInternal pkg_descr buildTool
]
565 -- Second, we collect any build-tools entry we don't know how to
566 -- desugar. We'll never have any idea how to build them, so we just
567 -- hope they are already on the PATH.
568 let unknownBuildTools
=
570 | buildTool
<- buildTools bi
571 , Nothing
== desugarBuildTool pkg_descr buildTool
]
572 externBuildToolDeps
++ unknownBuildTools
575 configureAllKnownPrograms
(lessVerbose verbosity
) programDb
576 >>= configureRequiredPrograms verbosity requiredBuildTools
578 (pkg_descr
', programDb
'') <-
579 configurePkgconfigPackages verbosity pkg_descr programDb
' enabled
581 -- Compute internal component graph
583 -- The general idea is that we take a look at all the source level
584 -- components (which may build-depends on each other) and form a graph.
585 -- From there, we build a ComponentLocalBuildInfo for each of the
586 -- components, which lets us actually build each component.
587 -- internalPackageSet
588 -- use_external_internal_deps
589 (buildComponents
:: [ComponentLocalBuildInfo
],
590 packageDependsIndex
:: InstalledPackageIndex
) <-
591 runLogProgress verbosity
$ configureComponentLocalBuildInfos
593 use_external_internal_deps
595 (fromFlagOrDefault
False (configDeterministic cfg
))
600 (configConfigurationsFlags cfg
)
601 (configInstantiateWith cfg
)
605 -- Decide if we're going to compile with split sections.
606 split_sections
:: Bool <-
607 if not (fromFlag
$ configSplitSections cfg
)
609 else case compilerFlavor comp
of
610 GHC | compilerVersion comp
>= mkVersion
[8,0]
614 _
-> do warn verbosity
615 ("this compiler does not support " ++
616 "--enable-split-sections; ignoring")
619 -- Decide if we're going to compile with split objects.
620 split_objs
:: Bool <-
621 if not (fromFlag
$ configSplitObjs cfg
)
623 else case compilerFlavor comp
of
626 ("--enable-split-sections and " ++
627 "--enable-split-objs are mutually" ++
628 "exclusive; ignoring the latter")
634 _
-> do warn verbosity
635 ("this compiler does not support " ++
636 "--enable-split-objs; ignoring")
639 let ghciLibByDefault
=
640 case compilerId comp
of
642 -- If ghc is non-dynamic, then ghci needs object files,
643 -- so we build one by default.
645 -- Technically, archive files should be sufficient for ghci,
646 -- but because of GHC bug #8942, it has never been safe to
647 -- rely on them. By the time that bug was fixed, ghci had
648 -- been changed to read shared libraries instead of archive
649 -- files (see next code block).
650 not (GHC
.isDynamic comp
)
651 CompilerId GHCJS _
->
652 not (GHCJS
.isDynamic comp
)
655 let sharedLibsByDefault
656 | fromFlag
(configDynExe cfg
) =
657 -- build a shared library if dynamically-linked
658 -- executables are requested
660 |
otherwise = case compilerId comp
of
662 -- if ghc is dynamic, then ghci needs a shared
663 -- library, so we build one by default.
665 CompilerId GHCJS _
->
669 -- build shared libraries if required by GHC or by the
670 -- executable linking mode, but allow the user to force
671 -- building only static library archives with
673 fromFlagOrDefault sharedLibsByDefault
$ configSharedLib cfg
676 -- build a static library (all dependent libraries rolled
677 -- into a huge .a archive) via GHCs -staticlib flag.
678 fromFlagOrDefault
False $ configStaticLib cfg
680 withDynExe_
= fromFlag
$ configDynExe cfg
681 when (withDynExe_
&& not withSharedLib_
) $ warn verbosity
$
682 "Executables will use dynamic linking, but a shared library "
683 ++ "is not being built. Linking will fail if any executables "
684 ++ "depend on the library."
686 setProfLBI
<- configureProfiling verbosity cfg comp
688 setCoverageLBI
<- configureCoverage verbosity cfg comp
690 let reloc
= fromFlagOrDefault
False $ configRelocatable cfg
692 let buildComponentsMap
=
693 foldl' (\m clbi
-> Map
.insertWith
(++)
694 (componentLocalName clbi
) [clbi
] m
)
695 Map
.empty buildComponents
697 let lbi
= (setCoverageLBI
. setProfLBI
)
700 flagAssignment
= flags
,
701 componentEnabledSpec
= enabled
,
702 extraConfigArgs
= [], -- Currently configure does not
703 -- take extra args, but if it
704 -- did they would go here.
705 installDirTemplates
= installDirs
,
707 hostPlatform
= compPlatform
,
709 cabalFilePath
= flagToMaybe
(configCabalFilePath cfg
),
710 componentGraph
= Graph
.fromDistinctList buildComponents
,
711 componentNameMap
= buildComponentsMap
,
712 installedPkgs
= packageDependsIndex
,
713 pkgDescrFile
= Nothing
,
714 localPkgDescr
= pkg_descr
',
715 withPrograms
= programDb
'',
716 withVanillaLib
= fromFlag
$ configVanillaLib cfg
,
717 withSharedLib
= withSharedLib_
,
718 withStaticLib
= withStaticLib_
,
719 withDynExe
= withDynExe_
,
721 withProfLibDetail
= ProfDetailNone
,
723 withProfExeDetail
= ProfDetailNone
,
724 withOptimization
= fromFlag
$ configOptimization cfg
,
725 withDebugInfo
= fromFlag
$ configDebugInfo cfg
,
726 withGHCiLib
= fromFlagOrDefault ghciLibByDefault
$
728 splitSections
= split_sections
,
729 splitObjs
= split_objs
,
730 stripExes
= fromFlag
$ configStripExes cfg
,
731 stripLibs
= fromFlag
$ configStripLibs cfg
,
734 withPackageDB
= packageDbs
,
735 progPrefix
= fromFlag
$ configProgPrefix cfg
,
736 progSuffix
= fromFlag
$ configProgSuffix cfg
,
740 when reloc
(checkRelocatable verbosity pkg_descr lbi
)
742 -- TODO: This is not entirely correct, because the dirs may vary
743 -- across libraries/executables
744 let dirs
= absoluteInstallDirs pkg_descr lbi NoCopyDest
745 relative
= prefixRelativeInstallDirs
(packageId pkg_descr
) lbi
747 -- PKGROOT: allowing ${pkgroot} to be passed as --prefix to
748 -- cabal configure, is only a hidden option. It allows packages
749 -- to be relocatable with their package database. This however
750 -- breaks when the Paths_* or other includes are used that
751 -- contain hard coded paths. This is still an open TODO.
753 -- Allowing ${pkgroot} here, however requires less custom hooks
754 -- in scripts that *really* want ${pkgroot}. See haskell/cabal/#4872
755 unless (isAbsolute
(prefix dirs
)
756 ||
"${pkgroot}" `
isPrefixOf` prefix dirs
) $ die
' verbosity
$
757 "expected an absolute directory name for --prefix: " ++ prefix dirs
759 when ("${pkgroot}" `
isPrefixOf` prefix dirs
) $
760 warn verbosity
$ "Using ${pkgroot} in prefix " ++ prefix dirs
761 ++ " will not work if you rely on the Path_* module "
762 ++ " or other hard coded paths. Cabal does not yet "
763 ++ " support fully relocatable builds! "
764 ++ " See #462 #2302 #2994 #3305 #3473 #3586 #3909 #4097 #4291 #4872"
766 info verbosity
$ "Using " ++ display currentCabalId
767 ++ " compiled by " ++ display currentCompilerId
768 info verbosity
$ "Using compiler: " ++ showCompilerId comp
769 info verbosity
$ "Using install prefix: " ++ prefix dirs
771 let dirinfo name dir isPrefixRelative
=
772 info verbosity
$ name
++ " installed in: " ++ dir
++ relNote
773 where relNote
= case buildOS
of
774 Windows |
not (hasLibs pkg_descr
)
775 && isNothing isPrefixRelative
776 -> " (fixed location)"
779 dirinfo
"Executables" (bindir dirs
) (bindir relative
)
780 dirinfo
"Libraries" (libdir dirs
) (libdir relative
)
781 dirinfo
"Dynamic Libraries" (dynlibdir dirs
) (dynlibdir relative
)
782 dirinfo
"Private executables" (libexecdir dirs
) (libexecdir relative
)
783 dirinfo
"Data files" (datadir dirs
) (datadir relative
)
784 dirinfo
"Documentation" (docdir dirs
) (docdir relative
)
785 dirinfo
"Configuration files" (sysconfdir dirs
) (sysconfdir relative
)
787 sequence_ [ reportProgram verbosity prog configuredProg
788 |
(prog
, configuredProg
) <- knownPrograms programDb
'' ]
793 verbosity
= fromFlag
(configVerbosity cfg
)
795 mkProgramDb
:: ConfigFlags
-> ProgramDb
-> ProgramDb
796 mkProgramDb cfg initialProgramDb
= programDb
798 programDb
= userSpecifyArgss
(configProgramArgs cfg
)
799 . userSpecifyPaths
(configProgramPaths cfg
)
800 . setProgramSearchPath searchpath
802 searchpath
= getProgramSearchPath initialProgramDb
803 ++ map ProgramSearchPathDir
804 (fromNubList
$ configProgramPathExtra cfg
)
806 -- -----------------------------------------------------------------------------
807 -- Helper functions for configure
809 -- | Check if the user used any deprecated flags.
810 checkDeprecatedFlags
:: Verbosity
-> ConfigFlags
-> IO ()
811 checkDeprecatedFlags verbosity cfg
= do
812 unless (configProfExe cfg
== NoFlag
) $ do
813 let enable | fromFlag
(configProfExe cfg
) = "enable"
814 |
otherwise = "disable"
816 ("The flag --" ++ enable
++ "-executable-profiling is deprecated. "
817 ++ "Please use --" ++ enable
++ "-profiling instead.")
819 unless (configLibCoverage cfg
== NoFlag
) $ do
820 let enable | fromFlag
(configLibCoverage cfg
) = "enable"
821 |
otherwise = "disable"
823 ("The flag --" ++ enable
++ "-library-coverage is deprecated. "
824 ++ "Please use --" ++ enable
++ "-coverage instead.")
826 -- | Sanity check: if '--exact-configuration' was given, ensure that the
827 -- complete flag assignment was specified on the command line.
828 checkExactConfiguration
:: Verbosity
-> GenericPackageDescription
-> ConfigFlags
-> IO ()
829 checkExactConfiguration verbosity pkg_descr0 cfg
=
830 when (fromFlagOrDefault
False (configExactConfiguration cfg
)) $ do
831 let cmdlineFlags
= map fst (unFlagAssignment
(configConfigurationsFlags cfg
))
832 allFlags
= map flagName
. genPackageFlags
$ pkg_descr0
833 diffFlags
= allFlags
\\ cmdlineFlags
834 when (not . null $ diffFlags
) $
835 die
' verbosity
$ "'--exact-configuration' was given, "
836 ++ "but the following flags were not specified: "
837 ++ intercalate
", " (map show diffFlags
)
839 -- | Create a PackageIndex that makes *any libraries that might be*
840 -- defined internally to this package look like installed packages, in
841 -- case an executable should refer to any of them as dependencies.
843 -- It must be *any libraries that might be* defined rather than the
844 -- actual definitions, because these depend on conditionals in the .cabal
845 -- file, and we haven't resolved them yet. finalizePD
846 -- does the resolution of conditionals, and it takes internalPackageSet
847 -- as part of its input.
848 getInternalPackages
:: GenericPackageDescription
849 -> Map PackageName
(Maybe UnqualComponentName
)
850 getInternalPackages pkg_descr0
=
851 -- TODO: some day, executables will be fair game here too!
852 let pkg_descr
= flattenPackageDescription pkg_descr0
853 f lib
= case libName lib
of
854 Nothing
-> (packageName pkg_descr
, Nothing
)
855 Just n
' -> (unqualComponentNameToPackageName n
', Just n
')
856 in Map
.fromList
(map f
(allLibraries pkg_descr
))
858 -- | Returns true if a dependency is satisfiable. This function may
859 -- report a dependency satisfiable even when it is not, but not vice
860 -- versa. This is to be passed to finalizePD.
861 dependencySatisfiable
862 :: Bool -- ^ use external internal deps?
863 -> Bool -- ^ exact configuration?
865 -> InstalledPackageIndex
-- ^ installed set
866 -> Map PackageName
(Maybe UnqualComponentName
) -- ^ internal set
867 -> Map PackageName InstalledPackageInfo
-- ^ required dependencies
868 -> (Dependency
-> Bool)
869 dependencySatisfiable
870 use_external_internal_deps
871 exact_config pn installedPackageSet internalPackageSet requiredDepsMap
872 d
@(Dependency depName vr
)
875 -- When we're given '--exact-configuration', we assume that all
876 -- dependencies and flags are exactly specified on the command
877 -- line. Thus we only consult the 'requiredDepsMap'. Note that
878 -- we're not doing the version range check, so if there's some
879 -- dependency that wasn't specified on the command line,
880 -- 'finalizePD' will fail.
881 -- TODO: mention '--exact-configuration' in the error message
883 = if isInternalDep
&& not use_external_internal_deps
884 -- Except for internal deps, when we're NOT per-component mode;
885 -- those are just True.
887 else depName `Map
.member` requiredDepsMap
890 = if use_external_internal_deps
891 -- When we are doing per-component configure, we now need to
892 -- test if the internal dependency is in the index. This has
893 -- DIFFERENT semantics from normal dependency satisfiability.
894 then internalDepSatisfiable
895 -- If a 'PackageName' is defined by an internal component, the dep is
896 -- satisfiable (we're going to build it ourselves)
903 isInternalDep
= Map
.member depName internalPackageSet
906 not . null $ PackageIndex
.lookupDependency installedPackageSet d
908 internalDepSatisfiable
=
909 not . null $ PackageIndex
.lookupInternalDependency
910 installedPackageSet
(Dependency pn vr
) cn
915 -- Reinterpret the "package name" as an unqualified component
917 = Just
(mkUnqualComponentName
(unPackageName depName
))
919 -- | Finalize a generic package description. The workhorse is
920 -- 'finalizePD' but there's a bit of other nattering
923 -- TODO: what exactly is the business with @flaggedTests@ and
924 -- @flaggedBenchmarks@?
925 configureFinalizedPackage
928 -> ComponentRequestedSpec
930 -> (Dependency
-> Bool) -- ^ tests if a dependency is satisfiable.
931 -- Might say it's satisfiable even when not.
934 -> GenericPackageDescription
935 -> IO (PackageDescription
, FlagAssignment
)
936 configureFinalizedPackage verbosity cfg enabled
937 allConstraints satisfies comp compPlatform pkg_descr0
= do
939 (pkg_descr0
', flags
) <-
941 (configConfigurationsFlags cfg
)
948 of Right r
-> return r
950 die
' verbosity
$ "Encountered missing dependencies:\n"
951 ++ (render
. nest
4 . sep
. punctuate comma
952 . map (disp
. simplifyDependency
)
955 -- add extra include/lib dirs as specified in cfg
956 -- we do it here so that those get checked too
957 let pkg_descr
= addExtraIncludeLibDirs pkg_descr0
'
959 unless (nullFlagAssignment flags
) $
960 info verbosity
$ "Flags chosen: "
961 ++ intercalate
", " [ unFlagName fn
++ "=" ++ display
value
962 |
(fn
, value) <- unFlagAssignment flags
]
964 return (pkg_descr
, flags
)
966 addExtraIncludeLibDirs pkg_descr
=
967 let extraBi
= mempty
{ extraLibDirs
= configExtraLibDirs cfg
968 , extraFrameworkDirs
= configExtraFrameworkDirs cfg
969 , PD
.includeDirs
= configExtraIncludeDirs cfg
}
970 modifyLib l
= l
{ libBuildInfo
= libBuildInfo l
972 modifyExecutable e
= e
{ buildInfo
= buildInfo e
974 modifyForeignLib f
= f
{ foreignLibBuildInfo
= foreignLibBuildInfo f
976 modifyTestsuite t
= t
{ testBuildInfo
= testBuildInfo t
978 modifyBenchmark b
= b
{ benchmarkBuildInfo
= benchmarkBuildInfo b
981 { library
= modifyLib `
fmap` library pkg_descr
982 , subLibraries
= modifyLib `
map` subLibraries pkg_descr
983 , executables
= modifyExecutable `
map` executables pkg_descr
984 , foreignLibs
= modifyForeignLib `
map` foreignLibs pkg_descr
985 , testSuites
= modifyTestsuite `
map` testSuites pkg_descr
986 , benchmarks
= modifyBenchmark `
map` benchmarks pkg_descr
989 -- | Check for use of Cabal features which require compiler support
990 checkCompilerProblems
:: Verbosity
-> Compiler
-> PackageDescription
-> ComponentRequestedSpec
-> IO ()
991 checkCompilerProblems verbosity comp pkg_descr enabled
= do
992 unless (renamingPackageFlagsSupported comp ||
993 all (all (isDefaultIncludeRenaming
. mixinIncludeRenaming
) . mixins
)
994 (enabledBuildInfos pkg_descr enabled
)) $
995 die
' verbosity
$ "Your compiler does not support thinning and renaming on "
996 ++ "package flags. To use this feature you must use "
997 ++ "GHC 7.9 or later."
999 when (any (not.null.PD
.reexportedModules
) (PD
.allLibraries pkg_descr
)
1000 && not (reexportedModulesSupported comp
)) $
1001 die
' verbosity
$ "Your compiler does not support module re-exports. To use "
1002 ++ "this feature you must use GHC 7.9 or later."
1004 when (any (not.null.PD
.signatures
) (PD
.allLibraries pkg_descr
)
1005 && not (backpackSupported comp
)) $
1006 die
' verbosity
$ "Your compiler does not support Backpack. To use "
1007 ++ "this feature you must use GHC 8.1 or later."
1009 -- | Select dependencies for the package.
1010 configureDependencies
1012 -> UseExternalInternalDeps
1013 -> Map PackageName
(Maybe UnqualComponentName
) -- ^ internal packages
1014 -> InstalledPackageIndex
-- ^ installed packages
1015 -> Map PackageName InstalledPackageInfo
-- ^ required deps
1016 -> PackageDescription
1017 -> ComponentRequestedSpec
1018 -> IO [PreExistingComponent
]
1019 configureDependencies verbosity use_external_internal_deps
1020 internalPackageSet installedPackageSet requiredDepsMap pkg_descr enableSpec
= do
1021 let failedDeps
:: [FailedDependency
]
1022 allPkgDeps
:: [ResolvedDependency
]
1023 (failedDeps
, allPkgDeps
) = partitionEithers
1024 [ (\s
-> (dep
, s
)) <$> status
1025 | dep
<- enabledBuildDepends pkg_descr enableSpec
1026 , let status
= selectDependency
(package pkg_descr
)
1027 internalPackageSet installedPackageSet
1028 requiredDepsMap use_external_internal_deps dep
]
1030 internalPkgDeps
= [ pkgid
1031 |
(_
, InternalDependency pkgid
) <- allPkgDeps
]
1032 -- NB: we have to SAVE the package name, because this is the only
1033 -- way we can be able to resolve package names in the package
1035 externalPkgDeps
= [ pec
1036 |
(_
, ExternalDependency pec
) <- allPkgDeps
]
1038 when (not (null internalPkgDeps
)
1039 && not (newPackageDepsBehaviour pkg_descr
)) $
1040 die
' verbosity
$ "The field 'build-depends: "
1041 ++ intercalate
", " (map (display
. packageName
) internalPkgDeps
)
1042 ++ "' refers to a library which is defined within the same "
1043 ++ "package. To use this feature the package must specify at "
1044 ++ "least 'cabal-version: >= 1.8'."
1046 reportFailedDependencies verbosity failedDeps
1047 reportSelectedDependencies verbosity allPkgDeps
1049 return externalPkgDeps
1051 -- | Select and apply coverage settings for the build based on the
1052 -- 'ConfigFlags' and 'Compiler'.
1053 configureCoverage
:: Verbosity
-> ConfigFlags
-> Compiler
1054 -> IO (LocalBuildInfo
-> LocalBuildInfo
)
1055 configureCoverage verbosity cfg comp
= do
1056 let tryExeCoverage
= fromFlagOrDefault
False (configCoverage cfg
)
1057 tryLibCoverage
= fromFlagOrDefault tryExeCoverage
1058 (mappend
(configCoverage cfg
) (configLibCoverage cfg
))
1059 if coverageSupported comp
1061 let apply lbi
= lbi
{ libCoverage
= tryLibCoverage
1062 , exeCoverage
= tryExeCoverage
1066 let apply lbi
= lbi
{ libCoverage
= False
1067 , exeCoverage
= False
1069 when (tryExeCoverage || tryLibCoverage
) $ warn verbosity
1070 ("The compiler " ++ showCompilerId comp
++ " does not support "
1071 ++ "program coverage. Program coverage has been disabled.")
1074 -- | Compute the effective value of the profiling flags
1075 -- @--enable-library-profiling@ and @--enable-executable-profiling@
1076 -- from the specified 'ConfigFlags'. This may be useful for
1077 -- external Cabal tools which need to interact with Setup in
1078 -- a backwards-compatible way: the most predictable mechanism
1079 -- for enabling profiling across many legacy versions is to
1080 -- NOT use @--enable-profiling@ and use those two flags instead.
1082 -- Note that @--enable-executable-profiling@ also affects profiling
1083 -- of benchmarks and (non-detailed) test suites.
1084 computeEffectiveProfiling
:: ConfigFlags
-> (Bool {- lib -}, Bool {- exe -})
1085 computeEffectiveProfiling cfg
=
1086 -- The --profiling flag sets the default for both libs and exes,
1087 -- but can be overidden by --library-profiling, or the old deprecated
1088 -- --executable-profiling flag.
1090 -- The --profiling-detail and --library-profiling-detail flags behave
1092 let tryExeProfiling
= fromFlagOrDefault
False
1093 (mappend
(configProf cfg
) (configProfExe cfg
))
1094 tryLibProfiling
= fromFlagOrDefault tryExeProfiling
1095 (mappend
(configProf cfg
) (configProfLib cfg
))
1096 in (tryLibProfiling
, tryExeProfiling
)
1098 -- | Select and apply profiling settings for the build based on the
1099 -- 'ConfigFlags' and 'Compiler'.
1100 configureProfiling
:: Verbosity
-> ConfigFlags
-> Compiler
1101 -> IO (LocalBuildInfo
-> LocalBuildInfo
)
1102 configureProfiling verbosity cfg comp
= do
1103 let (tryLibProfiling
, tryExeProfiling
) = computeEffectiveProfiling cfg
1105 tryExeProfileLevel
= fromFlagOrDefault ProfDetailDefault
1106 (configProfDetail cfg
)
1107 tryLibProfileLevel
= fromFlagOrDefault ProfDetailDefault
1109 (configProfDetail cfg
)
1110 (configProfLibDetail cfg
))
1112 checkProfileLevel
(ProfDetailOther other
) = do
1114 ("Unknown profiling detail level '" ++ other
1115 ++ "', using default.\nThe profiling detail levels are: "
1117 [ name |
(name
, _
, _
) <- knownProfDetailLevels
])
1118 return ProfDetailDefault
1119 checkProfileLevel other
= return other
1121 (exeProfWithoutLibProf
, applyProfiling
) <-
1122 if profilingSupported comp
1124 exeLevel
<- checkProfileLevel tryExeProfileLevel
1125 libLevel
<- checkProfileLevel tryLibProfileLevel
1126 let apply lbi
= lbi
{ withProfLib
= tryLibProfiling
1127 , withProfLibDetail
= libLevel
1128 , withProfExe
= tryExeProfiling
1129 , withProfExeDetail
= exeLevel
1131 return (tryExeProfiling
&& not tryLibProfiling
, apply
)
1133 let apply lbi
= lbi
{ withProfLib
= False
1134 , withProfLibDetail
= ProfDetailNone
1135 , withProfExe
= False
1136 , withProfExeDetail
= ProfDetailNone
1138 when (tryExeProfiling || tryLibProfiling
) $ warn verbosity
1139 ("The compiler " ++ showCompilerId comp
++ " does not support "
1140 ++ "profiling. Profiling has been disabled.")
1141 return (False, apply
)
1143 when exeProfWithoutLibProf
$ warn verbosity
1144 ("Executables will be built with profiling, but library "
1145 ++ "profiling is disabled. Linking will fail if any executables "
1146 ++ "depend on the library.")
1148 return applyProfiling
1150 -- -----------------------------------------------------------------------------
1151 -- Configuring package dependencies
1153 reportProgram
:: Verbosity
-> Program
-> Maybe ConfiguredProgram
-> IO ()
1154 reportProgram verbosity prog Nothing
1155 = info verbosity
$ "No " ++ programName prog
++ " found"
1156 reportProgram verbosity prog
(Just configuredProg
)
1157 = info verbosity
$ "Using " ++ programName prog
++ version
++ location
1158 where location
= case programLocation configuredProg
of
1159 FoundOnSystem p
-> " found on system at: " ++ p
1160 UserSpecified p
-> " given by user at: " ++ p
1161 version
= case programVersion configuredProg
of
1163 Just v
-> " version " ++ display v
1165 hackageUrl
:: String
1166 hackageUrl
= "http://hackage.haskell.org/package/"
1168 type ResolvedDependency
= (Dependency
, DependencyResolution
)
1170 data DependencyResolution
1171 -- | An external dependency from the package database, OR an
1172 -- internal dependency which we are getting from the package
1174 = ExternalDependency PreExistingComponent
1175 -- | An internal dependency ('PackageId' should be a library name)
1176 -- which we are going to have to build. (The
1177 -- 'PackageId' here is a hack to get a modest amount of
1178 -- polymorphism out of the 'Package' typeclass.)
1179 | InternalDependency PackageId
1181 data FailedDependency
= DependencyNotExists PackageName
1182 | DependencyMissingInternal PackageName PackageName
1183 | DependencyNoVersion Dependency
1185 -- | Test for a package dependency and record the version we have installed.
1186 selectDependency
:: PackageId
-- ^ Package id of current package
1187 -> Map PackageName
(Maybe UnqualComponentName
)
1188 -> InstalledPackageIndex
-- ^ Installed packages
1189 -> Map PackageName InstalledPackageInfo
1190 -- ^ Packages for which we have been given specific deps to
1192 -> UseExternalInternalDeps
-- ^ Are we configuring a
1193 -- single component?
1195 -> Either FailedDependency DependencyResolution
1196 selectDependency pkgid internalIndex installedIndex requiredDepsMap
1197 use_external_internal_deps
1198 dep
@(Dependency dep_pkgname vr
) =
1199 -- If the dependency specification matches anything in the internal package
1200 -- index, then we prefer that match to anything in the second.
1207 -- Executable my-exec
1208 -- build-depends: MyLibrary
1210 -- We want "build-depends: MyLibrary" always to match the internal library
1211 -- even if there is a newer installed library "MyLibrary-0.2".
1212 case Map
.lookup dep_pkgname internalIndex
of
1213 Just cname
-> if use_external_internal_deps
1214 then do_external
(Just cname
)
1216 _
-> do_external Nothing
1219 -- It's an internal library, and we're not per-component build
1220 do_internal
= Right
$ InternalDependency
1221 $ PackageIdentifier dep_pkgname
$ packageVersion pkgid
1223 -- We have to look it up externally
1224 do_external is_internal
= do
1225 ipi
<- case Map
.lookup dep_pkgname requiredDepsMap
of
1226 -- If we know the exact pkg to use, then use it.
1227 Just pkginstance
-> Right pkginstance
1228 -- Otherwise we just pick an arbitrary instance of the latest version.
1231 Nothing
-> do_external_external
1232 Just mb_uqn
-> do_external_internal mb_uqn
1233 return $ ExternalDependency
$ ipiToPreExistingComponent ipi
1235 -- It's an external package, normal situation
1236 do_external_external
=
1237 case PackageIndex
.lookupDependency installedIndex dep
of
1238 [] -> Left
(DependencyNotExists dep_pkgname
)
1239 pkgs
-> Right
$ head $ snd $ last pkgs
1241 -- It's an internal library, being looked up externally
1242 do_external_internal mb_uqn
=
1243 case PackageIndex
.lookupInternalDependency installedIndex
1244 (Dependency
(packageName pkgid
) vr
) mb_uqn
of
1245 [] -> Left
(DependencyMissingInternal dep_pkgname
(packageName pkgid
))
1246 pkgs
-> Right
$ head $ snd $ last pkgs
1248 reportSelectedDependencies
:: Verbosity
1249 -> [ResolvedDependency
] -> IO ()
1250 reportSelectedDependencies verbosity deps
=
1251 info verbosity
$ unlines
1252 [ "Dependency " ++ display
(simplifyDependency dep
)
1253 ++ ": using " ++ display pkgid
1254 |
(dep
, resolution
) <- deps
1255 , let pkgid
= case resolution
of
1256 ExternalDependency pkg
' -> packageId pkg
'
1257 InternalDependency pkgid
' -> pkgid
' ]
1259 reportFailedDependencies
:: Verbosity
-> [FailedDependency
] -> IO ()
1260 reportFailedDependencies _
[] = return ()
1261 reportFailedDependencies verbosity failed
=
1262 die
' verbosity
(intercalate
"\n\n" (map reportFailedDependency failed
))
1265 reportFailedDependency
(DependencyNotExists pkgname
) =
1266 "there is no version of " ++ display pkgname
++ " installed.\n"
1267 ++ "Perhaps you need to download and install it from\n"
1268 ++ hackageUrl
++ display pkgname
++ "?"
1270 reportFailedDependency
(DependencyMissingInternal pkgname real_pkgname
) =
1271 "internal dependency " ++ display pkgname
++ " not installed.\n"
1272 ++ "Perhaps you need to configure and install it first?\n"
1273 ++ "(This library was defined by " ++ display real_pkgname
++ ")"
1275 reportFailedDependency
(DependencyNoVersion dep
) =
1276 "cannot satisfy dependency " ++ display
(simplifyDependency dep
) ++ "\n"
1278 -- | List all installed packages in the given package databases.
1279 getInstalledPackages
:: Verbosity
-> Compiler
1280 -> PackageDBStack
-- ^ The stack of package databases.
1282 -> IO InstalledPackageIndex
1283 getInstalledPackages verbosity comp packageDBs progdb
= do
1284 when (null packageDBs
) $
1285 die
' verbosity
$ "No package databases have been specified. If you use "
1286 ++ "--package-db=clear, you must follow it with --package-db= "
1287 ++ "with 'global', 'user' or a specific file."
1289 info verbosity
"Reading installed packages..."
1290 case compilerFlavor comp
of
1291 GHC
-> GHC
.getInstalledPackages verbosity comp packageDBs progdb
1292 GHCJS
-> GHCJS
.getInstalledPackages verbosity packageDBs progdb
1293 UHC
-> UHC
.getInstalledPackages verbosity comp packageDBs progdb
1295 HaskellSuite
.getInstalledPackages verbosity packageDBs progdb
1296 flv
-> die
' verbosity
$ "don't know how to find the installed packages for "
1299 -- | Like 'getInstalledPackages', but for a single package DB.
1301 -- NB: Why isn't this always a fall through to 'getInstalledPackages'?
1302 -- That is because 'getInstalledPackages' performs some sanity checks
1303 -- on the package database stack in question. However, when sandboxes
1304 -- are involved these sanity checks are not desirable.
1305 getPackageDBContents
:: Verbosity
-> Compiler
1306 -> PackageDB
-> ProgramDb
1307 -> IO InstalledPackageIndex
1308 getPackageDBContents verbosity comp packageDB progdb
= do
1309 info verbosity
"Reading installed packages..."
1310 case compilerFlavor comp
of
1311 GHC
-> GHC
.getPackageDBContents verbosity packageDB progdb
1312 GHCJS
-> GHCJS
.getPackageDBContents verbosity packageDB progdb
1313 -- For other compilers, try to fall back on 'getInstalledPackages'.
1314 _
-> getInstalledPackages verbosity comp
[packageDB
] progdb
1317 -- | A set of files (or directories) that can be monitored to detect when
1318 -- there might have been a change in the installed packages.
1320 getInstalledPackagesMonitorFiles
:: Verbosity
-> Compiler
1322 -> ProgramDb
-> Platform
1324 getInstalledPackagesMonitorFiles verbosity comp packageDBs progdb platform
=
1325 case compilerFlavor comp
of
1326 GHC
-> GHC
.getInstalledPackagesMonitorFiles
1327 verbosity platform progdb packageDBs
1329 warn verbosity
$ "don't know how to find change monitoring files for "
1330 ++ "the installed package databases for " ++ display other
1333 -- | The user interface specifies the package dbs to use with a combination of
1334 -- @--global@, @--user@ and @--package-db=global|user|clear|$file@.
1335 -- This function combines the global/user flag and interprets the package-db
1336 -- flag into a single package db stack.
1338 interpretPackageDbFlags
:: Bool -> [Maybe PackageDB
] -> PackageDBStack
1339 interpretPackageDbFlags userInstall specificDBs
=
1340 extra initialStack specificDBs
1342 initialStack | userInstall
= [GlobalPackageDB
, UserPackageDB
]
1343 |
otherwise = [GlobalPackageDB
]
1345 extra dbs
' [] = dbs
'
1346 extra _
(Nothing
:dbs
) = extra
[] dbs
1347 extra dbs
' (Just db
:dbs
) = extra
(dbs
' ++ [db
]) dbs
1349 -- We are given both --constraint="foo < 2.0" style constraints and also
1350 -- specific packages to pick via --dependency="foo=foo-2.0-177d5cdf20962d0581".
1352 -- When finalising the package we have to take into account the specific
1353 -- installed deps we've been given, and the finalise function expects
1354 -- constraints, so we have to translate these deps into version constraints.
1356 -- But after finalising we then have to make sure we pick the right specific
1357 -- deps in the end. So we still need to remember which installed packages to
1359 combinedConstraints
:: [Dependency
] ->
1360 [(PackageName
, ComponentId
)] ->
1361 InstalledPackageIndex
->
1362 Either String ([Dependency
],
1363 Map PackageName InstalledPackageInfo
)
1364 combinedConstraints constraints dependencies installedPackages
= do
1366 when (not (null badComponentIds
)) $
1367 Left
$ render
$ text
"The following package dependencies were requested"
1368 $+$ nest
4 (dispDependencies badComponentIds
)
1369 $+$ text
"however the given installed package instance does not exist."
1371 --TODO: we don't check that all dependencies are used!
1373 return (allConstraints
, idConstraintMap
)
1376 allConstraints
:: [Dependency
]
1377 allConstraints
= constraints
1378 ++ [ thisPackageVersion
(packageId pkg
)
1379 |
(_
, _
, Just pkg
) <- dependenciesPkgInfo
]
1381 idConstraintMap
:: Map PackageName InstalledPackageInfo
1382 idConstraintMap
= Map
.fromList
1383 -- NB: do NOT use the packageName from
1384 -- dependenciesPkgInfo!
1386 |
(pn
, _
, Just pkg
) <- dependenciesPkgInfo
]
1388 -- The dependencies along with the installed package info, if it exists
1389 dependenciesPkgInfo
:: [(PackageName
, ComponentId
,
1390 Maybe InstalledPackageInfo
)]
1391 dependenciesPkgInfo
=
1392 [ (pkgname
, cid
, mpkg
)
1393 |
(pkgname
, cid
) <- dependencies
1394 , let mpkg
= PackageIndex
.lookupComponentId
1395 installedPackages cid
1398 -- If we looked up a package specified by an installed package id
1399 -- (i.e. someone has written a hash) and didn't find it then it's
1403 |
(pkgname
, cid
, Nothing
) <- dependenciesPkgInfo
]
1405 dispDependencies deps
=
1406 hsep
[ text
"--dependency="
1407 <<>> quotes
(disp pkgname
<<>> char
'=' <<>> disp cid
)
1408 |
(pkgname
, cid
) <- deps
]
1410 -- -----------------------------------------------------------------------------
1411 -- Configuring program dependencies
1413 configureRequiredPrograms
:: Verbosity
-> [LegacyExeDependency
] -> ProgramDb
1415 configureRequiredPrograms verbosity deps progdb
=
1416 foldM (configureRequiredProgram verbosity
) progdb deps
1418 -- | Configure a required program, ensuring that it exists in the PATH
1419 -- (or where the user has specified the program must live) and making it
1420 -- available for use via the 'ProgramDb' interface. If the program is
1421 -- known (exists in the input 'ProgramDb'), we will make sure that the
1422 -- program matches the required version; otherwise we will accept
1423 -- any version of the program and assume that it is a simpleProgram.
1424 configureRequiredProgram
:: Verbosity
-> ProgramDb
-> LegacyExeDependency
1426 configureRequiredProgram verbosity progdb
1427 (LegacyExeDependency progName verRange
) =
1428 case lookupKnownProgram progName progdb
of
1430 -- Try to configure it as a 'simpleProgram' automatically
1432 -- There's a bit of a story behind this line. In old versions
1433 -- of Cabal, there were only internal build-tools dependencies. So the
1434 -- behavior in this case was:
1436 -- - If a build-tool dependency was internal, don't do
1439 -- - If it was external, call 'configureRequiredProgram' to
1440 -- "configure" the executable. In particular, if
1441 -- the program was not "known" (present in 'ProgramDb'),
1442 -- then we would just error. This was fine, because
1443 -- the only way a program could be executed from 'ProgramDb'
1444 -- is if some library code from Cabal actually called it,
1445 -- and the pre-existing Cabal code only calls known
1446 -- programs from 'defaultProgramDb', and so if it
1447 -- is calling something else, you have a Custom setup
1448 -- script, and in that case you are expected to register
1449 -- the program you want to call in the ProgramDb.
1451 -- OK, so that was fine, until I (ezyang, in 2016) refactored
1452 -- Cabal to support per-component builds. In this case, what
1453 -- was previously an internal build-tool dependency now became
1454 -- an external one, and now previously "internal" dependencies
1455 -- are now external. But these are permitted to exist even
1456 -- when they are not previously configured (something that
1457 -- can only occur by a Custom script.)
1459 -- So, I decided, "Fine, let's just accept these in any
1460 -- case." Thus this line. The alternative would have been to
1461 -- somehow detect when a build-tools dependency was "internal" (by
1462 -- looking at the unflattened package description) but this
1463 -- would also be incompatible with future work to support
1464 -- external executable dependencies: we definitely cannot
1465 -- assume they will be preinitialized in the 'ProgramDb'.
1466 configureProgram verbosity
(simpleProgram progName
) progdb
1468 -- requireProgramVersion always requires the program have a version
1469 -- but if the user says "build-depends: foo" ie no version constraint
1470 -- then we should not fail if we cannot discover the program version.
1471 | verRange
== anyVersion
-> do
1472 (_
, progdb
') <- requireProgram verbosity prog progdb
1475 (_
, _
, progdb
') <- requireProgramVersion verbosity prog verRange progdb
1478 -- -----------------------------------------------------------------------------
1479 -- Configuring pkg-config package dependencies
1481 configurePkgconfigPackages
:: Verbosity
-> PackageDescription
1482 -> ProgramDb
-> ComponentRequestedSpec
1483 -> IO (PackageDescription
, ProgramDb
)
1484 configurePkgconfigPackages verbosity pkg_descr progdb enabled
1485 |
null allpkgs
= return (pkg_descr
, progdb
)
1487 (_
, _
, progdb
') <- requireProgramVersion
1488 (lessVerbose verbosity
) pkgConfigProgram
1489 (orLaterVersion
$ mkVersion
[0,9,0]) progdb
1490 traverse_ requirePkg allpkgs
1491 mlib
' <- traverse addPkgConfigBILib
(library pkg_descr
)
1492 libs
' <- traverse addPkgConfigBILib
(subLibraries pkg_descr
)
1493 exes
' <- traverse addPkgConfigBIExe
(executables pkg_descr
)
1494 tests
' <- traverse addPkgConfigBITest
(testSuites pkg_descr
)
1495 benches
' <- traverse addPkgConfigBIBench
(benchmarks pkg_descr
)
1496 let pkg_descr
' = pkg_descr
{ library
= mlib
',
1497 subLibraries
= libs
', executables
= exes
',
1498 testSuites
= tests
', benchmarks
= benches
' }
1499 return (pkg_descr
', progdb
')
1502 allpkgs
= concatMap pkgconfigDepends
(enabledBuildInfos pkg_descr enabled
)
1503 pkgconfig
= getDbProgramOutput
(lessVerbose verbosity
)
1504 pkgConfigProgram progdb
1506 requirePkg dep
@(PkgconfigDependency pkgn
range) = do
1507 version
<- pkgconfig
["--modversion", pkg
]
1508 `catchIO`
(\_
-> die
' verbosity notFound
)
1509 `catchExit`
(\_
-> die
' verbosity notFound
)
1510 case simpleParse version
of
1511 Nothing
-> die
' verbosity
"parsing output of pkg-config --modversion failed"
1512 Just v |
not (withinRange v
range) -> die
' verbosity
(badVersion v
)
1513 |
otherwise -> info verbosity
(depSatisfied v
)
1515 notFound
= "The pkg-config package '" ++ pkg
++ "'"
1516 ++ versionRequirement
1517 ++ " is required but it could not be found."
1518 badVersion v
= "The pkg-config package '" ++ pkg
++ "'"
1519 ++ versionRequirement
1520 ++ " is required but the version installed on the"
1521 ++ " system is version " ++ display v
1522 depSatisfied v
= "Dependency " ++ display dep
1523 ++ ": using version " ++ display v
1526 | isAnyVersion
range = ""
1527 |
otherwise = " version " ++ display
range
1529 pkg
= unPkgconfigName pkgn
1531 -- Adds pkgconfig dependencies to the build info for a component
1532 addPkgConfigBI compBI setCompBI comp
= do
1533 bi
<- pkgconfigBuildInfo
(pkgconfigDepends
(compBI comp
))
1534 return $ setCompBI comp
(compBI comp `mappend` bi
)
1536 -- Adds pkgconfig dependencies to the build info for a library
1537 addPkgConfigBILib
= addPkgConfigBI libBuildInfo
$
1538 \lib bi
-> lib
{ libBuildInfo
= bi
}
1540 -- Adds pkgconfig dependencies to the build info for an executable
1541 addPkgConfigBIExe
= addPkgConfigBI buildInfo
$
1542 \exe bi
-> exe
{ buildInfo
= bi
}
1544 -- Adds pkgconfig dependencies to the build info for a test suite
1545 addPkgConfigBITest
= addPkgConfigBI testBuildInfo
$
1546 \test bi
-> test
{ testBuildInfo
= bi
}
1548 -- Adds pkgconfig dependencies to the build info for a benchmark
1549 addPkgConfigBIBench
= addPkgConfigBI benchmarkBuildInfo
$
1550 \bench bi
-> bench
{ benchmarkBuildInfo
= bi
}
1552 pkgconfigBuildInfo
:: [PkgconfigDependency
] -> NoCallStackIO BuildInfo
1553 pkgconfigBuildInfo
[] = return mempty
1554 pkgconfigBuildInfo pkgdeps
= do
1555 let pkgs
= nub [ display pkg | PkgconfigDependency pkg _
<- pkgdeps
]
1556 ccflags
<- pkgconfig
("--cflags" : pkgs
)
1557 ldflags
<- pkgconfig
("--libs" : pkgs
)
1558 return (ccLdOptionsBuildInfo
(words ccflags
) (words ldflags
))
1560 -- | Makes a 'BuildInfo' from C compiler and linker flags.
1562 -- This can be used with the output from configuration programs like pkg-config
1563 -- and similar package-specific programs like mysql-config, freealut-config etc.
1566 -- > ccflags <- getDbProgramOutput verbosity prog progdb ["--cflags"]
1567 -- > ldflags <- getDbProgramOutput verbosity prog progdb ["--libs"]
1568 -- > return (ccldOptionsBuildInfo (words ccflags) (words ldflags))
1570 ccLdOptionsBuildInfo
:: [String] -> [String] -> BuildInfo
1571 ccLdOptionsBuildInfo cflags ldflags
=
1572 let (includeDirs
', cflags
') = partition ("-I" `
isPrefixOf`
) cflags
1573 (extraLibs
', ldflags
') = partition ("-l" `
isPrefixOf`
) ldflags
1574 (extraLibDirs
', ldflags
'') = partition ("-L" `
isPrefixOf`
) ldflags
'
1576 PD
.includeDirs
= map (drop 2) includeDirs
',
1577 PD
.extraLibs
= map (drop 2) extraLibs
',
1578 PD
.extraLibDirs
= map (drop 2) extraLibDirs
',
1579 PD
.ccOptions
= cflags
',
1580 PD
.ldOptions
= ldflags
''
1583 -- -----------------------------------------------------------------------------
1584 -- Determining the compiler details
1586 configCompilerAuxEx
:: ConfigFlags
1587 -> IO (Compiler
, Platform
, ProgramDb
)
1588 configCompilerAuxEx cfg
= configCompilerEx
(flagToMaybe
$ configHcFlavor cfg
)
1589 (flagToMaybe
$ configHcPath cfg
)
1590 (flagToMaybe
$ configHcPkg cfg
)
1592 (fromFlag
(configVerbosity cfg
))
1594 programDb
= mkProgramDb cfg defaultProgramDb
1596 configCompilerEx
:: Maybe CompilerFlavor
-> Maybe FilePath -> Maybe FilePath
1597 -> ProgramDb
-> Verbosity
1598 -> IO (Compiler
, Platform
, ProgramDb
)
1599 configCompilerEx Nothing _ _ _ verbosity
= die
' verbosity
"Unknown compiler"
1600 configCompilerEx
(Just hcFlavor
) hcPath hcPkg progdb verbosity
= do
1601 (comp
, maybePlatform
, programDb
) <- case hcFlavor
of
1602 GHC
-> GHC
.configure verbosity hcPath hcPkg progdb
1603 GHCJS
-> GHCJS
.configure verbosity hcPath hcPkg progdb
1604 UHC
-> UHC
.configure verbosity hcPath hcPkg progdb
1605 HaskellSuite
{} -> HaskellSuite
.configure verbosity hcPath hcPkg progdb
1606 _
-> die
' verbosity
"Unknown compiler"
1607 return (comp
, fromMaybe buildPlatform maybePlatform
, programDb
)
1609 -- Ideally we would like to not have separate configCompiler* and
1610 -- configCompiler*Ex sets of functions, but there are many custom setup scripts
1611 -- in the wild that are using them, so the versions with old types are kept for
1612 -- backwards compatibility. Platform was added to the return triple in 1.18.
1614 {-# DEPRECATED configCompiler
1615 "'configCompiler' is deprecated. Use 'configCompilerEx' instead." #-}
1616 configCompiler
:: Maybe CompilerFlavor
-> Maybe FilePath -> Maybe FilePath
1617 -> ProgramDb
-> Verbosity
1618 -> IO (Compiler
, ProgramDb
)
1619 configCompiler mFlavor hcPath hcPkg progdb verbosity
=
1620 fmap (\(a
,_
,b
) -> (a
,b
)) $ configCompilerEx mFlavor hcPath hcPkg progdb verbosity
1622 {-# DEPRECATED configCompilerAux
1623 "configCompilerAux is deprecated. Use 'configCompilerAuxEx' instead." #-}
1624 configCompilerAux
:: ConfigFlags
1625 -> IO (Compiler
, ProgramDb
)
1626 configCompilerAux
= fmap (\(a
,_
,b
) -> (a
,b
)) . configCompilerAuxEx
1628 -- -----------------------------------------------------------------------------
1629 -- Testing C lib and header dependencies
1631 -- Try to build a test C program which includes every header and links every
1632 -- lib. If that fails, try to narrow it down by preprocessing (only) and linking
1633 -- with individual headers and libs. If none is the obvious culprit then give a
1634 -- generic error message.
1635 -- TODO: produce a log file from the compiler errors, if any.
1636 checkForeignDeps
:: PackageDescription
-> LocalBuildInfo
-> Verbosity
-> IO ()
1637 checkForeignDeps pkg lbi verbosity
=
1638 ifBuildsWith allHeaders
(commonCcArgs
++ makeLdArgs allLibs
) -- I'm feeling
1641 (do missingLibs
<- findMissingLibs
1642 missingHdr
<- findOffendingHdr
1643 explainErrors missingHdr missingLibs
)
1645 allHeaders
= collectField PD
.includes
1646 allLibs
= collectField PD
.extraLibs
1648 ifBuildsWith headers args success failure
= do
1649 checkDuplicateHeaders
1650 ok
<- builds
(makeProgram headers
) args
1651 if ok
then success
else failure
1653 -- Ensure that there is only one header with a given name
1654 -- in either the generated (most likely by `configure`)
1655 -- build directory (e.g. `dist/build`) or in the source directory.
1657 -- If it exists in both, we'll remove the one in the source
1658 -- directory, as the generated should take precedence.
1660 -- C compilers like to prefer source local relative includes,
1661 -- so the search paths provided to the compiler via -I are
1662 -- ignored if the included file can be found relative to the
1663 -- including file. As such we need to take drastic measures
1664 -- and delete the offending file in the source directory.
1665 checkDuplicateHeaders
= do
1666 let relIncDirs
= filter (not . isAbsolute
) (collectField PD
.includeDirs
)
1667 isHeader
= isSuffixOf ".h"
1668 genHeaders
<- forM relIncDirs
$ \dir
->
1669 fmap (dir
</>) . filter isHeader
<$> listDirectory
(buildDir lbi
</> dir
)
1670 `catchIO`
(\_
-> return [])
1671 srcHeaders
<- forM relIncDirs
$ \dir
->
1672 fmap (dir
</>) . filter isHeader
<$> listDirectory
(baseDir lbi
</> dir
)
1673 `catchIO`
(\_
-> return [])
1674 let commonHeaders
= concat genHeaders `
intersect`
concat srcHeaders
1675 forM_ commonHeaders
$ \hdr
-> do
1676 warn verbosity
$ "Duplicate header found in "
1677 ++ (buildDir lbi
</> hdr
)
1679 ++ (baseDir lbi
</> hdr
)
1681 ++ (baseDir lbi
</> hdr
)
1682 removeFile (baseDir lbi
</> hdr
)
1685 ifBuildsWith allHeaders ccArgs
1687 (go
. tail . inits $ allHeaders
)
1689 go
[] = return Nothing
-- cannot happen
1690 go
(hdrs
:hdrsInits
) =
1691 -- Try just preprocessing first
1692 ifBuildsWith hdrs cppArgs
1693 -- If that works, try compiling too
1694 (ifBuildsWith hdrs ccArgs
1696 (return . Just
. Right
. last $ hdrs
))
1697 (return . Just
. Left
. last $ hdrs
)
1699 cppArgs
= "-E":commonCppArgs
-- preprocess only
1700 ccArgs
= "-c":commonCcArgs
-- don't try to link
1702 findMissingLibs
= ifBuildsWith
[] (makeLdArgs allLibs
)
1704 (filterM (fmap not . libExists
) allLibs
)
1706 libExists lib
= builds
(makeProgram
[]) (makeLdArgs
[lib
])
1708 baseDir lbi
' = fromMaybe "." (takeDirectory
<$> cabalFilePath lbi
')
1710 commonCppArgs
= platformDefines lbi
1711 -- TODO: This is a massive hack, to work around the
1712 -- fact that the test performed here should be
1713 -- PER-component (c.f. the "I'm Feeling Lucky"; we
1714 -- should NOT be glomming everything together.)
1715 ++ [ "-I" ++ buildDir lbi
</> "autogen" ]
1716 -- `configure' may generate headers in the build directory
1717 ++ [ "-I" ++ buildDir lbi
</> dir | dir
<- ordNub
(collectField PD
.includeDirs
)
1718 , not (isAbsolute dir
)]
1719 -- we might also reference headers from the packages directory.
1720 ++ [ "-I" ++ baseDir lbi
</> dir | dir
<- ordNub
(collectField PD
.includeDirs
)
1721 , not (isAbsolute dir
)]
1722 ++ [ "-I" ++ dir | dir
<- ordNub
(collectField PD
.includeDirs
)
1724 ++ ["-I" ++ baseDir lbi
]
1725 ++ collectField PD
.cppOptions
1726 ++ collectField PD
.ccOptions
1728 | dir
<- ordNub
[ dir
1730 , dir
<- Installed
.includeDirs dep
]
1731 -- dedupe include dirs of dependencies
1732 -- to prevent quadratic blow-up
1736 , opt
<- Installed
.ccOptions dep
]
1738 commonCcArgs
= commonCppArgs
1739 ++ collectField PD
.ccOptions
1742 , opt
<- Installed
.ccOptions dep
]
1744 commonLdArgs
= [ "-L" ++ dir | dir
<- ordNub
(collectField PD
.extraLibDirs
) ]
1745 ++ collectField PD
.ldOptions
1747 | dir
<- ordNub
[ dir
1749 , dir
<- Installed
.libraryDirs dep
]
1751 --TODO: do we also need dependent packages' ld options?
1752 makeLdArgs libs
= [ "-l"++lib | lib
<- libs
] ++ commonLdArgs
1754 makeProgram hdrs
= unlines $
1755 [ "#include \"" ++ hdr
++ "\"" | hdr
<- hdrs
] ++
1756 ["int main(int argc, char** argv) { return 0; }"]
1758 collectField f
= concatMap f allBi
1759 allBi
= enabledBuildInfos pkg
(componentEnabledSpec lbi
)
1760 deps
= PackageIndex
.topologicalOrder
(installedPkgs lbi
)
1762 builds program args
= do
1763 tempDir
<- getTemporaryDirectory
1764 withTempFile tempDir
".c" $ \cName cHnd
->
1765 withTempFile tempDir
"" $ \oNname oHnd
-> do
1766 hPutStrLn cHnd program
1769 _
<- getDbProgramOutput verbosity
1770 gccProgram
(withPrograms lbi
) (cName
:"-o":oNname
:args
)
1772 `catchIO`
(\_
-> return False)
1773 `catchExit`
(\_
-> return False)
1775 explainErrors Nothing
[] = return () -- should be impossible!
1777 |
isNothing . lookupProgram gccProgram
. withPrograms
$ lbi
1779 = die
' verbosity
$ unlines
1781 "This package depends on foreign library but we cannot "
1782 ++ "find a working C compiler. If you have it in a "
1783 ++ "non-standard location you can use the --with-gcc "
1784 ++ "flag to specify it." ]
1786 explainErrors hdr libs
= die
' verbosity
$ unlines $
1788 then "Missing dependencies on foreign libraries:"
1789 else "Missing dependency on a foreign library:"
1792 Just
(Left h
) -> ["* Missing (or bad) header file: " ++ h
]
1796 [lib
] -> ["* Missing (or bad) C library: " ++ lib
]
1797 _
-> ["* Missing (or bad) C libraries: " ++ intercalate
", " libs
]
1798 ++ [if plural
then messagePlural
else messageSingular | missing
]
1800 Just
(Left _
) -> [ headerCppMessage
]
1801 Just
(Right h
) -> [ (if missing
then "* " else "")
1802 ++ "Bad header file: " ++ h
1807 plural
= length libs
>= 2
1808 -- Is there something missing? (as opposed to broken)
1809 missing
= not (null libs
)
1810 ||
case hdr
of Just
(Left _
) -> True; _
-> False
1813 "This problem can usually be solved by installing the system "
1814 ++ "package that provides this library (you may need the "
1815 ++ "\"-dev\" version). If the library is already installed "
1816 ++ "but in a non-standard location then you can use the flags "
1817 ++ "--extra-include-dirs= and --extra-lib-dirs= to specify "
1819 ++ "If the library file does exist, it may contain errors that "
1820 ++ "are caught by the C compiler at the preprocessing stage. "
1821 ++ "In this case you can re-run configure with the verbosity "
1822 ++ "flag -v3 to see the error messages."
1824 "This problem can usually be solved by installing the system "
1825 ++ "packages that provide these libraries (you may need the "
1826 ++ "\"-dev\" versions). If the libraries are already installed "
1827 ++ "but in a non-standard location then you can use the flags "
1828 ++ "--extra-include-dirs= and --extra-lib-dirs= to specify "
1829 ++ "where they are."
1830 ++ "If the library files do exist, it may contain errors that "
1831 ++ "are caught by the C compiler at the preprocessing stage. "
1832 ++ "In this case you can re-run configure with the verbosity "
1833 ++ "flag -v3 to see the error messages."
1835 "If the header file does exist, it may contain errors that "
1836 ++ "are caught by the C compiler at the preprocessing stage. "
1837 ++ "In this case you can re-run configure with the verbosity "
1838 ++ "flag -v3 to see the error messages."
1840 "The header file contains a compile error. "
1841 ++ "You can re-run configure with the verbosity flag "
1842 ++ "-v3 to see the error messages from the C compiler."
1844 -- | Output package check warnings and errors. Exit if any errors.
1845 checkPackageProblems
:: Verbosity
1847 -- ^ Path to the @.cabal@ file's directory
1848 -> GenericPackageDescription
1849 -> PackageDescription
1851 checkPackageProblems verbosity dir gpkg pkg
= do
1852 ioChecks
<- checkPackageFiles verbosity pkg dir
1853 let pureChecks
= checkPackage gpkg
(Just pkg
)
1854 errors
= [ e | PackageBuildImpossible e
<- pureChecks
++ ioChecks
]
1855 warnings
= [ w | PackageBuildWarning w
<- pureChecks
++ ioChecks
]
1857 then traverse_
(warn verbosity
) warnings
1858 else die
' verbosity
(intercalate
"\n\n" errors
)
1860 -- | Preform checks if a relocatable build is allowed
1861 checkRelocatable
:: Verbosity
1862 -> PackageDescription
1865 checkRelocatable verbosity pkg lbi
1866 = sequence_ [ checkOS
1868 , packagePrefixRelative
1869 , depsPrefixRelative
1872 -- Check if the OS support relocatable builds.
1874 -- If you add new OS' to this list, and your OS supports dynamic libraries
1875 -- and RPATH, make sure you add your OS to RPATH-support list of:
1876 -- Distribution.Simple.GHC.getRPaths
1878 = unless (os `
elem`
[ OSX
, Linux
])
1879 $ die
' verbosity
$ "Operating system: " ++ display os
++
1880 ", does not support relocatable builds"
1882 (Platform _ os
) = hostPlatform lbi
1884 -- Check if the Compiler support relocatable builds
1886 = unless (compilerFlavor comp `
elem`
[ GHC
])
1887 $ die
' verbosity
$ "Compiler: " ++ show comp
++
1888 ", does not support relocatable builds"
1892 -- Check if all the install dirs are relative to same prefix
1893 packagePrefixRelative
1894 = unless (relativeInstallDirs installDirs
)
1895 $ die
' verbosity
$ "Installation directories are not prefix_relative:\n" ++
1898 -- NB: should be good enough to check this against the default
1899 -- component ID, but if we wanted to be strictly correct we'd
1900 -- check for each ComponentId.
1901 installDirs
= absoluteInstallDirs pkg lbi NoCopyDest
1902 p
= prefix installDirs
1903 relativeInstallDirs
(InstallDirs
{..}) =
1905 (fmap (stripPrefix p
)
1906 [ bindir
, libdir
, dynlibdir
, libexecdir
, includedir
, datadir
1907 , docdir
, mandir
, htmldir
, haddockdir
, sysconfdir
] )
1909 -- Check if the library dirs of the dependencies that are in the package
1910 -- database to which the package is installed are relative to the
1911 -- prefix of the package
1912 depsPrefixRelative
= do
1913 pkgr
<- GHC
.pkgRoot verbosity lbi
(last (withPackageDB lbi
))
1914 traverse_
(doCheck pkgr
) ipkgs
1917 |
maybe False (== pkgr
) (Installed
.pkgRoot ipkg
)
1918 = traverse_
(\l
-> when (isNothing $ stripPrefix p l
) (die
' verbosity
(msg l
)))
1919 (Installed
.libraryDirs ipkg
)
1922 -- NB: should be good enough to check this against the default
1923 -- component ID, but if we wanted to be strictly correct we'd
1924 -- check for each ComponentId.
1925 installDirs
= absoluteInstallDirs pkg lbi NoCopyDest
1926 p
= prefix installDirs
1927 ipkgs
= PackageIndex
.allPackages
(installedPkgs lbi
)
1928 msg l
= "Library directory of a dependency: " ++ show l
++
1929 "\nis not relative to the installation prefix:\n" ++
1932 -- -----------------------------------------------------------------------------
1933 -- Testing foreign library requirements
1935 unsupportedForeignLibs
:: Compiler
-> Platform
-> [ForeignLib
] -> [String]
1936 unsupportedForeignLibs comp platform
=
1937 mapMaybe (checkForeignLibSupported comp platform
)
1939 checkForeignLibSupported
:: Compiler
-> Platform
-> ForeignLib
-> Maybe String
1940 checkForeignLibSupported comp platform flib
= go
(compilerFlavor comp
)
1942 go
:: CompilerFlavor
-> Maybe String
1944 | compilerVersion comp
< mkVersion
[7,8] = unsupported
[
1945 "Building foreign libraires is only supported with GHC >= 7.8"
1947 |
otherwise = goGhcPlatform platform
1948 go _
= unsupported
[
1949 "Building foreign libraries is currently only supported with ghc"
1952 goGhcPlatform
:: Platform
-> Maybe String
1953 goGhcPlatform
(Platform X86_64 OSX
) = goGhcOsx
(foreignLibType flib
)
1954 goGhcPlatform
(Platform I386 Linux
) = goGhcLinux
(foreignLibType flib
)
1955 goGhcPlatform
(Platform X86_64 Linux
) = goGhcLinux
(foreignLibType flib
)
1956 goGhcPlatform
(Platform I386 Windows
) = goGhcWindows
(foreignLibType flib
)
1957 goGhcPlatform
(Platform X86_64 Windows
) = goGhcWindows
(foreignLibType flib
)
1958 goGhcPlatform _
= unsupported
[
1959 "Building foreign libraries is currently only supported on OSX, "
1960 , "Linux and Windows"
1963 goGhcOsx
:: ForeignLibType
-> Maybe String
1964 goGhcOsx ForeignLibNativeShared
1965 |
not (null (foreignLibModDefFile flib
)) = unsupported
[
1966 "Module definition file not supported on OSX"
1968 |
not (null (foreignLibVersionInfo flib
)) = unsupported
[
1969 "Foreign library versioning not currently supported on OSX"
1973 goGhcOsx _
= unsupported
[
1974 "We can currently only build shared foreign libraries on OSX"
1977 goGhcLinux
:: ForeignLibType
-> Maybe String
1978 goGhcLinux ForeignLibNativeShared
1979 |
not (null (foreignLibModDefFile flib
)) = unsupported
[
1980 "Module definition file not supported on Linux"
1982 |
not (null (foreignLibVersionInfo flib
))
1983 && not (null (foreignLibVersionLinux flib
)) = unsupported
[
1984 "You must not specify both lib-version-info and lib-version-linux"
1988 goGhcLinux _
= unsupported
[
1989 "We can currently only build shared foreign libraries on Linux"
1992 goGhcWindows
:: ForeignLibType
-> Maybe String
1993 goGhcWindows ForeignLibNativeShared
1994 |
not standalone
= unsupported
[
1995 "We can currently only build standalone libraries on Windows. Use\n"
1996 , " if os(Windows)\n"
1997 , " options: standalone\n"
1998 , "in your foreign-library stanza."
2000 |
not (null (foreignLibVersionInfo flib
)) = unsupported
[
2001 "Foreign library versioning not currently supported on Windows.\n"
2002 , "You can specify module definition files in the mod-def-file field."
2006 goGhcWindows _
= unsupported
[
2007 "We can currently only build shared foreign libraries on Windows"
2011 standalone
= ForeignLibStandalone `
elem` foreignLibOptions flib
2013 unsupported
:: [String] -> Maybe String
2014 unsupported
= Just
. concat