summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--compiler/basicTypes/Module.hs60
-rw-r--r--compiler/coreSyn/CorePrep.hs5
-rw-r--r--compiler/ghc.mk2
-rw-r--r--compiler/main/DynFlags.hs4
-rw-r--r--compiler/main/Packages.hs48
-rw-r--r--compiler/prelude/PrelNames.hs49
-rw-r--r--libraries/integer-gmp/integer-gmp.cabal5
-rw-r--r--libraries/integer-simple/integer-simple.cabal5
8 files changed, 110 insertions, 68 deletions
diff --git a/compiler/basicTypes/Module.hs b/compiler/basicTypes/Module.hs
index 1851496af1..339cb0f4f9 100644
--- a/compiler/basicTypes/Module.hs
+++ b/compiler/basicTypes/Module.hs
@@ -137,7 +137,6 @@ module Module
import GhcPrelude
-import Config
import Outputable
import Unique
import UniqFM
@@ -1042,36 +1041,45 @@ parseModSubst = Parse.between (Parse.char '[') (Parse.char ']')
return (k, v)
--- -----------------------------------------------------------------------------
--- $wired_in_packages
--- Certain packages are known to the compiler, in that we know about certain
--- entities that reside in these packages, and the compiler needs to
--- declare static Modules and Names that refer to these packages. Hence
--- the wired-in packages can't include version numbers, since we don't want
--- to bake the version numbers of these packages into GHC.
---
--- So here's the plan. Wired-in packages are still versioned as
--- normal in the packages database, and you can still have multiple
--- versions of them installed. However, for each invocation of GHC,
--- only a single instance of each wired-in package will be recognised
--- (the desired one is selected via @-package@\/@-hide-package@), and GHC
--- will use the unversioned 'UnitId' below when referring to it,
--- including in .hi files and object file symbols. Unselected
--- versions of wired-in packages will be ignored, as will any other
--- package that depends directly or indirectly on it (much as if you
--- had used @-ignore-package@).
-
--- Make sure you change 'Packages.findWiredInPackages' if you add an entry here
+{-
+Note [Wired-in packages]
+~~~~~~~~~~~~~~~~~~~~~~~~
+
+Certain packages are known to the compiler, in that we know about certain
+entities that reside in these packages, and the compiler needs to
+declare static Modules and Names that refer to these packages. Hence
+the wired-in packages can't include version numbers in their package UnitId,
+since we don't want to bake the version numbers of these packages into GHC.
+
+So here's the plan. Wired-in packages are still versioned as
+normal in the packages database, and you can still have multiple
+versions of them installed. To the user, everything looks normal.
+
+However, for each invocation of GHC, only a single instance of each wired-in
+package will be recognised (the desired one is selected via
+@-package@\/@-hide-package@), and GHC will internall pretend that it has the
+*unversioned* 'UnitId', including in .hi files and object file symbols.
+
+Unselected versions of wired-in packages will be ignored, as will any other
+package that depends directly or indirectly on it (much as if you
+had used @-ignore-package@).
+
+The affected packages are compiled with, e.g., @-this-unit-id base@, so that
+the symbols in the object files have the unversioned unit id in their name.
+
+Make sure you change 'Packages.findWiredInPackages' if you add an entry here.
+
+For `integer-gmp`/`integer-simple` we also change the base name to
+`integer-wired-in`, but this is fundamentally no different.
+See Note [The integer library] in PrelNames.
+-}
integerUnitId, primUnitId,
baseUnitId, rtsUnitId,
thUnitId, mainUnitId, thisGhcUnitId, interactiveUnitId :: UnitId
primUnitId = fsToUnitId (fsLit "ghc-prim")
-integerUnitId = fsToUnitId (fsLit n)
- where
- n = case cIntegerLibraryType of
- IntegerGMP -> "integer-gmp"
- IntegerSimple -> "integer-simple"
+integerUnitId = fsToUnitId (fsLit "integer-wired-in")
+ -- See Note [The integer library] in PrelNames
baseUnitId = fsToUnitId (fsLit "base")
rtsUnitId = fsToUnitId (fsLit "rts")
thUnitId = fsToUnitId (fsLit "template-haskell")
diff --git a/compiler/coreSyn/CorePrep.hs b/compiler/coreSyn/CorePrep.hs
index 9c2954d4ef..26706b1cdd 100644
--- a/compiler/coreSyn/CorePrep.hs
+++ b/compiler/coreSyn/CorePrep.hs
@@ -1537,14 +1537,15 @@ lookupMkNaturalName dflags hsc_env
= guardNaturalUse dflags $ liftM tyThingId $
lookupGlobal hsc_env mkNaturalName
+-- See Note [The integer library] in PrelNames
lookupIntegerSDataConName :: DynFlags -> HscEnv -> IO (Maybe DataCon)
-lookupIntegerSDataConName dflags hsc_env = case cIntegerLibraryType of
+lookupIntegerSDataConName dflags hsc_env = case integerLibrary dflags of
IntegerGMP -> guardIntegerUse dflags $ liftM (Just . tyThingDataCon) $
lookupGlobal hsc_env integerSDataConName
IntegerSimple -> return Nothing
lookupNaturalSDataConName :: DynFlags -> HscEnv -> IO (Maybe DataCon)
-lookupNaturalSDataConName dflags hsc_env = case cIntegerLibraryType of
+lookupNaturalSDataConName dflags hsc_env = case integerLibrary dflags of
IntegerGMP -> guardNaturalUse dflags $ liftM (Just . tyThingDataCon) $
lookupGlobal hsc_env naturalSDataConName
IntegerSimple -> return Nothing
diff --git a/compiler/ghc.mk b/compiler/ghc.mk
index 9bc6b3f278..8a4cc4317d 100644
--- a/compiler/ghc.mk
+++ b/compiler/ghc.mk
@@ -84,8 +84,6 @@ compiler/stage%/build/Config.hs : mk/config.mk mk/project.mk | $$(dir $$@)/.
@echo 'cBooterVersion = "$(GhcVersion)"' >> $@
@echo 'cStage :: String' >> $@
@echo 'cStage = show (STAGE :: Int)' >> $@
- @echo 'cIntegerLibrary :: String' >> $@
- @echo 'cIntegerLibrary = "$(INTEGER_LIBRARY)"' >> $@
@echo 'cIntegerLibraryType :: IntegerLibrary' >> $@
ifeq "$(INTEGER_LIBRARY)" "integer-gmp"
@echo 'cIntegerLibraryType = IntegerGMP' >> $@
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 7726001a47..f9ccc25225 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -850,6 +850,9 @@ data DynFlags = DynFlags {
ghcLink :: GhcLink,
hscTarget :: HscTarget,
settings :: Settings,
+ integerLibrary :: IntegerLibrary,
+ -- ^ IntegerGMP or IntegerSimple. Set at configure time, but may be overriden
+ -- by GHC-API users. See Note [The integer library] in PrelNames
llvmTargets :: LlvmTargets,
llvmPasses :: LlvmPasses,
verbosity :: Int, -- ^ Verbosity level: see Note [Verbosity levels]
@@ -1755,6 +1758,7 @@ defaultDynFlags mySettings (myLlvmTargets, myLlvmPasses) =
ghcMode = CompManager,
ghcLink = LinkBinary,
hscTarget = defaultHscTarget (sTargetPlatform mySettings),
+ integerLibrary = cIntegerLibraryType,
verbosity = 0,
optLevel = 0,
debugLevel = 0,
diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs
index 04efa1fe51..fadcd31f1e 100644
--- a/compiler/main/Packages.hs
+++ b/compiler/main/Packages.hs
@@ -953,12 +953,15 @@ pprTrustFlag flag = case flag of
-- -----------------------------------------------------------------------------
-- Wired-in packages
+--
+-- See Note [Wired-in packages] in Module
-wired_in_pkgids :: [String]
-wired_in_pkgids = map unitIdString wiredInUnitIds
-
+type WiredInUnitId = String
type WiredPackagesMap = Map WiredUnitId WiredUnitId
+wired_in_pkgids :: [WiredInUnitId]
+wired_in_pkgids = map unitIdString wiredInUnitIds
+
findWiredInPackages
:: DynFlags
-> PackagePrecedenceIndex
@@ -969,12 +972,15 @@ findWiredInPackages
WiredPackagesMap) -- map from unit id to wired identity
findWiredInPackages dflags prec_map pkgs vis_map = do
- --
-- Now we must find our wired-in packages, and rename them to
- -- their canonical names (eg. base-1.0 ==> base).
- --
+ -- their canonical names (eg. base-1.0 ==> base), as described
+ -- in Note [Wired-in packages] in Module
let
- matches :: PackageConfig -> String -> Bool
+ matches :: PackageConfig -> WiredInUnitId -> Bool
+ pc `matches` pid
+ -- See Note [The integer library] in PrelNames
+ | pid == unitIdString integerUnitId
+ = packageNameString pc `elem` ["integer-gmp", "integer-simple"]
pc `matches` pid = packageNameString pc == pid
-- find which package corresponds to each wired-in package
@@ -994,8 +1000,8 @@ findWiredInPackages dflags prec_map pkgs vis_map = do
-- this works even when there is no exposed wired in package
-- available.
--
- findWiredInPackage :: [PackageConfig] -> String
- -> IO (Maybe PackageConfig)
+ findWiredInPackage :: [PackageConfig] -> WiredInUnitId
+ -> IO (Maybe (WiredInUnitId, PackageConfig))
findWiredInPackage pkgs wired_pkg =
let all_ps = [ p | p <- pkgs, p `matches` wired_pkg ]
all_exposed_ps =
@@ -1014,20 +1020,19 @@ findWiredInPackages dflags prec_map pkgs vis_map = do
<> text " not found."
return Nothing
pick :: PackageConfig
- -> IO (Maybe PackageConfig)
+ -> IO (Maybe (WiredInUnitId, PackageConfig))
pick pkg = do
debugTraceMsg dflags 2 $
text "wired-in package "
<> text wired_pkg
<> text " mapped to "
<> ppr (unitId pkg)
- return (Just pkg)
+ return (Just (wired_pkg, pkg))
mb_wired_in_pkgs <- mapM (findWiredInPackage pkgs) wired_in_pkgids
let
wired_in_pkgs = catMaybes mb_wired_in_pkgs
- wired_in_ids = mapMaybe definitePackageConfigId wired_in_pkgs
-- this is old: we used to assume that if there were
-- multiple versions of wired-in packages installed that
@@ -1043,18 +1048,17 @@ findWiredInPackages dflags prec_map pkgs vis_map = do
-}
wiredInMap :: Map WiredUnitId WiredUnitId
- wiredInMap = foldl' add_mapping Map.empty pkgs
- where add_mapping m pkg
- | Just key <- definitePackageConfigId pkg
- , key `elem` wired_in_ids
- = Map.insert key (DefUnitId (stringToInstalledUnitId (packageNameString pkg))) m
- | otherwise = m
+ wiredInMap = Map.fromList
+ [ (key, DefUnitId (stringToInstalledUnitId wiredInUnitId))
+ | (wiredInUnitId, pkg) <- wired_in_pkgs
+ , Just key <- pure $ definitePackageConfigId pkg
+ ]
updateWiredInDependencies pkgs = map (upd_deps . upd_pkg) pkgs
where upd_pkg pkg
| Just def_uid <- definitePackageConfigId pkg
- , def_uid `elem` wired_in_ids
- = let PackageName fs = packageName pkg
+ , Just wiredInUnitId <- Map.lookup def_uid wiredInMap
+ = let fs = installedUnitIdFS (unDefUnitId wiredInUnitId)
in pkg {
unitId = fsToInstalledUnitId fs,
componentId = ComponentId fs
@@ -1074,7 +1078,9 @@ findWiredInPackages dflags prec_map pkgs vis_map = do
-- Helper functions for rewiring Module and UnitId. These
-- rewrite UnitIds of modules in wired-in packages to the form known to the
--- compiler. For instance, base-4.9.0.0 will be rewritten to just base, to match
+-- compiler, as described in Note [Wired-in packages] in Module.
+--
+-- For instance, base-4.9.0.0 will be rewritten to just base, to match
-- what appears in PrelNames.
upd_wired_in_mod :: WiredPackagesMap -> Module -> Module
diff --git a/compiler/prelude/PrelNames.hs b/compiler/prelude/PrelNames.hs
index d75ad47c6d..d69eaebdcb 100644
--- a/compiler/prelude/PrelNames.hs
+++ b/compiler/prelude/PrelNames.hs
@@ -110,6 +110,36 @@ by the user. For those things that *can* appear in source programs,
original-name cache.
See also Note [Built-in syntax and the OrigNameCache]
+
+
+Note [The integer library]
+~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+Clearly, we need to know the names of various definitions of the integer
+library, e.g. the type itself, `mkInteger` etc. But there are two possible
+implementations of the integer library:
+
+ * integer-gmp (fast, but uses libgmp, which may not be available on all
+ targets and is GPL licensed)
+ * integer-simple (slow, but pure Haskell and BSD-licensed)
+
+We want the compiler to work with either one. The way we achieve this is:
+
+ * When compiling the integer-{gmp,simple} library, we pass
+ -this-unit-id integer-wired-in
+ to GHC (see the cabal file libraries/integer-{gmp,simple}.
+ * This way, GHC can use just this UnitID (see Module.integerUnitId) when
+ generating code, and the linker will succeed.
+
+Unfortuately, the abstraction is not complete: When using integer-gmp, we
+really want to use the S# constructor directly. This is controlled by
+the `integerLibrary` field of `DynFlags`: If it is IntegerGMP, we use
+this constructor directly (see CorePrep.lookupIntegerSDataConName)
+
+When GHC reads the package data base, it (internally only) pretends it has UnitId
+`integer-wired-in` instead of the actual UnitId (which includes the version
+number); just like for `base` and other packages, as described in
+Note [Wired-in packages] in Module. This is done in Packages.findWiredInPackages.
-}
{-# LANGUAGE CPP #-}
@@ -136,8 +166,6 @@ import Unique
import Name
import SrcLoc
import FastString
-import Config ( cIntegerLibraryType, IntegerLibrary(..) )
-import Panic ( panic )
{-
************************************************************************
@@ -355,6 +383,7 @@ basicKnownKeyNames
gcdIntegerName, lcmIntegerName,
andIntegerName, orIntegerName, xorIntegerName, complementIntegerName,
shiftLIntegerName, shiftRIntegerName, bitIntegerName,
+ integerSDataConName,naturalSDataConName,
-- Natural
naturalTyConName,
@@ -433,9 +462,7 @@ basicKnownKeyNames
, typeErrorVAppendDataConName
, typeErrorShowTypeDataConName
- ] ++ case cIntegerLibraryType of
- IntegerGMP -> [integerSDataConName,naturalSDataConName]
- IntegerSimple -> []
+ ]
genericTyConNames :: [Name]
genericTyConNames = [
@@ -1118,11 +1145,8 @@ integerTyConName, mkIntegerName, integerSDataConName,
gcdIntegerName, lcmIntegerName,
andIntegerName, orIntegerName, xorIntegerName, complementIntegerName,
shiftLIntegerName, shiftRIntegerName, bitIntegerName :: Name
-integerTyConName = tcQual gHC_INTEGER_TYPE (fsLit "Integer") integerTyConKey
-integerSDataConName = dcQual gHC_INTEGER_TYPE (fsLit n) integerSDataConKey
- where n = case cIntegerLibraryType of
- IntegerGMP -> "S#"
- IntegerSimple -> panic "integerSDataConName evaluated for integer-simple"
+integerTyConName = tcQual gHC_INTEGER_TYPE (fsLit "Integer") integerTyConKey
+integerSDataConName = dcQual gHC_INTEGER_TYPE (fsLit "S#") integerSDataConKey
mkIntegerName = varQual gHC_INTEGER_TYPE (fsLit "mkInteger") mkIntegerIdKey
integerToWord64Name = varQual gHC_INTEGER_TYPE (fsLit "integerToWord64") integerToWord64IdKey
integerToInt64Name = varQual gHC_INTEGER_TYPE (fsLit "integerToInt64") integerToInt64IdKey
@@ -1169,10 +1193,7 @@ bitIntegerName = varQual gHC_INTEGER_TYPE (fsLit "bitInteger") bit
-- GHC.Natural types
naturalTyConName, naturalSDataConName :: Name
naturalTyConName = tcQual gHC_NATURAL (fsLit "Natural") naturalTyConKey
-naturalSDataConName = dcQual gHC_NATURAL (fsLit n) naturalSDataConKey
- where n = case cIntegerLibraryType of
- IntegerGMP -> "NatS#"
- IntegerSimple -> panic "naturalSDataConName evaluated for integer-simple"
+naturalSDataConName = dcQual gHC_NATURAL (fsLit "NatS#") naturalSDataConKey
naturalFromIntegerName :: Name
naturalFromIntegerName = varQual gHC_NATURAL (fsLit "naturalFromInteger") naturalFromIntegerIdKey
diff --git a/libraries/integer-gmp/integer-gmp.cabal b/libraries/integer-gmp/integer-gmp.cabal
index 5d2f89039c..52834bb4ea 100644
--- a/libraries/integer-gmp/integer-gmp.cabal
+++ b/libraries/integer-gmp/integer-gmp.cabal
@@ -60,7 +60,10 @@ library
UnliftedFFITypes
build-depends: ghc-prim ^>= 0.5.1.0
hs-source-dirs: src/
- ghc-options: -this-unit-id integer-gmp -Wall
+ -- We need to set the unit ID to integer-wired-in
+ -- (without a version number) as it's magic.
+ -- See Note [The integer library] in PrelNames
+ ghc-options: -this-unit-id integer-wired-in -Wall
cc-options: -std=c99 -Wall
include-dirs: include
diff --git a/libraries/integer-simple/integer-simple.cabal b/libraries/integer-simple/integer-simple.cabal
index 231619c6c7..96c2e2358e 100644
--- a/libraries/integer-simple/integer-simple.cabal
+++ b/libraries/integer-simple/integer-simple.cabal
@@ -26,6 +26,7 @@ Library
other-modules: GHC.Integer.Type
default-extensions: CPP, MagicHash, BangPatterns, UnboxedTuples,
UnliftedFFITypes, NoImplicitPrelude
- -- We need to set the unit ID to integer-simple
+ -- We need to set the unit ID to integer-wired-in
-- (without a version number) as it's magic.
- ghc-options: -this-unit-id integer-simple -Wall
+ -- See Note [The integer library] in PrelNames
+ ghc-options: -this-unit-id integer-wired-in -Wall