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