-
Notifications
You must be signed in to change notification settings - Fork 699
/
Configure.hs
1971 lines (1780 loc) · 88.7 KB
/
Configure.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
894
895
896
897
898
899
900
901
902
903
904
905
906
907
908
909
910
911
912
913
914
915
916
917
918
919
920
921
922
923
924
925
926
927
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
944
945
946
947
948
949
950
951
952
953
954
955
956
957
958
959
960
961
962
963
964
965
966
967
968
969
970
971
972
973
974
975
976
977
978
979
980
981
982
983
984
985
986
987
988
989
990
991
992
993
994
995
996
997
998
999
1000
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
-----------------------------------------------------------------------------
-- |
-- Module : Distribution.Simple.Configure
-- Copyright : Isaac Jones 2003-2005
-- License : BSD3
--
-- Maintainer : cabal-devel@haskell.org
-- Portability : portable
--
-- This deals with the /configure/ phase. It provides the 'configure' action
-- which is given the package description and configure flags. It then tries
-- to: configure the compiler; resolves any conditionals in the package
-- description; resolve the package dependencies; check if all the extensions
-- used by this package are supported by the compiler; check that all the build
-- tools are available (including version checks if appropriate); checks for
-- any required @pkg-config@ packages (updating the 'BuildInfo' with the
-- results)
--
-- Then based on all this it saves the info in the 'LocalBuildInfo' and writes
-- it out to the @dist\/setup-config@ file. It also displays various details to
-- the user, the amount of information displayed depending on the verbosity
-- level.
module Distribution.Simple.Configure (configure,
writePersistBuildConfig,
getConfigStateFile,
getPersistBuildConfig,
checkPersistBuildConfigOutdated,
tryGetPersistBuildConfig,
maybeGetPersistBuildConfig,
findDistPref, findDistPrefOrDefault,
getInternalPackages,
computeComponentId,
computeCompatPackageKey,
computeCompatPackageName,
localBuildInfoFile,
getInstalledPackages,
getInstalledPackagesMonitorFiles,
getPackageDBContents,
configCompiler, configCompilerAux,
configCompilerEx, configCompilerAuxEx,
computeEffectiveProfiling,
ccLdOptionsBuildInfo,
checkForeignDeps,
interpretPackageDbFlags,
ConfigStateFileError(..),
tryGetConfigStateFile,
platformDefines,
relaxPackageDeps,
)
where
import Prelude ()
import Distribution.Compat.Prelude
import Distribution.Compiler
import Distribution.Types.IncludeRenaming
import Distribution.Utils.NubList
import Distribution.Simple.Compiler hiding (Flag)
import Distribution.Simple.PreProcess
import Distribution.Package
import qualified Distribution.InstalledPackageInfo as Installed
import Distribution.InstalledPackageInfo (InstalledPackageInfo)
import qualified Distribution.Simple.PackageIndex as PackageIndex
import Distribution.Simple.PackageIndex (InstalledPackageIndex)
import Distribution.PackageDescription as PD hiding (Flag)
import Distribution.Types.PackageDescription as PD
import Distribution.PackageDescription.PrettyPrint
import Distribution.PackageDescription.Configuration
import Distribution.PackageDescription.Check hiding (doesFileExist)
import Distribution.Simple.BuildToolDepends
import Distribution.Simple.Program
import Distribution.Simple.Setup as Setup
import Distribution.Simple.BuildTarget
import Distribution.Simple.LocalBuildInfo
import Distribution.Types.ExeDependency
import Distribution.Types.LegacyExeDependency
import Distribution.Types.PkgconfigDependency
import Distribution.Types.MungedPackageName
import Distribution.Types.LocalBuildInfo
import Distribution.Types.ComponentRequestedSpec
import Distribution.Types.ForeignLib
import Distribution.Types.ForeignLibType
import Distribution.Types.ForeignLibOption
import Distribution.Types.Mixin
import Distribution.Types.UnqualComponentName
import Distribution.Simple.Utils
import Distribution.System
import Distribution.Version
import Distribution.Verbosity
import qualified Distribution.Compat.Graph as Graph
import Distribution.Compat.Stack
import Distribution.Backpack.Configure
import Distribution.Backpack.DescribeUnitId
import Distribution.Backpack.PreExistingComponent
import Distribution.Backpack.ConfiguredComponent (newPackageDepsBehaviour)
import Distribution.Backpack.Id
import Distribution.Utils.LogProgress
import qualified Distribution.Simple.GHC as GHC
import qualified Distribution.Simple.GHCJS as GHCJS
import qualified Distribution.Simple.JHC as JHC
import qualified Distribution.Simple.LHC as LHC
import qualified Distribution.Simple.UHC as UHC
import qualified Distribution.Simple.HaskellSuite as HaskellSuite
import Control.Exception
( ErrorCall, Exception, evaluate, throw, throwIO, try )
import Distribution.Compat.Binary ( decodeOrFailIO, encode )
import Data.ByteString.Lazy (ByteString)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy.Char8 as BLC8
import Data.List
( (\\), partition, inits, stripPrefix )
import Data.Either
( partitionEithers )
import qualified Data.Map as Map
import System.Directory
( doesFileExist, createDirectoryIfMissing, getTemporaryDirectory )
import System.FilePath
( (</>), isAbsolute )
import qualified System.Info
( compilerName, compilerVersion )
import System.IO
( hPutStrLn, hClose )
import Distribution.Text
( Text(disp), defaultStyle, display, simpleParse )
import Text.PrettyPrint
( Doc, (<+>), ($+$), char, comma, hsep, nest
, punctuate, quotes, render, renderStyle, sep, text )
import Distribution.Compat.Environment ( lookupEnv )
import Distribution.Compat.Exception ( catchExit, catchIO )
type UseExternalInternalDeps = Bool
-- | The errors that can be thrown when reading the @setup-config@ file.
data ConfigStateFileError
= ConfigStateFileNoHeader -- ^ No header found.
| ConfigStateFileBadHeader -- ^ Incorrect header.
| ConfigStateFileNoParse -- ^ Cannot parse file contents.
| ConfigStateFileMissing -- ^ No file!
| ConfigStateFileBadVersion PackageIdentifier PackageIdentifier
(Either ConfigStateFileError LocalBuildInfo) -- ^ Mismatched version.
deriving (Typeable)
-- | Format a 'ConfigStateFileError' as a user-facing error message.
dispConfigStateFileError :: ConfigStateFileError -> Doc
dispConfigStateFileError ConfigStateFileNoHeader =
text "Saved package config file header is missing."
<+> text "Re-run the 'configure' command."
dispConfigStateFileError ConfigStateFileBadHeader =
text "Saved package config file header is corrupt."
<+> text "Re-run the 'configure' command."
dispConfigStateFileError ConfigStateFileNoParse =
text "Saved package config file is corrupt."
<+> text "Re-run the 'configure' command."
dispConfigStateFileError ConfigStateFileMissing =
text "Run the 'configure' command first."
dispConfigStateFileError (ConfigStateFileBadVersion oldCabal oldCompiler _) =
text "Saved package config file is outdated:"
$+$ badCabal $+$ badCompiler
$+$ text "Re-run the 'configure' command."
where
badCabal =
text "• the Cabal version changed from"
<+> disp oldCabal <+> "to" <+> disp currentCabalId
badCompiler
| oldCompiler == currentCompilerId = mempty
| otherwise =
text "• the compiler changed from"
<+> disp oldCompiler <+> "to" <+> disp currentCompilerId
instance Show ConfigStateFileError where
show = renderStyle defaultStyle . dispConfigStateFileError
instance Exception ConfigStateFileError
-- | Read the 'localBuildInfoFile'. Throw an exception if the file is
-- missing, if the file cannot be read, or if the file was created by an older
-- version of Cabal.
getConfigStateFile :: FilePath -- ^ The file path of the @setup-config@ file.
-> IO LocalBuildInfo
getConfigStateFile filename = do
exists <- doesFileExist filename
unless exists $ throwIO ConfigStateFileMissing
-- Read the config file into a strict ByteString to avoid problems with
-- lazy I/O, then convert to lazy because the binary package needs that.
contents <- BS.readFile filename
let (header, body) = BLC8.span (/='\n') (BLC8.fromChunks [contents])
headerParseResult <- try $ evaluate $ parseHeader header
let (cabalId, compId) =
case headerParseResult of
Left (_ :: ErrorCall) -> throw ConfigStateFileBadHeader
Right x -> x
let getStoredValue = do
result <- decodeOrFailIO (BLC8.tail body)
case result of
Left _ -> throw ConfigStateFileNoParse
Right x -> return x
deferErrorIfBadVersion act
| cabalId /= currentCabalId = do
eResult <- try act
throw $ ConfigStateFileBadVersion cabalId compId eResult
| otherwise = act
deferErrorIfBadVersion getStoredValue
where
_ = callStack -- TODO: attach call stack to exception
-- | Read the 'localBuildInfoFile', returning either an error or the local build
-- info.
tryGetConfigStateFile :: FilePath -- ^ The file path of the @setup-config@ file.
-> IO (Either ConfigStateFileError LocalBuildInfo)
tryGetConfigStateFile = try . getConfigStateFile
-- | Try to read the 'localBuildInfoFile'.
tryGetPersistBuildConfig :: FilePath -- ^ The @dist@ directory path.
-> IO (Either ConfigStateFileError LocalBuildInfo)
tryGetPersistBuildConfig = try . getPersistBuildConfig
-- | Read the 'localBuildInfoFile'. Throw an exception if the file is
-- missing, if the file cannot be read, or if the file was created by an older
-- version of Cabal.
getPersistBuildConfig :: FilePath -- ^ The @dist@ directory path.
-> IO LocalBuildInfo
getPersistBuildConfig = getConfigStateFile . localBuildInfoFile
-- | Try to read the 'localBuildInfoFile'.
maybeGetPersistBuildConfig :: FilePath -- ^ The @dist@ directory path.
-> IO (Maybe LocalBuildInfo)
maybeGetPersistBuildConfig =
liftM (either (const Nothing) Just) . tryGetPersistBuildConfig
-- | After running configure, output the 'LocalBuildInfo' to the
-- 'localBuildInfoFile'.
writePersistBuildConfig :: FilePath -- ^ The @dist@ directory path.
-> LocalBuildInfo -- ^ The 'LocalBuildInfo' to write.
-> NoCallStackIO ()
writePersistBuildConfig distPref lbi = do
createDirectoryIfMissing False distPref
writeFileAtomic (localBuildInfoFile distPref) $
BLC8.unlines [showHeader pkgId, encode lbi]
where
pkgId = localPackage lbi
-- | Identifier of the current Cabal package.
currentCabalId :: PackageIdentifier
currentCabalId = PackageIdentifier (mkPackageName "Cabal") cabalVersion
-- | Identifier of the current compiler package.
currentCompilerId :: PackageIdentifier
currentCompilerId = PackageIdentifier (mkPackageName System.Info.compilerName)
(mkVersion' System.Info.compilerVersion)
-- | Parse the @setup-config@ file header, returning the package identifiers
-- for Cabal and the compiler.
parseHeader :: ByteString -- ^ The file contents.
-> (PackageIdentifier, PackageIdentifier)
parseHeader header = case BLC8.words header of
["Saved", "package", "config", "for", pkgId, "written", "by", cabalId,
"using", compId] ->
fromMaybe (throw ConfigStateFileBadHeader) $ do
_ <- simpleParse (BLC8.unpack pkgId) :: Maybe PackageIdentifier
cabalId' <- simpleParse (BLC8.unpack cabalId)
compId' <- simpleParse (BLC8.unpack compId)
return (cabalId', compId')
_ -> throw ConfigStateFileNoHeader
-- | Generate the @setup-config@ file header.
showHeader :: PackageIdentifier -- ^ The processed package.
-> ByteString
showHeader pkgId = BLC8.unwords
[ "Saved", "package", "config", "for"
, BLC8.pack $ display pkgId
, "written", "by"
, BLC8.pack $ display currentCabalId
, "using"
, BLC8.pack $ display currentCompilerId
]
-- | Check that localBuildInfoFile is up-to-date with respect to the
-- .cabal file.
checkPersistBuildConfigOutdated :: FilePath -> FilePath -> NoCallStackIO Bool
checkPersistBuildConfigOutdated distPref pkg_descr_file =
pkg_descr_file `moreRecentFile` localBuildInfoFile distPref
-- | Get the path of @dist\/setup-config@.
localBuildInfoFile :: FilePath -- ^ The @dist@ directory path.
-> FilePath
localBuildInfoFile distPref = distPref </> "setup-config"
-- -----------------------------------------------------------------------------
-- * Configuration
-- -----------------------------------------------------------------------------
-- | Return the \"dist/\" prefix, or the default prefix. The prefix is taken
-- from (in order of highest to lowest preference) the override prefix, the
-- \"CABAL_BUILDDIR\" environment variable, or the default prefix.
findDistPref :: FilePath -- ^ default \"dist\" prefix
-> Setup.Flag FilePath -- ^ override \"dist\" prefix
-> NoCallStackIO FilePath
findDistPref defDistPref overrideDistPref = do
envDistPref <- liftM parseEnvDistPref (lookupEnv "CABAL_BUILDDIR")
return $ fromFlagOrDefault defDistPref (mappend envDistPref overrideDistPref)
where
parseEnvDistPref env =
case env of
Just distPref | not (null distPref) -> toFlag distPref
_ -> NoFlag
-- | Return the \"dist/\" prefix, or the default prefix. The prefix is taken
-- from (in order of highest to lowest preference) the override prefix, the
-- \"CABAL_BUILDDIR\" environment variable, or 'defaultDistPref' is used. Call
-- this function to resolve a @*DistPref@ flag whenever it is not known to be
-- set. (The @*DistPref@ flags are always set to a definite value before
-- invoking 'UserHooks'.)
findDistPrefOrDefault :: Setup.Flag FilePath -- ^ override \"dist\" prefix
-> NoCallStackIO FilePath
findDistPrefOrDefault = findDistPref defaultDistPref
-- |Perform the \"@.\/setup configure@\" action.
-- Returns the @.setup-config@ file.
configure :: (GenericPackageDescription, HookedBuildInfo)
-> ConfigFlags -> IO LocalBuildInfo
configure (pkg_descr0', pbi) cfg = do
let pkg_descr0 =
-- Ignore '--allow-{older,newer}' when we're given
-- '--exact-configuration'.
if fromFlagOrDefault False (configExactConfiguration cfg)
then pkg_descr0'
else relaxPackageDeps removeLowerBound
(maybe RelaxDepsNone unAllowOlder $ configAllowOlder cfg) $
relaxPackageDeps removeUpperBound
(maybe RelaxDepsNone unAllowNewer $ configAllowNewer cfg)
pkg_descr0'
-- Determine the component we are configuring, if a user specified
-- one on the command line. We use a fake, flattened version of
-- the package since at this point, we're not really sure what
-- components we *can* configure. @Nothing@ means that we should
-- configure everything (the old behavior).
(mb_cname :: Maybe ComponentName) <- do
let flat_pkg_descr = flattenPackageDescription pkg_descr0
targets <- readBuildTargets verbosity flat_pkg_descr (configArgs cfg)
-- TODO: bleat if you use the module/file syntax
let targets' = [ cname | BuildTargetComponent cname <- targets ]
case targets' of
_ | null (configArgs cfg) -> return Nothing
[cname] -> return (Just cname)
[] -> die' verbosity "No valid component targets found"
_ -> die' verbosity "Can only configure either single component or all of them"
let use_external_internal_deps = isJust mb_cname
case mb_cname of
Nothing -> setupMessage verbosity "Configuring" (packageId pkg_descr0)
Just cname -> setupMessage' verbosity "Configuring" (packageId pkg_descr0)
cname (Just (configInstantiateWith cfg))
-- configCID is only valid for per-component configure
when (isJust (flagToMaybe (configCID cfg)) && isNothing mb_cname) $
die' verbosity "--cid is only supported for per-component configure"
checkDeprecatedFlags verbosity cfg
checkExactConfiguration verbosity pkg_descr0 cfg
-- Where to build the package
let buildDir :: FilePath -- e.g. dist/build
-- fromFlag OK due to Distribution.Simple calling
-- findDistPrefOrDefault to fill it in
buildDir = fromFlag (configDistPref cfg) </> "build"
createDirectoryIfMissingVerbose (lessVerbose verbosity) True buildDir
-- What package database(s) to use
let packageDbs :: PackageDBStack
packageDbs
= interpretPackageDbFlags
(fromFlag (configUserInstall cfg))
(configPackageDBs cfg)
-- comp: the compiler we're building with
-- compPlatform: the platform we're building for
-- programDb: location and args of all programs we're
-- building with
(comp :: Compiler,
compPlatform :: Platform,
programDb :: ProgramDb)
<- configCompilerEx
(flagToMaybe (configHcFlavor cfg))
(flagToMaybe (configHcPath cfg))
(flagToMaybe (configHcPkg cfg))
(mkProgramDb cfg (configPrograms cfg))
(lessVerbose verbosity)
-- The InstalledPackageIndex of all installed packages
installedPackageSet :: InstalledPackageIndex
<- getInstalledPackages (lessVerbose verbosity) comp
packageDbs programDb
-- The set of package names which are "shadowed" by internal
-- packages, and which component they map to
let internalPackageSet :: Map PackageName (Maybe UnqualComponentName)
internalPackageSet = getInternalPackages pkg_descr0
-- Make a data structure describing what components are enabled.
let enabled :: ComponentRequestedSpec
enabled = case mb_cname of
Just cname -> OneComponentRequestedSpec cname
Nothing -> ComponentRequestedSpec
-- The flag name (@--enable-tests@) is a
-- little bit of a misnomer, because
-- just passing this flag won't
-- "enable", in our internal
-- nomenclature; it's just a request; a
-- @buildable: False@ might make it
-- not possible to enable.
{ testsRequested = fromFlag (configTests cfg)
, benchmarksRequested =
fromFlag (configBenchmarks cfg) }
-- Some sanity checks related to enabling components.
when (isJust mb_cname
&& (fromFlag (configTests cfg) || fromFlag (configBenchmarks cfg))) $
die' verbosity $ "--enable-tests/--enable-benchmarks are incompatible with" ++
" explicitly specifying a component to configure."
-- allConstraints: The set of all 'Dependency's we have. Used ONLY
-- to 'configureFinalizedPackage'.
-- requiredDepsMap: A map from 'PackageName' to the specifically
-- required 'InstalledPackageInfo', due to --dependency
--
-- NB: These constraints are to be applied to ALL components of
-- a package. Thus, it's not an error if allConstraints contains
-- more constraints than is necessary for a component (another
-- component might need it.)
--
-- NB: The fact that we bundle all the constraints together means
-- that is not possible to configure a test-suite to use one
-- version of a dependency, and the executable to use another.
(allConstraints :: [Dependency],
requiredDepsMap :: Map PackageName InstalledPackageInfo)
<- either (die' verbosity) return $
combinedConstraints (configConstraints cfg)
(configDependencies cfg)
installedPackageSet
-- pkg_descr: The resolved package description, that does not contain any
-- conditionals, because we have have an assignment for
-- every flag, either picking them ourselves using a
-- simple naive algorithm, or having them be passed to
-- us by 'configConfigurationsFlags')
-- flags: The 'FlagAssignment' that the conditionals were
-- resolved with.
--
-- NB: Why doesn't finalizing a package also tell us what the
-- dependencies are (e.g. when we run the naive algorithm,
-- we are checking if dependencies are satisfiable)? The
-- primary reason is that we may NOT have done any solving:
-- if the flags are all chosen for us, this step is a simple
-- matter of flattening according to that assignment. It's
-- cleaner to then configure the dependencies afterwards.
(pkg_descr :: PackageDescription,
flags :: FlagAssignment)
<- configureFinalizedPackage verbosity cfg enabled
allConstraints
(dependencySatisfiable
use_external_internal_deps
(fromFlagOrDefault False (configExactConfiguration cfg))
(packageName pkg_descr0)
installedPackageSet
internalPackageSet
requiredDepsMap)
comp
compPlatform
pkg_descr0
debug verbosity $ "Finalized package description:\n"
++ showPackageDescription pkg_descr
-- NB: showPackageDescription does not display the AWFUL HACK GLOBAL
-- buildDepends, so we have to display it separately. See #2066
-- Some day, we should eliminate this, so that
-- configureFinalizedPackage returns the set of overall dependencies
-- separately. Then 'configureDependencies' and
-- 'Distribution.PackageDescription.Check' need to be adjusted
-- accordingly.
debug verbosity $ "Finalized build-depends: "
++ intercalate ", " (map display (buildDepends pkg_descr))
checkCompilerProblems verbosity comp pkg_descr enabled
checkPackageProblems verbosity pkg_descr0
(updatePackageDescription pbi pkg_descr)
-- The list of 'InstalledPackageInfo' recording the selected
-- dependencies on external packages.
--
-- Invariant: For any package name, there is at most one package
-- in externalPackageDeps which has that name.
--
-- NB: The dependency selection is global over ALL components
-- in the package (similar to how allConstraints and
-- requiredDepsMap are global over all components). In particular,
-- if *any* component (post-flag resolution) has an unsatisfiable
-- dependency, we will fail. This can sometimes be undesirable
-- for users, see #1786 (benchmark conflicts with executable),
--
-- In the presence of Backpack, these package dependencies are
-- NOT complete: they only ever include the INDEFINITE
-- dependencies. After we apply an instantiation, we'll get
-- definite references which constitute extra dependencies.
-- (Why not have cabal-install pass these in explicitly?
-- For one it's deterministic; for two, we need to associate
-- them with renamings which would require a far more complicated
-- input scheme than what we have today.)
externalPkgDeps :: [PreExistingComponent]
<- configureDependencies
verbosity
use_external_internal_deps
internalPackageSet
installedPackageSet
requiredDepsMap
pkg_descr
-- Compute installation directory templates, based on user
-- configuration.
--
-- TODO: Move this into a helper function.
defaultDirs :: InstallDirTemplates
<- defaultInstallDirs' use_external_internal_deps
(compilerFlavor comp)
(fromFlag (configUserInstall cfg))
(hasLibs pkg_descr)
let installDirs :: InstallDirTemplates
installDirs = combineInstallDirs fromFlagOrDefault
defaultDirs (configInstallDirs cfg)
-- Check languages and extensions
-- TODO: Move this into a helper function.
let langlist = nub $ catMaybes $ map defaultLanguage
(enabledBuildInfos pkg_descr enabled)
let langs = unsupportedLanguages comp langlist
when (not (null langs)) $
die' verbosity $ "The package " ++ display (packageId pkg_descr0)
++ " requires the following languages which are not "
++ "supported by " ++ display (compilerId comp) ++ ": "
++ intercalate ", " (map display langs)
let extlist = nub $ concatMap allExtensions (enabledBuildInfos pkg_descr enabled)
let exts = unsupportedExtensions comp extlist
when (not (null exts)) $
die' verbosity $ "The package " ++ display (packageId pkg_descr0)
++ " requires the following language extensions which are not "
++ "supported by " ++ display (compilerId comp) ++ ": "
++ intercalate ", " (map display exts)
-- Check foreign library build requirements
let flibs = [flib | CFLib flib <- enabledComponents pkg_descr enabled]
let unsupportedFLibs = unsupportedForeignLibs comp compPlatform flibs
when (not (null unsupportedFLibs)) $
die' verbosity $ "Cannot build some foreign libraries: "
++ intercalate "," unsupportedFLibs
-- Configure certain external build tools, see below for which ones.
let requiredBuildTools = do
bi <- enabledBuildInfos pkg_descr enabled
-- First, we collect any tool dep that we know is external. This is,
-- in practice:
--
-- 1. `build-tools` entries on the whitelist
--
-- 2. `build-tool-depends` that aren't from the current package.
let externBuildToolDeps =
[ LegacyExeDependency (unUnqualComponentName eName) versionRange
| buildTool@(ExeDependency _ eName versionRange)
<- getAllToolDependencies pkg_descr bi
, not $ isInternal pkg_descr buildTool ]
-- Second, we collect any build-tools entry we don't know how to
-- desugar. We'll never have any idea how to build them, so we just
-- hope they are already on the PATH.
let unknownBuildTools =
[ buildTool
| buildTool <- buildTools bi
, Nothing == desugarBuildTool pkg_descr buildTool ]
externBuildToolDeps ++ unknownBuildTools
programDb' <-
configureAllKnownPrograms (lessVerbose verbosity) programDb
>>= configureRequiredPrograms verbosity requiredBuildTools
(pkg_descr', programDb'') <-
configurePkgconfigPackages verbosity pkg_descr programDb' enabled
-- Compute internal component graph
--
-- The general idea is that we take a look at all the source level
-- components (which may build-depends on each other) and form a graph.
-- From there, we build a ComponentLocalBuildInfo for each of the
-- components, which lets us actually build each component.
-- internalPackageSet
-- use_external_internal_deps
(buildComponents :: [ComponentLocalBuildInfo],
packageDependsIndex :: InstalledPackageIndex) <-
runLogProgress verbosity $ configureComponentLocalBuildInfos
verbosity
use_external_internal_deps
enabled
(fromFlagOrDefault False (configDeterministic cfg))
(configIPID cfg)
(configCID cfg)
pkg_descr
externalPkgDeps
(configConfigurationsFlags cfg)
(configInstantiateWith cfg)
installedPackageSet
comp
-- Decide if we're going to compile with split objects.
split_objs :: Bool <-
if not (fromFlag $ configSplitObjs cfg)
then return False
else case compilerFlavor comp of
GHC | compilerVersion comp >= mkVersion [6,5]
-> return True
GHCJS
-> return True
_ -> do warn verbosity
("this compiler does not support " ++
"--enable-split-objs; ignoring")
return False
let ghciLibByDefault =
case compilerId comp of
CompilerId GHC _ ->
-- If ghc is non-dynamic, then ghci needs object files,
-- so we build one by default.
--
-- Technically, archive files should be sufficient for ghci,
-- but because of GHC bug #8942, it has never been safe to
-- rely on them. By the time that bug was fixed, ghci had
-- been changed to read shared libraries instead of archive
-- files (see next code block).
not (GHC.isDynamic comp)
CompilerId GHCJS _ ->
not (GHCJS.isDynamic comp)
_ -> False
let sharedLibsByDefault
| fromFlag (configDynExe cfg) =
-- build a shared library if dynamically-linked
-- executables are requested
True
| otherwise = case compilerId comp of
CompilerId GHC _ ->
-- if ghc is dynamic, then ghci needs a shared
-- library, so we build one by default.
GHC.isDynamic comp
CompilerId GHCJS _ ->
GHCJS.isDynamic comp
_ -> False
withSharedLib_ =
-- build shared libraries if required by GHC or by the
-- executable linking mode, but allow the user to force
-- building only static library archives with
-- --disable-shared.
fromFlagOrDefault sharedLibsByDefault $ configSharedLib cfg
withDynExe_ = fromFlag $ configDynExe cfg
when (withDynExe_ && not withSharedLib_) $ warn verbosity $
"Executables will use dynamic linking, but a shared library "
++ "is not being built. Linking will fail if any executables "
++ "depend on the library."
setProfLBI <- configureProfiling verbosity cfg comp
setCoverageLBI <- configureCoverage verbosity cfg comp
reloc <-
if not (fromFlag $ configRelocatable cfg)
then return False
else return True
let buildComponentsMap =
foldl' (\m clbi -> Map.insertWith (++)
(componentLocalName clbi) [clbi] m)
Map.empty buildComponents
let lbi = (setCoverageLBI . setProfLBI)
LocalBuildInfo {
configFlags = cfg,
flagAssignment = flags,
componentEnabledSpec = enabled,
extraConfigArgs = [], -- Currently configure does not
-- take extra args, but if it
-- did they would go here.
installDirTemplates = installDirs,
compiler = comp,
hostPlatform = compPlatform,
buildDir = buildDir,
componentGraph = Graph.fromDistinctList buildComponents,
componentNameMap = buildComponentsMap,
installedPkgs = packageDependsIndex,
pkgDescrFile = Nothing,
localPkgDescr = pkg_descr',
withPrograms = programDb'',
withVanillaLib = fromFlag $ configVanillaLib cfg,
withSharedLib = withSharedLib_,
withDynExe = withDynExe_,
withProfLib = False,
withProfLibDetail = ProfDetailNone,
withProfExe = False,
withProfExeDetail = ProfDetailNone,
withOptimization = fromFlag $ configOptimization cfg,
withDebugInfo = fromFlag $ configDebugInfo cfg,
withGHCiLib = fromFlagOrDefault ghciLibByDefault $
configGHCiLib cfg,
splitObjs = split_objs,
stripExes = fromFlag $ configStripExes cfg,
stripLibs = fromFlag $ configStripLibs cfg,
exeCoverage = False,
libCoverage = False,
withPackageDB = packageDbs,
progPrefix = fromFlag $ configProgPrefix cfg,
progSuffix = fromFlag $ configProgSuffix cfg,
relocatable = reloc
}
when reloc (checkRelocatable verbosity pkg_descr lbi)
-- TODO: This is not entirely correct, because the dirs may vary
-- across libraries/executables
let dirs = absoluteInstallDirs pkg_descr lbi NoCopyDest
relative = prefixRelativeInstallDirs (packageId pkg_descr) lbi
unless (isAbsolute (prefix dirs)) $ die' verbosity $
"expected an absolute directory name for --prefix: " ++ prefix dirs
info verbosity $ "Using " ++ display currentCabalId
++ " compiled by " ++ display currentCompilerId
info verbosity $ "Using compiler: " ++ showCompilerId comp
info verbosity $ "Using install prefix: " ++ prefix dirs
let dirinfo name dir isPrefixRelative =
info verbosity $ name ++ " installed in: " ++ dir ++ relNote
where relNote = case buildOS of
Windows | not (hasLibs pkg_descr)
&& isNothing isPrefixRelative
-> " (fixed location)"
_ -> ""
dirinfo "Executables" (bindir dirs) (bindir relative)
dirinfo "Libraries" (libdir dirs) (libdir relative)
dirinfo "Dynamic Libraries" (dynlibdir dirs) (dynlibdir relative)
dirinfo "Private executables" (libexecdir dirs) (libexecdir relative)
dirinfo "Data files" (datadir dirs) (datadir relative)
dirinfo "Documentation" (docdir dirs) (docdir relative)
dirinfo "Configuration files" (sysconfdir dirs) (sysconfdir relative)
sequence_ [ reportProgram verbosity prog configuredProg
| (prog, configuredProg) <- knownPrograms programDb'' ]
return lbi
where
verbosity = fromFlag (configVerbosity cfg)
mkProgramDb :: ConfigFlags -> ProgramDb -> ProgramDb
mkProgramDb cfg initialProgramDb = programDb
where
programDb = userSpecifyArgss (configProgramArgs cfg)
. userSpecifyPaths (configProgramPaths cfg)
. setProgramSearchPath searchpath
$ initialProgramDb
searchpath = getProgramSearchPath initialProgramDb
++ map ProgramSearchPathDir
(fromNubList $ configProgramPathExtra cfg)
-- -----------------------------------------------------------------------------
-- Helper functions for configure
-- | Check if the user used any deprecated flags.
checkDeprecatedFlags :: Verbosity -> ConfigFlags -> IO ()
checkDeprecatedFlags verbosity cfg = do
unless (configProfExe cfg == NoFlag) $ do
let enable | fromFlag (configProfExe cfg) = "enable"
| otherwise = "disable"
warn verbosity
("The flag --" ++ enable ++ "-executable-profiling is deprecated. "
++ "Please use --" ++ enable ++ "-profiling instead.")
unless (configLibCoverage cfg == NoFlag) $ do
let enable | fromFlag (configLibCoverage cfg) = "enable"
| otherwise = "disable"
warn verbosity
("The flag --" ++ enable ++ "-library-coverage is deprecated. "
++ "Please use --" ++ enable ++ "-coverage instead.")
-- | Sanity check: if '--exact-configuration' was given, ensure that the
-- complete flag assignment was specified on the command line.
checkExactConfiguration :: Verbosity -> GenericPackageDescription -> ConfigFlags -> IO ()
checkExactConfiguration verbosity pkg_descr0 cfg =
when (fromFlagOrDefault False (configExactConfiguration cfg)) $ do
let cmdlineFlags = map fst (configConfigurationsFlags cfg)
allFlags = map flagName . genPackageFlags $ pkg_descr0
diffFlags = allFlags \\ cmdlineFlags
when (not . null $ diffFlags) $
die' verbosity $ "'--exact-configuration' was given, "
++ "but the following flags were not specified: "
++ intercalate ", " (map show diffFlags)
-- | Create a PackageIndex that makes *any libraries that might be*
-- defined internally to this package look like installed packages, in
-- case an executable should refer to any of them as dependencies.
--
-- It must be *any libraries that might be* defined rather than the
-- actual definitions, because these depend on conditionals in the .cabal
-- file, and we haven't resolved them yet. finalizePD
-- does the resolution of conditionals, and it takes internalPackageSet
-- as part of its input.
getInternalPackages :: GenericPackageDescription
-> Map PackageName (Maybe UnqualComponentName)
getInternalPackages pkg_descr0 =
-- TODO: some day, executables will be fair game here too!
let pkg_descr = flattenPackageDescription pkg_descr0
f lib = case libName lib of
Nothing -> (packageName pkg_descr, Nothing)
Just n' -> (unqualComponentNameToPackageName n', Just n')
in Map.fromList (map f (allLibraries pkg_descr))
-- | Returns true if a dependency is satisfiable. This function may
-- report a dependency satisfiable even when it is not, but not vice
-- versa. This is to be passed to finalizePD.
dependencySatisfiable
:: Bool -- ^ use external internal deps?
-> Bool -- ^ exact configuration?
-> PackageName
-> InstalledPackageIndex -- ^ installed set
-> Map PackageName (Maybe UnqualComponentName) -- ^ internal set
-> Map PackageName InstalledPackageInfo -- ^ required dependencies
-> (Dependency -> Bool)
dependencySatisfiable
use_external_internal_deps
exact_config pn installedPackageSet internalPackageSet requiredDepsMap
d@(Dependency depName vr)
| exact_config
-- When we're given '--exact-configuration', we assume that all
-- dependencies and flags are exactly specified on the command
-- line. Thus we only consult the 'requiredDepsMap'. Note that
-- we're not doing the version range check, so if there's some
-- dependency that wasn't specified on the command line,
-- 'finalizePD' will fail.
-- TODO: mention '--exact-configuration' in the error message
-- when this fails?
= if isInternalDep && not use_external_internal_deps
-- Except for internal deps, when we're NOT per-component mode;
-- those are just True.
then True
else depName `Map.member` requiredDepsMap
| isInternalDep
= if use_external_internal_deps
-- When we are doing per-component configure, we now need to
-- test if the internal dependency is in the index. This has
-- DIFFERENT semantics from normal dependency satisfiability.
then internalDepSatisfiable
-- If a 'PackageName' is defined by an internal component, the dep is
-- satisfiable (we're going to build it ourselves)
else True
| otherwise
= depSatisfiable
where
isInternalDep = Map.member depName internalPackageSet
depSatisfiable =
not . null $ PackageIndex.lookupDependency installedPackageSet d
internalDepSatisfiable =
not . null $ PackageIndex.lookupInternalDependency
installedPackageSet (Dependency pn vr) cn
where
cn | pn == depName
= Nothing
| otherwise
-- Reinterpret the "package name" as an unqualified component
-- name
= Just (mkUnqualComponentName (unPackageName depName))
-- | Relax the dependencies of this package if needed.
relaxPackageDeps :: (VersionRange -> VersionRange)
-> RelaxDeps
-> GenericPackageDescription -> GenericPackageDescription
relaxPackageDeps _ RelaxDepsNone gpd = gpd
relaxPackageDeps vrtrans RelaxDepsAll gpd = transformAllBuildDepends relaxAll gpd
where
relaxAll = \(Dependency pkgName verRange) ->
Dependency pkgName (vrtrans verRange)
relaxPackageDeps vrtrans (RelaxDepsSome allowNewerDeps') gpd =
transformAllBuildDepends relaxSome gpd
where
thisPkgName = packageName gpd
allowNewerDeps = mapMaybe f allowNewerDeps'
f (Setup.RelaxedDep p) = Just p
f (Setup.RelaxedDepScoped scope p) | scope == thisPkgName = Just p
| otherwise = Nothing
relaxSome = \d@(Dependency depName verRange) ->
if depName `elem` allowNewerDeps
then Dependency depName (vrtrans verRange)
else d
-- | Finalize a generic package description. The workhorse is
-- 'finalizePD' but there's a bit of other nattering
-- about necessary.
--
-- TODO: what exactly is the business with @flaggedTests@ and
-- @flaggedBenchmarks@?
configureFinalizedPackage
:: Verbosity
-> ConfigFlags
-> ComponentRequestedSpec
-> [Dependency]
-> (Dependency -> Bool) -- ^ tests if a dependency is satisfiable.
-- Might say it's satisfiable even when not.
-> Compiler
-> Platform
-> GenericPackageDescription
-> IO (PackageDescription, FlagAssignment)
configureFinalizedPackage verbosity cfg enabled
allConstraints satisfies comp compPlatform pkg_descr0 = do
(pkg_descr0', flags) <-
case finalizePD
(configConfigurationsFlags cfg)
enabled
satisfies
compPlatform
(compilerInfo comp)
allConstraints
pkg_descr0
of Right r -> return r
Left missing ->
die' verbosity $ "Encountered missing dependencies:\n"
++ (render . nest 4 . sep . punctuate comma
. map (disp . simplifyDependency)
$ missing)
-- add extra include/lib dirs as specified in cfg
-- we do it here so that those get checked too
let pkg_descr = addExtraIncludeLibDirs pkg_descr0'
when (not (null flags)) $
info verbosity $ "Flags chosen: "
++ intercalate ", " [ unFlagName fn ++ "=" ++ display value
| (fn, value) <- flags ]
return (pkg_descr, flags)
where
addExtraIncludeLibDirs pkg_descr =
let extraBi = mempty { extraLibDirs = configExtraLibDirs cfg
, extraFrameworkDirs = configExtraFrameworkDirs cfg
, PD.includeDirs = configExtraIncludeDirs cfg}
modifyLib l = l{ libBuildInfo = libBuildInfo l
`mappend` extraBi }
modifyExecutable e = e{ buildInfo = buildInfo e
`mappend` extraBi}
modifyForeignLib f = f{ foreignLibBuildInfo = foreignLibBuildInfo f
`mappend` extraBi}
modifyTestsuite t = t{ testBuildInfo = testBuildInfo t
`mappend` extraBi}
modifyBenchmark b = b{ benchmarkBuildInfo = benchmarkBuildInfo b
`mappend` extraBi}
in pkg_descr
{ library = modifyLib `fmap` library pkg_descr
, subLibraries = modifyLib `map` subLibraries pkg_descr
, executables = modifyExecutable `map` executables pkg_descr
, foreignLibs = modifyForeignLib `map` foreignLibs pkg_descr
, testSuites = modifyTestsuite `map` testSuites pkg_descr
, benchmarks = modifyBenchmark `map` benchmarks pkg_descr
}
-- | Check for use of Cabal features which require compiler support
checkCompilerProblems :: Verbosity -> Compiler -> PackageDescription -> ComponentRequestedSpec -> IO ()
checkCompilerProblems verbosity comp pkg_descr enabled = do
unless (renamingPackageFlagsSupported comp ||
all (all (isDefaultIncludeRenaming . mixinIncludeRenaming) . mixins)
(enabledBuildInfos pkg_descr enabled)) $
die' verbosity $ "Your compiler does not support thinning and renaming on "
++ "package flags. To use this feature you must use "
++ "GHC 7.9 or later."
when (any (not.null.PD.reexportedModules) (PD.allLibraries pkg_descr)
&& not (reexportedModulesSupported comp)) $
die' verbosity $ "Your compiler does not support module re-exports. To use "
++ "this feature you must use GHC 7.9 or later."