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
33 , writePersistBuildConfig
35 , getPersistBuildConfig
36 , checkPersistBuildConfigOutdated
37 , tryGetPersistBuildConfig
38 , maybeGetPersistBuildConfig
39 , findDistPref
, findDistPrefOrDefault
40 , getInternalLibraries
42 , computeCompatPackageKey
44 , getInstalledPackages
45 , getInstalledPackagesMonitorFiles
46 , getPackageDBContents
47 , configCompilerEx
, configCompilerAuxEx
48 , computeEffectiveProfiling
49 , ccLdOptionsBuildInfo
51 , interpretPackageDbFlags
52 , ConfigStateFileError
(..)
53 , tryGetConfigStateFile
58 import Distribution
.Compat
.Prelude
60 import Distribution
.Compiler
61 import Distribution
.Types
.IncludeRenaming
62 import Distribution
.Utils
.NubList
63 import Distribution
.Simple
.Compiler
64 import Distribution
.Simple
.PreProcess
65 import Distribution
.Package
66 import qualified Distribution
.InstalledPackageInfo
as IPI
67 import Distribution
.InstalledPackageInfo
(InstalledPackageInfo
)
68 import qualified Distribution
.Simple
.PackageIndex
as PackageIndex
69 import Distribution
.Simple
.PackageIndex
(InstalledPackageIndex
)
70 import Distribution
.PackageDescription
71 import Distribution
.PackageDescription
.PrettyPrint
72 import Distribution
.PackageDescription
.Configuration
73 import Distribution
.PackageDescription
.Check
hiding (doesFileExist)
74 import Distribution
.Simple
.BuildToolDepends
75 import Distribution
.Simple
.Program
76 import Distribution
.Simple
.Setup
as Setup
77 import Distribution
.Simple
.BuildTarget
78 import Distribution
.Simple
.LocalBuildInfo
79 import Distribution
.Simple
.Program
.Db
(appendProgramSearchPath
, modifyProgramSearchPath
, lookupProgramByName
)
80 import Distribution
.Simple
.Utils
81 import Distribution
.System
82 import Distribution
.Types
.PackageVersionConstraint
83 import Distribution
.Types
.LocalBuildInfo
84 import Distribution
.Types
.ComponentRequestedSpec
85 import Distribution
.Types
.GivenComponent
86 import Distribution
.Version
87 import Distribution
.Verbosity
88 import qualified Distribution
.Compat
.Graph
as Graph
89 import Distribution
.Compat
.Stack
90 import Distribution
.Backpack
.Configure
91 import Distribution
.Backpack
.DescribeUnitId
92 import Distribution
.Backpack
.PreExistingComponent
93 import Distribution
.Backpack
.ConfiguredComponent
(newPackageDepsBehaviour
)
94 import Distribution
.Backpack
.Id
95 import Distribution
.Utils
.LogProgress
97 import qualified Distribution
.Simple
.GHC
as GHC
98 import qualified Distribution
.Simple
.GHCJS
as GHCJS
99 import qualified Distribution
.Simple
.UHC
as UHC
100 import qualified Distribution
.Simple
.HaskellSuite
as HaskellSuite
102 import Control
.Exception
104 import Distribution
.Utils
.Structured
( structuredDecodeOrFailIO
, structuredEncode
)
105 import Distribution
.Compat
.Directory
106 ( listDirectory
, doesPathExist
)
107 import Data
.ByteString
.Lazy
( ByteString
)
108 import qualified Data
.ByteString
as BS
109 import qualified Data
.ByteString
.Lazy
.Char8
as BLC8
111 ( (\\), stripPrefix
, intersect)
112 import qualified Data
.List
.NonEmpty
as NEL
113 import qualified Data
.Map
as Map
114 import System
.Directory
115 ( canonicalizePath
, createDirectoryIfMissing
, doesFileExist
116 , getTemporaryDirectory
, removeFile)
117 import System
.FilePath
118 ( (</>), isAbsolute
, takeDirectory
)
119 import qualified System
.Info
120 ( compilerName
, compilerVersion
)
122 ( hPutStrLn, hClose )
123 import Distribution
.Pretty
124 ( pretty
, defaultStyle
, prettyShow
)
125 import Distribution
.Parsec
127 import Text
.PrettyPrint
128 ( Doc
, ($+$), char
, comma
, hsep
, nest
129 , punctuate
, quotes
, render
, renderStyle
, sep
, text
)
130 import Distribution
.Compat
.Environment
( lookupEnv
)
132 import qualified Data
.Maybe as M
133 import qualified Data
.Set
as Set
134 import qualified Distribution
.Compat
.NonEmptySet
as NES
137 type UseExternalInternalDeps
= Bool
139 -- | The errors that can be thrown when reading the @setup-config@ file.
140 data ConfigStateFileError
141 = ConfigStateFileNoHeader
-- ^ No header found.
142 | ConfigStateFileBadHeader
-- ^ Incorrect header.
143 | ConfigStateFileNoParse
-- ^ Cannot parse file contents.
144 | ConfigStateFileMissing
-- ^ No file!
145 | ConfigStateFileBadVersion PackageIdentifier PackageIdentifier
146 (Either ConfigStateFileError LocalBuildInfo
) -- ^ Mismatched version.
149 -- | Format a 'ConfigStateFileError' as a user-facing error message.
150 dispConfigStateFileError
:: ConfigStateFileError
-> Doc
151 dispConfigStateFileError ConfigStateFileNoHeader
=
152 text
"Saved package config file header is missing."
153 <+> text
"Re-run the 'configure' command."
154 dispConfigStateFileError ConfigStateFileBadHeader
=
155 text
"Saved package config file header is corrupt."
156 <+> text
"Re-run the 'configure' command."
157 dispConfigStateFileError ConfigStateFileNoParse
=
158 text
"Saved package config file is corrupt."
159 <+> text
"Re-run the 'configure' command."
160 dispConfigStateFileError ConfigStateFileMissing
=
161 text
"Run the 'configure' command first."
162 dispConfigStateFileError
(ConfigStateFileBadVersion oldCabal oldCompiler _
) =
163 text
"Saved package config file is outdated:"
164 $+$ badCabal
$+$ badCompiler
165 $+$ text
"Re-run the 'configure' command."
168 text
"• the Cabal version changed from"
169 <+> pretty oldCabal
<+> "to" <+> pretty currentCabalId
171 | oldCompiler
== currentCompilerId
= mempty
173 text
"• the compiler changed from"
174 <+> pretty oldCompiler
<+> "to" <+> pretty currentCompilerId
176 instance Show ConfigStateFileError
where
177 show = renderStyle defaultStyle
. dispConfigStateFileError
179 instance Exception ConfigStateFileError
181 -- | Read the 'localBuildInfoFile'. Throw an exception if the file is
182 -- missing, if the file cannot be read, or if the file was created by an older
184 getConfigStateFile
:: FilePath -- ^ The file path of the @setup-config@ file.
186 getConfigStateFile filename
= do
187 exists
<- doesFileExist filename
188 unless exists
$ throwIO ConfigStateFileMissing
189 -- Read the config file into a strict ByteString to avoid problems with
190 -- lazy I/O, then convert to lazy because the binary package needs that.
191 contents
<- BS
.readFile filename
192 let (header
, body
) = BLC8
.span
(/='\n') (BLC8
.fromChunks
[contents
])
194 (cabalId
, compId
) <- parseHeader header
196 let getStoredValue
= do
197 result
<- structuredDecodeOrFailIO
(BLC8
.tail body
)
199 Left _
-> throwIO ConfigStateFileNoParse
201 deferErrorIfBadVersion act
202 | cabalId
/= currentCabalId
= do
204 throwIO
$ ConfigStateFileBadVersion cabalId compId eResult
206 deferErrorIfBadVersion getStoredValue
208 _
= callStack
-- TODO: attach call stack to exception
210 -- | Read the 'localBuildInfoFile', returning either an error or the local build
212 tryGetConfigStateFile
:: FilePath -- ^ The file path of the @setup-config@ file.
213 -> IO (Either ConfigStateFileError LocalBuildInfo
)
214 tryGetConfigStateFile
= try . getConfigStateFile
216 -- | Try to read the 'localBuildInfoFile'.
217 tryGetPersistBuildConfig
:: FilePath -- ^ The @dist@ directory path.
218 -> IO (Either ConfigStateFileError LocalBuildInfo
)
219 tryGetPersistBuildConfig
= try . getPersistBuildConfig
221 -- | Read the 'localBuildInfoFile'. Throw an exception if the file is
222 -- missing, if the file cannot be read, or if the file was created by an older
224 getPersistBuildConfig
:: FilePath -- ^ The @dist@ directory path.
226 getPersistBuildConfig
= getConfigStateFile
. localBuildInfoFile
228 -- | Try to read the 'localBuildInfoFile'.
229 maybeGetPersistBuildConfig
:: FilePath -- ^ The @dist@ directory path.
230 -> IO (Maybe LocalBuildInfo
)
231 maybeGetPersistBuildConfig
=
232 liftM (either (const Nothing
) Just
) . tryGetPersistBuildConfig
234 -- | After running configure, output the 'LocalBuildInfo' to the
235 -- 'localBuildInfoFile'.
236 writePersistBuildConfig
:: FilePath -- ^ The @dist@ directory path.
237 -> LocalBuildInfo
-- ^ The 'LocalBuildInfo' to write.
239 writePersistBuildConfig distPref lbi
= do
240 createDirectoryIfMissing
False distPref
241 writeFileAtomic
(localBuildInfoFile distPref
) $
242 BLC8
.unlines [showHeader pkgId
, structuredEncode lbi
]
244 pkgId
= localPackage lbi
246 -- | Identifier of the current Cabal package.
247 currentCabalId
:: PackageIdentifier
248 currentCabalId
= PackageIdentifier
(mkPackageName
"Cabal") cabalVersion
250 -- | Identifier of the current compiler package.
251 currentCompilerId
:: PackageIdentifier
252 currentCompilerId
= PackageIdentifier
(mkPackageName System
.Info
.compilerName
)
253 (mkVersion
' System
.Info
.compilerVersion
)
255 -- | Parse the @setup-config@ file header, returning the package identifiers
256 -- for Cabal and the compiler.
257 parseHeader
:: ByteString
-- ^ The file contents.
258 -> IO (PackageIdentifier
, PackageIdentifier
)
259 parseHeader header
= case BLC8
.words header
of
260 ["Saved", "package", "config", "for", pkgId
, "written", "by", cabalId
,
262 maybe (throwIO ConfigStateFileBadHeader
) return $ do
263 _
<- simpleParsec
(fromUTF8LBS pkgId
) :: Maybe PackageIdentifier
264 cabalId
' <- simpleParsec
(BLC8
.unpack cabalId
)
265 compId
' <- simpleParsec
(BLC8
.unpack compId
)
266 return (cabalId
', compId
')
267 _
-> throwIO ConfigStateFileNoHeader
269 -- | Generate the @setup-config@ file header.
270 showHeader
:: PackageIdentifier
-- ^ The processed package.
272 showHeader pkgId
= BLC8
.unwords
273 [ "Saved", "package", "config", "for"
274 , toUTF8LBS
$ prettyShow pkgId
276 , BLC8
.pack
$ prettyShow currentCabalId
278 , BLC8
.pack
$ prettyShow currentCompilerId
281 -- | Check that localBuildInfoFile is up-to-date with respect to the
283 checkPersistBuildConfigOutdated
:: FilePath -> FilePath -> IO Bool
284 checkPersistBuildConfigOutdated distPref pkg_descr_file
=
285 pkg_descr_file `moreRecentFile` localBuildInfoFile distPref
287 -- | Get the path of @dist\/setup-config@.
288 localBuildInfoFile
:: FilePath -- ^ The @dist@ directory path.
290 localBuildInfoFile distPref
= distPref
</> "setup-config"
292 -- -----------------------------------------------------------------------------
294 -- -----------------------------------------------------------------------------
296 -- | Return the \"dist/\" prefix, or the default prefix. The prefix is taken
297 -- from (in order of highest to lowest preference) the override prefix, the
298 -- \"CABAL_BUILDDIR\" environment variable, or the default prefix.
299 findDistPref
:: FilePath -- ^ default \"dist\" prefix
300 -> Setup
.Flag
FilePath -- ^ override \"dist\" prefix
302 findDistPref defDistPref overrideDistPref
= do
303 envDistPref
<- liftM parseEnvDistPref
(lookupEnv
"CABAL_BUILDDIR")
304 return $ fromFlagOrDefault defDistPref
(mappend envDistPref overrideDistPref
)
306 parseEnvDistPref env
=
308 Just distPref |
not (null distPref
) -> toFlag distPref
311 -- | Return the \"dist/\" prefix, or the default prefix. The prefix is taken
312 -- from (in order of highest to lowest preference) the override prefix, the
313 -- \"CABAL_BUILDDIR\" environment variable, or 'defaultDistPref' is used. Call
314 -- this function to resolve a @*DistPref@ flag whenever it is not known to be
315 -- set. (The @*DistPref@ flags are always set to a definite value before
316 -- invoking 'UserHooks'.)
317 findDistPrefOrDefault
:: Setup
.Flag
FilePath -- ^ override \"dist\" prefix
319 findDistPrefOrDefault
= findDistPref defaultDistPref
321 -- |Perform the \"@.\/setup configure@\" action.
322 -- Returns the @.setup-config@ file.
323 configure
:: (GenericPackageDescription
, HookedBuildInfo
)
324 -> ConfigFlags
-> IO LocalBuildInfo
325 configure
(pkg_descr0
, pbi
) cfg
= do
326 -- Determine the component we are configuring, if a user specified
327 -- one on the command line. We use a fake, flattened version of
328 -- the package since at this point, we're not really sure what
329 -- components we *can* configure. @Nothing@ means that we should
330 -- configure everything (the old behavior).
331 (mb_cname
:: Maybe ComponentName
) <- do
332 let flat_pkg_descr
= flattenPackageDescription pkg_descr0
333 targets
<- readBuildTargets verbosity flat_pkg_descr
(configArgs cfg
)
334 -- TODO: bleat if you use the module/file syntax
335 let targets
' = [ cname | BuildTargetComponent cname
<- targets
]
337 _ |
null (configArgs cfg
) -> return Nothing
338 [cname
] -> return (Just cname
)
339 [] -> die
' verbosity
"No valid component targets found"
341 "Can only configure either single component or all of them"
343 let use_external_internal_deps
= isJust mb_cname
345 Nothing
-> setupMessage verbosity
"Configuring" (packageId pkg_descr0
)
346 Just cname
-> setupMessage
' verbosity
"Configuring" (packageId pkg_descr0
)
347 cname
(Just
(configInstantiateWith cfg
))
349 -- configCID is only valid for per-component configure
350 when (isJust (flagToMaybe
(configCID cfg
)) && isNothing mb_cname
) $
351 die
' verbosity
"--cid is only supported for per-component configure"
353 checkDeprecatedFlags verbosity cfg
354 checkExactConfiguration verbosity pkg_descr0 cfg
356 -- Where to build the package
357 let buildDir
:: FilePath -- e.g. dist/build
358 -- fromFlag OK due to Distribution.Simple calling
359 -- findDistPrefOrDefault to fill it in
360 buildDir
= fromFlag
(configDistPref cfg
) </> "build"
361 createDirectoryIfMissingVerbose
(lessVerbose verbosity
) True buildDir
363 -- What package database(s) to use
364 let packageDbs
:: PackageDBStack
366 = interpretPackageDbFlags
367 (fromFlag
(configUserInstall cfg
))
368 (configPackageDBs cfg
)
370 programDbPre
<- mkProgramDb cfg
(configPrograms cfg
)
371 -- comp: the compiler we're building with
372 -- compPlatform: the platform we're building for
373 -- programDb: location and args of all programs we're
376 compPlatform
:: Platform
,
377 programDb
:: ProgramDb
)
379 (flagToMaybe
(configHcFlavor cfg
))
380 (flagToMaybe
(configHcPath cfg
))
381 (flagToMaybe
(configHcPkg cfg
))
383 (lessVerbose verbosity
)
385 -- The InstalledPackageIndex of all installed packages
386 installedPackageSet
:: InstalledPackageIndex
387 <- getInstalledPackages
(lessVerbose verbosity
) comp
390 -- The set of package names which are "shadowed" by internal
391 -- packages, and which component they map to
392 let internalPackageSet
:: Set LibraryName
393 internalPackageSet
= getInternalLibraries pkg_descr0
395 -- Make a data structure describing what components are enabled.
396 let enabled
:: ComponentRequestedSpec
397 enabled
= case mb_cname
of
398 Just cname
-> OneComponentRequestedSpec cname
399 Nothing
-> ComponentRequestedSpec
400 -- The flag name (@--enable-tests@) is a
401 -- little bit of a misnomer, because
402 -- just passing this flag won't
403 -- "enable", in our internal
404 -- nomenclature; it's just a request; a
405 -- @buildable: False@ might make it
406 -- not possible to enable.
407 { testsRequested
= fromFlag
(configTests cfg
)
408 , benchmarksRequested
=
409 fromFlag
(configBenchmarks cfg
) }
410 -- Some sanity checks related to enabling components.
411 when (isJust mb_cname
412 && (fromFlag
(configTests cfg
) || fromFlag
(configBenchmarks cfg
))) $
414 "--enable-tests/--enable-benchmarks are incompatible with" ++
415 " explicitly specifying a component to configure."
417 -- Some sanity checks related to dynamic/static linking.
418 when (fromFlag
(configDynExe cfg
) && fromFlag
(configFullyStaticExe cfg
)) $
420 "--enable-executable-dynamic and --enable-executable-static" ++
421 " are incompatible with each other."
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
:: [PackageVersionConstraint
],
437 requiredDepsMap
:: Map
(PackageName
, ComponentName
) 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 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 (fromFlagOrDefault
False (configAllowDependingOnPrivateLibs cfg
))
466 (packageName pkg_descr0
)
474 debug verbosity
$ "Finalized package description:\n"
475 ++ showPackageDescription pkg_descr
477 let cabalFileDir
= maybe "." takeDirectory
$
478 flagToMaybe
(configCabalFilePath cfg
)
479 checkCompilerProblems verbosity comp pkg_descr enabled
480 checkPackageProblems verbosity cabalFileDir pkg_descr0
481 (updatePackageDescription pbi pkg_descr
)
483 -- The list of 'InstalledPackageInfo' recording the selected
484 -- dependencies on external packages.
486 -- Invariant: For any package name, there is at most one package
487 -- in externalPackageDeps which has that name.
489 -- NB: The dependency selection is global over ALL components
490 -- in the package (similar to how allConstraints and
491 -- requiredDepsMap are global over all components). In particular,
492 -- if *any* component (post-flag resolution) has an unsatisfiable
493 -- dependency, we will fail. This can sometimes be undesirable
494 -- for users, see #1786 (benchmark conflicts with executable),
496 -- In the presence of Backpack, these package dependencies are
497 -- NOT complete: they only ever include the INDEFINITE
498 -- dependencies. After we apply an instantiation, we'll get
499 -- definite references which constitute extra dependencies.
500 -- (Why not have cabal-install pass these in explicitly?
501 -- For one it's deterministic; for two, we need to associate
502 -- them with renamings which would require a far more complicated
503 -- input scheme than what we have today.)
504 externalPkgDeps
:: [PreExistingComponent
]
505 <- configureDependencies
507 use_external_internal_deps
514 -- Compute installation directory templates, based on user
517 -- TODO: Move this into a helper function.
518 defaultDirs
:: InstallDirTemplates
519 <- defaultInstallDirs
' use_external_internal_deps
520 (compilerFlavor comp
)
521 (fromFlag
(configUserInstall cfg
))
523 let installDirs
:: InstallDirTemplates
524 installDirs
= combineInstallDirs fromFlagOrDefault
525 defaultDirs
(configInstallDirs cfg
)
527 -- Check languages and extensions
528 -- TODO: Move this into a helper function.
529 let langlist
= nub $ catMaybes $ map defaultLanguage
530 (enabledBuildInfos pkg_descr enabled
)
531 let langs
= unsupportedLanguages comp langlist
532 when (not (null langs
)) $
533 die
' verbosity
$ "The package " ++ prettyShow
(packageId pkg_descr0
)
534 ++ " requires the following languages which are not "
535 ++ "supported by " ++ prettyShow
(compilerId comp
) ++ ": "
536 ++ intercalate
", " (map prettyShow langs
)
537 let extlist
= nub $ concatMap allExtensions
538 (enabledBuildInfos pkg_descr enabled
)
539 let exts
= unsupportedExtensions comp extlist
540 when (not (null exts
)) $
541 die
' verbosity
$ "The package " ++ prettyShow
(packageId pkg_descr0
)
542 ++ " requires the following language extensions which are not "
543 ++ "supported by " ++ prettyShow
(compilerId comp
) ++ ": "
544 ++ intercalate
", " (map prettyShow exts
)
546 -- Check foreign library build requirements
547 let flibs
= [flib | CFLib flib
<- enabledComponents pkg_descr enabled
]
548 let unsupportedFLibs
= unsupportedForeignLibs comp compPlatform flibs
549 when (not (null unsupportedFLibs
)) $
550 die
' verbosity
$ "Cannot build some foreign libraries: "
551 ++ intercalate
"," unsupportedFLibs
553 -- Configure certain external build tools, see below for which ones.
554 let requiredBuildTools
= do
555 bi
<- enabledBuildInfos pkg_descr enabled
556 -- First, we collect any tool dep that we know is external. This is,
559 -- 1. `build-tools` entries on the whitelist
561 -- 2. `build-tool-depends` that aren't from the current package.
562 let externBuildToolDeps
=
563 [ LegacyExeDependency
(unUnqualComponentName eName
) versionRange
564 | buildTool
@(ExeDependency _ eName versionRange
)
565 <- getAllToolDependencies pkg_descr bi
566 , not $ isInternal pkg_descr buildTool
]
567 -- Second, we collect any build-tools entry we don't know how to
568 -- desugar. We'll never have any idea how to build them, so we just
569 -- hope they are already on the PATH.
570 let unknownBuildTools
=
572 | buildTool
<- buildTools bi
573 , Nothing
== desugarBuildTool pkg_descr buildTool
]
574 externBuildToolDeps
++ unknownBuildTools
577 configureAllKnownPrograms
(lessVerbose verbosity
) programDb
578 >>= configureRequiredPrograms verbosity requiredBuildTools
580 (pkg_descr
', programDb
'') <-
581 configurePkgconfigPackages verbosity pkg_descr programDb
' enabled
583 -- Compute internal component graph
585 -- The general idea is that we take a look at all the source level
586 -- components (which may build-depends on each other) and form a graph.
587 -- From there, we build a ComponentLocalBuildInfo for each of the
588 -- components, which lets us actually build each component.
589 -- internalPackageSet
590 -- use_external_internal_deps
591 (buildComponents
:: [ComponentLocalBuildInfo
],
592 packageDependsIndex
:: InstalledPackageIndex
) <-
593 runLogProgress verbosity
$ configureComponentLocalBuildInfos
595 use_external_internal_deps
597 (fromFlagOrDefault
False (configDeterministic cfg
))
602 (configConfigurationsFlags cfg
)
603 (configInstantiateWith cfg
)
607 -- Decide if we're going to compile with split sections.
608 split_sections
:: Bool <-
609 if not (fromFlag
$ configSplitSections cfg
)
611 else case compilerFlavor comp
of
612 GHC | compilerVersion comp
>= mkVersion
[8,0]
616 _
-> do warn verbosity
617 ("this compiler does not support " ++
618 "--enable-split-sections; ignoring")
621 -- Decide if we're going to compile with split objects.
622 split_objs
:: Bool <-
623 if not (fromFlag
$ configSplitObjs cfg
)
625 else case compilerFlavor comp
of
628 ("--enable-split-sections and " ++
629 "--enable-split-objs are mutually" ++
630 "exclusive; ignoring the latter")
636 _
-> do warn verbosity
637 ("this compiler does not support " ++
638 "--enable-split-objs; ignoring")
641 -- Basically yes/no/unknown.
642 let linkerSupportsRelocations
:: Maybe Bool
643 linkerSupportsRelocations
=
644 case lookupProgramByName
"ld" programDb
'' of
647 case Map
.lookup "Supports relocatable output" $ programProperties ld
of
648 Just
"YES" -> Just
True
649 Just
"NO" -> Just
False
652 let ghciLibByDefault
=
653 case compilerId comp
of
655 -- If ghc is non-dynamic, then ghci needs object files,
656 -- so we build one by default.
658 -- Technically, archive files should be sufficient for ghci,
659 -- but because of GHC bug #8942, it has never been safe to
660 -- rely on them. By the time that bug was fixed, ghci had
661 -- been changed to read shared libraries instead of archive
662 -- files (see next code block).
663 not (GHC
.isDynamic comp
)
664 CompilerId GHCJS _
->
665 not (GHCJS
.isDynamic comp
)
669 case fromFlagOrDefault ghciLibByDefault
(configGHCiLib cfg
) of
670 -- NOTE: If linkerSupportsRelocations is Nothing this may still fail if the
671 -- linker does not support -r.
672 True |
not (fromMaybe True linkerSupportsRelocations
) -> do
674 "--enable-library-for-ghci is not supported with the current"
675 ++ " linker; ignoring..."
679 let sharedLibsByDefault
680 | fromFlag
(configDynExe cfg
) =
681 -- build a shared library if dynamically-linked
682 -- executables are requested
684 |
otherwise = case compilerId comp
of
686 -- if ghc is dynamic, then ghci needs a shared
687 -- library, so we build one by default.
689 CompilerId GHCJS _
->
693 -- build shared libraries if required by GHC or by the
694 -- executable linking mode, but allow the user to force
695 -- building only static library archives with
697 fromFlagOrDefault sharedLibsByDefault
$ configSharedLib cfg
700 -- build a static library (all dependent libraries rolled
701 -- into a huge .a archive) via GHCs -staticlib flag.
702 fromFlagOrDefault
False $ configStaticLib cfg
704 withDynExe_
= fromFlag
$ configDynExe cfg
706 withFullyStaticExe_
= fromFlag
$ configFullyStaticExe cfg
708 when (withDynExe_
&& not withSharedLib_
) $ warn verbosity
$
709 "Executables will use dynamic linking, but a shared library "
710 ++ "is not being built. Linking will fail if any executables "
711 ++ "depend on the library."
713 setProfLBI
<- configureProfiling verbosity cfg comp
715 setCoverageLBI
<- configureCoverage verbosity cfg comp
719 -- Turn off library and executable stripping when `debug-info` is set
720 -- to anything other than zero.
723 let defaultStrip
= fromFlagOrDefault
True (f cfg
)
724 in case fromFlag
(configDebugInfo cfg
) of
725 NoDebugInfo
-> return defaultStrip
728 warn verbosity
$ "Setting debug-info implies "
729 ++ s
++ "-stripping: False"
734 strip_lib
<- strip_libexe
"library" configStripLibs
735 strip_exe
<- strip_libexe
"executable" configStripExes
738 let reloc
= fromFlagOrDefault
False $ configRelocatable cfg
740 let buildComponentsMap
=
741 foldl' (\m clbi
-> Map
.insertWith
(++)
742 (componentLocalName clbi
) [clbi
] m
)
743 Map
.empty buildComponents
745 let lbi
= (setCoverageLBI
. setProfLBI
)
748 flagAssignment
= flags
,
749 componentEnabledSpec
= enabled
,
750 extraConfigArgs
= [], -- Currently configure does not
751 -- take extra args, but if it
752 -- did they would go here.
753 installDirTemplates
= installDirs
,
755 hostPlatform
= compPlatform
,
757 cabalFilePath
= flagToMaybe
(configCabalFilePath cfg
),
758 componentGraph
= Graph
.fromDistinctList buildComponents
,
759 componentNameMap
= buildComponentsMap
,
760 installedPkgs
= packageDependsIndex
,
761 pkgDescrFile
= Nothing
,
762 localPkgDescr
= pkg_descr
',
763 withPrograms
= programDb
'',
764 withVanillaLib
= fromFlag
$ configVanillaLib cfg
,
765 withSharedLib
= withSharedLib_
,
766 withStaticLib
= withStaticLib_
,
767 withDynExe
= withDynExe_
,
768 withFullyStaticExe
= withFullyStaticExe_
,
770 withProfLibDetail
= ProfDetailNone
,
772 withProfExeDetail
= ProfDetailNone
,
773 withOptimization
= fromFlag
$ configOptimization cfg
,
774 withDebugInfo
= fromFlag
$ configDebugInfo cfg
,
775 withGHCiLib
= withGHCiLib_
,
776 splitSections
= split_sections
,
777 splitObjs
= split_objs
,
778 stripExes
= strip_exe
,
779 stripLibs
= strip_lib
,
782 withPackageDB
= packageDbs
,
783 progPrefix
= fromFlag
$ configProgPrefix cfg
,
784 progSuffix
= fromFlag
$ configProgSuffix cfg
,
788 when reloc
(checkRelocatable verbosity pkg_descr lbi
)
790 -- TODO: This is not entirely correct, because the dirs may vary
791 -- across libraries/executables
792 let dirs
= absoluteInstallDirs pkg_descr lbi NoCopyDest
793 relative
= prefixRelativeInstallDirs
(packageId pkg_descr
) lbi
795 -- PKGROOT: allowing ${pkgroot} to be passed as --prefix to
796 -- cabal configure, is only a hidden option. It allows packages
797 -- to be relocatable with their package database. This however
798 -- breaks when the Paths_* or other includes are used that
799 -- contain hard coded paths. This is still an open TODO.
801 -- Allowing ${pkgroot} here, however requires less custom hooks
802 -- in scripts that *really* want ${pkgroot}. See haskell/cabal/#4872
803 unless (isAbsolute
(prefix dirs
)
804 ||
"${pkgroot}" `
isPrefixOf` prefix dirs
) $ die
' verbosity
$
805 "expected an absolute directory name for --prefix: " ++ prefix dirs
807 when ("${pkgroot}" `
isPrefixOf` prefix dirs
) $
808 warn verbosity
$ "Using ${pkgroot} in prefix " ++ prefix dirs
809 ++ " will not work if you rely on the Path_* module "
810 ++ " or other hard coded paths. Cabal does not yet "
811 ++ " support fully relocatable builds! "
812 ++ " See #462 #2302 #2994 #3305 #3473 #3586 #3909"
813 ++ " #4097 #4291 #4872"
815 info verbosity
$ "Using " ++ prettyShow currentCabalId
816 ++ " compiled by " ++ prettyShow currentCompilerId
817 info verbosity
$ "Using compiler: " ++ showCompilerId comp
818 info verbosity
$ "Using install prefix: " ++ prefix dirs
820 let dirinfo name dir isPrefixRelative
=
821 info verbosity
$ name
++ " installed in: " ++ dir
++ relNote
822 where relNote
= case buildOS
of
823 Windows |
not (hasLibs pkg_descr
)
824 && isNothing isPrefixRelative
825 -> " (fixed location)"
828 dirinfo
"Executables" (bindir dirs
) (bindir relative
)
829 dirinfo
"Libraries" (libdir dirs
) (libdir relative
)
830 dirinfo
"Dynamic Libraries" (dynlibdir dirs
) (dynlibdir relative
)
831 dirinfo
"Private executables" (libexecdir dirs
) (libexecdir relative
)
832 dirinfo
"Data files" (datadir dirs
) (datadir relative
)
833 dirinfo
"Documentation" (docdir dirs
) (docdir relative
)
834 dirinfo
"Configuration files" (sysconfdir dirs
) (sysconfdir relative
)
836 sequence_ [ reportProgram verbosity prog configuredProg
837 |
(prog
, configuredProg
) <- knownPrograms programDb
'' ]
842 verbosity
= fromFlag
(configVerbosity cfg
)
844 -- | Adds the extra program paths from the flags provided to @configure@ as
845 -- well as specified locations for certain known programs and their default
847 mkProgramDb
:: ConfigFlags
-> ProgramDb
-> IO ProgramDb
848 mkProgramDb cfg initialProgramDb
= do
850 modifyProgramSearchPath
(getProgramSearchPath initialProgramDb
++)
851 <$> appendProgramSearchPath
(fromFlagOrDefault normal
(configVerbosity cfg
)) searchpath initialProgramDb
853 . userSpecifyArgss
(configProgramArgs cfg
)
854 . userSpecifyPaths
(configProgramPaths cfg
)
857 searchpath
= fromNubList
$ configProgramPathExtra cfg
859 -- Note. We try as much as possible to _prepend_ rather than postpend the extra-prog-path
860 -- so that we can override the system path. However, in a v2-build, at this point, the "system" path
861 -- has already been extended by both the built-tools-depends paths, as well as the program-path-extra
862 -- so for v2 builds adding it again is entirely unnecessary. However, it needs to get added again _anyway_
863 -- so as to take effect for v1 builds or standalone calls to Setup.hs
864 -- In this instance, the lesser evil is to not allow it to override the system path.
866 -- -----------------------------------------------------------------------------
867 -- Helper functions for configure
869 -- | Check if the user used any deprecated flags.
870 checkDeprecatedFlags
:: Verbosity
-> ConfigFlags
-> IO ()
871 checkDeprecatedFlags verbosity cfg
= do
872 unless (configProfExe cfg
== NoFlag
) $ do
873 let enable | fromFlag
(configProfExe cfg
) = "enable"
874 |
otherwise = "disable"
876 ("The flag --" ++ enable
++ "-executable-profiling is deprecated. "
877 ++ "Please use --" ++ enable
++ "-profiling instead.")
879 unless (configLibCoverage cfg
== NoFlag
) $ do
880 let enable | fromFlag
(configLibCoverage cfg
) = "enable"
881 |
otherwise = "disable"
883 ("The flag --" ++ enable
++ "-library-coverage is deprecated. "
884 ++ "Please use --" ++ enable
++ "-coverage instead.")
886 -- | Sanity check: if '--exact-configuration' was given, ensure that the
887 -- complete flag assignment was specified on the command line.
888 checkExactConfiguration
889 :: Verbosity
-> GenericPackageDescription
-> ConfigFlags
-> IO ()
890 checkExactConfiguration verbosity pkg_descr0 cfg
=
891 when (fromFlagOrDefault
False (configExactConfiguration cfg
)) $ do
892 let cmdlineFlags
= map fst (unFlagAssignment
(configConfigurationsFlags cfg
))
893 allFlags
= map flagName
. genPackageFlags
$ pkg_descr0
894 diffFlags
= allFlags
\\ cmdlineFlags
895 when (not . null $ diffFlags
) $
896 die
' verbosity
$ "'--exact-configuration' was given, "
897 ++ "but the following flags were not specified: "
898 ++ intercalate
", " (map show diffFlags
)
900 -- | Create a PackageIndex that makes *any libraries that might be*
901 -- defined internally to this package look like installed packages, in
902 -- case an executable should refer to any of them as dependencies.
904 -- It must be *any libraries that might be* defined rather than the
905 -- actual definitions, because these depend on conditionals in the .cabal
906 -- file, and we haven't resolved them yet. finalizePD
907 -- does the resolution of conditionals, and it takes internalPackageSet
908 -- as part of its input.
909 getInternalLibraries
:: GenericPackageDescription
911 getInternalLibraries pkg_descr0
=
912 -- TODO: some day, executables will be fair game here too!
913 let pkg_descr
= flattenPackageDescription pkg_descr0
914 in Set
.fromList
(map libName
(allLibraries pkg_descr
))
916 -- | Returns true if a dependency is satisfiable. This function may
917 -- report a dependency satisfiable even when it is not, but not vice
918 -- versa. This is to be passed to finalize
919 dependencySatisfiable
920 :: Bool -- ^ use external internal deps?
921 -> Bool -- ^ exact configuration?
922 -> Bool -- ^ allow depending on private libs?
924 -> InstalledPackageIndex
-- ^ installed set
925 -> Set LibraryName
-- ^ library components
926 -> Map
(PackageName
, ComponentName
) InstalledPackageInfo
927 -- ^ required dependencies
928 -> (Dependency
-> Bool)
929 dependencySatisfiable
930 use_external_internal_deps
933 pn installedPackageSet packageLibraries requiredDepsMap
934 (Dependency depName vr sublibs
)
936 -- When we're given '--exact-configuration', we assume that all
937 -- dependencies and flags are exactly specified on the command
938 -- line. Thus we only consult the 'requiredDepsMap'. Note that
939 -- we're not doing the version range check, so if there's some
940 -- dependency that wasn't specified on the command line,
941 -- 'finalizePD' will fail.
942 -- TODO: mention '--exact-configuration' in the error message
944 = if isInternalDep
&& not use_external_internal_deps
945 -- Except for internal deps, when we're NOT per-component mode;
946 -- those are just True.
947 then internalDepSatisfiable
949 -- Backward compatibility for the old sublibrary syntax
950 sublibs
== mainLibSet
952 (pn
, CLibName
$ LSubLibName
$
953 packageNameToUnqualComponentName depName
)
956 ||
all visible sublibs
959 = if use_external_internal_deps
960 -- When we are doing per-component configure, we now need to
961 -- test if the internal dependency is in the index. This has
962 -- DIFFERENT semantics from normal dependency satisfiability.
963 then internalDepSatisfiableExternally
964 -- If a 'PackageName' is defined by an internal component, the dep is
965 -- satisfiable (we're going to build it ourselves)
966 else internalDepSatisfiable
972 -- Internal dependency is when dependency is the same as package.
973 isInternalDep
= pn
== depName
976 not . null $ PackageIndex
.lookupDependency installedPackageSet depName vr
978 internalDepSatisfiable
=
979 Set
.isSubsetOf
(NES
.toSet sublibs
) packageLibraries
980 internalDepSatisfiableExternally
=
981 all (not . null . PackageIndex
.lookupInternalDependency installedPackageSet pn vr
) sublibs
983 -- Check whether a library exists and is visible.
984 -- We don't disambiguate between dependency on non-existent or private
985 -- library yet, so we just return a bool and later report a generic error.
987 False -- Does not even exist (wasn't in the depsMap)
988 (\ipi
-> IPI
.libVisibility ipi
== LibraryVisibilityPublic
989 -- If the override is enabled, the visibility does
990 -- not matter (it's handled externally)
991 || allow_private_deps
992 -- If it's a library of the same package then it's
994 -- This is only triggered when passing a component
995 -- of the same package as --dependency, such as in:
996 -- cabal-testsuite/PackageTests/ConfigureComponent/SubLib/setup-explicit.test.hs
997 || pkgName
(IPI
.sourcePackageId ipi
) == pn
)
999 where maybeIPI
= Map
.lookup (depName
, CLibName lib
) requiredDepsMap
1001 -- | Finalize a generic package description. The workhorse is
1002 -- 'finalizePD' but there's a bit of other nattering
1005 -- TODO: what exactly is the business with @flaggedTests@ and
1006 -- @flaggedBenchmarks@?
1007 configureFinalizedPackage
1010 -> ComponentRequestedSpec
1011 -> [PackageVersionConstraint
]
1012 -> (Dependency
-> Bool) -- ^ tests if a dependency is satisfiable.
1013 -- Might say it's satisfiable even when not.
1016 -> GenericPackageDescription
1017 -> IO (PackageDescription
, FlagAssignment
)
1018 configureFinalizedPackage verbosity cfg enabled
1019 allConstraints satisfies comp compPlatform pkg_descr0
= do
1021 (pkg_descr0
', flags
) <-
1023 (configConfigurationsFlags cfg
)
1030 of Right r
-> return r
1032 die
' verbosity
$ "Encountered missing or private dependencies:\n"
1033 ++ (render
. nest
4 . sep
. punctuate comma
1034 . map (pretty
. simplifyDependency
)
1037 -- add extra include/lib dirs as specified in cfg
1038 -- we do it here so that those get checked too
1039 let pkg_descr
= addExtraIncludeLibDirs pkg_descr0
'
1041 unless (nullFlagAssignment flags
) $
1042 info verbosity
$ "Flags chosen: "
1043 ++ intercalate
", " [ unFlagName fn
++ "=" ++ prettyShow
value
1044 |
(fn
, value) <- unFlagAssignment flags
]
1046 return (pkg_descr
, flags
)
1048 addExtraIncludeLibDirs pkg_descr
=
1049 let extraBi
= mempty
{ extraLibDirs
= configExtraLibDirs cfg
1050 , extraLibDirsStatic
= configExtraLibDirsStatic cfg
1051 , extraFrameworkDirs
= configExtraFrameworkDirs cfg
1052 , includeDirs
= configExtraIncludeDirs cfg
}
1053 modifyLib l
= l
{ libBuildInfo
= libBuildInfo l
1055 modifyExecutable e
= e
{ buildInfo
= buildInfo e
1057 modifyForeignLib f
= f
{ foreignLibBuildInfo
= foreignLibBuildInfo f
1059 modifyTestsuite t
= t
{ testBuildInfo
= testBuildInfo t
1061 modifyBenchmark b
= b
{ benchmarkBuildInfo
= benchmarkBuildInfo b
1064 { library
= modifyLib `
fmap` library pkg_descr
1065 , subLibraries
= modifyLib `
map` subLibraries pkg_descr
1066 , executables
= modifyExecutable `
map` executables pkg_descr
1067 , foreignLibs
= modifyForeignLib `
map` foreignLibs pkg_descr
1068 , testSuites
= modifyTestsuite `
map` testSuites pkg_descr
1069 , benchmarks
= modifyBenchmark `
map` benchmarks pkg_descr
1072 -- | Check for use of Cabal features which require compiler support
1073 checkCompilerProblems
1074 :: Verbosity
-> Compiler
-> PackageDescription
-> ComponentRequestedSpec
-> IO ()
1075 checkCompilerProblems verbosity comp pkg_descr enabled
= do
1076 unless (renamingPackageFlagsSupported comp ||
1077 all (all (isDefaultIncludeRenaming
. mixinIncludeRenaming
) . mixins
)
1078 (enabledBuildInfos pkg_descr enabled
)) $
1080 "Your compiler does not support thinning and renaming on "
1081 ++ "package flags. To use this feature you must use "
1082 ++ "GHC 7.9 or later."
1084 when (any (not.null.reexportedModules
) (allLibraries pkg_descr
)
1085 && not (reexportedModulesSupported comp
)) $
1087 "Your compiler does not support module re-exports. To use "
1088 ++ "this feature you must use GHC 7.9 or later."
1090 when (any (not.null.signatures
) (allLibraries pkg_descr
)
1091 && not (backpackSupported comp
)) $
1093 "Your compiler does not support Backpack. To use "
1094 ++ "this feature you must use GHC 8.1 or later."
1096 -- | Select dependencies for the package.
1097 configureDependencies
1099 -> UseExternalInternalDeps
1101 -> InstalledPackageIndex
-- ^ installed packages
1102 -> Map
(PackageName
, ComponentName
) InstalledPackageInfo
-- ^ required deps
1103 -> PackageDescription
1104 -> ComponentRequestedSpec
1105 -> IO [PreExistingComponent
]
1106 configureDependencies verbosity use_external_internal_deps
1107 packageLibraries installedPackageSet requiredDepsMap pkg_descr enableSpec
= do
1108 let failedDeps
:: [FailedDependency
]
1109 allPkgDeps
:: [ResolvedDependency
]
1110 (failedDeps
, allPkgDeps
) = partitionEithers
$ concat
1111 [ fmap (\s
-> (dep
, s
)) <$> status
1112 | dep
<- enabledBuildDepends pkg_descr enableSpec
1113 , let status
= selectDependency
(package pkg_descr
)
1114 packageLibraries installedPackageSet
1115 requiredDepsMap use_external_internal_deps dep
]
1117 internalPkgDeps
= [ pkgid
1118 |
(_
, InternalDependency pkgid
) <- allPkgDeps
]
1119 -- NB: we have to SAVE the package name, because this is the only
1120 -- way we can be able to resolve package names in the package
1122 externalPkgDeps
= [ pec
1123 |
(_
, ExternalDependency pec
) <- allPkgDeps
]
1125 when (not (null internalPkgDeps
)
1126 && not (newPackageDepsBehaviour pkg_descr
)) $
1127 die
' verbosity
$ "The field 'build-depends: "
1128 ++ intercalate
", " (map (prettyShow
. packageName
) internalPkgDeps
)
1129 ++ "' refers to a library which is defined within the same "
1130 ++ "package. To use this feature the package must specify at "
1131 ++ "least 'cabal-version: >= 1.8'."
1133 reportFailedDependencies verbosity failedDeps
1134 reportSelectedDependencies verbosity allPkgDeps
1136 return externalPkgDeps
1138 -- | Select and apply coverage settings for the build based on the
1139 -- 'ConfigFlags' and 'Compiler'.
1140 configureCoverage
:: Verbosity
-> ConfigFlags
-> Compiler
1141 -> IO (LocalBuildInfo
-> LocalBuildInfo
)
1142 configureCoverage verbosity cfg comp
= do
1143 let tryExeCoverage
= fromFlagOrDefault
False (configCoverage cfg
)
1144 tryLibCoverage
= fromFlagOrDefault tryExeCoverage
1145 (mappend
(configCoverage cfg
) (configLibCoverage cfg
))
1146 if coverageSupported comp
1148 let apply lbi
= lbi
{ libCoverage
= tryLibCoverage
1149 , exeCoverage
= tryExeCoverage
1153 let apply lbi
= lbi
{ libCoverage
= False
1154 , exeCoverage
= False
1156 when (tryExeCoverage || tryLibCoverage
) $ warn verbosity
1157 ("The compiler " ++ showCompilerId comp
++ " does not support "
1158 ++ "program coverage. Program coverage has been disabled.")
1161 -- | Compute the effective value of the profiling flags
1162 -- @--enable-library-profiling@ and @--enable-executable-profiling@
1163 -- from the specified 'ConfigFlags'. This may be useful for
1164 -- external Cabal tools which need to interact with Setup in
1165 -- a backwards-compatible way: the most predictable mechanism
1166 -- for enabling profiling across many legacy versions is to
1167 -- NOT use @--enable-profiling@ and use those two flags instead.
1169 -- Note that @--enable-executable-profiling@ also affects profiling
1170 -- of benchmarks and (non-detailed) test suites.
1171 computeEffectiveProfiling
:: ConfigFlags
-> (Bool {- lib -}, Bool {- exe -})
1172 computeEffectiveProfiling cfg
=
1173 -- The --profiling flag sets the default for both libs and exes,
1174 -- but can be overridden by --library-profiling, or the old deprecated
1175 -- --executable-profiling flag.
1177 -- The --profiling-detail and --library-profiling-detail flags behave
1179 let tryExeProfiling
= fromFlagOrDefault
False
1180 (mappend
(configProf cfg
) (configProfExe cfg
))
1181 tryLibProfiling
= fromFlagOrDefault tryExeProfiling
1182 (mappend
(configProf cfg
) (configProfLib cfg
))
1183 in (tryLibProfiling
, tryExeProfiling
)
1185 -- | Select and apply profiling settings for the build based on the
1186 -- 'ConfigFlags' and 'Compiler'.
1187 configureProfiling
:: Verbosity
-> ConfigFlags
-> Compiler
1188 -> IO (LocalBuildInfo
-> LocalBuildInfo
)
1189 configureProfiling verbosity cfg comp
= do
1190 let (tryLibProfiling
, tryExeProfiling
) = computeEffectiveProfiling cfg
1192 tryExeProfileLevel
= fromFlagOrDefault ProfDetailDefault
1193 (configProfDetail cfg
)
1194 tryLibProfileLevel
= fromFlagOrDefault ProfDetailDefault
1196 (configProfDetail cfg
)
1197 (configProfLibDetail cfg
))
1199 checkProfileLevel
(ProfDetailOther other
) = do
1201 ("Unknown profiling detail level '" ++ other
1202 ++ "', using default.\nThe profiling detail levels are: "
1204 [ name |
(name
, _
, _
) <- knownProfDetailLevels
])
1205 return ProfDetailDefault
1206 checkProfileLevel other
= return other
1208 (exeProfWithoutLibProf
, applyProfiling
) <-
1209 if profilingSupported comp
1211 exeLevel
<- checkProfileLevel tryExeProfileLevel
1212 libLevel
<- checkProfileLevel tryLibProfileLevel
1213 let apply lbi
= lbi
{ withProfLib
= tryLibProfiling
1214 , withProfLibDetail
= libLevel
1215 , withProfExe
= tryExeProfiling
1216 , withProfExeDetail
= exeLevel
1218 return (tryExeProfiling
&& not tryLibProfiling
, apply
)
1220 let apply lbi
= lbi
{ withProfLib
= False
1221 , withProfLibDetail
= ProfDetailNone
1222 , withProfExe
= False
1223 , withProfExeDetail
= ProfDetailNone
1225 when (tryExeProfiling || tryLibProfiling
) $ warn verbosity
1226 ("The compiler " ++ showCompilerId comp
++ " does not support "
1227 ++ "profiling. Profiling has been disabled.")
1228 return (False, apply
)
1230 when exeProfWithoutLibProf
$ warn verbosity
1231 ("Executables will be built with profiling, but library "
1232 ++ "profiling is disabled. Linking will fail if any executables "
1233 ++ "depend on the library.")
1235 return applyProfiling
1237 -- -----------------------------------------------------------------------------
1238 -- Configuring package dependencies
1240 reportProgram
:: Verbosity
-> Program
-> Maybe ConfiguredProgram
-> IO ()
1241 reportProgram verbosity prog Nothing
1242 = info verbosity
$ "No " ++ programName prog
++ " found"
1243 reportProgram verbosity prog
(Just configuredProg
)
1244 = info verbosity
$ "Using " ++ programName prog
++ version
++ location
1245 where location
= case programLocation configuredProg
of
1246 FoundOnSystem p
-> " found on system at: " ++ p
1247 UserSpecified p
-> " given by user at: " ++ p
1248 version
= case programVersion configuredProg
of
1250 Just v
-> " version " ++ prettyShow v
1252 hackageUrl
:: String
1253 hackageUrl
= "http://hackage.haskell.org/package/"
1255 type ResolvedDependency
= (Dependency
, DependencyResolution
)
1257 data DependencyResolution
1258 -- | An external dependency from the package database, OR an
1259 -- internal dependency which we are getting from the package
1261 = ExternalDependency PreExistingComponent
1262 -- | An internal dependency ('PackageId' should be a library name)
1263 -- which we are going to have to build. (The
1264 -- 'PackageId' here is a hack to get a modest amount of
1265 -- polymorphism out of the 'Package' typeclass.)
1266 | InternalDependency PackageId
1268 data FailedDependency
= DependencyNotExists PackageName
1269 | DependencyMissingInternal PackageName LibraryName
1270 | DependencyNoVersion Dependency
1272 -- | Test for a package dependency and record the version we have installed.
1273 selectDependency
:: PackageId
-- ^ Package id of current package
1274 -> Set LibraryName
-- ^ package libraries
1275 -> InstalledPackageIndex
-- ^ Installed packages
1276 -> Map
(PackageName
, ComponentName
) InstalledPackageInfo
1277 -- ^ Packages for which we have been given specific deps to
1279 -> UseExternalInternalDeps
-- ^ Are we configuring a
1280 -- single component?
1282 -> [Either FailedDependency DependencyResolution
]
1283 selectDependency pkgid internalIndex installedIndex requiredDepsMap
1284 use_external_internal_deps
1285 (Dependency dep_pkgname vr libs
) =
1286 -- If the dependency specification matches anything in the internal package
1287 -- index, then we prefer that match to anything in the second.
1294 -- Executable my-exec
1295 -- build-depends: MyLibrary
1297 -- We want "build-depends: MyLibrary" always to match the internal library
1298 -- even if there is a newer installed library "MyLibrary-0.2".
1299 if dep_pkgname
== pn
1301 if use_external_internal_deps
1302 then do_external_internal
<$> NES
.toList libs
1303 else do_internal
<$> NES
.toList libs
1305 do_external_external
<$> NES
.toList libs
1307 pn
= packageName pkgid
1309 -- It's an internal library, and we're not per-component build
1311 | Set
.member lib internalIndex
1312 = Right
$ InternalDependency
$ PackageIdentifier dep_pkgname
$ packageVersion pkgid
1315 = Left
$ DependencyMissingInternal dep_pkgname lib
1317 -- We have to look it up externally
1318 do_external_external
:: LibraryName
-> Either FailedDependency DependencyResolution
1319 do_external_external lib
= do
1320 ipi
<- case Map
.lookup (dep_pkgname
, CLibName lib
) requiredDepsMap
of
1321 -- If we know the exact pkg to use, then use it.
1322 Just pkginstance
-> Right pkginstance
1323 -- Otherwise we just pick an arbitrary instance of the latest version.
1324 Nothing
-> case pickLastIPI
$ PackageIndex
.lookupInternalDependency installedIndex dep_pkgname vr lib
of
1325 Nothing
-> Left
(DependencyNotExists dep_pkgname
)
1326 Just pkg
-> Right pkg
1327 return $ ExternalDependency
$ ipiToPreExistingComponent ipi
1329 do_external_internal
:: LibraryName
-> Either FailedDependency DependencyResolution
1330 do_external_internal lib
= do
1331 ipi
<- case Map
.lookup (dep_pkgname
, CLibName lib
) requiredDepsMap
of
1332 -- If we know the exact pkg to use, then use it.
1333 Just pkginstance
-> Right pkginstance
1334 Nothing
-> case pickLastIPI
$ PackageIndex
.lookupInternalDependency installedIndex pn vr lib
of
1335 -- It's an internal library, being looked up externally
1336 Nothing
-> Left
(DependencyMissingInternal dep_pkgname lib
)
1337 Just pkg
-> Right pkg
1338 return $ ExternalDependency
$ ipiToPreExistingComponent ipi
1340 pickLastIPI
:: [(Version
, [InstalledPackageInfo
])] -> Maybe InstalledPackageInfo
1341 pickLastIPI pkgs
= safeHead
. snd . last =<< nonEmpty pkgs
1343 reportSelectedDependencies
:: Verbosity
1344 -> [ResolvedDependency
] -> IO ()
1345 reportSelectedDependencies verbosity deps
=
1346 info verbosity
$ unlines
1347 [ "Dependency " ++ prettyShow
(simplifyDependency dep
)
1348 ++ ": using " ++ prettyShow pkgid
1349 |
(dep
, resolution
) <- deps
1350 , let pkgid
= case resolution
of
1351 ExternalDependency pkg
' -> packageId pkg
'
1352 InternalDependency pkgid
' -> pkgid
' ]
1354 reportFailedDependencies
:: Verbosity
-> [FailedDependency
] -> IO ()
1355 reportFailedDependencies _
[] = return ()
1356 reportFailedDependencies verbosity failed
=
1357 die
' verbosity
(intercalate
"\n\n" (map reportFailedDependency failed
))
1360 reportFailedDependency
(DependencyNotExists pkgname
) =
1361 "there is no version of " ++ prettyShow pkgname
++ " installed.\n"
1362 ++ "Perhaps you need to download and install it from\n"
1363 ++ hackageUrl
++ prettyShow pkgname
++ "?"
1365 reportFailedDependency
(DependencyMissingInternal pkgname lib
) =
1366 "internal dependency " ++ prettyShow
(prettyLibraryNameComponent lib
) ++ " not installed.\n"
1367 ++ "Perhaps you need to configure and install it first?\n"
1368 ++ "(This library was defined by " ++ prettyShow pkgname
++ ")"
1370 reportFailedDependency
(DependencyNoVersion dep
) =
1371 "cannot satisfy dependency " ++ prettyShow
(simplifyDependency dep
) ++ "\n"
1373 -- | List all installed packages in the given package databases.
1374 -- Non-existent package databases do not cause errors, they just get skipped
1375 -- with a warning and treated as empty ones, since technically they do not
1376 -- contain any package.
1377 getInstalledPackages
:: Verbosity
-> Compiler
1378 -> PackageDBStack
-- ^ The stack of package databases.
1380 -> IO InstalledPackageIndex
1381 getInstalledPackages verbosity comp packageDBs progdb
= do
1382 when (null packageDBs
) $
1383 die
' verbosity
$ "No package databases have been specified. If you use "
1384 ++ "--package-db=clear, you must follow it with --package-db= "
1385 ++ "with 'global', 'user' or a specific file."
1387 info verbosity
"Reading installed packages..."
1388 -- do not check empty packagedbs (ghc-pkg would error out)
1389 packageDBs
' <- filterM packageDBExists packageDBs
1390 case compilerFlavor comp
of
1391 GHC
-> GHC
.getInstalledPackages verbosity comp packageDBs
' progdb
1392 GHCJS
-> GHCJS
.getInstalledPackages verbosity packageDBs
' progdb
1393 UHC
-> UHC
.getInstalledPackages verbosity comp packageDBs
' progdb
1395 HaskellSuite
.getInstalledPackages verbosity packageDBs
' progdb
1396 flv
-> die
' verbosity
$ "don't know how to find the installed packages for "
1399 packageDBExists
(SpecificPackageDB path
) = do
1400 exists
<- doesPathExist path
1402 warn verbosity
$ "Package db " <> path
<> " does not exist yet"
1404 -- Checking the user and global package dbs is more complicated and needs
1405 -- way more data. Also ghc-pkg won't error out unless the user/global
1406 -- pkgdb is overridden with an empty one, so we just don't check for them.
1407 packageDBExists UserPackageDB
= pure
True
1408 packageDBExists GlobalPackageDB
= pure
True
1410 -- | Like 'getInstalledPackages', but for a single package DB.
1412 -- NB: Why isn't this always a fall through to 'getInstalledPackages'?
1413 -- That is because 'getInstalledPackages' performs some sanity checks
1414 -- on the package database stack in question. However, when sandboxes
1415 -- are involved these sanity checks are not desirable.
1416 getPackageDBContents
:: Verbosity
-> Compiler
1417 -> PackageDB
-> ProgramDb
1418 -> IO InstalledPackageIndex
1419 getPackageDBContents verbosity comp packageDB progdb
= do
1420 info verbosity
"Reading installed packages..."
1421 case compilerFlavor comp
of
1422 GHC
-> GHC
.getPackageDBContents verbosity packageDB progdb
1423 GHCJS
-> GHCJS
.getPackageDBContents verbosity packageDB progdb
1424 -- For other compilers, try to fall back on 'getInstalledPackages'.
1425 _
-> getInstalledPackages verbosity comp
[packageDB
] progdb
1428 -- | A set of files (or directories) that can be monitored to detect when
1429 -- there might have been a change in the installed packages.
1431 getInstalledPackagesMonitorFiles
:: Verbosity
-> Compiler
1433 -> ProgramDb
-> Platform
1435 getInstalledPackagesMonitorFiles verbosity comp packageDBs progdb platform
=
1436 case compilerFlavor comp
of
1437 GHC
-> GHC
.getInstalledPackagesMonitorFiles
1438 verbosity platform progdb packageDBs
1440 warn verbosity
$ "don't know how to find change monitoring files for "
1441 ++ "the installed package databases for " ++ prettyShow other
1444 -- | The user interface specifies the package dbs to use with a combination of
1445 -- @--global@, @--user@ and @--package-db=global|user|clear|$file@.
1446 -- This function combines the global/user flag and interprets the package-db
1447 -- flag into a single package db stack.
1449 interpretPackageDbFlags
:: Bool -> [Maybe PackageDB
] -> PackageDBStack
1450 interpretPackageDbFlags userInstall
= extra initialStack
1452 initialStack | userInstall
= [GlobalPackageDB
, UserPackageDB
]
1453 |
otherwise = [GlobalPackageDB
]
1455 extra dbs
' [] = dbs
'
1456 extra _
(Nothing
:dbs
) = extra
[] dbs
1457 extra dbs
' (Just db
:dbs
) = extra
(dbs
' ++ [db
]) dbs
1459 -- We are given both --constraint="foo < 2.0" style constraints and also
1460 -- specific packages to pick via --dependency="foo=foo-2.0-177d5cdf20962d0581".
1462 -- When finalising the package we have to take into account the specific
1463 -- installed deps we've been given, and the finalise function expects
1464 -- constraints, so we have to translate these deps into version constraints.
1466 -- But after finalising we then have to make sure we pick the right specific
1467 -- deps in the end. So we still need to remember which installed packages to
1470 :: [PackageVersionConstraint
]
1472 -> InstalledPackageIndex
1473 -> Either String ([PackageVersionConstraint
],
1474 Map
(PackageName
, ComponentName
) InstalledPackageInfo
)
1475 combinedConstraints constraints dependencies installedPackages
= do
1477 when (not (null badComponentIds
)) $
1478 Left
$ render
$ text
"The following package dependencies were requested"
1479 $+$ nest
4 (dispDependencies badComponentIds
)
1480 $+$ text
"however the given installed package instance does not exist."
1482 --TODO: we don't check that all dependencies are used!
1484 return (allConstraints
, idConstraintMap
)
1487 allConstraints
:: [PackageVersionConstraint
]
1488 allConstraints
= constraints
1489 ++ [ thisPackageVersionConstraint
(packageId pkg
)
1490 |
(_
, _
, _
, Just pkg
) <- dependenciesPkgInfo
]
1492 idConstraintMap
:: Map
(PackageName
, ComponentName
) InstalledPackageInfo
1493 idConstraintMap
= Map
.fromList
1494 -- NB: do NOT use the packageName from
1495 -- dependenciesPkgInfo!
1496 [ ((pn
, cname
), pkg
)
1497 |
(pn
, cname
, _
, Just pkg
) <- dependenciesPkgInfo
]
1499 -- The dependencies along with the installed package info, if it exists
1500 dependenciesPkgInfo
:: [(PackageName
, ComponentName
, ComponentId
,
1501 Maybe InstalledPackageInfo
)]
1502 dependenciesPkgInfo
=
1503 [ (pkgname
, CLibName lname
, cid
, mpkg
)
1504 | GivenComponent pkgname lname cid
<- dependencies
1505 , let mpkg
= PackageIndex
.lookupComponentId
1506 installedPackages cid
1509 -- If we looked up a package specified by an installed package id
1510 -- (i.e. someone has written a hash) and didn't find it then it's
1513 [ (pkgname
, cname
, cid
)
1514 |
(pkgname
, cname
, cid
, Nothing
) <- dependenciesPkgInfo
]
1516 dispDependencies deps
=
1517 hsep
[ text
"--dependency="
1521 CLibName LMainLibName
-> ""
1522 CLibName
(LSubLibName n
) -> ":" <<>> pretty n
1523 _
-> ":" <<>> pretty cname
1526 |
(pkgname
, cname
, cid
) <- deps
]
1528 -- -----------------------------------------------------------------------------
1529 -- Configuring program dependencies
1531 configureRequiredPrograms
:: Verbosity
-> [LegacyExeDependency
] -> ProgramDb
1533 configureRequiredPrograms verbosity deps progdb
=
1534 foldM (configureRequiredProgram verbosity
) progdb deps
1536 -- | Configure a required program, ensuring that it exists in the PATH
1537 -- (or where the user has specified the program must live) and making it
1538 -- available for use via the 'ProgramDb' interface. If the program is
1539 -- known (exists in the input 'ProgramDb'), we will make sure that the
1540 -- program matches the required version; otherwise we will accept
1541 -- any version of the program and assume that it is a simpleProgram.
1542 configureRequiredProgram
:: Verbosity
-> ProgramDb
-> LegacyExeDependency
1544 configureRequiredProgram verbosity progdb
1545 (LegacyExeDependency progName verRange
) =
1546 case lookupKnownProgram progName progdb
of
1548 -- Try to configure it as a 'simpleProgram' automatically
1550 -- There's a bit of a story behind this line. In old versions
1551 -- of Cabal, there were only internal build-tools dependencies. So the
1552 -- behavior in this case was:
1554 -- - If a build-tool dependency was internal, don't do
1557 -- - If it was external, call 'configureRequiredProgram' to
1558 -- "configure" the executable. In particular, if
1559 -- the program was not "known" (present in 'ProgramDb'),
1560 -- then we would just error. This was fine, because
1561 -- the only way a program could be executed from 'ProgramDb'
1562 -- is if some library code from Cabal actually called it,
1563 -- and the pre-existing Cabal code only calls known
1564 -- programs from 'defaultProgramDb', and so if it
1565 -- is calling something else, you have a Custom setup
1566 -- script, and in that case you are expected to register
1567 -- the program you want to call in the ProgramDb.
1569 -- OK, so that was fine, until I (ezyang, in 2016) refactored
1570 -- Cabal to support per-component builds. In this case, what
1571 -- was previously an internal build-tool dependency now became
1572 -- an external one, and now previously "internal" dependencies
1573 -- are now external. But these are permitted to exist even
1574 -- when they are not previously configured (something that
1575 -- can only occur by a Custom script.)
1577 -- So, I decided, "Fine, let's just accept these in any
1578 -- case." Thus this line. The alternative would have been to
1579 -- somehow detect when a build-tools dependency was "internal" (by
1580 -- looking at the unflattened package description) but this
1581 -- would also be incompatible with future work to support
1582 -- external executable dependencies: we definitely cannot
1583 -- assume they will be preinitialized in the 'ProgramDb'.
1584 configureProgram verbosity
(simpleProgram progName
) progdb
1586 -- requireProgramVersion always requires the program have a version
1587 -- but if the user says "build-depends: foo" ie no version constraint
1588 -- then we should not fail if we cannot discover the program version.
1589 | verRange
== anyVersion
-> do
1590 (_
, progdb
') <- requireProgram verbosity prog progdb
1593 (_
, _
, progdb
') <- requireProgramVersion verbosity prog verRange progdb
1596 -- -----------------------------------------------------------------------------
1597 -- Configuring pkg-config package dependencies
1599 configurePkgconfigPackages
:: Verbosity
-> PackageDescription
1600 -> ProgramDb
-> ComponentRequestedSpec
1601 -> IO (PackageDescription
, ProgramDb
)
1602 configurePkgconfigPackages verbosity pkg_descr progdb enabled
1603 |
null allpkgs
= return (pkg_descr
, progdb
)
1605 (_
, _
, progdb
') <- requireProgramVersion
1606 (lessVerbose verbosity
) pkgConfigProgram
1607 (orLaterVersion
$ mkVersion
[0,9,0]) progdb
1608 traverse_ requirePkg allpkgs
1609 mlib
' <- traverse addPkgConfigBILib
(library pkg_descr
)
1610 libs
' <- traverse addPkgConfigBILib
(subLibraries pkg_descr
)
1611 exes
' <- traverse addPkgConfigBIExe
(executables pkg_descr
)
1612 tests
' <- traverse addPkgConfigBITest
(testSuites pkg_descr
)
1613 benches
' <- traverse addPkgConfigBIBench
(benchmarks pkg_descr
)
1614 let pkg_descr
' = pkg_descr
{ library
= mlib
',
1615 subLibraries
= libs
', executables
= exes
',
1616 testSuites
= tests
', benchmarks
= benches
' }
1617 return (pkg_descr
', progdb
')
1620 allpkgs
= concatMap pkgconfigDepends
(enabledBuildInfos pkg_descr enabled
)
1621 pkgconfig
= getDbProgramOutput
(lessVerbose verbosity
)
1622 pkgConfigProgram progdb
1624 requirePkg dep
@(PkgconfigDependency pkgn
range) = do
1625 version
<- pkgconfig
["--modversion", pkg
]
1626 `catchIO`
(\_
-> die
' verbosity notFound
)
1627 `catchExit`
(\_
-> die
' verbosity notFound
)
1628 let trim
= dropWhile isSpace . dropWhileEnd
isSpace
1629 let v
= PkgconfigVersion
(toUTF8BS
$ trim version
)
1630 if not (withinPkgconfigVersionRange v
range)
1631 then die
' verbosity
(badVersion v
)
1632 else info verbosity
(depSatisfied v
)
1634 notFound
= "The pkg-config package '" ++ pkg
++ "'"
1635 ++ versionRequirement
1636 ++ " is required but it could not be found."
1637 badVersion v
= "The pkg-config package '" ++ pkg
++ "'"
1638 ++ versionRequirement
1639 ++ " is required but the version installed on the"
1640 ++ " system is version " ++ prettyShow v
1641 depSatisfied v
= "Dependency " ++ prettyShow dep
1642 ++ ": using version " ++ prettyShow v
1645 | isAnyPkgconfigVersion
range = ""
1646 |
otherwise = " version " ++ prettyShow
range
1648 pkg
= unPkgconfigName pkgn
1650 -- Adds pkgconfig dependencies to the build info for a component
1651 addPkgConfigBI compBI setCompBI comp
= do
1652 bi
<- pkgconfigBuildInfo
(pkgconfigDepends
(compBI comp
))
1653 return $ setCompBI comp
(compBI comp `mappend` bi
)
1655 -- Adds pkgconfig dependencies to the build info for a library
1656 addPkgConfigBILib
= addPkgConfigBI libBuildInfo
$
1657 \lib bi
-> lib
{ libBuildInfo
= bi
}
1659 -- Adds pkgconfig dependencies to the build info for an executable
1660 addPkgConfigBIExe
= addPkgConfigBI buildInfo
$
1661 \exe bi
-> exe
{ buildInfo
= bi
}
1663 -- Adds pkgconfig dependencies to the build info for a test suite
1664 addPkgConfigBITest
= addPkgConfigBI testBuildInfo
$
1665 \test bi
-> test
{ testBuildInfo
= bi
}
1667 -- Adds pkgconfig dependencies to the build info for a benchmark
1668 addPkgConfigBIBench
= addPkgConfigBI benchmarkBuildInfo
$
1669 \bench bi
-> bench
{ benchmarkBuildInfo
= bi
}
1671 pkgconfigBuildInfo
:: [PkgconfigDependency
] -> IO BuildInfo
1672 pkgconfigBuildInfo
[] = return mempty
1673 pkgconfigBuildInfo pkgdeps
= do
1674 let pkgs
= nub [ prettyShow pkg | PkgconfigDependency pkg _
<- pkgdeps
]
1675 ccflags
<- pkgconfig
("--cflags" : pkgs
)
1676 ldflags
<- pkgconfig
("--libs" : pkgs
)
1677 ldflags_static
<- pkgconfig
("--libs" : "--static" : pkgs
)
1678 return (ccLdOptionsBuildInfo
(words ccflags
) (words ldflags
) (words ldflags_static
))
1680 -- | Makes a 'BuildInfo' from C compiler and linker flags.
1682 -- This can be used with the output from configuration programs like pkg-config
1683 -- and similar package-specific programs like mysql-config, freealut-config etc.
1686 -- > ccflags <- getDbProgramOutput verbosity prog progdb ["--cflags"]
1687 -- > ldflags <- getDbProgramOutput verbosity prog progdb ["--libs"]
1688 -- > ldflags_static <- getDbProgramOutput verbosity prog progdb ["--libs", "--static"]
1689 -- > return (ccldOptionsBuildInfo (words ccflags) (words ldflags) (words ldflags_static))
1691 ccLdOptionsBuildInfo
:: [String] -> [String] -> [String] -> BuildInfo
1692 ccLdOptionsBuildInfo cflags ldflags ldflags_static
=
1693 let (includeDirs
', cflags
') = partition ("-I" `
isPrefixOf`
) cflags
1694 (extraLibs
', ldflags
') = partition ("-l" `
isPrefixOf`
) ldflags
1695 (extraLibDirs
', ldflags
'') = partition ("-L" `
isPrefixOf`
) ldflags
'
1696 extraLibsStatic
' = filter ("-l" `
isPrefixOf`
) ldflags_static
1697 extraLibDirsStatic
' = filter ("-L" `
isPrefixOf`
) ldflags_static
1699 includeDirs
= map (drop 2) includeDirs
',
1700 extraLibs
= map (drop 2) extraLibs
',
1701 extraLibDirs
= map (drop 2) extraLibDirs
',
1702 extraLibsStatic
= map (drop 2) extraLibsStatic
',
1703 extraLibDirsStatic
= map (drop 2) extraLibDirsStatic
',
1704 ccOptions
= cflags
',
1705 ldOptions
= ldflags
''
1708 -- -----------------------------------------------------------------------------
1709 -- Determining the compiler details
1711 configCompilerAuxEx
:: ConfigFlags
1712 -> IO (Compiler
, Platform
, ProgramDb
)
1713 configCompilerAuxEx cfg
= do
1714 programDb
<- mkProgramDb cfg defaultProgramDb
1715 configCompilerEx
(flagToMaybe
$ configHcFlavor cfg
)
1716 (flagToMaybe
$ configHcPath cfg
)
1717 (flagToMaybe
$ configHcPkg cfg
)
1719 (fromFlag
(configVerbosity cfg
))
1721 configCompilerEx
:: Maybe CompilerFlavor
-> Maybe FilePath -> Maybe FilePath
1722 -> ProgramDb
-> Verbosity
1723 -> IO (Compiler
, Platform
, ProgramDb
)
1724 configCompilerEx Nothing _ _ _ verbosity
= die
' verbosity
"Unknown compiler"
1725 configCompilerEx
(Just hcFlavor
) hcPath hcPkg progdb verbosity
= do
1726 (comp
, maybePlatform
, programDb
) <- case hcFlavor
of
1727 GHC
-> GHC
.configure verbosity hcPath hcPkg progdb
1728 GHCJS
-> GHCJS
.configure verbosity hcPath hcPkg progdb
1729 UHC
-> UHC
.configure verbosity hcPath hcPkg progdb
1730 HaskellSuite
{} -> HaskellSuite
.configure verbosity hcPath hcPkg progdb
1731 _
-> die
' verbosity
"Unknown compiler"
1732 return (comp
, fromMaybe buildPlatform maybePlatform
, programDb
)
1734 -- -----------------------------------------------------------------------------
1735 -- Testing C lib and header dependencies
1737 -- Try to build a test C program which includes every header and links every
1738 -- lib. If that fails, try to narrow it down by preprocessing (only) and linking
1739 -- with individual headers and libs. If none is the obvious culprit then give a
1740 -- generic error message.
1741 -- TODO: produce a log file from the compiler errors, if any.
1742 checkForeignDeps
:: PackageDescription
-> LocalBuildInfo
-> Verbosity
-> IO ()
1743 checkForeignDeps pkg lbi verbosity
=
1744 ifBuildsWith allHeaders
(commonCcArgs
++ makeLdArgs allLibs
) -- I'm feeling
1747 (do missingLibs
<- findMissingLibs
1748 missingHdr
<- findOffendingHdr
1749 explainErrors missingHdr missingLibs
)
1751 allHeaders
= collectField includes
1752 allLibs
= collectField
$
1753 if withFullyStaticExe lbi
1754 then extraLibsStatic
1757 ifBuildsWith headers args success failure
= do
1758 checkDuplicateHeaders
1759 ok
<- builds
(makeProgram headers
) args
1760 if ok
then success
else failure
1762 -- Ensure that there is only one header with a given name
1763 -- in either the generated (most likely by `configure`)
1764 -- build directory (e.g. `dist/build`) or in the source directory.
1766 -- If it exists in both, we'll remove the one in the source
1767 -- directory, as the generated should take precedence.
1769 -- C compilers like to prefer source local relative includes,
1770 -- so the search paths provided to the compiler via -I are
1771 -- ignored if the included file can be found relative to the
1772 -- including file. As such we need to take drastic measures
1773 -- and delete the offending file in the source directory.
1774 checkDuplicateHeaders
= do
1775 let relIncDirs
= filter (not . isAbsolute
) (collectField includeDirs
)
1776 isHeader
= isSuffixOf ".h"
1777 genHeaders
<- for relIncDirs
$ \dir
->
1778 fmap (dir
</>) . filter isHeader
<$>
1779 listDirectory
(buildDir lbi
</> dir
) `catchIO`
(\_
-> return [])
1780 srcHeaders
<- for relIncDirs
$ \dir
->
1781 fmap (dir
</>) . filter isHeader
<$>
1782 listDirectory
(baseDir lbi
</> dir
) `catchIO`
(\_
-> return [])
1783 let commonHeaders
= concat genHeaders `
intersect`
concat srcHeaders
1784 for_ commonHeaders
$ \hdr
-> do
1785 warn verbosity
$ "Duplicate header found in "
1786 ++ (buildDir lbi
</> hdr
)
1788 ++ (baseDir lbi
</> hdr
)
1790 ++ (baseDir lbi
</> hdr
)
1791 removeFile (baseDir lbi
</> hdr
)
1794 ifBuildsWith allHeaders ccArgs
1796 (go
. tail . NEL
.inits $ allHeaders
)
1798 go
[] = return Nothing
-- cannot happen
1799 go
(hdrs
:hdrsInits
) =
1800 -- Try just preprocessing first
1801 ifBuildsWith hdrs cppArgs
1802 -- If that works, try compiling too
1803 (ifBuildsWith hdrs ccArgs
1805 (return . fmap Right
. safeLast
$ hdrs
))
1806 (return . fmap Left
. safeLast
$ hdrs
)
1809 cppArgs
= "-E":commonCppArgs
-- preprocess only
1810 ccArgs
= "-c":commonCcArgs
-- don't try to link
1812 findMissingLibs
= ifBuildsWith
[] (makeLdArgs allLibs
)
1814 (filterM (fmap not . libExists
) allLibs
)
1816 libExists lib
= builds
(makeProgram
[]) (makeLdArgs
[lib
])
1818 baseDir lbi
' = fromMaybe "." (takeDirectory
<$> cabalFilePath lbi
')
1820 commonCppArgs
= platformDefines lbi
1821 -- TODO: This is a massive hack, to work around the
1822 -- fact that the test performed here should be
1823 -- PER-component (c.f. the "I'm Feeling Lucky"; we
1824 -- should NOT be glomming everything together.)
1825 ++ [ "-I" ++ buildDir lbi
</> "autogen" ]
1826 -- `configure' may generate headers in the build directory
1827 ++ [ "-I" ++ buildDir lbi
</> dir
1828 | dir
<- ordNub
(collectField includeDirs
)
1829 , not (isAbsolute dir
)]
1830 -- we might also reference headers from the
1831 -- packages directory.
1832 ++ [ "-I" ++ baseDir lbi
</> dir
1833 | dir
<- ordNub
(collectField includeDirs
)
1834 , not (isAbsolute dir
)]
1835 ++ [ "-I" ++ dir | dir
<- ordNub
(collectField includeDirs
)
1837 ++ ["-I" ++ baseDir lbi
]
1838 ++ collectField cppOptions
1839 ++ collectField ccOptions
1841 | dir
<- ordNub
[ dir
1843 , dir
<- IPI
.includeDirs dep
]
1844 -- dedupe include dirs of dependencies
1845 -- to prevent quadratic blow-up
1849 , opt
<- IPI
.ccOptions dep
]
1851 commonCcArgs
= commonCppArgs
1852 ++ collectField ccOptions
1855 , opt
<- IPI
.ccOptions dep
]
1857 commonLdArgs
= [ "-L" ++ dir
1858 | dir
<- ordNub
$ collectField
(if withFullyStaticExe lbi
1859 then extraLibDirsStatic
1862 ++ collectField ldOptions
1864 | dir
<- ordNub
[ dir
1866 , dir
<- if withFullyStaticExe lbi
1867 then IPI
.libraryDirsStatic dep
1868 else IPI
.libraryDirs dep
]
1870 --TODO: do we also need dependent packages' ld options?
1871 makeLdArgs libs
= [ "-l"++lib | lib
<- libs
] ++ commonLdArgs
1873 makeProgram hdrs
= unlines $
1874 [ "#include \"" ++ hdr
++ "\"" | hdr
<- hdrs
] ++
1875 ["int main(int argc, char** argv) { return 0; }"]
1877 collectField f
= concatMap f allBi
1878 allBi
= enabledBuildInfos pkg
(componentEnabledSpec lbi
)
1879 deps
= PackageIndex
.topologicalOrder
(installedPkgs lbi
)
1881 builds program args
= do
1882 tempDir
<- getTemporaryDirectory
1883 withTempFile tempDir
".c" $ \cName cHnd
->
1884 withTempFile tempDir
"" $ \oNname oHnd
-> do
1885 hPutStrLn cHnd program
1888 _
<- getDbProgramOutput verbosity
1889 gccProgram
(withPrograms lbi
) (cName
:"-o":oNname
:args
)
1891 `catchIO`
(\_
-> return False)
1892 `catchExit`
(\_
-> return False)
1894 explainErrors Nothing
[] = return () -- should be impossible!
1896 |
isNothing . lookupProgram gccProgram
. withPrograms
$ lbi
1898 = die
' verbosity
$ unlines
1900 "This package depends on foreign library but we cannot "
1901 ++ "find a working C compiler. If you have it in a "
1902 ++ "non-standard location you can use the --with-gcc "
1903 ++ "flag to specify it." ]
1905 explainErrors hdr libs
= die
' verbosity
$ unlines $
1907 then "Missing dependencies on foreign libraries:"
1908 else "Missing dependency on a foreign library:"
1911 Just
(Left h
) -> ["* Missing (or bad) header file: " ++ h
]
1915 [lib
] -> ["* Missing (or bad) C library: " ++ lib
]
1916 _
-> ["* Missing (or bad) C libraries: " ++
1917 intercalate
", " libs
]
1918 ++ [if plural
then messagePlural
else messageSingular | missing
]
1920 Just
(Left _
) -> [ headerCppMessage
]
1921 Just
(Right h
) -> [ (if missing
then "* " else "")
1922 ++ "Bad header file: " ++ h
1927 plural
= length libs
>= 2
1928 -- Is there something missing? (as opposed to broken)
1929 missing
= not (null libs
)
1930 ||
case hdr
of Just
(Left _
) -> True; _
-> False
1933 "This problem can usually be solved by installing the system "
1934 ++ "package that provides this library (you may need the "
1935 ++ "\"-dev\" version). If the library is already installed "
1936 ++ "but in a non-standard location then you can use the flags "
1937 ++ "--extra-include-dirs= and --extra-lib-dirs= to specify "
1939 ++ "If the library file does exist, it may contain errors that "
1940 ++ "are caught by the C compiler at the preprocessing stage. "
1941 ++ "In this case you can re-run configure with the verbosity "
1942 ++ "flag -v3 to see the error messages."
1944 "This problem can usually be solved by installing the system "
1945 ++ "packages that provide these libraries (you may need the "
1946 ++ "\"-dev\" versions). If the libraries are already installed "
1947 ++ "but in a non-standard location then you can use the flags "
1948 ++ "--extra-include-dirs= and --extra-lib-dirs= to specify "
1949 ++ "where they are."
1950 ++ "If the library files do exist, it may contain errors that "
1951 ++ "are caught by the C compiler at the preprocessing stage. "
1952 ++ "In this case you can re-run configure with the verbosity "
1953 ++ "flag -v3 to see the error messages."
1955 "If the header file does exist, it may contain errors that "
1956 ++ "are caught by the C compiler at the preprocessing stage. "
1957 ++ "In this case you can re-run configure with the verbosity "
1958 ++ "flag -v3 to see the error messages."
1960 "The header file contains a compile error. "
1961 ++ "You can re-run configure with the verbosity flag "
1962 ++ "-v3 to see the error messages from the C compiler."
1964 -- | Output package check warnings and errors. Exit if any errors.
1965 checkPackageProblems
:: Verbosity
1967 -- ^ Path to the @.cabal@ file's directory
1968 -> GenericPackageDescription
1969 -> PackageDescription
1971 checkPackageProblems verbosity dir gpkg pkg
= do
1972 ioChecks
<- checkPackageFiles verbosity pkg dir
1973 let pureChecks
= checkPackage gpkg
(Just pkg
)
1974 (errors
, warnings
) =
1975 partitionEithers
(M
.mapMaybe classEW
$ pureChecks
++ ioChecks
)
1977 then traverse_
(warn verbosity
) (map ppPackageCheck warnings
)
1978 else die
' verbosity
(intercalate
"\n\n" $ map ppPackageCheck errors
)
1980 -- Classify error/warnings. Left: error, Right: warning.
1981 classEW
:: PackageCheck
-> Maybe (Either PackageCheck PackageCheck
)
1982 classEW e
@(PackageBuildImpossible _
) = Just
(Left e
)
1983 classEW w
@(PackageBuildWarning _
) = Just
(Right w
)
1984 classEW
(PackageDistSuspicious _
) = Nothing
1985 classEW
(PackageDistSuspiciousWarn _
) = Nothing
1986 classEW
(PackageDistInexcusable _
) = Nothing
1988 -- | Preform checks if a relocatable build is allowed
1989 checkRelocatable
:: Verbosity
1990 -> PackageDescription
1993 checkRelocatable verbosity pkg lbi
1994 = sequence_ [ checkOS
1996 , packagePrefixRelative
1997 , depsPrefixRelative
2000 -- Check if the OS support relocatable builds.
2002 -- If you add new OS' to this list, and your OS supports dynamic libraries
2003 -- and RPATH, make sure you add your OS to RPATH-support list of:
2004 -- Distribution.Simple.GHC.getRPaths
2006 = unless (os `
elem`
[ OSX
, Linux
])
2007 $ die
' verbosity
$ "Operating system: " ++ prettyShow os
++
2008 ", does not support relocatable builds"
2010 (Platform _ os
) = hostPlatform lbi
2012 -- Check if the Compiler support relocatable builds
2014 = unless (compilerFlavor comp `
elem`
[ GHC
])
2015 $ die
' verbosity
$ "Compiler: " ++ show comp
++
2016 ", does not support relocatable builds"
2020 -- Check if all the install dirs are relative to same prefix
2021 packagePrefixRelative
2022 = unless (relativeInstallDirs installDirs
)
2023 $ die
' verbosity
$ "Installation directories are not prefix_relative:\n" ++
2026 -- NB: should be good enough to check this against the default
2027 -- component ID, but if we wanted to be strictly correct we'd
2028 -- check for each ComponentId.
2029 installDirs
= absoluteInstallDirs pkg lbi NoCopyDest
2030 p
= prefix installDirs
2031 relativeInstallDirs
(InstallDirs
{..}) =
2033 (fmap (stripPrefix p
)
2034 [ bindir
, libdir
, dynlibdir
, libexecdir
, includedir
, datadir
2035 , docdir
, mandir
, htmldir
, haddockdir
, sysconfdir
] )
2037 -- Check if the library dirs of the dependencies that are in the package
2038 -- database to which the package is installed are relative to the
2039 -- prefix of the package
2040 depsPrefixRelative
= do
2041 pkgr
<- GHC
.pkgRoot verbosity lbi
(registrationPackageDB
(withPackageDB lbi
))
2042 traverse_
(doCheck pkgr
) ipkgs
2045 |
maybe False (== pkgr
) (IPI
.pkgRoot ipkg
)
2046 = for_
(IPI
.libraryDirs ipkg
) $ \libdir
-> do
2047 -- When @prefix@ is not under @pkgroot@,
2048 -- @shortRelativePath prefix pkgroot@ will return a path with
2049 -- @..@s and following check will fail without @canonicalizePath@.
2050 canonicalized
<- canonicalizePath libdir
2051 unless (p `
isPrefixOf` canonicalized
) $
2052 die
' verbosity
$ msg libdir
2055 -- NB: should be good enough to check this against the default
2056 -- component ID, but if we wanted to be strictly correct we'd
2057 -- check for each ComponentId.
2058 installDirs
= absoluteInstallDirs pkg lbi NoCopyDest
2059 p
= prefix installDirs
2060 ipkgs
= PackageIndex
.allPackages
(installedPkgs lbi
)
2061 msg l
= "Library directory of a dependency: " ++ show l
++
2062 "\nis not relative to the installation prefix:\n" ++
2065 -- -----------------------------------------------------------------------------
2066 -- Testing foreign library requirements
2068 unsupportedForeignLibs
:: Compiler
-> Platform
-> [ForeignLib
] -> [String]
2069 unsupportedForeignLibs comp platform
=
2070 mapMaybe (checkForeignLibSupported comp platform
)
2072 checkForeignLibSupported
:: Compiler
-> Platform
-> ForeignLib
-> Maybe String
2073 checkForeignLibSupported comp platform flib
= go
(compilerFlavor comp
)
2075 go
:: CompilerFlavor
-> Maybe String
2077 | compilerVersion comp
< mkVersion
[7,8] = unsupported
[
2078 "Building foreign libraries is only supported with GHC >= 7.8"
2080 |
otherwise = goGhcPlatform platform
2081 go _
= unsupported
[
2082 "Building foreign libraries is currently only supported with ghc"
2085 goGhcPlatform
:: Platform
-> Maybe String
2086 goGhcPlatform
(Platform _ OSX
) = goGhcOsx
(foreignLibType flib
)
2087 goGhcPlatform
(Platform _ Linux
) = goGhcLinux
(foreignLibType flib
)
2088 goGhcPlatform
(Platform I386 Windows
) = goGhcWindows
(foreignLibType flib
)
2089 goGhcPlatform
(Platform X86_64 Windows
) = goGhcWindows
(foreignLibType flib
)
2090 goGhcPlatform _
= unsupported
[
2091 "Building foreign libraries is currently only supported on Mac OS, "
2092 , "Linux and Windows"
2095 goGhcOsx
:: ForeignLibType
-> Maybe String
2096 goGhcOsx ForeignLibNativeShared
2097 |
not (null (foreignLibModDefFile flib
)) = unsupported
[
2098 "Module definition file not supported on OSX"
2100 |
not (null (foreignLibVersionInfo flib
)) = unsupported
[
2101 "Foreign library versioning not currently supported on OSX"
2105 goGhcOsx _
= unsupported
[
2106 "We can currently only build shared foreign libraries on OSX"
2109 goGhcLinux
:: ForeignLibType
-> Maybe String
2110 goGhcLinux ForeignLibNativeShared
2111 |
not (null (foreignLibModDefFile flib
)) = unsupported
[
2112 "Module definition file not supported on Linux"
2114 |
not (null (foreignLibVersionInfo flib
))
2115 && not (null (foreignLibVersionLinux flib
)) = unsupported
[
2116 "You must not specify both lib-version-info and lib-version-linux"
2120 goGhcLinux _
= unsupported
[
2121 "We can currently only build shared foreign libraries on Linux"
2124 goGhcWindows
:: ForeignLibType
-> Maybe String
2125 goGhcWindows ForeignLibNativeShared
2126 |
not standalone
= unsupported
[
2127 "We can currently only build standalone libraries on Windows. Use\n"
2128 , " if os(Windows)\n"
2129 , " options: standalone\n"
2130 , "in your foreign-library stanza."
2132 |
not (null (foreignLibVersionInfo flib
)) = unsupported
[
2133 "Foreign library versioning not currently supported on Windows.\n"
2134 , "You can specify module definition files in the mod-def-file field."
2138 goGhcWindows _
= unsupported
[
2139 "We can currently only build shared foreign libraries on Windows"
2143 standalone
= ForeignLibStandalone `
elem` foreignLibOptions flib
2145 unsupported
:: [String] -> Maybe String
2146 unsupported
= Just
. concat