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