Make more dependency types, and PkgconfigName
[cabal.git] / Cabal / Distribution / Simple / Configure.hs
blob8baa996f2987ebf1585a87ddf1471fcd51222be4
1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE FlexibleContexts #-}
3 {-# LANGUAGE OverloadedStrings #-}
4 {-# LANGUAGE RankNTypes #-}
5 {-# LANGUAGE RecordWildCards #-}
6 {-# LANGUAGE ScopedTypeVariables #-}
8 -----------------------------------------------------------------------------
9 -- |
10 -- Module : Distribution.Simple.Configure
11 -- Copyright : Isaac Jones 2003-2005
12 -- License : BSD3
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
24 -- results)
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
29 -- level.
31 module Distribution.Simple.Configure (configure,
32 writePersistBuildConfig,
33 getConfigStateFile,
34 getPersistBuildConfig,
35 checkPersistBuildConfigOutdated,
36 tryGetPersistBuildConfig,
37 maybeGetPersistBuildConfig,
38 findDistPref, findDistPrefOrDefault,
39 getInternalPackages,
40 computeComponentId,
41 computeCompatPackageKey,
42 computeCompatPackageName,
43 localBuildInfoFile,
44 getInstalledPackages,
45 getInstalledPackagesMonitorFiles,
46 getPackageDBContents,
47 configCompiler, configCompilerAux,
48 configCompilerEx, configCompilerAuxEx,
49 computeEffectiveProfiling,
50 ccLdOptionsBuildInfo,
51 checkForeignDeps,
52 interpretPackageDbFlags,
53 ConfigStateFileError(..),
54 tryGetConfigStateFile,
55 platformDefines,
56 relaxPackageDeps,
58 where
60 import Prelude ()
61 import Distribution.Compat.Prelude
63 import Distribution.Compiler
64 import Distribution.Types.IncludeRenaming
65 import Distribution.Utils.NubList
66 import Distribution.Simple.Compiler hiding (Flag)
67 import Distribution.Simple.PreProcess
68 import Distribution.Package
69 import qualified Distribution.InstalledPackageInfo as Installed
70 import Distribution.InstalledPackageInfo (InstalledPackageInfo)
71 import qualified Distribution.Simple.PackageIndex as PackageIndex
72 import Distribution.Simple.PackageIndex (InstalledPackageIndex)
73 import Distribution.PackageDescription as PD hiding (Flag)
74 import Distribution.Types.PackageDescription as PD
75 import Distribution.PackageDescription.PrettyPrint
76 import Distribution.PackageDescription.Configuration
77 import Distribution.PackageDescription.Check hiding (doesFileExist)
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.LocalBuildInfo
83 import Distribution.Types.ComponentRequestedSpec
84 import Distribution.Types.ForeignLib
85 import Distribution.Types.ForeignLibType
86 import Distribution.Types.ForeignLibOption
87 import Distribution.Types.Mixin
88 import Distribution.Simple.Utils
89 import Distribution.System
90 import Distribution.Version
91 import Distribution.Verbosity
92 import qualified Distribution.Compat.Graph as Graph
93 import Distribution.Compat.Stack
94 import Distribution.Backpack.Configure
95 import Distribution.Backpack.PreExistingComponent
96 import Distribution.Backpack.ConfiguredComponent (newPackageDepsBehaviour)
97 import Distribution.Backpack.Id
98 import Distribution.Utils.LogProgress
100 import qualified Distribution.Simple.GHC as GHC
101 import qualified Distribution.Simple.GHCJS as GHCJS
102 import qualified Distribution.Simple.JHC as JHC
103 import qualified Distribution.Simple.LHC as LHC
104 import qualified Distribution.Simple.UHC as UHC
105 import qualified Distribution.Simple.HaskellSuite as HaskellSuite
107 import Control.Exception
108 ( ErrorCall, Exception, evaluate, throw, throwIO, try )
109 import Distribution.Compat.Binary ( decodeOrFailIO, encode )
110 import Data.ByteString.Lazy (ByteString)
111 import qualified Data.ByteString as BS
112 import qualified Data.ByteString.Lazy.Char8 as BLC8
113 import Data.List
114 ( (\\), partition, inits, stripPrefix )
115 import Data.Either
116 ( partitionEithers )
117 import qualified Data.Map as Map
118 import System.Directory
119 ( doesFileExist, createDirectoryIfMissing, getTemporaryDirectory )
120 import System.FilePath
121 ( (</>), isAbsolute )
122 import qualified System.Info
123 ( compilerName, compilerVersion )
124 import System.IO
125 ( hPutStrLn, hClose )
126 import Distribution.Text
127 ( Text(disp), defaultStyle, display, simpleParse )
128 import Text.PrettyPrint
129 ( Doc, (<+>), ($+$), char, comma, hsep, nest
130 , punctuate, quotes, render, renderStyle, sep, text )
131 import Distribution.Compat.Environment ( lookupEnv )
132 import Distribution.Compat.Exception ( catchExit, catchIO )
134 type UseExternalInternalDeps = Bool
136 -- | The errors that can be thrown when reading the @setup-config@ file.
137 data ConfigStateFileError
138 = ConfigStateFileNoHeader -- ^ No header found.
139 | ConfigStateFileBadHeader -- ^ Incorrect header.
140 | ConfigStateFileNoParse -- ^ Cannot parse file contents.
141 | ConfigStateFileMissing -- ^ No file!
142 | ConfigStateFileBadVersion PackageIdentifier PackageIdentifier
143 (Either ConfigStateFileError LocalBuildInfo) -- ^ Mismatched version.
144 deriving (Typeable)
146 -- | Format a 'ConfigStateFileError' as a user-facing error message.
147 dispConfigStateFileError :: ConfigStateFileError -> Doc
148 dispConfigStateFileError ConfigStateFileNoHeader =
149 text "Saved package config file header is missing."
150 <+> text "Re-run the 'configure' command."
151 dispConfigStateFileError ConfigStateFileBadHeader =
152 text "Saved package config file header is corrupt."
153 <+> text "Re-run the 'configure' command."
154 dispConfigStateFileError ConfigStateFileNoParse =
155 text "Saved package config file is corrupt."
156 <+> text "Re-run the 'configure' command."
157 dispConfigStateFileError ConfigStateFileMissing =
158 text "Run the 'configure' command first."
159 dispConfigStateFileError (ConfigStateFileBadVersion oldCabal oldCompiler _) =
160 text "Saved package config file is outdated:"
161 $+$ badCabal $+$ badCompiler
162 $+$ text "Re-run the 'configure' command."
163 where
164 badCabal =
165 text "• the Cabal version changed from"
166 <+> disp oldCabal <+> "to" <+> disp currentCabalId
167 badCompiler
168 | oldCompiler == currentCompilerId = mempty
169 | otherwise =
170 text "• the compiler changed from"
171 <+> disp oldCompiler <+> "to" <+> disp currentCompilerId
173 instance Show ConfigStateFileError where
174 show = renderStyle defaultStyle . dispConfigStateFileError
176 instance Exception ConfigStateFileError
178 -- | Read the 'localBuildInfoFile'. Throw an exception if the file is
179 -- missing, if the file cannot be read, or if the file was created by an older
180 -- version of Cabal.
181 getConfigStateFile :: FilePath -- ^ The file path of the @setup-config@ file.
182 -> IO LocalBuildInfo
183 getConfigStateFile filename = do
184 exists <- doesFileExist filename
185 unless exists $ throwIO ConfigStateFileMissing
186 -- Read the config file into a strict ByteString to avoid problems with
187 -- lazy I/O, then convert to lazy because the binary package needs that.
188 contents <- BS.readFile filename
189 let (header, body) = BLC8.span (/='\n') (BLC8.fromChunks [contents])
191 headerParseResult <- try $ evaluate $ parseHeader header
192 let (cabalId, compId) =
193 case headerParseResult of
194 Left (_ :: ErrorCall) -> throw ConfigStateFileBadHeader
195 Right x -> x
197 let getStoredValue = do
198 result <- decodeOrFailIO (BLC8.tail body)
199 case result of
200 Left _ -> throw ConfigStateFileNoParse
201 Right x -> return x
202 deferErrorIfBadVersion act
203 | cabalId /= currentCabalId = do
204 eResult <- try act
205 throw $ ConfigStateFileBadVersion cabalId compId eResult
206 | otherwise = act
207 deferErrorIfBadVersion getStoredValue
208 where
209 _ = callStack -- TODO: attach call stack to exception
211 -- | Read the 'localBuildInfoFile', returning either an error or the local build
212 -- info.
213 tryGetConfigStateFile :: FilePath -- ^ The file path of the @setup-config@ file.
214 -> IO (Either ConfigStateFileError LocalBuildInfo)
215 tryGetConfigStateFile = try . getConfigStateFile
217 -- | Try to read the 'localBuildInfoFile'.
218 tryGetPersistBuildConfig :: FilePath -- ^ The @dist@ directory path.
219 -> IO (Either ConfigStateFileError LocalBuildInfo)
220 tryGetPersistBuildConfig = try . getPersistBuildConfig
222 -- | Read the 'localBuildInfoFile'. Throw an exception if the file is
223 -- missing, if the file cannot be read, or if the file was created by an older
224 -- version of Cabal.
225 getPersistBuildConfig :: FilePath -- ^ The @dist@ directory path.
226 -> IO LocalBuildInfo
227 getPersistBuildConfig = getConfigStateFile . localBuildInfoFile
229 -- | Try to read the 'localBuildInfoFile'.
230 maybeGetPersistBuildConfig :: FilePath -- ^ The @dist@ directory path.
231 -> IO (Maybe LocalBuildInfo)
232 maybeGetPersistBuildConfig =
233 liftM (either (const Nothing) Just) . tryGetPersistBuildConfig
235 -- | After running configure, output the 'LocalBuildInfo' to the
236 -- 'localBuildInfoFile'.
237 writePersistBuildConfig :: FilePath -- ^ The @dist@ directory path.
238 -> LocalBuildInfo -- ^ The 'LocalBuildInfo' to write.
239 -> NoCallStackIO ()
240 writePersistBuildConfig distPref lbi = do
241 createDirectoryIfMissing False distPref
242 writeFileAtomic (localBuildInfoFile distPref) $
243 BLC8.unlines [showHeader pkgId, encode lbi]
244 where
245 pkgId = localPackage lbi
247 -- | Identifier of the current Cabal package.
248 currentCabalId :: PackageIdentifier
249 currentCabalId = PackageIdentifier (mkPackageName "Cabal") cabalVersion
251 -- | Identifier of the current compiler package.
252 currentCompilerId :: PackageIdentifier
253 currentCompilerId = PackageIdentifier (mkPackageName System.Info.compilerName)
254 (mkVersion' System.Info.compilerVersion)
256 -- | Parse the @setup-config@ file header, returning the package identifiers
257 -- for Cabal and the compiler.
258 parseHeader :: ByteString -- ^ The file contents.
259 -> (PackageIdentifier, PackageIdentifier)
260 parseHeader header = case BLC8.words header of
261 ["Saved", "package", "config", "for", pkgId, "written", "by", cabalId,
262 "using", compId] ->
263 fromMaybe (throw ConfigStateFileBadHeader) $ do
264 _ <- simpleParse (BLC8.unpack pkgId) :: Maybe PackageIdentifier
265 cabalId' <- simpleParse (BLC8.unpack cabalId)
266 compId' <- simpleParse (BLC8.unpack compId)
267 return (cabalId', compId')
268 _ -> throw ConfigStateFileNoHeader
270 -- | Generate the @setup-config@ file header.
271 showHeader :: PackageIdentifier -- ^ The processed package.
272 -> ByteString
273 showHeader pkgId = BLC8.unwords
274 [ "Saved", "package", "config", "for"
275 , BLC8.pack $ display pkgId
276 , "written", "by"
277 , BLC8.pack $ display currentCabalId
278 , "using"
279 , BLC8.pack $ display currentCompilerId
282 -- | Check that localBuildInfoFile is up-to-date with respect to the
283 -- .cabal file.
284 checkPersistBuildConfigOutdated :: FilePath -> FilePath -> NoCallStackIO Bool
285 checkPersistBuildConfigOutdated distPref pkg_descr_file = do
286 pkg_descr_file `moreRecentFile` (localBuildInfoFile distPref)
288 -- | Get the path of @dist\/setup-config@.
289 localBuildInfoFile :: FilePath -- ^ The @dist@ directory path.
290 -> FilePath
291 localBuildInfoFile distPref = distPref </> "setup-config"
293 -- -----------------------------------------------------------------------------
294 -- * Configuration
295 -- -----------------------------------------------------------------------------
297 -- | Return the \"dist/\" prefix, or the default prefix. The prefix is taken
298 -- from (in order of highest to lowest preference) the override prefix, the
299 -- \"CABAL_BUILDDIR\" environment variable, or the default prefix.
300 findDistPref :: FilePath -- ^ default \"dist\" prefix
301 -> Setup.Flag FilePath -- ^ override \"dist\" prefix
302 -> NoCallStackIO FilePath
303 findDistPref defDistPref overrideDistPref = do
304 envDistPref <- liftM parseEnvDistPref (lookupEnv "CABAL_BUILDDIR")
305 return $ fromFlagOrDefault defDistPref (mappend envDistPref overrideDistPref)
306 where
307 parseEnvDistPref env =
308 case env of
309 Just distPref | not (null distPref) -> toFlag distPref
310 _ -> NoFlag
312 -- | Return the \"dist/\" prefix, or the default prefix. The prefix is taken
313 -- from (in order of highest to lowest preference) the override prefix, the
314 -- \"CABAL_BUILDDIR\" environment variable, or 'defaultDistPref' is used. Call
315 -- this function to resolve a @*DistPref@ flag whenever it is not known to be
316 -- set. (The @*DistPref@ flags are always set to a definite value before
317 -- invoking 'UserHooks'.)
318 findDistPrefOrDefault :: Setup.Flag FilePath -- ^ override \"dist\" prefix
319 -> NoCallStackIO FilePath
320 findDistPrefOrDefault = findDistPref defaultDistPref
322 -- |Perform the \"@.\/setup configure@\" action.
323 -- Returns the @.setup-config@ file.
324 configure :: (GenericPackageDescription, HookedBuildInfo)
325 -> ConfigFlags -> IO LocalBuildInfo
326 configure (pkg_descr0', pbi) cfg = do
327 let pkg_descr0 =
328 -- Ignore '--allow-{older,newer}' when we're given
329 -- '--exact-configuration'.
330 if fromFlagOrDefault False (configExactConfiguration cfg)
331 then pkg_descr0'
332 else relaxPackageDeps removeLowerBound
333 (maybe RelaxDepsNone unAllowOlder $ configAllowOlder cfg) $
334 relaxPackageDeps removeUpperBound
335 (maybe RelaxDepsNone unAllowNewer $ configAllowNewer cfg)
336 pkg_descr0'
338 -- Determine the component we are configuring, if a user specified
339 -- one on the command line. We use a fake, flattened version of
340 -- the package since at this point, we're not really sure what
341 -- components we *can* configure. @Nothing@ means that we should
342 -- configure everything (the old behavior).
343 (mb_cname :: Maybe ComponentName) <- do
344 let flat_pkg_descr = flattenPackageDescription pkg_descr0
345 targets <- readBuildTargets flat_pkg_descr (configArgs cfg)
346 -- TODO: bleat if you use the module/file syntax
347 let targets' = [ cname | BuildTargetComponent cname <- targets ]
348 case targets' of
349 _ | null (configArgs cfg) -> return Nothing
350 [cname] -> return (Just cname)
351 [] -> die "No valid component targets found"
352 _ -> die "Can only configure either single component or all of them"
354 let use_external_internal_deps = isJust mb_cname
355 case mb_cname of
356 Nothing -> setupMessage verbosity "Configuring" (packageId pkg_descr0)
357 Just cname -> notice verbosity
358 ("Configuring component " ++ display cname ++
359 " from " ++ display (packageId pkg_descr0))
361 -- configCID is only valid for per-component configure
362 when (isJust (flagToMaybe (configCID cfg)) && isNothing mb_cname) $
363 die "--cid is only supported for per-component configure"
365 checkDeprecatedFlags verbosity cfg
366 checkExactConfiguration pkg_descr0 cfg
368 -- Where to build the package
369 let buildDir :: FilePath -- e.g. dist/build
370 -- fromFlag OK due to Distribution.Simple calling
371 -- findDistPrefOrDefault to fill it in
372 buildDir = fromFlag (configDistPref cfg) </> "build"
373 createDirectoryIfMissingVerbose (lessVerbose verbosity) True buildDir
375 -- What package database(s) to use
376 let packageDbs :: PackageDBStack
377 packageDbs
378 = interpretPackageDbFlags
379 (fromFlag (configUserInstall cfg))
380 (configPackageDBs cfg)
382 -- comp: the compiler we're building with
383 -- compPlatform: the platform we're building for
384 -- programDb: location and args of all programs we're
385 -- building with
386 (comp :: Compiler,
387 compPlatform :: Platform,
388 programDb :: ProgramDb)
389 <- configCompilerEx
390 (flagToMaybe (configHcFlavor cfg))
391 (flagToMaybe (configHcPath cfg))
392 (flagToMaybe (configHcPkg cfg))
393 (mkProgramDb cfg (configPrograms cfg))
394 (lessVerbose verbosity)
396 -- The InstalledPackageIndex of all installed packages
397 installedPackageSet :: InstalledPackageIndex
398 <- getInstalledPackages (lessVerbose verbosity) comp
399 packageDbs programDb
401 -- The set of package names which are "shadowed" by internal
402 -- packages, and which component they map to
403 let internalPackageSet :: Map PackageName ComponentName
404 internalPackageSet = getInternalPackages pkg_descr0
406 -- Make a data structure describing what components are enabled.
407 let enabled :: ComponentRequestedSpec
408 enabled = case mb_cname of
409 Just cname -> OneComponentRequestedSpec cname
410 Nothing -> ComponentRequestedSpec
411 -- The flag name (@--enable-tests@) is a
412 -- little bit of a misnomer, because
413 -- just passing this flag won't
414 -- "enable", in our internal
415 -- nomenclature; it's just a request; a
416 -- @buildable: False@ might make it
417 -- not possible to enable.
418 { testsRequested = fromFlag (configTests cfg)
419 , benchmarksRequested =
420 fromFlag (configBenchmarks cfg) }
421 -- Some sanity checks related to enabling components.
422 when (isJust mb_cname
423 && (fromFlag (configTests cfg) || fromFlag (configBenchmarks cfg))) $
424 die $ "--enable-tests/--enable-benchmarks are incompatible with" ++
425 " explicitly specifying a component to configure."
427 -- allConstraints: The set of all 'Dependency's we have. Used ONLY
428 -- to 'configureFinalizedPackage'.
429 -- requiredDepsMap: A map from 'PackageName' to the specifically
430 -- required 'InstalledPackageInfo', due to --dependency
432 -- NB: These constraints are to be applied to ALL components of
433 -- a package. Thus, it's not an error if allConstraints contains
434 -- more constraints than is necessary for a component (another
435 -- component might need it.)
437 -- NB: The fact that we bundle all the constraints together means
438 -- that is not possible to configure a test-suite to use one
439 -- version of a dependency, and the executable to use another.
440 (allConstraints :: [Dependency],
441 requiredDepsMap :: Map PackageName InstalledPackageInfo)
442 <- either die return $
443 combinedConstraints (configConstraints cfg)
444 (configDependencies cfg)
445 installedPackageSet
447 -- pkg_descr: The resolved package description, that does not contain any
448 -- conditionals, because we have have an assignment for
449 -- every flag, either picking them ourselves using a
450 -- simple naive algorithm, or having them be passed to
451 -- us by 'configConfigurationsFlags')
452 -- flags: The 'FlagAssignment' that the conditionals were
453 -- resolved with.
455 -- NB: Why doesn't finalizing a package also tell us what the
456 -- dependencies are (e.g. when we run the naive algorithm,
457 -- we are checking if dependencies are satisfiable)? The
458 -- primary reason is that we may NOT have done any solving:
459 -- if the flags are all chosen for us, this step is a simple
460 -- matter of flattening according to that assignment. It's
461 -- cleaner to then configure the dependencies afterwards.
462 (pkg_descr :: PackageDescription,
463 flags :: FlagAssignment)
464 <- configureFinalizedPackage verbosity cfg enabled
465 allConstraints
466 (dependencySatisfiable
467 (fromFlagOrDefault False (configExactConfiguration cfg))
468 (packageVersion pkg_descr0)
469 installedPackageSet
470 internalPackageSet
471 requiredDepsMap)
472 comp
473 compPlatform
474 pkg_descr0
476 debug verbosity $ "Finalized package description:\n"
477 ++ showPackageDescription pkg_descr
478 -- NB: showPackageDescription does not display the AWFUL HACK GLOBAL
479 -- buildDepends, so we have to display it separately. See #2066
480 -- Some day, we should eliminate this, so that
481 -- configureFinalizedPackage returns the set of overall dependencies
482 -- separately. Then 'configureDependencies' and
483 -- 'Distribution.PackageDescription.Check' need to be adjusted
484 -- accordingly.
485 debug verbosity $ "Finalized build-depends: "
486 ++ intercalate ", " (map display (buildDepends pkg_descr))
488 checkCompilerProblems comp pkg_descr enabled
489 checkPackageProblems verbosity pkg_descr0
490 (updatePackageDescription pbi pkg_descr)
492 -- The list of 'InstalledPackageInfo' recording the selected
493 -- dependencies on external packages.
495 -- Invariant: For any package name, there is at most one package
496 -- in externalPackageDeps which has that name.
498 -- NB: The dependency selection is global over ALL components
499 -- in the package (similar to how allConstraints and
500 -- requiredDepsMap are global over all components). In particular,
501 -- if *any* component (post-flag resolution) has an unsatisfiable
502 -- dependency, we will fail. This can sometimes be undesirable
503 -- for users, see #1786 (benchmark conflicts with executable),
505 -- In the presence of Backpack, these package dependencies are
506 -- NOT complete: they only ever include the INDEFINITE
507 -- dependencies. After we apply an instantiation, we'll get
508 -- definite references which constitute extra dependencies.
509 -- (Why not have cabal-install pass these in explicitly?
510 -- For one it's deterministic; for two, we need to associate
511 -- them with renamings which would require a far more complicated
512 -- input scheme than what we have today.)
513 externalPkgDeps :: [(PackageName, InstalledPackageInfo)]
514 <- configureDependencies
515 verbosity
516 use_external_internal_deps
517 internalPackageSet
518 installedPackageSet
519 requiredDepsMap
520 pkg_descr
522 -- Compute installation directory templates, based on user
523 -- configuration.
525 -- TODO: Move this into a helper function.
526 defaultDirs :: InstallDirTemplates
527 <- defaultInstallDirs' use_external_internal_deps
528 (compilerFlavor comp)
529 (fromFlag (configUserInstall cfg))
530 (hasLibs pkg_descr)
531 let installDirs :: InstallDirTemplates
532 installDirs = combineInstallDirs fromFlagOrDefault
533 defaultDirs (configInstallDirs cfg)
535 -- Check languages and extensions
536 -- TODO: Move this into a helper function.
537 let langlist = nub $ catMaybes $ map defaultLanguage
538 (enabledBuildInfos pkg_descr enabled)
539 let langs = unsupportedLanguages comp langlist
540 when (not (null langs)) $
541 die $ "The package " ++ display (packageId pkg_descr0)
542 ++ " requires the following languages which are not "
543 ++ "supported by " ++ display (compilerId comp) ++ ": "
544 ++ intercalate ", " (map display langs)
545 let extlist = nub $ concatMap allExtensions (enabledBuildInfos pkg_descr enabled)
546 let exts = unsupportedExtensions comp extlist
547 when (not (null exts)) $
548 die $ "The package " ++ display (packageId pkg_descr0)
549 ++ " requires the following language extensions which are not "
550 ++ "supported by " ++ display (compilerId comp) ++ ": "
551 ++ intercalate ", " (map display exts)
553 -- Check foreign library build requirements
554 let flibs = [flib | CFLib flib <- enabledComponents pkg_descr enabled]
555 let unsupportedFLibs = unsupportedForeignLibs comp compPlatform flibs
556 when (not (null unsupportedFLibs)) $
557 die $ "Cannot build some foreign libraries: "
558 ++ intercalate "," unsupportedFLibs
560 -- Configure known/required programs & external build tools.
561 -- Exclude build-tool deps on "internal" exes in the same package
563 -- TODO: Factor this into a helper package.
564 let requiredBuildTools =
565 [ buildTool
566 | let exeNames = map (unUnqualComponentName . exeName) (executables pkg_descr)
567 , bi <- enabledBuildInfos pkg_descr enabled
568 , buildTool@(LegacyExeDependency toolPName reqVer)
569 <- buildTools bi
570 , let isInternal =
571 toolPName `elem` exeNames
572 -- we assume all internal build-tools are
573 -- versioned with the package:
574 && packageVersion pkg_descr `withinRange` reqVer
575 , not isInternal ]
577 programDb' <-
578 configureAllKnownPrograms (lessVerbose verbosity) programDb
579 >>= configureRequiredPrograms verbosity requiredBuildTools
581 (pkg_descr', programDb'') <-
582 configurePkgconfigPackages verbosity pkg_descr programDb' enabled
584 -- Compute internal component graph
586 -- The general idea is that we take a look at all the source level
587 -- components (which may build-depends on each other) and form a graph.
588 -- From there, we build a ComponentLocalBuildInfo for each of the
589 -- components, which lets us actually build each component.
590 -- internalPackageSet
591 -- use_external_internal_deps
592 (buildComponents :: [ComponentLocalBuildInfo],
593 packageDependsIndex :: InstalledPackageIndex) <-
594 let prePkgDeps = map ipiToPreExistingComponent externalPkgDeps
595 in runLogProgress verbosity $ configureComponentLocalBuildInfos
596 verbosity
597 use_external_internal_deps
598 enabled
599 (configIPID cfg)
600 (configCID cfg)
601 pkg_descr
602 prePkgDeps
603 (configConfigurationsFlags cfg)
604 (configInstantiateWith cfg)
605 installedPackageSet
606 comp
608 -- Decide if we're going to compile with split objects.
609 split_objs :: Bool <-
610 if not (fromFlag $ configSplitObjs cfg)
611 then return False
612 else case compilerFlavor comp of
613 GHC | compilerVersion comp >= mkVersion [6,5]
614 -> return True
615 GHCJS
616 -> return True
617 _ -> do warn verbosity
618 ("this compiler does not support " ++
619 "--enable-split-objs; ignoring")
620 return False
622 let ghciLibByDefault =
623 case compilerId comp of
624 CompilerId GHC _ ->
625 -- If ghc is non-dynamic, then ghci needs object files,
626 -- so we build one by default.
628 -- Technically, archive files should be sufficient for ghci,
629 -- but because of GHC bug #8942, it has never been safe to
630 -- rely on them. By the time that bug was fixed, ghci had
631 -- been changed to read shared libraries instead of archive
632 -- files (see next code block).
633 not (GHC.isDynamic comp)
634 CompilerId GHCJS _ ->
635 not (GHCJS.isDynamic comp)
636 _ -> False
638 let sharedLibsByDefault
639 | fromFlag (configDynExe cfg) =
640 -- build a shared library if dynamically-linked
641 -- executables are requested
642 True
643 | otherwise = case compilerId comp of
644 CompilerId GHC _ ->
645 -- if ghc is dynamic, then ghci needs a shared
646 -- library, so we build one by default.
647 GHC.isDynamic comp
648 CompilerId GHCJS _ ->
649 GHCJS.isDynamic comp
650 _ -> False
651 withSharedLib_ =
652 -- build shared libraries if required by GHC or by the
653 -- executable linking mode, but allow the user to force
654 -- building only static library archives with
655 -- --disable-shared.
656 fromFlagOrDefault sharedLibsByDefault $ configSharedLib cfg
657 withDynExe_ = fromFlag $ configDynExe cfg
658 when (withDynExe_ && not withSharedLib_) $ warn verbosity $
659 "Executables will use dynamic linking, but a shared library "
660 ++ "is not being built. Linking will fail if any executables "
661 ++ "depend on the library."
663 setProfLBI <- configureProfiling verbosity cfg comp
665 setCoverageLBI <- configureCoverage verbosity cfg comp
667 reloc <-
668 if not (fromFlag $ configRelocatable cfg)
669 then return False
670 else return True
672 let buildComponentsMap =
673 foldl' (\m clbi -> Map.insertWith (++)
674 (componentLocalName clbi) [clbi] m)
675 Map.empty buildComponents
677 let lbi = (setCoverageLBI . setProfLBI)
678 LocalBuildInfo {
679 configFlags = cfg,
680 flagAssignment = flags,
681 componentEnabledSpec = enabled,
682 extraConfigArgs = [], -- Currently configure does not
683 -- take extra args, but if it
684 -- did they would go here.
685 installDirTemplates = installDirs,
686 compiler = comp,
687 hostPlatform = compPlatform,
688 buildDir = buildDir,
689 componentGraph = Graph.fromList buildComponents,
690 componentNameMap = buildComponentsMap,
691 installedPkgs = packageDependsIndex,
692 pkgDescrFile = Nothing,
693 localPkgDescr = pkg_descr',
694 withPrograms = programDb'',
695 withVanillaLib = fromFlag $ configVanillaLib cfg,
696 withSharedLib = withSharedLib_,
697 withDynExe = withDynExe_,
698 withProfLib = False,
699 withProfLibDetail = ProfDetailNone,
700 withProfExe = False,
701 withProfExeDetail = ProfDetailNone,
702 withOptimization = fromFlag $ configOptimization cfg,
703 withDebugInfo = fromFlag $ configDebugInfo cfg,
704 withGHCiLib = fromFlagOrDefault ghciLibByDefault $
705 configGHCiLib cfg,
706 splitObjs = split_objs,
707 stripExes = fromFlag $ configStripExes cfg,
708 stripLibs = fromFlag $ configStripLibs cfg,
709 exeCoverage = False,
710 libCoverage = False,
711 withPackageDB = packageDbs,
712 progPrefix = fromFlag $ configProgPrefix cfg,
713 progSuffix = fromFlag $ configProgSuffix cfg,
714 relocatable = reloc
717 when reloc (checkRelocatable verbosity pkg_descr lbi)
719 -- TODO: This is not entirely correct, because the dirs may vary
720 -- across libraries/executables
721 let dirs = absoluteInstallDirs pkg_descr lbi NoCopyDest
722 relative = prefixRelativeInstallDirs (packageId pkg_descr) lbi
724 unless (isAbsolute (prefix dirs)) $ die $
725 "expected an absolute directory name for --prefix: " ++ prefix dirs
727 info verbosity $ "Using " ++ display currentCabalId
728 ++ " compiled by " ++ display currentCompilerId
729 info verbosity $ "Using compiler: " ++ showCompilerId comp
730 info verbosity $ "Using install prefix: " ++ prefix dirs
732 let dirinfo name dir isPrefixRelative =
733 info verbosity $ name ++ " installed in: " ++ dir ++ relNote
734 where relNote = case buildOS of
735 Windows | not (hasLibs pkg_descr)
736 && isNothing isPrefixRelative
737 -> " (fixed location)"
738 _ -> ""
740 dirinfo "Binaries" (bindir dirs) (bindir relative)
741 dirinfo "Libraries" (libdir dirs) (libdir relative)
742 dirinfo "Dynamic Libraries" (dynlibdir dirs) (dynlibdir relative)
743 dirinfo "Private binaries" (libexecdir dirs) (libexecdir relative)
744 dirinfo "Data files" (datadir dirs) (datadir relative)
745 dirinfo "Documentation" (docdir dirs) (docdir relative)
746 dirinfo "Configuration files" (sysconfdir dirs) (sysconfdir relative)
748 sequence_ [ reportProgram verbosity prog configuredProg
749 | (prog, configuredProg) <- knownPrograms programDb'' ]
751 return lbi
753 where
754 verbosity = fromFlag (configVerbosity cfg)
756 mkProgramDb :: ConfigFlags -> ProgramDb -> ProgramDb
757 mkProgramDb cfg initialProgramDb = programDb
758 where
759 programDb = userSpecifyArgss (configProgramArgs cfg)
760 . userSpecifyPaths (configProgramPaths cfg)
761 . setProgramSearchPath searchpath
762 $ initialProgramDb
763 searchpath = getProgramSearchPath (initialProgramDb)
764 ++ map ProgramSearchPathDir
765 (fromNubList $ configProgramPathExtra cfg)
767 -- -----------------------------------------------------------------------------
768 -- Helper functions for configure
770 -- | Check if the user used any deprecated flags.
771 checkDeprecatedFlags :: Verbosity -> ConfigFlags -> IO ()
772 checkDeprecatedFlags verbosity cfg = do
773 unless (configProfExe cfg == NoFlag) $ do
774 let enable | fromFlag (configProfExe cfg) = "enable"
775 | otherwise = "disable"
776 warn verbosity
777 ("The flag --" ++ enable ++ "-executable-profiling is deprecated. "
778 ++ "Please use --" ++ enable ++ "-profiling instead.")
780 unless (configLibCoverage cfg == NoFlag) $ do
781 let enable | fromFlag (configLibCoverage cfg) = "enable"
782 | otherwise = "disable"
783 warn verbosity
784 ("The flag --" ++ enable ++ "-library-coverage is deprecated. "
785 ++ "Please use --" ++ enable ++ "-coverage instead.")
787 -- | Sanity check: if '--exact-configuration' was given, ensure that the
788 -- complete flag assignment was specified on the command line.
789 checkExactConfiguration :: GenericPackageDescription -> ConfigFlags -> IO ()
790 checkExactConfiguration pkg_descr0 cfg = do
791 when (fromFlagOrDefault False (configExactConfiguration cfg)) $ do
792 let cmdlineFlags = map fst (configConfigurationsFlags cfg)
793 allFlags = map flagName . genPackageFlags $ pkg_descr0
794 diffFlags = allFlags \\ cmdlineFlags
795 when (not . null $ diffFlags) $
796 die $ "'--exact-configuration' was given, "
797 ++ "but the following flags were not specified: "
798 ++ intercalate ", " (map show diffFlags)
800 -- | Create a PackageIndex that makes *any libraries that might be*
801 -- defined internally to this package look like installed packages, in
802 -- case an executable should refer to any of them as dependencies.
804 -- It must be *any libraries that might be* defined rather than the
805 -- actual definitions, because these depend on conditionals in the .cabal
806 -- file, and we haven't resolved them yet. finalizePD
807 -- does the resolution of conditionals, and it takes internalPackageSet
808 -- as part of its input.
809 getInternalPackages :: GenericPackageDescription
810 -> Map PackageName ComponentName
811 getInternalPackages pkg_descr0 =
812 -- TODO: some day, executables will be fair game here too!
813 let pkg_descr = flattenPackageDescription pkg_descr0
814 f lib = case libName lib of
815 Nothing -> (packageName pkg_descr, CLibName)
816 Just n' -> (unqualComponentNameToPackageName n', CSubLibName n')
817 in Map.fromList (map f (allLibraries pkg_descr))
819 -- | Returns true if a dependency is satisfiable. This function
820 -- may report a dependency satisfiable even when it is not,
821 -- but not vice versa. This is to be passed
822 -- to finalizePD.
823 dependencySatisfiable
824 :: Bool
825 -> Version
826 -> InstalledPackageIndex -- ^ installed set
827 -> Map PackageName ComponentName -- ^ internal set
828 -> Map PackageName InstalledPackageInfo -- ^ required dependencies
829 -> (Dependency -> Bool)
830 dependencySatisfiable
831 exact_config _ installedPackageSet internalPackageSet requiredDepsMap
832 d@(Dependency depName _)
833 | exact_config =
834 -- When we're given '--exact-configuration', we assume that all
835 -- dependencies and flags are exactly specified on the command
836 -- line. Thus we only consult the 'requiredDepsMap'. Note that
837 -- we're not doing the version range check, so if there's some
838 -- dependency that wasn't specified on the command line,
839 -- 'finalizePD' will fail.
841 -- TODO: mention '--exact-configuration' in the error message
842 -- when this fails?
844 -- (However, note that internal deps don't have to be
845 -- specified!)
847 -- NB: Just like the case below, we might incorrectly
848 -- determine an external internal dep is satisfiable
849 -- when it actually isn't.
850 (depName `Map.member` requiredDepsMap) || isInternalDep
852 | isInternalDep =
853 -- If a 'PackageName' is defined by an internal component, the
854 -- dep is satisfiable (and we are going to use the internal
855 -- dependency.) Note that this doesn't mean we are actually
856 -- going to SUCCEED when we configure the package, if
857 -- UseExternalInternalDeps is True.
858 True
860 | otherwise =
861 -- Normal operation: just look up dependency in the
862 -- package index.
863 not . null . PackageIndex.lookupDependency installedPackageSet $ d
864 where
865 isInternalDep = Map.member depName internalPackageSet
867 -- | Relax the dependencies of this package if needed.
868 relaxPackageDeps :: (VersionRange -> VersionRange)
869 -> RelaxDeps
870 -> GenericPackageDescription -> GenericPackageDescription
871 relaxPackageDeps _ RelaxDepsNone gpd = gpd
872 relaxPackageDeps vrtrans RelaxDepsAll gpd = transformAllBuildDepends relaxAll gpd
873 where
874 relaxAll = \(Dependency pkgName verRange) ->
875 Dependency pkgName (vrtrans verRange)
876 relaxPackageDeps vrtrans (RelaxDepsSome allowNewerDeps') gpd =
877 transformAllBuildDepends relaxSome gpd
878 where
879 thisPkgName = packageName gpd
880 allowNewerDeps = mapMaybe f allowNewerDeps'
882 f (Setup.RelaxedDep p) = Just p
883 f (Setup.RelaxedDepScoped scope p) | scope == thisPkgName = Just p
884 | otherwise = Nothing
886 relaxSome = \d@(Dependency depName verRange) ->
887 if depName `elem` allowNewerDeps
888 then Dependency depName (vrtrans verRange)
889 else d
891 -- | Finalize a generic package description. The workhorse is
892 -- 'finalizePD' but there's a bit of other nattering
893 -- about necessary.
895 -- TODO: what exactly is the business with @flaggedTests@ and
896 -- @flaggedBenchmarks@?
897 configureFinalizedPackage
898 :: Verbosity
899 -> ConfigFlags
900 -> ComponentRequestedSpec
901 -> [Dependency]
902 -> (Dependency -> Bool) -- ^ tests if a dependency is satisfiable.
903 -- Might say it's satisfiable even when not.
904 -> Compiler
905 -> Platform
906 -> GenericPackageDescription
907 -> IO (PackageDescription, FlagAssignment)
908 configureFinalizedPackage verbosity cfg enabled
909 allConstraints satisfies comp compPlatform pkg_descr0 = do
911 (pkg_descr0', flags) <-
912 case finalizePD
913 (configConfigurationsFlags cfg)
914 enabled
915 satisfies
916 compPlatform
917 (compilerInfo comp)
918 allConstraints
919 pkg_descr0
920 of Right r -> return r
921 Left missing ->
922 die $ "Encountered missing dependencies:\n"
923 ++ (render . nest 4 . sep . punctuate comma
924 . map (disp . simplifyDependency)
925 $ missing)
927 -- add extra include/lib dirs as specified in cfg
928 -- we do it here so that those get checked too
929 let pkg_descr = addExtraIncludeLibDirs pkg_descr0'
931 when (not (null flags)) $
932 info verbosity $ "Flags chosen: "
933 ++ intercalate ", " [ unFlagName fn ++ "=" ++ display value
934 | (fn, value) <- flags ]
936 return (pkg_descr, flags)
937 where
938 addExtraIncludeLibDirs pkg_descr =
939 let extraBi = mempty { extraLibDirs = configExtraLibDirs cfg
940 , extraFrameworkDirs = configExtraFrameworkDirs cfg
941 , PD.includeDirs = configExtraIncludeDirs cfg}
942 modifyLib l = l{ libBuildInfo = libBuildInfo l
943 `mappend` extraBi }
944 modifyExecutable e = e{ buildInfo = buildInfo e
945 `mappend` extraBi}
946 in pkg_descr{ library = modifyLib `fmap` library pkg_descr
947 , subLibraries = modifyLib `map` subLibraries pkg_descr
948 , executables = modifyExecutable `map`
949 executables pkg_descr}
951 -- | Check for use of Cabal features which require compiler support
952 checkCompilerProblems :: Compiler -> PackageDescription -> ComponentRequestedSpec -> IO ()
953 checkCompilerProblems comp pkg_descr enabled = do
954 unless (renamingPackageFlagsSupported comp ||
955 all (all (isDefaultIncludeRenaming . mixinIncludeRenaming) . mixins)
956 (enabledBuildInfos pkg_descr enabled)) $
957 die $ "Your compiler does not support thinning and renaming on "
958 ++ "package flags. To use this feature you must use "
959 ++ "GHC 7.9 or later."
961 when (any (not.null.PD.reexportedModules) (PD.allLibraries pkg_descr)
962 && not (reexportedModulesSupported comp)) $ do
963 die $ "Your compiler does not support module re-exports. To use "
964 ++ "this feature you must use GHC 7.9 or later."
966 when (any (not.null.PD.signatures) (PD.allLibraries pkg_descr)
967 && not (backpackSupported comp)) $ do
968 die $ "Your compiler does not support Backpack. To use "
969 ++ "this feature you must use GHC 8.1 or later."
971 -- | Select dependencies for the package.
972 configureDependencies
973 :: Verbosity
974 -> UseExternalInternalDeps
975 -> Map PackageName ComponentName -- ^ internal packages
976 -> InstalledPackageIndex -- ^ installed packages
977 -> Map PackageName InstalledPackageInfo -- ^ required deps
978 -> PackageDescription
979 -> IO [(PackageName, InstalledPackageInfo)]
980 configureDependencies verbosity use_external_internal_deps
981 internalPackageSet installedPackageSet requiredDepsMap pkg_descr = do
982 let selectDependencies :: [Dependency] ->
983 ([FailedDependency], [ResolvedDependency])
984 selectDependencies =
985 partitionEithers
986 . map (selectDependency (package pkg_descr)
987 internalPackageSet installedPackageSet
988 requiredDepsMap use_external_internal_deps)
990 (failedDeps, allPkgDeps) =
991 selectDependencies (buildDepends pkg_descr)
993 internalPkgDeps = [ pkgid
994 | InternalDependency _ pkgid <- allPkgDeps ]
995 -- NB: we have to SAVE the package name, because this is the only
996 -- way we can be able to resolve package names in the package
997 -- description.
998 externalPkgDeps = [ (pn, pkg)
999 | ExternalDependency (Dependency pn _) pkg <- allPkgDeps ]
1001 when (not (null internalPkgDeps)
1002 && not (newPackageDepsBehaviour pkg_descr)) $
1003 die $ "The field 'build-depends: "
1004 ++ intercalate ", " (map (display . packageName) internalPkgDeps)
1005 ++ "' refers to a library which is defined within the same "
1006 ++ "package. To use this feature the package must specify at "
1007 ++ "least 'cabal-version: >= 1.8'."
1009 reportFailedDependencies failedDeps
1010 reportSelectedDependencies verbosity allPkgDeps
1012 return externalPkgDeps
1014 -- | Select and apply coverage settings for the build based on the
1015 -- 'ConfigFlags' and 'Compiler'.
1016 configureCoverage :: Verbosity -> ConfigFlags -> Compiler
1017 -> IO (LocalBuildInfo -> LocalBuildInfo)
1018 configureCoverage verbosity cfg comp = do
1019 let tryExeCoverage = fromFlagOrDefault False (configCoverage cfg)
1020 tryLibCoverage = fromFlagOrDefault tryExeCoverage
1021 (mappend (configCoverage cfg) (configLibCoverage cfg))
1022 if coverageSupported comp
1023 then do
1024 let apply lbi = lbi { libCoverage = tryLibCoverage
1025 , exeCoverage = tryExeCoverage
1027 return apply
1028 else do
1029 let apply lbi = lbi { libCoverage = False
1030 , exeCoverage = False
1032 when (tryExeCoverage || tryLibCoverage) $ warn verbosity
1033 ("The compiler " ++ showCompilerId comp ++ " does not support "
1034 ++ "program coverage. Program coverage has been disabled.")
1035 return apply
1037 -- | Compute the effective value of the profiling flags
1038 -- @--enable-library-profiling@ and @--enable-executable-profiling@
1039 -- from the specified 'ConfigFlags'. This may be useful for
1040 -- external Cabal tools which need to interact with Setup in
1041 -- a backwards-compatible way: the most predictable mechanism
1042 -- for enabling profiling across many legacy versions is to
1043 -- NOT use @--enable-profiling@ and use those two flags instead.
1045 -- Note that @--enable-executable-profiling@ also affects profiling
1046 -- of benchmarks and (non-detailed) test suites.
1047 computeEffectiveProfiling :: ConfigFlags -> (Bool {- lib -}, Bool {- exe -})
1048 computeEffectiveProfiling cfg =
1049 -- The --profiling flag sets the default for both libs and exes,
1050 -- but can be overidden by --library-profiling, or the old deprecated
1051 -- --executable-profiling flag.
1053 -- The --profiling-detail and --library-profiling-detail flags behave
1054 -- similarly
1055 let tryExeProfiling = fromFlagOrDefault False
1056 (mappend (configProf cfg) (configProfExe cfg))
1057 tryLibProfiling = fromFlagOrDefault tryExeProfiling
1058 (mappend (configProf cfg) (configProfLib cfg))
1059 in (tryLibProfiling, tryExeProfiling)
1061 -- | Select and apply profiling settings for the build based on the
1062 -- 'ConfigFlags' and 'Compiler'.
1063 configureProfiling :: Verbosity -> ConfigFlags -> Compiler
1064 -> IO (LocalBuildInfo -> LocalBuildInfo)
1065 configureProfiling verbosity cfg comp = do
1066 let (tryLibProfiling, tryExeProfiling) = computeEffectiveProfiling cfg
1068 tryExeProfileLevel = fromFlagOrDefault ProfDetailDefault
1069 (configProfDetail cfg)
1070 tryLibProfileLevel = fromFlagOrDefault ProfDetailDefault
1071 (mappend
1072 (configProfDetail cfg)
1073 (configProfLibDetail cfg))
1075 checkProfileLevel (ProfDetailOther other) = do
1076 warn verbosity
1077 ("Unknown profiling detail level '" ++ other
1078 ++ "', using default.\nThe profiling detail levels are: "
1079 ++ intercalate ", "
1080 [ name | (name, _, _) <- knownProfDetailLevels ])
1081 return ProfDetailDefault
1082 checkProfileLevel other = return other
1084 (exeProfWithoutLibProf, applyProfiling) <-
1085 if profilingSupported comp
1086 then do
1087 exeLevel <- checkProfileLevel tryExeProfileLevel
1088 libLevel <- checkProfileLevel tryLibProfileLevel
1089 let apply lbi = lbi { withProfLib = tryLibProfiling
1090 , withProfLibDetail = libLevel
1091 , withProfExe = tryExeProfiling
1092 , withProfExeDetail = exeLevel
1094 return (tryExeProfiling && not tryLibProfiling, apply)
1095 else do
1096 let apply lbi = lbi { withProfLib = False
1097 , withProfLibDetail = ProfDetailNone
1098 , withProfExe = False
1099 , withProfExeDetail = ProfDetailNone
1101 when (tryExeProfiling || tryLibProfiling) $ warn verbosity
1102 ("The compiler " ++ showCompilerId comp ++ " does not support "
1103 ++ "profiling. Profiling has been disabled.")
1104 return (False, apply)
1106 when exeProfWithoutLibProf $ warn verbosity
1107 ("Executables will be built with profiling, but library "
1108 ++ "profiling is disabled. Linking will fail if any executables "
1109 ++ "depend on the library.")
1111 return applyProfiling
1113 -- -----------------------------------------------------------------------------
1114 -- Configuring package dependencies
1116 reportProgram :: Verbosity -> Program -> Maybe ConfiguredProgram -> IO ()
1117 reportProgram verbosity prog Nothing
1118 = info verbosity $ "No " ++ programName prog ++ " found"
1119 reportProgram verbosity prog (Just configuredProg)
1120 = info verbosity $ "Using " ++ programName prog ++ version ++ location
1121 where location = case programLocation configuredProg of
1122 FoundOnSystem p -> " found on system at: " ++ p
1123 UserSpecified p -> " given by user at: " ++ p
1124 version = case programVersion configuredProg of
1125 Nothing -> ""
1126 Just v -> " version " ++ display v
1128 hackageUrl :: String
1129 hackageUrl = "http://hackage.haskell.org/package/"
1131 data ResolvedDependency
1132 -- | An external dependency from the package database, OR an
1133 -- internal dependency which we are getting from the package
1134 -- database.
1135 = ExternalDependency Dependency InstalledPackageInfo
1136 -- | An internal dependency ('PackageId' should be a library name)
1137 -- which we are going to have to build. (The
1138 -- 'PackageId' here is a hack to get a modest amount of
1139 -- polymorphism out of the 'Package' typeclass.)
1140 | InternalDependency Dependency PackageId
1142 data FailedDependency = DependencyNotExists PackageName
1143 | DependencyMissingInternal PackageName PackageName
1144 | DependencyNoVersion Dependency
1146 -- | Test for a package dependency and record the version we have installed.
1147 selectDependency :: PackageId -- ^ Package id of current package
1148 -> Map PackageName ComponentName
1149 -> InstalledPackageIndex -- ^ Installed packages
1150 -> Map PackageName InstalledPackageInfo
1151 -- ^ Packages for which we have been given specific deps to
1152 -- use
1153 -> UseExternalInternalDeps -- ^ Are we configuring a
1154 -- single component?
1155 -> Dependency
1156 -> Either FailedDependency ResolvedDependency
1157 selectDependency pkgid internalIndex installedIndex requiredDepsMap
1158 use_external_internal_deps
1159 dep@(Dependency dep_pkgname vr) =
1160 -- If the dependency specification matches anything in the internal package
1161 -- index, then we prefer that match to anything in the second.
1162 -- For example:
1164 -- Name: MyLibrary
1165 -- Version: 0.1
1166 -- Library
1167 -- ..
1168 -- Executable my-exec
1169 -- build-depends: MyLibrary
1171 -- We want "build-depends: MyLibrary" always to match the internal library
1172 -- even if there is a newer installed library "MyLibrary-0.2".
1173 case Map.lookup dep_pkgname internalIndex of
1174 Just cname -> if use_external_internal_deps
1175 then do_external (Just cname)
1176 else do_internal
1177 _ -> do_external Nothing
1178 where
1179 do_internal = Right (InternalDependency dep
1180 (PackageIdentifier dep_pkgname (packageVersion pkgid)))
1181 do_external is_internal = case Map.lookup dep_pkgname requiredDepsMap of
1182 -- If we know the exact pkg to use, then use it.
1183 Just pkginstance -> Right (ExternalDependency dep pkginstance)
1184 -- Otherwise we just pick an arbitrary instance of the latest version.
1185 Nothing -> case PackageIndex.lookupDependency installedIndex dep' of
1186 [] -> Left $
1187 case is_internal of
1188 Just cname -> DependencyMissingInternal dep_pkgname
1189 (computeCompatPackageName (packageName pkgid) cname)
1190 Nothing -> DependencyNotExists dep_pkgname
1191 pkgs -> Right $ ExternalDependency dep $
1192 case last pkgs of
1193 (_ver, pkginstances) -> head pkginstances
1194 where
1195 dep' | Just cname <- is_internal
1196 = Dependency (computeCompatPackageName (packageName pkgid) cname) vr
1197 | otherwise = dep
1198 -- NB: here computeCompatPackageName we want to pick up the INDEFINITE ones
1199 -- which is why we pass 'Nothing' as 'UnitId'
1201 reportSelectedDependencies :: Verbosity
1202 -> [ResolvedDependency] -> IO ()
1203 reportSelectedDependencies verbosity deps =
1204 info verbosity $ unlines
1205 [ "Dependency " ++ display (simplifyDependency dep)
1206 ++ ": using " ++ display pkgid
1207 | resolved <- deps
1208 , let (dep, pkgid) = case resolved of
1209 ExternalDependency dep' pkg' -> (dep', packageId pkg')
1210 InternalDependency dep' pkgid' -> (dep', pkgid') ]
1212 reportFailedDependencies :: [FailedDependency] -> IO ()
1213 reportFailedDependencies [] = return ()
1214 reportFailedDependencies failed =
1215 die (intercalate "\n\n" (map reportFailedDependency failed))
1217 where
1218 reportFailedDependency (DependencyNotExists pkgname) =
1219 "there is no version of " ++ display pkgname ++ " installed.\n"
1220 ++ "Perhaps you need to download and install it from\n"
1221 ++ hackageUrl ++ display pkgname ++ "?"
1223 reportFailedDependency (DependencyMissingInternal pkgname real_pkgname) =
1224 "internal dependency " ++ display pkgname ++ " not installed.\n"
1225 ++ "Perhaps you need to configure and install it first?\n"
1226 ++ "(Munged package name we searched for was "
1227 ++ display real_pkgname ++ ")"
1229 reportFailedDependency (DependencyNoVersion dep) =
1230 "cannot satisfy dependency " ++ display (simplifyDependency dep) ++ "\n"
1232 -- | List all installed packages in the given package databases.
1233 getInstalledPackages :: Verbosity -> Compiler
1234 -> PackageDBStack -- ^ The stack of package databases.
1235 -> ProgramDb
1236 -> IO InstalledPackageIndex
1237 getInstalledPackages verbosity comp packageDBs progdb = do
1238 when (null packageDBs) $
1239 die $ "No package databases have been specified. If you use "
1240 ++ "--package-db=clear, you must follow it with --package-db= "
1241 ++ "with 'global', 'user' or a specific file."
1243 info verbosity "Reading installed packages..."
1244 case compilerFlavor comp of
1245 GHC -> GHC.getInstalledPackages verbosity comp packageDBs progdb
1246 GHCJS -> GHCJS.getInstalledPackages verbosity packageDBs progdb
1247 JHC -> JHC.getInstalledPackages verbosity packageDBs progdb
1248 LHC -> LHC.getInstalledPackages verbosity packageDBs progdb
1249 UHC -> UHC.getInstalledPackages verbosity comp packageDBs progdb
1250 HaskellSuite {} ->
1251 HaskellSuite.getInstalledPackages verbosity packageDBs progdb
1252 flv -> die $ "don't know how to find the installed packages for "
1253 ++ display flv
1255 -- | Like 'getInstalledPackages', but for a single package DB.
1257 -- NB: Why isn't this always a fall through to 'getInstalledPackages'?
1258 -- That is because 'getInstalledPackages' performs some sanity checks
1259 -- on the package database stack in question. However, when sandboxes
1260 -- are involved these sanity checks are not desirable.
1261 getPackageDBContents :: Verbosity -> Compiler
1262 -> PackageDB -> ProgramDb
1263 -> IO InstalledPackageIndex
1264 getPackageDBContents verbosity comp packageDB progdb = do
1265 info verbosity "Reading installed packages..."
1266 case compilerFlavor comp of
1267 GHC -> GHC.getPackageDBContents verbosity packageDB progdb
1268 GHCJS -> GHCJS.getPackageDBContents verbosity packageDB progdb
1269 -- For other compilers, try to fall back on 'getInstalledPackages'.
1270 _ -> getInstalledPackages verbosity comp [packageDB] progdb
1273 -- | A set of files (or directories) that can be monitored to detect when
1274 -- there might have been a change in the installed packages.
1276 getInstalledPackagesMonitorFiles :: Verbosity -> Compiler
1277 -> PackageDBStack
1278 -> ProgramDb -> Platform
1279 -> IO [FilePath]
1280 getInstalledPackagesMonitorFiles verbosity comp packageDBs progdb platform =
1281 case compilerFlavor comp of
1282 GHC -> GHC.getInstalledPackagesMonitorFiles
1283 verbosity platform progdb packageDBs
1284 other -> do
1285 warn verbosity $ "don't know how to find change monitoring files for "
1286 ++ "the installed package databases for " ++ display other
1287 return []
1289 -- | The user interface specifies the package dbs to use with a combination of
1290 -- @--global@, @--user@ and @--package-db=global|user|clear|$file@.
1291 -- This function combines the global/user flag and interprets the package-db
1292 -- flag into a single package db stack.
1294 interpretPackageDbFlags :: Bool -> [Maybe PackageDB] -> PackageDBStack
1295 interpretPackageDbFlags userInstall specificDBs =
1296 extra initialStack specificDBs
1297 where
1298 initialStack | userInstall = [GlobalPackageDB, UserPackageDB]
1299 | otherwise = [GlobalPackageDB]
1301 extra dbs' [] = dbs'
1302 extra _ (Nothing:dbs) = extra [] dbs
1303 extra dbs' (Just db:dbs) = extra (dbs' ++ [db]) dbs
1305 -- We are given both --constraint="foo < 2.0" style constraints and also
1306 -- specific packages to pick via --dependency="foo=foo-2.0-177d5cdf20962d0581".
1308 -- When finalising the package we have to take into account the specific
1309 -- installed deps we've been given, and the finalise function expects
1310 -- constraints, so we have to translate these deps into version constraints.
1312 -- But after finalising we then have to make sure we pick the right specific
1313 -- deps in the end. So we still need to remember which installed packages to
1314 -- pick.
1315 combinedConstraints :: [Dependency] ->
1316 [(PackageName, ComponentId)] ->
1317 InstalledPackageIndex ->
1318 Either String ([Dependency],
1319 Map PackageName InstalledPackageInfo)
1320 combinedConstraints constraints dependencies installedPackages = do
1322 when (not (null badComponentIds)) $
1323 Left $ render $ text "The following package dependencies were requested"
1324 $+$ nest 4 (dispDependencies badComponentIds)
1325 $+$ text "however the given installed package instance does not exist."
1327 --TODO: we don't check that all dependencies are used!
1329 return (allConstraints, idConstraintMap)
1331 where
1332 allConstraints :: [Dependency]
1333 allConstraints = constraints
1334 ++ [ thisPackageVersion (packageId pkg)
1335 | (_, _, Just pkg) <- dependenciesPkgInfo ]
1337 idConstraintMap :: Map PackageName InstalledPackageInfo
1338 idConstraintMap = Map.fromList
1339 [ (packageName pkg, pkg)
1340 | (_, _, Just pkg) <- dependenciesPkgInfo ]
1342 -- The dependencies along with the installed package info, if it exists
1343 dependenciesPkgInfo :: [(PackageName, ComponentId,
1344 Maybe InstalledPackageInfo)]
1345 dependenciesPkgInfo =
1346 [ (pkgname, cid, mpkg)
1347 | (pkgname, cid) <- dependencies
1348 , let mpkg = PackageIndex.lookupComponentId
1349 installedPackages cid
1352 -- If we looked up a package specified by an installed package id
1353 -- (i.e. someone has written a hash) and didn't find it then it's
1354 -- an error.
1355 badComponentIds =
1356 [ (pkgname, cid)
1357 | (pkgname, cid, Nothing) <- dependenciesPkgInfo ]
1359 dispDependencies deps =
1360 hsep [ text "--dependency="
1361 <<>> quotes (disp pkgname <<>> char '=' <<>> disp cid)
1362 | (pkgname, cid) <- deps ]
1364 -- -----------------------------------------------------------------------------
1365 -- Configuring program dependencies
1367 configureRequiredPrograms :: Verbosity -> [LegacyExeDependency] -> ProgramDb
1368 -> IO ProgramDb
1369 configureRequiredPrograms verbosity deps progdb =
1370 foldM (configureRequiredProgram verbosity) progdb deps
1372 -- | Configure a required program, ensuring that it exists in the PATH
1373 -- (or where the user has specified the program must live) and making it
1374 -- available for use via the 'ProgramDb' interface. If the program is
1375 -- known (exists in the input 'ProgramDb'), we will make sure that the
1376 -- program matches the required version; otherwise we will accept
1377 -- any version of the program and assume that it is a simpleProgram.
1378 configureRequiredProgram :: Verbosity -> ProgramDb -> LegacyExeDependency
1379 -> IO ProgramDb
1380 configureRequiredProgram verbosity progdb
1381 (LegacyExeDependency progName verRange) =
1382 case lookupKnownProgram progName progdb of
1383 Nothing ->
1384 -- Try to configure it as a 'simpleProgram' automatically
1386 -- There's a bit of a story behind this line. In old versions
1387 -- of Cabal, there were only internal build-tools dependencies. So the
1388 -- behavior in this case was:
1390 -- - If a build-tool dependency was internal, don't do
1391 -- any checking.
1393 -- - If it was external, call 'configureRequiredProgram' to
1394 -- "configure" the executable. In particular, if
1395 -- the program was not "known" (present in 'ProgramDb'),
1396 -- then we would just error. This was fine, because
1397 -- the only way a program could be executed from 'ProgramDb'
1398 -- is if some library code from Cabal actually called it,
1399 -- and the pre-existing Cabal code only calls known
1400 -- programs from 'defaultProgramDb', and so if it
1401 -- is calling something else, you have a Custom setup
1402 -- script, and in that case you are expected to register
1403 -- the program you want to call in the ProgramDb.
1405 -- OK, so that was fine, until I (ezyang, in 2016) refactored
1406 -- Cabal to support per-component builds. In this case, what
1407 -- was previously an internal build-tool dependency now became
1408 -- an external one, and now previously "internal" dependencies
1409 -- are now external. But these are permitted to exist even
1410 -- when they are not previously configured (something that
1411 -- can only occur by a Custom script.)
1413 -- So, I decided, "Fine, let's just accept these in any
1414 -- case." Thus this line. The alternative would have been to
1415 -- somehow detect when a build-tools dependency was "internal" (by
1416 -- looking at the unflattened package description) but this
1417 -- would also be incompatible with future work to support
1418 -- external executable dependencies: we definitely cannot
1419 -- assume they will be preinitialized in the 'ProgramDb'.
1420 configureProgram verbosity (simpleProgram progName) progdb
1421 Just prog
1422 -- requireProgramVersion always requires the program have a version
1423 -- but if the user says "build-depends: foo" ie no version constraint
1424 -- then we should not fail if we cannot discover the program version.
1425 | verRange == anyVersion -> do
1426 (_, progdb') <- requireProgram verbosity prog progdb
1427 return progdb'
1428 | otherwise -> do
1429 (_, _, progdb') <- requireProgramVersion verbosity prog verRange progdb
1430 return progdb'
1432 -- -----------------------------------------------------------------------------
1433 -- Configuring pkg-config package dependencies
1435 configurePkgconfigPackages :: Verbosity -> PackageDescription
1436 -> ProgramDb -> ComponentRequestedSpec
1437 -> IO (PackageDescription, ProgramDb)
1438 configurePkgconfigPackages verbosity pkg_descr progdb enabled
1439 | null allpkgs = return (pkg_descr, progdb)
1440 | otherwise = do
1441 (_, _, progdb') <- requireProgramVersion
1442 (lessVerbose verbosity) pkgConfigProgram
1443 (orLaterVersion $ mkVersion [0,9,0]) progdb
1444 traverse_ requirePkg allpkgs
1445 mlib' <- traverse addPkgConfigBILib (library pkg_descr)
1446 libs' <- traverse addPkgConfigBILib (subLibraries pkg_descr)
1447 exes' <- traverse addPkgConfigBIExe (executables pkg_descr)
1448 tests' <- traverse addPkgConfigBITest (testSuites pkg_descr)
1449 benches' <- traverse addPkgConfigBIBench (benchmarks pkg_descr)
1450 let pkg_descr' = pkg_descr { library = mlib',
1451 subLibraries = libs', executables = exes',
1452 testSuites = tests', benchmarks = benches' }
1453 return (pkg_descr', progdb')
1455 where
1456 allpkgs = concatMap pkgconfigDepends (enabledBuildInfos pkg_descr enabled)
1457 pkgconfig = getDbProgramOutput (lessVerbose verbosity)
1458 pkgConfigProgram progdb
1460 requirePkg dep@(PkgconfigDependency pkgn range) = do
1461 version <- pkgconfig ["--modversion", pkg]
1462 `catchIO` (\_ -> die notFound)
1463 `catchExit` (\_ -> die notFound)
1464 case simpleParse version of
1465 Nothing -> die "parsing output of pkg-config --modversion failed"
1466 Just v | not (withinRange v range) -> die (badVersion v)
1467 | otherwise -> info verbosity (depSatisfied v)
1468 where
1469 notFound = "The pkg-config package '" ++ pkg ++ "'"
1470 ++ versionRequirement
1471 ++ " is required but it could not be found."
1472 badVersion v = "The pkg-config package '" ++ pkg ++ "'"
1473 ++ versionRequirement
1474 ++ " is required but the version installed on the"
1475 ++ " system is version " ++ display v
1476 depSatisfied v = "Dependency " ++ display dep
1477 ++ ": using version " ++ display v
1479 versionRequirement
1480 | isAnyVersion range = ""
1481 | otherwise = " version " ++ display range
1483 pkg = unPkgconfigName pkgn
1485 -- Adds pkgconfig dependencies to the build info for a component
1486 addPkgConfigBI compBI setCompBI comp = do
1487 bi <- pkgconfigBuildInfo (pkgconfigDepends (compBI comp))
1488 return $ setCompBI comp (compBI comp `mappend` bi)
1490 -- Adds pkgconfig dependencies to the build info for a library
1491 addPkgConfigBILib = addPkgConfigBI libBuildInfo $
1492 \lib bi -> lib { libBuildInfo = bi }
1494 -- Adds pkgconfig dependencies to the build info for an executable
1495 addPkgConfigBIExe = addPkgConfigBI buildInfo $
1496 \exe bi -> exe { buildInfo = bi }
1498 -- Adds pkgconfig dependencies to the build info for a test suite
1499 addPkgConfigBITest = addPkgConfigBI testBuildInfo $
1500 \test bi -> test { testBuildInfo = bi }
1502 -- Adds pkgconfig dependencies to the build info for a benchmark
1503 addPkgConfigBIBench = addPkgConfigBI benchmarkBuildInfo $
1504 \bench bi -> bench { benchmarkBuildInfo = bi }
1506 pkgconfigBuildInfo :: [PkgconfigDependency] -> NoCallStackIO BuildInfo
1507 pkgconfigBuildInfo [] = return mempty
1508 pkgconfigBuildInfo pkgdeps = do
1509 let pkgs = nub [ display pkg | PkgconfigDependency pkg _ <- pkgdeps ]
1510 ccflags <- pkgconfig ("--cflags" : pkgs)
1511 ldflags <- pkgconfig ("--libs" : pkgs)
1512 return (ccLdOptionsBuildInfo (words ccflags) (words ldflags))
1514 -- | Makes a 'BuildInfo' from C compiler and linker flags.
1516 -- This can be used with the output from configuration programs like pkg-config
1517 -- and similar package-specific programs like mysql-config, freealut-config etc.
1518 -- For example:
1520 -- > ccflags <- getDbProgramOutput verbosity prog progdb ["--cflags"]
1521 -- > ldflags <- getDbProgramOutput verbosity prog progdb ["--libs"]
1522 -- > return (ccldOptionsBuildInfo (words ccflags) (words ldflags))
1524 ccLdOptionsBuildInfo :: [String] -> [String] -> BuildInfo
1525 ccLdOptionsBuildInfo cflags ldflags =
1526 let (includeDirs', cflags') = partition ("-I" `isPrefixOf`) cflags
1527 (extraLibs', ldflags') = partition ("-l" `isPrefixOf`) ldflags
1528 (extraLibDirs', ldflags'') = partition ("-L" `isPrefixOf`) ldflags'
1529 in mempty {
1530 PD.includeDirs = map (drop 2) includeDirs',
1531 PD.extraLibs = map (drop 2) extraLibs',
1532 PD.extraLibDirs = map (drop 2) extraLibDirs',
1533 PD.ccOptions = cflags',
1534 PD.ldOptions = ldflags''
1537 -- -----------------------------------------------------------------------------
1538 -- Determining the compiler details
1540 configCompilerAuxEx :: ConfigFlags
1541 -> IO (Compiler, Platform, ProgramDb)
1542 configCompilerAuxEx cfg = configCompilerEx (flagToMaybe $ configHcFlavor cfg)
1543 (flagToMaybe $ configHcPath cfg)
1544 (flagToMaybe $ configHcPkg cfg)
1545 programDb
1546 (fromFlag (configVerbosity cfg))
1547 where
1548 programDb = mkProgramDb cfg defaultProgramDb
1550 configCompilerEx :: Maybe CompilerFlavor -> Maybe FilePath -> Maybe FilePath
1551 -> ProgramDb -> Verbosity
1552 -> IO (Compiler, Platform, ProgramDb)
1553 configCompilerEx Nothing _ _ _ _ = die "Unknown compiler"
1554 configCompilerEx (Just hcFlavor) hcPath hcPkg progdb verbosity = do
1555 (comp, maybePlatform, programDb) <- case hcFlavor of
1556 GHC -> GHC.configure verbosity hcPath hcPkg progdb
1557 GHCJS -> GHCJS.configure verbosity hcPath hcPkg progdb
1558 JHC -> JHC.configure verbosity hcPath hcPkg progdb
1559 LHC -> do (_, _, ghcConf) <- GHC.configure verbosity Nothing hcPkg progdb
1560 LHC.configure verbosity hcPath Nothing ghcConf
1561 UHC -> UHC.configure verbosity hcPath hcPkg progdb
1562 HaskellSuite {} -> HaskellSuite.configure verbosity hcPath hcPkg progdb
1563 _ -> die "Unknown compiler"
1564 return (comp, fromMaybe buildPlatform maybePlatform, programDb)
1566 -- Ideally we would like to not have separate configCompiler* and
1567 -- configCompiler*Ex sets of functions, but there are many custom setup scripts
1568 -- in the wild that are using them, so the versions with old types are kept for
1569 -- backwards compatibility. Platform was added to the return triple in 1.18.
1571 {-# DEPRECATED configCompiler
1572 "'configCompiler' is deprecated. Use 'configCompilerEx' instead." #-}
1573 configCompiler :: Maybe CompilerFlavor -> Maybe FilePath -> Maybe FilePath
1574 -> ProgramDb -> Verbosity
1575 -> IO (Compiler, ProgramDb)
1576 configCompiler mFlavor hcPath hcPkg progdb verbosity =
1577 fmap (\(a,_,b) -> (a,b)) $ configCompilerEx mFlavor hcPath hcPkg progdb verbosity
1579 {-# DEPRECATED configCompilerAux
1580 "configCompilerAux is deprecated. Use 'configCompilerAuxEx' instead." #-}
1581 configCompilerAux :: ConfigFlags
1582 -> IO (Compiler, ProgramDb)
1583 configCompilerAux = fmap (\(a,_,b) -> (a,b)) . configCompilerAuxEx
1585 -- -----------------------------------------------------------------------------
1586 -- Testing C lib and header dependencies
1588 -- Try to build a test C program which includes every header and links every
1589 -- lib. If that fails, try to narrow it down by preprocessing (only) and linking
1590 -- with individual headers and libs. If none is the obvious culprit then give a
1591 -- generic error message.
1592 -- TODO: produce a log file from the compiler errors, if any.
1593 checkForeignDeps :: PackageDescription -> LocalBuildInfo -> Verbosity -> IO ()
1594 checkForeignDeps pkg lbi verbosity = do
1595 ifBuildsWith allHeaders (commonCcArgs ++ makeLdArgs allLibs) -- I'm feeling
1596 -- lucky
1597 (return ())
1598 (do missingLibs <- findMissingLibs
1599 missingHdr <- findOffendingHdr
1600 explainErrors missingHdr missingLibs)
1601 where
1602 allHeaders = collectField PD.includes
1603 allLibs = collectField PD.extraLibs
1605 ifBuildsWith headers args success failure = do
1606 ok <- builds (makeProgram headers) args
1607 if ok then success else failure
1609 findOffendingHdr =
1610 ifBuildsWith allHeaders ccArgs
1611 (return Nothing)
1612 (go . tail . inits $ allHeaders)
1613 where
1614 go [] = return Nothing -- cannot happen
1615 go (hdrs:hdrsInits) =
1616 -- Try just preprocessing first
1617 ifBuildsWith hdrs cppArgs
1618 -- If that works, try compiling too
1619 (ifBuildsWith hdrs ccArgs
1620 (go hdrsInits)
1621 (return . Just . Right . last $ hdrs))
1622 (return . Just . Left . last $ hdrs)
1624 cppArgs = "-E":commonCppArgs -- preprocess only
1625 ccArgs = "-c":commonCcArgs -- don't try to link
1627 findMissingLibs = ifBuildsWith [] (makeLdArgs allLibs)
1628 (return [])
1629 (filterM (fmap not . libExists) allLibs)
1631 libExists lib = builds (makeProgram []) (makeLdArgs [lib])
1633 commonCppArgs = platformDefines lbi
1634 -- TODO: This is a massive hack, to work around the
1635 -- fact that the test performed here should be
1636 -- PER-component (c.f. the "I'm Feeling Lucky"; we
1637 -- should NOT be glomming everything together.)
1638 ++ [ "-I" ++ buildDir lbi </> "autogen" ]
1639 ++ [ "-I" ++ dir | dir <- collectField PD.includeDirs ]
1640 ++ ["-I."]
1641 ++ collectField PD.cppOptions
1642 ++ collectField PD.ccOptions
1643 ++ [ "-I" ++ dir
1644 | dir <- ordNub [ dir
1645 | dep <- deps
1646 , dir <- Installed.includeDirs dep ]
1647 -- dedupe include dirs of dependencies
1648 -- to prevent quadratic blow-up
1650 ++ [ opt
1651 | dep <- deps
1652 , opt <- Installed.ccOptions dep ]
1654 commonCcArgs = commonCppArgs
1655 ++ collectField PD.ccOptions
1656 ++ [ opt
1657 | dep <- deps
1658 , opt <- Installed.ccOptions dep ]
1660 commonLdArgs = [ "-L" ++ dir | dir <- collectField PD.extraLibDirs ]
1661 ++ collectField PD.ldOptions
1662 ++ [ "-L" ++ dir
1663 | dep <- deps
1664 , dir <- Installed.libraryDirs dep ]
1665 --TODO: do we also need dependent packages' ld options?
1666 makeLdArgs libs = [ "-l"++lib | lib <- libs ] ++ commonLdArgs
1668 makeProgram hdrs = unlines $
1669 [ "#include \"" ++ hdr ++ "\"" | hdr <- hdrs ] ++
1670 ["int main(int argc, char** argv) { return 0; }"]
1672 collectField f = concatMap f allBi
1673 allBi = enabledBuildInfos pkg (componentEnabledSpec lbi)
1674 deps = PackageIndex.topologicalOrder (installedPkgs lbi)
1676 builds program args = do
1677 tempDir <- getTemporaryDirectory
1678 withTempFile tempDir ".c" $ \cName cHnd ->
1679 withTempFile tempDir "" $ \oNname oHnd -> do
1680 hPutStrLn cHnd program
1681 hClose cHnd
1682 hClose oHnd
1683 _ <- getDbProgramOutput verbosity
1684 gccProgram (withPrograms lbi) (cName:"-o":oNname:args)
1685 return True
1686 `catchIO` (\_ -> return False)
1687 `catchExit` (\_ -> return False)
1689 explainErrors Nothing [] = return () -- should be impossible!
1690 explainErrors _ _
1691 | isNothing . lookupProgram gccProgram . withPrograms $ lbi
1693 = die $ unlines $
1694 [ "No working gcc",
1695 "This package depends on foreign library but we cannot "
1696 ++ "find a working C compiler. If you have it in a "
1697 ++ "non-standard location you can use the --with-gcc "
1698 ++ "flag to specify it." ]
1700 explainErrors hdr libs = die $ unlines $
1701 [ if plural
1702 then "Missing dependencies on foreign libraries:"
1703 else "Missing dependency on a foreign library:"
1704 | missing ]
1705 ++ case hdr of
1706 Just (Left h) -> ["* Missing (or bad) header file: " ++ h ]
1707 _ -> []
1708 ++ case libs of
1709 [] -> []
1710 [lib] -> ["* Missing C library: " ++ lib]
1711 _ -> ["* Missing C libraries: " ++ intercalate ", " libs]
1712 ++ [if plural then messagePlural else messageSingular | missing]
1713 ++ case hdr of
1714 Just (Left _) -> [ headerCppMessage ]
1715 Just (Right h) -> [ (if missing then "* " else "")
1716 ++ "Bad header file: " ++ h
1717 , headerCcMessage ]
1718 _ -> []
1720 where
1721 plural = length libs >= 2
1722 -- Is there something missing? (as opposed to broken)
1723 missing = not (null libs)
1724 || case hdr of Just (Left _) -> True; _ -> False
1726 messageSingular =
1727 "This problem can usually be solved by installing the system "
1728 ++ "package that provides this library (you may need the "
1729 ++ "\"-dev\" version). If the library is already installed "
1730 ++ "but in a non-standard location then you can use the flags "
1731 ++ "--extra-include-dirs= and --extra-lib-dirs= to specify "
1732 ++ "where it is."
1733 messagePlural =
1734 "This problem can usually be solved by installing the system "
1735 ++ "packages that provide these libraries (you may need the "
1736 ++ "\"-dev\" versions). If the libraries are already installed "
1737 ++ "but in a non-standard location then you can use the flags "
1738 ++ "--extra-include-dirs= and --extra-lib-dirs= to specify "
1739 ++ "where they are."
1740 headerCppMessage =
1741 "If the header file does exist, it may contain errors that "
1742 ++ "are caught by the C compiler at the preprocessing stage. "
1743 ++ "In this case you can re-run configure with the verbosity "
1744 ++ "flag -v3 to see the error messages."
1745 headerCcMessage =
1746 "The header file contains a compile error. "
1747 ++ "You can re-run configure with the verbosity flag "
1748 ++ "-v3 to see the error messages from the C compiler."
1750 -- | Output package check warnings and errors. Exit if any errors.
1751 checkPackageProblems :: Verbosity
1752 -> GenericPackageDescription
1753 -> PackageDescription
1754 -> IO ()
1755 checkPackageProblems verbosity gpkg pkg = do
1756 ioChecks <- checkPackageFiles pkg "."
1757 let pureChecks = checkPackage gpkg (Just pkg)
1758 errors = [ e | PackageBuildImpossible e <- pureChecks ++ ioChecks ]
1759 warnings = [ w | PackageBuildWarning w <- pureChecks ++ ioChecks ]
1760 if null errors
1761 then traverse_ (warn verbosity) warnings
1762 else die (intercalate "\n\n" errors)
1764 -- | Preform checks if a relocatable build is allowed
1765 checkRelocatable :: Verbosity
1766 -> PackageDescription
1767 -> LocalBuildInfo
1768 -> IO ()
1769 checkRelocatable verbosity pkg lbi
1770 = sequence_ [ checkOS
1771 , checkCompiler
1772 , packagePrefixRelative
1773 , depsPrefixRelative
1775 where
1776 -- Check if the OS support relocatable builds.
1778 -- If you add new OS' to this list, and your OS supports dynamic libraries
1779 -- and RPATH, make sure you add your OS to RPATH-support list of:
1780 -- Distribution.Simple.GHC.getRPaths
1781 checkOS
1782 = unless (os `elem` [ OSX, Linux ])
1783 $ die $ "Operating system: " ++ display os ++
1784 ", does not support relocatable builds"
1785 where
1786 (Platform _ os) = hostPlatform lbi
1788 -- Check if the Compiler support relocatable builds
1789 checkCompiler
1790 = unless (compilerFlavor comp `elem` [ GHC ])
1791 $ die $ "Compiler: " ++ show comp ++
1792 ", does not support relocatable builds"
1793 where
1794 comp = compiler lbi
1796 -- Check if all the install dirs are relative to same prefix
1797 packagePrefixRelative
1798 = unless (relativeInstallDirs installDirs)
1799 $ die $ "Installation directories are not prefix_relative:\n" ++
1800 show installDirs
1801 where
1802 -- NB: should be good enough to check this against the default
1803 -- component ID, but if we wanted to be strictly correct we'd
1804 -- check for each ComponentId.
1805 installDirs = absoluteInstallDirs pkg lbi NoCopyDest
1806 p = prefix installDirs
1807 relativeInstallDirs (InstallDirs {..}) =
1808 all isJust
1809 (fmap (stripPrefix p)
1810 [ bindir, libdir, dynlibdir, libexecdir, includedir, datadir
1811 , docdir, mandir, htmldir, haddockdir, sysconfdir] )
1813 -- Check if the library dirs of the dependencies that are in the package
1814 -- database to which the package is installed are relative to the
1815 -- prefix of the package
1816 depsPrefixRelative = do
1817 pkgr <- GHC.pkgRoot verbosity lbi (last (withPackageDB lbi))
1818 traverse_ (doCheck pkgr) ipkgs
1819 where
1820 doCheck pkgr ipkg
1821 | maybe False (== pkgr) (Installed.pkgRoot ipkg)
1822 = traverse_ (\l -> when (isNothing $ stripPrefix p l) (die (msg l)))
1823 (Installed.libraryDirs ipkg)
1824 | otherwise
1825 = return ()
1826 -- NB: should be good enough to check this against the default
1827 -- component ID, but if we wanted to be strictly correct we'd
1828 -- check for each ComponentId.
1829 installDirs = absoluteInstallDirs pkg lbi NoCopyDest
1830 p = prefix installDirs
1831 ipkgs = PackageIndex.allPackages (installedPkgs lbi)
1832 msg l = "Library directory of a dependency: " ++ show l ++
1833 "\nis not relative to the installation prefix:\n" ++
1834 show p
1836 -- -----------------------------------------------------------------------------
1837 -- Testing foreign library requirements
1839 unsupportedForeignLibs :: Compiler -> Platform -> [ForeignLib] -> [String]
1840 unsupportedForeignLibs comp platform =
1841 mapMaybe (checkForeignLibSupported comp platform)
1843 checkForeignLibSupported :: Compiler -> Platform -> ForeignLib -> Maybe String
1844 checkForeignLibSupported comp platform flib = go (compilerFlavor comp)
1845 where
1846 go :: CompilerFlavor -> Maybe String
1847 go GHC
1848 | compilerVersion comp < mkVersion [7,8] = unsupported [
1849 "Building foreign libraires is only supported with GHC >= 7.8"
1851 | otherwise = goGhcPlatform platform
1852 go _ = unsupported [
1853 "Building foreign libraries is currently only supported with ghc"
1856 goGhcPlatform :: Platform -> Maybe String
1857 goGhcPlatform (Platform X86_64 OSX ) = goGhcOsx (foreignLibType flib)
1858 goGhcPlatform (Platform I386 Linux ) = goGhcLinux (foreignLibType flib)
1859 goGhcPlatform (Platform X86_64 Linux ) = goGhcLinux (foreignLibType flib)
1860 goGhcPlatform (Platform I386 Windows) = goGhcWindows (foreignLibType flib)
1861 goGhcPlatform (Platform X86_64 Windows) = goGhcWindows (foreignLibType flib)
1862 goGhcPlatform _ = unsupported [
1863 "Building foreign libraries is currently only supported on OSX, "
1864 , "Linux and Windows"
1867 goGhcOsx :: ForeignLibType -> Maybe String
1868 goGhcOsx ForeignLibNativeShared
1869 | standalone = unsupported [
1870 "We cannot build standalone libraries on OSX"
1872 | not (null (foreignLibModDefFile flib)) = unsupported [
1873 "Module definition file not supported on OSX"
1875 | otherwise =
1876 Nothing
1877 goGhcOsx _ = unsupported [
1878 "We can currently only build shared foreign libraries on OSX"
1881 goGhcLinux :: ForeignLibType -> Maybe String
1882 goGhcLinux ForeignLibNativeShared
1883 | standalone = unsupported [
1884 "We cannot build standalone libraries on OSX"
1886 | not (null (foreignLibModDefFile flib)) = unsupported [
1887 "Module definition file not supported on OSX"
1889 | otherwise =
1890 Nothing
1891 goGhcLinux _ = unsupported [
1892 "We can currently only build shared foreign libraries on Linux"
1895 goGhcWindows :: ForeignLibType -> Maybe String
1896 goGhcWindows ForeignLibNativeShared
1897 | not standalone = unsupported [
1898 "We can currently only build standalone libraries on Windows. Use\n"
1899 , " if os(Windows)\n"
1900 , " options: standalone\n"
1901 , "in your foreign-library stanza."
1903 | otherwise =
1904 Nothing
1905 goGhcWindows _ = unsupported [
1906 "We can currently only build shared foreign libraries on Windows"
1909 standalone :: Bool
1910 standalone = ForeignLibStandalone `elem` foreignLibOptions flib
1912 unsupported :: [String] -> Maybe String
1913 unsupported = Just . concat