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