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