From 240ddd7c39536776e955e881d709bbb039b48513 Mon Sep 17 00:00:00 2001
From: "Edward Z. Yang" <ezyang@cs.stanford.edu>
Date: Mon, 18 Jan 2016 17:32:27 +0100
Subject: [PATCH] Switch from -this-package-key to -this-unit-id.

A small cosmetic change, but we have to do a bit of work to
actually support it:

    - Cabal submodule update, so that Cabal passes us
      -this-unit-id when we ask for it.  This includes
      a Cabal renaming to be consistent with Unit ID, which
      makes ghc-pkg a bit more scrutable.

    - Build system is updated to use -this-unit-id rather than
      -this-package-key, to avoid deprecation warnings.  Needs
      a version test so I resurrected the old test we had
      (sorry rwbarton!)

    - I've *undeprecated* -package-name, so that we are in the same
      state as GHC 7.10, since the "correct" flag will have only
      entered circulation in GHC 8.0.

    - I removed -package-key.  Since we didn't deprecate -package-id
      I think this should not cause any problems for users; they
      can just change their code to use -package-id.

    - The package database is indexed by UNIT IDs, not component IDs.
      I updated the naming here.

    - I dropped the signatures field from ExposedModule; nothing
      was using it, and instantiatedWith from the package database
      field.

    - ghc-pkg was updated to use unit ID nomenclature, I removed
      the -package-key flags but I decided not to add any new flags
      for now.

Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu>

Test Plan: validate

Reviewers: austin, hvr, bgamari

Reviewed By: bgamari

Subscribers: 23Skidoo, thomie, erikd

Differential Revision: https://phabricator.haskell.org/D1780
---
 compiler/ghc.cabal.in                         | 15 +--
 compiler/main/DynFlags.hs                     | 45 ++++++---
 compiler/main/HscTypes.hs                     |  4 +-
 compiler/main/PackageConfig.hs                | 18 +---
 compiler/main/Packages.hs                     | 11 +--
 configure.ac                                  |  5 +
 docs/users_guide/8.0.1-notes.rst              |  8 ++
 docs/users_guide/packages.rst                 | 17 ++--
 libraries/Cabal                               |  2 +-
 libraries/base/base.cabal                     |  2 +-
 libraries/ghc-boot/GHC/PackageDb.hs           | 83 ++++++----------
 libraries/ghc-prim/ghc-prim.cabal             |  2 +-
 libraries/integer-gmp/integer-gmp.cabal       |  2 +-
 libraries/integer-simple/integer-simple.cabal |  4 +-
 .../template-haskell/template-haskell.cabal   |  9 +-
 mk/config.mk.in                               |  2 +
 rts/ghc.mk                                    |  6 +-
 rules/distdir-way-opts.mk                     | 14 ++-
 testsuite/tests/module/base01/Makefile        |  4 +-
 testsuite/tests/rename/prog006/Makefile       |  2 +-
 .../tests/rename/should_compile/T3103/test.T  |  2 +-
 utils/ghc-cabal/Main.hs                       | 14 +--
 utils/ghc-pkg/Main.hs                         | 95 +++++++++----------
 utils/mkUserGuidePart/Options/Packages.hs     |  4 +-
 24 files changed, 190 insertions(+), 180 deletions(-)

diff --git a/compiler/ghc.cabal.in b/compiler/ghc.cabal.in
index d0e74b0d089a..9557d34ddd30 100644
--- a/compiler/ghc.cabal.in
+++ b/compiler/ghc.cabal.in
@@ -104,12 +104,15 @@ Library
 
     Include-Dirs: . parser utils
 
-    if impl( ghc >= 7.9 )
-        -- We need to set the unit id to ghc (without a version number)
-        -- as it's magic.  But we can't set it for old versions of GHC (e.g.
-        -- when bootstrapping) because those versions of GHC don't understand
-        -- that GHC is wired-in.
-        GHC-Options: -this-package-key ghc
+    -- We need to set the unit id to ghc (without a version number)
+    -- as it's magic.  But we can't set it for old versions of GHC (e.g.
+    -- when bootstrapping) because those versions of GHC don't understand
+    -- that GHC is wired-in.
+    if impl ( ghc >= 7.11 )
+        GHC-Options: -this-unit-id ghc
+    else
+        if impl( ghc >= 7.9 )
+            GHC-Options: -this-package-key ghc
 
     if flag(stage1)
         Include-Dirs: stage1
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index d28dd3077335..ea0bc53343e3 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -1133,8 +1133,7 @@ isNoLink _      = False
 -- is used.
 data PackageArg =
       PackageArg String    -- ^ @-package@, by 'PackageName'
-    | PackageIdArg String  -- ^ @-package-id@, by 'SourcePackageId'
-    | UnitIdArg String -- ^ @-package-key@, by 'ComponentId'
+    | UnitIdArg String     -- ^ @-package-id@, by 'UnitId'
   deriving (Eq, Show)
 
 -- | Represents the renaming that may be associated with an exposed
@@ -1167,7 +1166,6 @@ data TrustFlag
 -- | Flags for manipulating packages visibility.
 data PackageFlag
   = ExposePackage   String PackageArg ModRenaming -- ^ @-package@, @-package-id@
-                                           -- and @-package-key@
   | HidePackage     String -- ^ @-hide-package@
   deriving (Eq)
 -- NB: equality instance is used by InteractiveUI to test if
@@ -2774,15 +2772,21 @@ package_flags = [
       (NoArg $ do removeUserPkgConf
                   deprecate "Use -no-user-package-db instead")
 
-  , defGhcFlag "package-name"      (HasArg $ \name -> do
+  , defGhcFlag "package-name"       (HasArg $ \name -> do
+                                      upd (setUnitId name))
+                                      -- TODO: Since we JUST deprecated
+                                      -- -this-package-key, let's keep this
+                                      -- undeprecated for another cycle.
+                                      -- Deprecate this eventually.
+                                      -- deprecate "Use -this-unit-id instead")
+  , defGhcFlag "this-package-key"   (HasArg $ \name -> do
                                       upd (setUnitId name)
-                                      deprecate "Use -this-package-key instead")
-  , defGhcFlag "this-package-key"   (hasArg setUnitId)
-  , defFlag "package-id"            (HasArg exposePackageId)
+                                      deprecate "Use -this-unit-id instead")
+  , defGhcFlag "this-unit-id"       (hasArg setUnitId)
   , defFlag "package"               (HasArg exposePackage)
   , defFlag "plugin-package-id"     (HasArg exposePluginPackageId)
   , defFlag "plugin-package"        (HasArg exposePluginPackage)
-  , defFlag "package-key"           (HasArg exposeUnitId)
+  , defFlag "package-id"            (HasArg exposePackageId)
   , defFlag "hide-package"          (HasArg hidePackage)
   , defFlag "hide-all-packages"     (NoArg (setGeneralFlag Opt_HideAllPackages))
   , defFlag "hide-all-plugin-packages" (NoArg (setGeneralFlag Opt_HideAllPluginPackages))
@@ -3860,23 +3864,20 @@ parsePackageFlag flag constr str
              return (orig, orig))
         tok m = m >>= \x -> skipSpaces >> return x
 
-exposePackage, exposePackageId, exposeUnitId, hidePackage,
+exposePackage, exposePackageId, hidePackage,
         exposePluginPackage, exposePluginPackageId,
         ignorePackage,
         trustPackage, distrustPackage :: String -> DynP ()
 exposePackage p = upd (exposePackage' p)
 exposePackageId p =
   upd (\s -> s{ packageFlags =
-    parsePackageFlag "-package-id" PackageIdArg p : packageFlags s })
+    parsePackageFlag "-package-id" UnitIdArg p : packageFlags s })
 exposePluginPackage p =
   upd (\s -> s{ pluginPackageFlags =
     parsePackageFlag "-plugin-package" PackageArg p : pluginPackageFlags s })
 exposePluginPackageId p =
   upd (\s -> s{ pluginPackageFlags =
-    parsePackageFlag "-plugin-package-id" PackageIdArg p : pluginPackageFlags s })
-exposeUnitId p =
-  upd (\s -> s{ packageFlags =
-    parsePackageFlag "-package-key" UnitIdArg p : packageFlags s })
+    parsePackageFlag "-plugin-package-id" UnitIdArg p : pluginPackageFlags s })
 hidePackage p =
   upd (\s -> s{ packageFlags = HidePackage p : packageFlags s })
 ignorePackage p =
@@ -4285,18 +4286,34 @@ compilerInfo dflags
        ("Tables next to code",         cGhcEnableTablesNextToCode),
        ("RTS ways",                    cGhcRTSWays),
        ("RTS expects libdw",           showBool cGhcRtsWithLibdw),
+       -- Whether or not we support @-dynamic-too@
        ("Support dynamic-too",         showBool $ not isWindows),
+       -- Whether or not we support the @-j@ flag with @--make@.
        ("Support parallel --make",     "YES"),
+       -- Whether or not we support "Foo from foo-0.1-XXX:Foo" syntax in
+       -- installed package info.
        ("Support reexported-modules",  "YES"),
+       -- Whether or not we support extended @-package foo (Foo)@ syntax.
        ("Support thinning and renaming package flags", "YES"),
+       -- If true, we require that the 'id' field in installed package info
+       -- match what is passed to the @-this-unit-id@ flag for modules
+       -- built in it
        ("Requires unified installed package IDs", "YES"),
+       -- Whether or not we support the @-this-package-key@ flag.  Prefer
+       -- "Uses unit IDs" over it.
        ("Uses package keys",           "YES"),
+       -- Whether or not we support the @-this-unit-id@ flag
+       ("Uses unit IDs",               "YES"),
+       -- Whether or not GHC compiles libraries as dynamic by default
        ("Dynamic by default",          showBool $ dYNAMIC_BY_DEFAULT dflags),
+       -- Whether or not GHC was compiled using -dynamic
        ("GHC Dynamic",                 showBool dynamicGhc),
+       -- Whether or not GHC was compiled using -prof
        ("GHC Profiled",                showBool rtsIsProfiled),
        ("Leading underscore",          cLeadingUnderscore),
        ("Debug on",                    show debugIsOn),
        ("LibDir",                      topDir dflags),
+       -- The path of the global package database used by GHC
        ("Global Package DB",           systemPackageConfig dflags)
       ]
   where
diff --git a/compiler/main/HscTypes.hs b/compiler/main/HscTypes.hs
index 6b5458ea79db..9b4cd650166c 100644
--- a/compiler/main/HscTypes.hs
+++ b/compiler/main/HscTypes.hs
@@ -1229,7 +1229,7 @@ The details are a bit tricky though:
    extend the HPT.
 
  * The 'thisPackage' field of DynFlags is *not* set to 'interactive'.
-   It stays as 'main' (or whatever -this-package-key says), and is the
+   It stays as 'main' (or whatever -this-unit-id says), and is the
    package to which :load'ed modules are added to.
 
  * So how do we arrange that declarations at the command prompt get to
@@ -1238,7 +1238,7 @@ The details are a bit tricky though:
    call to initTc in initTcInteractive, which in turn get the module
    from it 'icInteractiveModule' field of the interactive context.
 
-   The 'thisPackage' field stays as 'main' (or whatever -this-package-key says.
+   The 'thisPackage' field stays as 'main' (or whatever -this-unit-id says.
 
  * The main trickiness is that the type environment (tcg_type_env) and
    fixity envt (tcg_fix_env), now contain entities from all the
diff --git a/compiler/main/PackageConfig.hs b/compiler/main/PackageConfig.hs
index 3fdb0af1d337..b19257bcea5f 100644
--- a/compiler/main/PackageConfig.hs
+++ b/compiler/main/PackageConfig.hs
@@ -20,7 +20,6 @@ module PackageConfig (
         PackageName(..),
         Version(..),
         defaultPackageConfig,
-        componentIdString,
         sourcePackageIdString,
         packageNameString,
         pprPackageConfig,
@@ -41,7 +40,6 @@ import Unique
 -- which is similar to a subset of the InstalledPackageInfo type from Cabal.
 
 type PackageConfig = InstalledPackageInfo
-                       ComponentId
                        SourcePackageId
                        PackageName
                        Module.UnitId
@@ -88,14 +86,11 @@ instance Outputable PackageName where
 -- | Pretty-print an 'ExposedModule' in the same format used by the textual
 -- installed package database.
 pprExposedModule :: (Outputable a, Outputable b) => ExposedModule a b -> SDoc
-pprExposedModule (ExposedModule exposedName exposedReexport exposedSignature) =
+pprExposedModule (ExposedModule exposedName exposedReexport) =
     sep [ ppr exposedName
         , case exposedReexport of
             Just m -> sep [text "from", pprOriginalModule m]
             Nothing -> empty
-        , case exposedSignature of
-            Just m -> sep [text "is", pprOriginalModule m]
-            Nothing -> empty
         ]
 
 -- | Pretty-print an 'OriginalModule' in the same format used by the textual
@@ -107,11 +102,6 @@ pprOriginalModule (OriginalModule originalPackageId originalModuleName) =
 defaultPackageConfig :: PackageConfig
 defaultPackageConfig = emptyInstalledPackageInfo
 
-componentIdString :: PackageConfig -> String
-componentIdString pkg = unpackFS str
-  where
-    ComponentId str = componentId pkg
-
 sourcePackageIdString :: PackageConfig -> String
 sourcePackageIdString pkg = unpackFS str
   where
@@ -127,7 +117,7 @@ pprPackageConfig InstalledPackageInfo {..} =
     vcat [
       field "name"                 (ppr packageName),
       field "version"              (text (showVersion packageVersion)),
-      field "id"                   (ppr componentId),
+      field "id"                   (ppr unitId),
       field "exposed"              (ppr exposed),
       field "exposed-modules"
         (if all isExposedModule exposedModules
@@ -152,7 +142,7 @@ pprPackageConfig InstalledPackageInfo {..} =
     ]
   where
     field name body = text name <> colon <+> nest 4 body
-    isExposedModule (ExposedModule _ Nothing Nothing) = True
+    isExposedModule (ExposedModule _ Nothing) = True
     isExposedModule _ = False
 
 
@@ -163,7 +153,7 @@ pprPackageConfig InstalledPackageInfo {..} =
 -- #package_naming#
 -- Mostly the compiler deals in terms of 'UnitId's, which are md5 hashes
 -- of a package ID, keys of its dependencies, and Cabal flags. You're expected
--- to pass in the unit id in the @-this-package-key@ flag. However, for
+-- to pass in the unit id in the @-this-unit-id@ flag. However, for
 -- wired-in packages like @base@ & @rts@, we don't necessarily know what the
 -- version is, so these are handled specially; see #wired_in_packages#.
 
diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs
index cf181046f0e4..0a8b27937452 100644
--- a/compiler/main/Packages.hs
+++ b/compiler/main/Packages.hs
@@ -602,15 +602,11 @@ matchingStr str p
         || str == packageNameString p
 
 matchingId :: String -> PackageConfig -> Bool
-matchingId str p =  str == componentIdString p
-
-matchingKey :: String -> PackageConfig -> Bool
-matchingKey str p = str == unitIdString (packageConfigId p)
+matchingId str p = str == unitIdString (packageConfigId p)
 
 matching :: PackageArg -> PackageConfig -> Bool
 matching (PackageArg str) = matchingStr str
-matching (PackageIdArg str) = matchingId str
-matching (UnitIdArg str) = matchingKey str
+matching (UnitIdArg str)  = matchingId str
 
 sortByVersion :: [PackageConfig] -> [PackageConfig]
 sortByVersion = sortBy (flip (comparing packageVersion))
@@ -1159,8 +1155,7 @@ mkModuleToPkgConfAll dflags pkg_db vis_map =
 
     es :: Bool -> [(ModuleName, Map Module ModuleOrigin)]
     es e = do
-     -- TODO: signature support
-     ExposedModule m exposedReexport _exposedSignature <- exposed_mods
+     ExposedModule m exposedReexport <- exposed_mods
      let (pk', m', pkg', origin') =
           case exposedReexport of
            Nothing -> (pk, m, pkg, fromExposedModules e)
diff --git a/configure.ac b/configure.ac
index 771ec43824c6..cc162e7c08dd 100644
--- a/configure.ac
+++ b/configure.ac
@@ -153,6 +153,11 @@ fi
 GHC_PACKAGE_DB_FLAG=package-db
 AC_SUBST(GHC_PACKAGE_DB_FLAG)
 
+FP_COMPARE_VERSIONS([$GhcVersion],[-lt],[7.11],
+                    SUPPORTS_THIS_UNIT_ID=NO,
+                    SUPPORTS_THIS_UNIT_ID=YES)
+AC_SUBST(SUPPORTS_THIS_UNIT_ID)
+
 # GHC is passed to Cabal, so we need a native path
 if test "${WithGhc}" != ""
 then
diff --git a/docs/users_guide/8.0.1-notes.rst b/docs/users_guide/8.0.1-notes.rst
index aaf9ca38259f..c36c721be51f 100644
--- a/docs/users_guide/8.0.1-notes.rst
+++ b/docs/users_guide/8.0.1-notes.rst
@@ -274,6 +274,14 @@ Compiler
    expressivity may come with a high price in terms of compilation time and
    memory consumption, it is turned off by default.
 
+-  :ghc-flag:`-this-package-key` has been renamed again (hopefully for the last time!)
+   to :ghc-flag:`-this-unit-id`.  The renaming was motivated by the fact that
+   the identifier you pass to GHC here doesn't have much to do with packages:
+   you may provide different unit IDs for libraries which are in the same
+   package.  :ghc-flag:`-this-package-key` is deprecated; you should use
+   :ghc-flag:`-this-unit-id` or, if you need compatibility over multiple
+   versions of GHC, :ghc-flag:`-package-name`.
+
 GHCi
 ~~~~
 
diff --git a/docs/users_guide/packages.rst b/docs/users_guide/packages.rst
index 02d9cc699287..89eb2579a14e 100644
--- a/docs/users_guide/packages.rst
+++ b/docs/users_guide/packages.rst
@@ -161,10 +161,12 @@ The GHC command line options that control packages are:
 
         $ ghc -o myprog Foo.hs Main.hs -package network
 
-.. ghc-flag:: -package-id ⟨pkg-id⟩
+.. ghc-flag:: -package-id ⟨unit-id⟩
 
     Exposes a package like :ghc-flag:`-package`, but the package is named by its
-    installed package ID rather than by name. This is a more robust way
+    unit ID (i.e. the value of ``id`` in its entry in the installed
+    package database, also previously known as an installed package ID)
+    rather than by name. This is a more robust way
     to name packages, and can be used to select packages that would
     otherwise be shadowed. Cabal passes ``-package-id`` flags to GHC.
     ``-package-id`` supports thinning and renaming described in
@@ -208,11 +210,14 @@ The GHC command line options that control packages are:
     By default, GHC will automatically link in the ``base`` and ``rts``
     packages. This flag disables that behaviour.
 
-.. ghc-flag:: -this-package-key ⟨pkg-key⟩
+.. ghc-flag:: -this-unit-id ⟨unit-id⟩
 
     Tells GHC the the module being compiled forms part of unit ID
-    ⟨pkg-key⟩; internally, these keys are used to determine type equality
-    and linker symbols.
+    ⟨unit-id⟩; internally, these keys are used to determine type equality
+    and linker symbols.  As of GHC 8.0, unit IDs must consist solely
+    of alphanumeric characters, dashes, underscores and periods.  GHC
+    reserves the right to interpret other characters in a special
+    way in later releases.
 
 .. ghc-flag:: -library-name ⟨hash⟩
 
@@ -255,7 +260,7 @@ The ``main`` package
 --------------------
 
 Every complete Haskell program must define ``main`` in module ``Main``
-in package ``main``. Omitting the :ghc-flag:`-this-package-key` flag compiles
+in package ``main``. Omitting the :ghc-flag:`-this-unit-id` flag compiles
 code for package ``main``. Failure to do so leads to a somewhat obscure
 link-time error of the form:
 
diff --git a/libraries/Cabal b/libraries/Cabal
index a8a121ea4d78..ecdf65a3c1e0 160000
--- a/libraries/Cabal
+++ b/libraries/Cabal
@@ -1 +1 @@
-Subproject commit a8a121ea4d78783dd303dd2992d8e73ef337e7ed
+Subproject commit ecdf65a3c1e01b798e9d073258a6d1c8ff63a6d8
diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal
index cd77e55ee6ed..7d9367a6be35 100644
--- a/libraries/base/base.cabal
+++ b/libraries/base/base.cabal
@@ -362,4 +362,4 @@ Library
 
     -- We need to set the unit id to base (without a version number)
     -- as it's magic.
-    ghc-options: -this-package-key base
+    ghc-options: -this-unit-id base
diff --git a/libraries/ghc-boot/GHC/PackageDb.hs b/libraries/ghc-boot/GHC/PackageDb.hs
index 2be20b24054a..cc03c3b17f18 100644
--- a/libraries/ghc-boot/GHC/PackageDb.hs
+++ b/libraries/ghc-boot/GHC/PackageDb.hs
@@ -64,15 +64,14 @@ import System.Directory
 -- | This is a subset of Cabal's 'InstalledPackageInfo', with just the bits
 -- that GHC is interested in.
 --
-data InstalledPackageInfo instpkgid srcpkgid srcpkgname pkgkey modulename
+data InstalledPackageInfo srcpkgid srcpkgname unitid modulename
    = InstalledPackageInfo {
-       componentId :: instpkgid,
+       unitId             :: unitid,
        sourcePackageId    :: srcpkgid,
        packageName        :: srcpkgname,
        packageVersion     :: Version,
-       unitId         :: pkgkey,
        abiHash            :: String,
-       depends            :: [pkgkey],
+       depends            :: [unitid],
        importDirs         :: [FilePath],
        hsLibraries        :: [String],
        extraLibraries     :: [String],
@@ -86,9 +85,8 @@ data InstalledPackageInfo instpkgid srcpkgid srcpkgname pkgkey modulename
        includeDirs        :: [FilePath],
        haddockInterfaces  :: [FilePath],
        haddockHTMLs       :: [FilePath],
-       exposedModules     :: [ExposedModule pkgkey modulename],
+       exposedModules     :: [ExposedModule unitid modulename],
        hiddenModules      :: [modulename],
-       instantiatedWith   :: [(modulename,OriginalModule pkgkey modulename)],
        exposed            :: Bool,
        trusted            :: Bool
      }
@@ -98,40 +96,30 @@ data InstalledPackageInfo instpkgid srcpkgid srcpkgname pkgkey modulename
 -- plus module name) representing where a module was *originally* defined
 -- (i.e., the 'exposedReexport' field of the original ExposedModule entry should
 -- be 'Nothing').  Invariant: an OriginalModule never points to a reexport.
-data OriginalModule pkgkey modulename
+data OriginalModule unitid modulename
    = OriginalModule {
-       originalPackageId :: pkgkey,
+       originalPackageId :: unitid,
        originalModuleName :: modulename
      }
   deriving (Eq, Show)
 
 -- | Represents a module name which is exported by a package, stored in the
--- 'exposedModules' field.  A module export may be a reexport (in which
--- case 'exposedReexport' is filled in with the original source of the module),
--- and may be a signature (in which case 'exposedSignature is filled in with
--- what the signature was compiled against).  Thus:
+-- 'exposedModules' field.  A module export may be a reexport (in which case
+-- 'exposedReexport' is filled in with the original source of the module).
+-- Thus:
 --
---  * @ExposedModule n Nothing Nothing@ represents an exposed module @n@ which
+--  * @ExposedModule n Nothing@ represents an exposed module @n@ which
 --    was defined in this package.
 --
---  * @ExposedModule n (Just o) Nothing@ represents a reexported module @n@
+--  * @ExposedModule n (Just o)@ represents a reexported module @n@
 --    which was originally defined in @o@.
 --
---  * @ExposedModule n Nothing (Just s)@ represents an exposed signature @n@
---    which was compiled against the implementation @s@.
---
---  * @ExposedModule n (Just o) (Just s)@ represents a reexported signature
---    which was originally defined in @o@ and was compiled against the
---    implementation @s@.
---
--- We use two 'Maybe' data types instead of an ADT with four branches or
--- four fields because this representation allows us to treat
--- reexports/signatures uniformly.
-data ExposedModule pkgkey modulename
+-- We use a 'Maybe' data types instead of an ADT with two branches because this
+-- representation allows us to treat reexports uniformly.
+data ExposedModule unitid modulename
    = ExposedModule {
        exposedName      :: modulename,
-       exposedReexport  :: Maybe (OriginalModule pkgkey modulename),
-       exposedSignature :: Maybe (OriginalModule pkgkey modulename)
+       exposedReexport  :: Maybe (OriginalModule unitid modulename)
      }
   deriving (Eq, Show)
 
@@ -140,15 +128,14 @@ class BinaryStringRep a where
   toStringRep   :: a -> BS.ByteString
 
 emptyInstalledPackageInfo :: (BinaryStringRep a, BinaryStringRep b,
-                              BinaryStringRep c, BinaryStringRep d)
-                          => InstalledPackageInfo a b c d e
+                              BinaryStringRep c)
+                          => InstalledPackageInfo a b c d
 emptyInstalledPackageInfo =
   InstalledPackageInfo {
-       componentId = fromStringRep BS.empty,
+       unitId             = fromStringRep BS.empty,
        sourcePackageId    = fromStringRep BS.empty,
        packageName        = fromStringRep BS.empty,
        packageVersion     = Version [] [],
-       unitId         = fromStringRep BS.empty,
        abiHash            = "",
        depends            = [],
        importDirs         = [],
@@ -166,7 +153,6 @@ emptyInstalledPackageInfo =
        haddockHTMLs       = [],
        exposedModules     = [],
        hiddenModules      = [],
-       instantiatedWith   = [],
        exposed            = False,
        trusted            = False
   }
@@ -174,8 +160,8 @@ emptyInstalledPackageInfo =
 -- | Read the part of the package DB that GHC is interested in.
 --
 readPackageDbForGhc :: (BinaryStringRep a, BinaryStringRep b, BinaryStringRep c,
-                        BinaryStringRep d, BinaryStringRep e) =>
-                       FilePath -> IO [InstalledPackageInfo a b c d e]
+                        BinaryStringRep d) =>
+                       FilePath -> IO [InstalledPackageInfo a b c d]
 readPackageDbForGhc file =
     decodeFromFile file getDbForGhc
   where
@@ -208,8 +194,8 @@ readPackageDbForGhcPkg file =
 -- | Write the whole of the package DB, both parts.
 --
 writePackageDb :: (Binary pkgs, BinaryStringRep a, BinaryStringRep b,
-                   BinaryStringRep c, BinaryStringRep d, BinaryStringRep e) =>
-                  FilePath -> [InstalledPackageInfo a b c d e] -> pkgs -> IO ()
+                   BinaryStringRep c, BinaryStringRep d) =>
+                  FilePath -> [InstalledPackageInfo a b c d] -> pkgs -> IO ()
 writePackageDb file ghcPkgs ghcPkgPart =
     writeFileAtomic file (runPut putDbForGhcPkg)
   where
@@ -296,20 +282,19 @@ writeFileAtomic targetPath content = do
         renameFile tmpPath targetPath)
 
 instance (BinaryStringRep a, BinaryStringRep b, BinaryStringRep c,
-          BinaryStringRep d, BinaryStringRep e) =>
-         Binary (InstalledPackageInfo a b c d e) where
+          BinaryStringRep d) =>
+         Binary (InstalledPackageInfo a b c d) where
   put (InstalledPackageInfo
-         componentId sourcePackageId
-         packageName packageVersion unitId
+         unitId sourcePackageId
+         packageName packageVersion
          abiHash depends importDirs
          hsLibraries extraLibraries extraGHCiLibraries libraryDirs
          frameworks frameworkDirs
          ldOptions ccOptions
          includes includeDirs
          haddockInterfaces haddockHTMLs
-         exposedModules hiddenModules instantiatedWith
+         exposedModules hiddenModules
          exposed trusted) = do
-    put (toStringRep componentId)
     put (toStringRep sourcePackageId)
     put (toStringRep packageName)
     put packageVersion
@@ -331,12 +316,10 @@ instance (BinaryStringRep a, BinaryStringRep b, BinaryStringRep c,
     put haddockHTMLs
     put exposedModules
     put (map toStringRep hiddenModules)
-    put (map (\(k,v) -> (toStringRep k, v)) instantiatedWith)
     put exposed
     put trusted
 
   get = do
-    componentId <- get
     sourcePackageId    <- get
     packageName        <- get
     packageVersion     <- get
@@ -358,14 +341,12 @@ instance (BinaryStringRep a, BinaryStringRep b, BinaryStringRep c,
     haddockHTMLs       <- get
     exposedModules     <- get
     hiddenModules      <- get
-    instantiatedWith   <- get
     exposed            <- get
     trusted            <- get
     return (InstalledPackageInfo
-              (fromStringRep componentId)
+              (fromStringRep unitId)
               (fromStringRep sourcePackageId)
               (fromStringRep packageName) packageVersion
-              (fromStringRep unitId)
               abiHash
               (map fromStringRep depends)
               importDirs
@@ -376,7 +357,6 @@ instance (BinaryStringRep a, BinaryStringRep b, BinaryStringRep c,
               haddockInterfaces haddockHTMLs
               exposedModules
               (map fromStringRep hiddenModules)
-              (map (\(k,v) -> (fromStringRep k, v)) instantiatedWith)
               exposed trusted)
 
 instance (BinaryStringRep a, BinaryStringRep b) =>
@@ -392,14 +372,11 @@ instance (BinaryStringRep a, BinaryStringRep b) =>
 
 instance (BinaryStringRep a, BinaryStringRep b) =>
          Binary (ExposedModule a b) where
-  put (ExposedModule exposedName exposedReexport exposedSignature) = do
+  put (ExposedModule exposedName exposedReexport) = do
     put (toStringRep exposedName)
     put exposedReexport
-    put exposedSignature
   get = do
     exposedName <- get
     exposedReexport <- get
-    exposedSignature <- get
     return (ExposedModule (fromStringRep exposedName)
-                          exposedReexport
-                          exposedSignature)
+                          exposedReexport)
diff --git a/libraries/ghc-prim/ghc-prim.cabal b/libraries/ghc-prim/ghc-prim.cabal
index 1f09b45fca9f..2077e6d79964 100644
--- a/libraries/ghc-prim/ghc-prim.cabal
+++ b/libraries/ghc-prim/ghc-prim.cabal
@@ -68,4 +68,4 @@ Library
 
     -- We need to set the unit ID to ghc-prim (without a version number)
     -- as it's magic.
-    ghc-options: -this-package-key ghc-prim
+    ghc-options: -this-unit-id ghc-prim
diff --git a/libraries/integer-gmp/integer-gmp.cabal b/libraries/integer-gmp/integer-gmp.cabal
index 5b5fb56ffecd..377efb39f946 100644
--- a/libraries/integer-gmp/integer-gmp.cabal
+++ b/libraries/integer-gmp/integer-gmp.cabal
@@ -48,7 +48,7 @@ library
     UnliftedFFITypes
   build-depends:       ghc-prim
   hs-source-dirs:      src/
-  ghc-options: -this-package-key integer-gmp -Wall
+  ghc-options: -this-unit-id integer-gmp -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 f958aa820163..0c05ad71ec9a 100644
--- a/libraries/integer-simple/integer-simple.cabal
+++ b/libraries/integer-simple/integer-simple.cabal
@@ -26,6 +26,6 @@ Library
     other-modules: GHC.Integer.Type
     default-extensions: CPP, MagicHash, BangPatterns, UnboxedTuples,
                 UnliftedFFITypes, NoImplicitPrelude
-    -- We need to set the package name to integer-simple
+    -- We need to set the unit ID to integer-simple
     -- (without a version number) as it's magic.
-    ghc-options: -this-package-key integer-simple -Wall
+    ghc-options: -this-unit-id integer-simple -Wall
diff --git a/libraries/template-haskell/template-haskell.cabal b/libraries/template-haskell/template-haskell.cabal
index aae8afee59d2..b96e1226101d 100644
--- a/libraries/template-haskell/template-haskell.cabal
+++ b/libraries/template-haskell/template-haskell.cabal
@@ -55,7 +55,10 @@ Library
     -- version number) as it's magic.
     ghc-options: -Wall
 
-    if impl( ghc >= 7.9 )
-        ghc-options:  -this-package-key template-haskell
+    if impl( ghc >= 7.11 )
+        ghc-options:  -this-unit-id template-haskell
     else
-        ghc-options:  -package-name template-haskell
+        if impl( ghc >= 7.9 )
+            ghc-options:  -this-package-key template-haskell
+        else
+            ghc-options:  -package-name template-haskell
diff --git a/mk/config.mk.in b/mk/config.mk.in
index 966f34aad23e..927e686be015 100644
--- a/mk/config.mk.in
+++ b/mk/config.mk.in
@@ -498,6 +498,8 @@ endif
 
 GHC_PACKAGE_DB_FLAG = @GHC_PACKAGE_DB_FLAG@
 
+SUPPORTS_THIS_UNIT_ID = @SUPPORTS_THIS_UNIT_ID@
+
 #-----------------------------------------------------------------------------
 # C compiler
 #
diff --git a/rts/ghc.mk b/rts/ghc.mk
index 84b59d3c2a1c..71da10d5af91 100644
--- a/rts/ghc.mk
+++ b/rts/ghc.mk
@@ -206,7 +206,7 @@ ifneq "$$(findstring dyn, $1)" ""
 ifeq "$$(HostOS_CPP)" "mingw32" 
 $$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) rts/dist/libs.depend rts/dist/build/$$(LIBFFI_DLL)
 	"$$(RM)" $$(RM_OPTS) $$@
-	"$$(rts_dist_HC)" -this-package-key rts -shared -dynamic -dynload deploy \
+	"$$(rts_dist_HC)" -this-unit-id rts -shared -dynamic -dynload deploy \
 	  -no-auto-link-packages -Lrts/dist/build -l$$(LIBFFI_NAME) \
          `cat rts/dist/libs.depend` $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) \
          $$(rts_dist_$1_GHC_LD_OPTS) \
@@ -227,7 +227,7 @@ LIBFFI_LIBS =
 endif
 $$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) rts/dist/libs.depend $$(rts_dist_FFI_SO)
 	"$$(RM)" $$(RM_OPTS) $$@
-	"$$(rts_dist_HC)" -this-package-key rts -shared -dynamic -dynload deploy \
+	"$$(rts_dist_HC)" -this-unit-id rts -shared -dynamic -dynload deploy \
 	  -no-auto-link-packages $$(LIBFFI_LIBS) `cat rts/dist/libs.depend` $$(rts_$1_OBJS) \
           $$(rts_dist_$1_GHC_LD_OPTS) \
 	  $$(rts_$1_DTRACE_OBJS) -o $$@
@@ -301,7 +301,7 @@ STANDARD_OPTS += -DCOMPILING_RTS
 rts_CC_OPTS += $(WARNING_OPTS)
 rts_CC_OPTS += $(STANDARD_OPTS)
 
-rts_HC_OPTS += $(STANDARD_OPTS) -this-package-key rts
+rts_HC_OPTS += $(STANDARD_OPTS) -this-unit-id rts
 
 ifneq "$(GhcWithSMP)" "YES"
 rts_CC_OPTS += -DNOSMP
diff --git a/rules/distdir-way-opts.mk b/rules/distdir-way-opts.mk
index f6b9a45b8f64..66c00afc73ae 100644
--- a/rules/distdir-way-opts.mk
+++ b/rules/distdir-way-opts.mk
@@ -96,9 +96,21 @@ define distdir-way-opts # args: $1 = dir, $2 = distdir, $3 = way, $4 = stage
 # $1_$2_$3_MOST_HC_OPTS is also passed to C compilations when we use
 # GHC as the C compiler.
 
+ifeq "$(SUPPORTS_THIS_UNIT_ID)" "NO"
+ifeq "$4" "0"
+$4_USE_THIS_UNIT_ID=NO
+endif
+endif
+
 $1_$2_$4_DEP_OPTS = \
  $$(foreach pkg,$$($1_$2_DEP_IPIDS),-package-id $$(pkg))
 
+ifeq "$($4_USE_THIS_UNIT_ID)" "NO"
+$4_THIS_UNIT_ID = -this-package-key
+else
+$4_THIS_UNIT_ID = -this-unit-id
+endif
+
 $1_$2_$3_MOST_HC_OPTS = \
  $$(WAY_$3_HC_OPTS) \
  $$(CONF_HC_OPTS) \
@@ -107,7 +119,7 @@ $1_$2_$3_MOST_HC_OPTS = \
  $$($1_HC_OPTS) \
  $$($1_$2_HC_PKGCONF) \
  $$(if $$($1_$2_PROG),, \
-        $$(if $$($1_PACKAGE),-this-package-key $$($1_$2_COMPONENT_ID))) \
+        $$(if $$($1_PACKAGE),$$($4_THIS_UNIT_ID) $$($1_$2_COMPONENT_ID))) \
  $$(if $$($1_PACKAGE),-hide-all-packages) \
  -i $$(if $$($1_$2_HS_SRC_DIRS),$$(foreach dir,$$($1_$2_HS_SRC_DIRS),-i$1/$$(dir)),-i$1) \
  -i$1/$2/build -i$1/$2/build/autogen \
diff --git a/testsuite/tests/module/base01/Makefile b/testsuite/tests/module/base01/Makefile
index 6f77c09a36eb..4358f0b3e67a 100644
--- a/testsuite/tests/module/base01/Makefile
+++ b/testsuite/tests/module/base01/Makefile
@@ -9,6 +9,6 @@ clean:
 base01:
 	rm -f GHC/*.o
 	rm -f GHC/*.hi
-	'$(TEST_HC)' $(filter-out -fforce-recomp,$(TEST_HC_OPTS)) -XNoImplicitPrelude -this-package-key base -c GHC/Base.hs
-	'$(TEST_HC)' $(filter-out -fforce-recomp,$(TEST_HC_OPTS)) -XNoImplicitPrelude -this-package-key base --make GHC.Foo
+	'$(TEST_HC)' $(filter-out -fforce-recomp,$(TEST_HC_OPTS)) -XNoImplicitPrelude -this-unit-id base -c GHC/Base.hs
+	'$(TEST_HC)' $(filter-out -fforce-recomp,$(TEST_HC_OPTS)) -XNoImplicitPrelude -this-unit-id base --make GHC.Foo
 
diff --git a/testsuite/tests/rename/prog006/Makefile b/testsuite/tests/rename/prog006/Makefile
index 0012e50bad0e..8d4777d5f0da 100644
--- a/testsuite/tests/rename/prog006/Makefile
+++ b/testsuite/tests/rename/prog006/Makefile
@@ -28,7 +28,7 @@ rn.prog006:
 	rm -f pkg.conf
 	rm -f pwd pwd.exe pwd.exe.manifest pwd.hi pwd.o
 	'$(TEST_HC)' $(TEST_HC_OPTS) --make pwd -v0
-	'$(TEST_HC)' $(TEST_HC_OPTS) --make -this-package-key test-1.0-XXX B.C -fforce-recomp -v0 $(RM_PROG006_EXTRA_FLAGS)
+	'$(TEST_HC)' $(TEST_HC_OPTS) --make -this-unit-id test-1.0-XXX B.C -fforce-recomp -v0 $(RM_PROG006_EXTRA_FLAGS)
 	rm -f pkg.conf
 	echo "name: test" >>pkg.conf
 	echo "version: 1.0" >>pkg.conf
diff --git a/testsuite/tests/rename/should_compile/T3103/test.T b/testsuite/tests/rename/should_compile/T3103/test.T
index 716839d527be..24745b4b08a5 100644
--- a/testsuite/tests/rename/should_compile/T3103/test.T
+++ b/testsuite/tests/rename/should_compile/T3103/test.T
@@ -10,5 +10,5 @@ test('T3103',
                    'GHC/Unicode.o',  'GHC/Unicode.o-boot',
                    'GHC/Word.hi',    'GHC/Word.o'])],
      multimod_compile,
-     ['Foreign.Ptr', '-v0 -hide-all-packages -package ghc-prim -package integer-gmp -this-package-key base'])
+     ['Foreign.Ptr', '-v0 -hide-all-packages -package ghc-prim -package integer-gmp -this-unit-id base'])
 
diff --git a/utils/ghc-cabal/Main.hs b/utils/ghc-cabal/Main.hs
index 2c05da83a71a..575f8f341aa6 100644
--- a/utils/ghc-cabal/Main.hs
+++ b/utils/ghc-cabal/Main.hs
@@ -313,12 +313,12 @@ generate directory distdir dll0Modules config_args
       -- generate inplace-pkg-config
       withLibLBI pd lbi $ \lib clbi ->
           do cwd <- getCurrentDirectory
-             let ipid = ComponentId (display (packageId pd))
+             let ipid = mkUnitId (display (packageId pd))
              let installedPkgInfo = inplaceInstalledPackageInfo cwd distdir
-                                        pd (Installed.AbiHash "") lib lbi clbi
+                                        pd (AbiHash "") lib lbi clbi
                  final_ipi = mangleIPI directory distdir lbi $ installedPkgInfo {
-                                 Installed.installedComponentId = ipid,
-                                 Installed.compatPackageKey = ipid,
+                                 Installed.installedUnitId = ipid,
+                                 Installed.compatPackageKey = display (packageId pd),
                                  Installed.haddockHTMLs = []
                              }
                  content = Installed.showInstalledPackageInfo final_ipi ++ "\n"
@@ -369,12 +369,12 @@ generate directory distdir dll0Modules config_args
           dep_ids  = map snd (externalPackageDeps lbi)
           deps     = map display dep_ids
           dep_direct = map (fromMaybe (error "ghc-cabal: dep_keys failed")
-                           . PackageIndex.lookupComponentId
+                           . PackageIndex.lookupUnitId
                                             (installedPkgs lbi)
                            . fst)
                        . externalPackageDeps
                        $ lbi
-          dep_ipids = map (display . Installed.installedComponentId) dep_direct
+          dep_ipids = map (display . Installed.installedUnitId) dep_direct
           depLibNames
             | packageKeySupported comp = dep_ipids
             | otherwise = deps
@@ -406,7 +406,7 @@ generate directory distdir dll0Modules config_args
           allMods = mods ++ otherMods
       let xs = [variablePrefix ++ "_VERSION = " ++ display (pkgVersion (package pd)),
                 -- TODO: move inside withLibLBI
-                variablePrefix ++ "_COMPONENT_ID = " ++ display (localCompatPackageKey lbi),
+                variablePrefix ++ "_COMPONENT_ID = " ++ localCompatPackageKey lbi,
                 variablePrefix ++ "_MODULES = " ++ unwords mods,
                 variablePrefix ++ "_HIDDEN_MODULES = " ++ unwords otherMods,
                 variablePrefix ++ "_SYNOPSIS =" ++ (unwords $ lines $ synopsis pd),
diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs
index 4a3fbdb2947a..084579219865 100644
--- a/utils/ghc-pkg/Main.hs
+++ b/utils/ghc-pkg/Main.hs
@@ -19,7 +19,7 @@ import Distribution.ModuleName (ModuleName)
 import Distribution.InstalledPackageInfo as Cabal
 import Distribution.Compat.ReadP hiding (get)
 import Distribution.ParseUtils
-import Distribution.Package hiding (installedComponentId)
+import Distribution.Package hiding (installedUnitId)
 import Distribution.Text
 import Distribution.Version
 import Distribution.Simple.Utils (fromUTF8, toUTF8, writeUTF8File, readUTF8File)
@@ -132,7 +132,7 @@ data Flag
   | FlagIgnoreCase
   | FlagNoUserDb
   | FlagVerbosity (Maybe String)
-  | FlagComponentId
+  | FlagUnitId
   deriving Eq
 
 flags :: [OptDescr Flag]
@@ -175,8 +175,8 @@ flags = [
         "only print package names, not versions; can only be used with list --simple-output",
   Option [] ["ignore-case"] (NoArg FlagIgnoreCase)
         "ignore case for substring matching",
-  Option [] ["ipid", "package-key"] (NoArg FlagComponentId)
-        "interpret package arguments as installed package IDs",
+  Option [] ["ipid", "unit-id"] (NoArg FlagUnitId)
+        "interpret package arguments as unit IDs (e.g. installed package IDs)",
   Option ['v'] ["verbose"] (OptArg FlagVerbosity "Verbosity")
         "verbosity level (0-2, default 1)"
   ]
@@ -315,7 +315,7 @@ data Force = NoForce | ForceFiles | ForceAll | CannotForce
 
 -- | Enum flag representing argument type
 data AsPackageArg
-    = AsComponentId
+    = AsUnitId
     | AsDefault
 
 -- | Represents how a package may be specified by a user on the command line.
@@ -324,7 +324,7 @@ data PackageArg
     = Id PackageIdentifier
     -- | An installed package ID foo-0.1-HASH.  This is guaranteed to uniquely
     -- match a single entry in the package database.
-    | ICId ComponentId
+    | IUId UnitId
     -- | A glob against the package name.  The first string is the literal
     -- glob, the second is a function which returns @True@ if the argument
     -- matches.
@@ -341,8 +341,8 @@ runit verbosity cli nonopts = do
           | FlagForce `elem` cli        = ForceAll
           | FlagForceFiles `elem` cli   = ForceFiles
           | otherwise                   = NoForce
-        as_arg | FlagComponentId        `elem` cli = AsComponentId
-               | otherwise                  = AsDefault
+        as_arg | FlagUnitId `elem` cli = AsUnitId
+               | otherwise             = AsDefault
         multi_instance = FlagMultiInstance `elem` cli
         expand_env_vars= FlagExpandEnvVars `elem` cli
         mexpand_pkgroot= foldl' accumExpandPkgroot Nothing cli
@@ -494,8 +494,8 @@ parseGlobPackageId =
       return (PackageIdentifier{ pkgName = n, pkgVersion = globVersion }))
 
 readPackageArg :: AsPackageArg -> String -> IO PackageArg
-readPackageArg AsComponentId str =
-    parseCheck (ICId `fmap` parse) str "installed package id"
+readPackageArg AsUnitId str =
+    parseCheck (IUId `fmap` parse) str "installed package id"
 readPackageArg AsDefault str = Id `fmap` readGlobPkgId str
 
 -- globVersion means "all versions"
@@ -1021,7 +1021,7 @@ updateInternalDB :: PackageDB -> [DBOp] -> PackageDB
 updateInternalDB db cmds = db{ packages = foldl do_cmd (packages db) cmds }
  where
   do_cmd pkgs (RemovePackage p) =
-    filter ((/= installedComponentId p) . installedComponentId) pkgs
+    filter ((/= installedUnitId p) . installedUnitId) pkgs
   do_cmd pkgs (AddPackage p) = p : pkgs
   do_cmd pkgs (ModifyPackage p) =
     do_cmd (do_cmd pkgs (RemovePackage p)) (AddPackage p)
@@ -1033,11 +1033,11 @@ changeDBDir verbosity cmds db = do
   updateDBCache verbosity db
  where
   do_cmd (RemovePackage p) = do
-    let file = location db </> display (installedComponentId p) <.> "conf"
+    let file = location db </> display (installedUnitId p) <.> "conf"
     when (verbosity > Normal) $ infoLn ("removing " ++ file)
     removeFileSafe file
   do_cmd (AddPackage p) = do
-    let file = location db </> display (installedComponentId p) <.> "conf"
+    let file = location db </> display (installedUnitId p) <.> "conf"
     when (verbosity > Normal) $ infoLn ("writing " ++ file)
     writeUTF8File file (showInstalledPackageInfo p)
   do_cmd (ModifyPackage p) =
@@ -1071,7 +1071,6 @@ updateDBCache verbosity db = do
       hPutChar handle c
 
 type PackageCacheFormat = GhcPkg.InstalledPackageInfo
-                            String     -- installed package id
                             String     -- src package id
                             String     -- package name
                             String     -- unit id
@@ -1080,11 +1079,10 @@ type PackageCacheFormat = GhcPkg.InstalledPackageInfo
 convertPackageInfoToCacheFormat :: InstalledPackageInfo -> PackageCacheFormat
 convertPackageInfoToCacheFormat pkg =
     GhcPkg.InstalledPackageInfo {
-       GhcPkg.componentId = display (installedComponentId pkg),
+       GhcPkg.unitId             = display (installedUnitId pkg),
        GhcPkg.sourcePackageId    = display (sourcePackageId pkg),
        GhcPkg.packageName        = display (packageName pkg),
        GhcPkg.packageVersion     = packageVersion pkg,
-       GhcPkg.unitId            = display (installedComponentId pkg),
        GhcPkg.depends            = map display (depends pkg),
        GhcPkg.abiHash            = let AbiHash abi = abiHash pkg
                                    in abi,
@@ -1103,16 +1101,13 @@ convertPackageInfoToCacheFormat pkg =
        GhcPkg.haddockHTMLs       = haddockHTMLs pkg,
        GhcPkg.exposedModules     = map convertExposed (exposedModules pkg),
        GhcPkg.hiddenModules      = hiddenModules pkg,
-       GhcPkg.instantiatedWith   = map convertInst (instantiatedWith pkg),
        GhcPkg.exposed            = exposed pkg,
        GhcPkg.trusted            = trusted pkg
     }
-  where convertExposed (ExposedModule n reexport sig) =
+  where convertExposed (ExposedModule n reexport) =
             GhcPkg.ExposedModule n (fmap convertOriginal reexport)
-                                   (fmap convertOriginal sig)
         convertOriginal (OriginalModule ipid m) =
             GhcPkg.OriginalModule (display ipid) m
-        convertInst (m, o) = (m, convertOriginal o)
 
 instance GhcPkg.BinaryStringRep ModuleName where
   fromStringRep = ModuleName.fromString . fromUTF8 . BS.unpack
@@ -1159,9 +1154,9 @@ modifyPackage fn pkgarg verbosity my_flags force = do
       db_name = location db
       pkgs    = packages db
 
-      pks = map installedComponentId ps
+      pks = map installedUnitId ps
 
-      cmds = [ fn pkg | pkg <- pkgs, installedComponentId pkg `elem` pks ]
+      cmds = [ fn pkg | pkg <- pkgs, installedUnitId pkg `elem` pks ]
       new_db = updateInternalDB db cmds
 
       -- ...but do consistency checks with regards to the full stack
@@ -1169,14 +1164,14 @@ modifyPackage fn pkgarg verbosity my_flags force = do
       rest_of_stack = filter ((/= db_name) . location) db_stack
       new_stack = new_db : rest_of_stack
       new_broken = brokenPackages (allPackagesInStack new_stack)
-      newly_broken = filter ((`notElem` map installedComponentId old_broken)
-                            . installedComponentId) new_broken
+      newly_broken = filter ((`notElem` map installedUnitId old_broken)
+                            . installedUnitId) new_broken
   --
   let displayQualPkgId pkg
         | [_] <- filter ((== pkgid) . sourcePackageId)
                         (allPackagesInStack db_stack)
             = display pkgid
-        | otherwise = display pkgid ++ "@" ++ display (installedComponentId pkg)
+        | otherwise = display pkgid ++ "@" ++ display (installedUnitId pkg)
         where pkgid = sourcePackageId pkg
   when (not (null newly_broken)) $
       dieOrForceAll force ("unregistering would break the following packages: "
@@ -1227,7 +1222,7 @@ listPackages verbosity my_flags mPackageName mModuleName = do
                         EQ -> case pkgVersion p1 `compare` pkgVersion p2 of
                                 LT -> LT
                                 GT -> GT
-                                EQ -> installedComponentId pkg1 `compare` installedComponentId pkg2
+                                EQ -> installedUnitId pkg1 `compare` installedUnitId pkg2
                    where (p1,p2) = (sourcePackageId pkg1, sourcePackageId pkg2)
 
       stack = reverse db_stack_sorted
@@ -1235,7 +1230,7 @@ listPackages verbosity my_flags mPackageName mModuleName = do
       match `exposedInPkg` pkg = any match (map display $ exposedModules pkg)
 
       pkg_map = allPackagesInStack db_stack
-      broken = map installedComponentId (brokenPackages pkg_map)
+      broken = map installedUnitId (brokenPackages pkg_map)
 
       show_normal PackageDB{ location = db_name, packages = pkg_confs } =
           do hPutStrLn stdout db_name
@@ -1244,13 +1239,12 @@ listPackages verbosity my_flags mPackageName mModuleName = do
                  else hPutStrLn stdout $ unlines (map ("    " ++) (map pp_pkg pkg_confs))
            where
                  pp_pkg p
-                   | installedComponentId p `elem` broken = printf "{%s}" doc
+                   | installedUnitId p `elem` broken = printf "{%s}" doc
                    | exposed p = doc
                    | otherwise = printf "(%s)" doc
-                   where doc | verbosity >= Verbose = printf "%s (%s)" pkg pk
+                   where doc | verbosity >= Verbose = printf "%s (%s)" pkg (display (installedUnitId p))
                              | otherwise            = pkg
                           where
-                          ComponentId pk = installedComponentId p
                           pkg = display (sourcePackageId p)
 
       show_simple = simplePackageList my_flags . allPackagesInStack
@@ -1274,15 +1268,14 @@ listPackages verbosity my_flags mPackageName mModuleName = do
                             : map (termText "    " <#>) (map pp_pkg pkg_confs))
           where
                    pp_pkg p
-                     | installedComponentId p `elem` broken = withF Red  doc
+                     | installedUnitId p `elem` broken = withF Red  doc
                      | exposed p                       = doc
                      | otherwise                       = withF Blue doc
                      where doc | verbosity >= Verbose
-                               = termText (printf "%s (%s)" pkg pk)
+                               = termText (printf "%s (%s)" pkg (display (installedUnitId p)))
                                | otherwise
                                = termText pkg
                             where
-                            ComponentId pk = installedComponentId p
                             pkg = display (sourcePackageId p)
 
     is_tty <- hIsTerminalDevice stdout
@@ -1318,7 +1311,7 @@ showPackageDot verbosity myflags = do
                  | p <- all_pkgs,
                    let from = display (sourcePackageId p),
                    key <- depends p,
-                   Just dep <- [PackageIndex.lookupComponentId ipix key],
+                   Just dep <- [PackageIndex.lookupUnitId ipix key],
                    let to = display (sourcePackageId dep)
                  ]
   putStrLn "}"
@@ -1390,7 +1383,7 @@ findPackagesByDB db_stack pkgarg
         ps -> return ps
   where
         pkg_msg (Id pkgid)           = display pkgid
-        pkg_msg (ICId ipid)          = display ipid
+        pkg_msg (IUId ipid)          = display ipid
         pkg_msg (Substring pkgpat _) = "matching " ++ pkgpat
 
 matches :: PackageIdentifier -> PackageIdentifier -> Bool
@@ -1404,7 +1397,7 @@ realVersion pkgid = versionBranch (pkgVersion pkgid) /= []
 
 matchesPkg :: PackageArg -> InstalledPackageInfo -> Bool
 (Id pid)        `matchesPkg` pkg = pid `matches` sourcePackageId pkg
-(ICId ipid)     `matchesPkg` pkg = ipid == installedComponentId pkg
+(IUId ipid)     `matchesPkg` pkg = ipid == installedUnitId pkg
 (Substring _ m) `matchesPkg` pkg = m (display (sourcePackageId pkg))
 
 -- -----------------------------------------------------------------------------
@@ -1492,7 +1485,7 @@ closure pkgs db_stack = go pkgs db_stack
                  -> Bool
    depsAvailable pkgs_ok pkg = null dangling
         where dangling = filter (`notElem` pids) (depends pkg)
-              pids = map installedComponentId pkgs_ok
+              pids = map installedUnitId pkgs_ok
 
         -- we want mutually recursive groups of package to show up
         -- as broken. (#1750)
@@ -1580,7 +1573,7 @@ checkPackageConfig :: InstalledPackageInfo
 checkPackageConfig pkg verbosity db_stack
                    multi_instance update = do
   checkPackageId pkg
-  checkComponentId pkg db_stack update
+  checkUnitId pkg db_stack update
   checkDuplicates db_stack pkg multi_instance update
   mapM_ (checkDep db_stack) (depends pkg)
   checkDuplicateDepends (depends pkg)
@@ -1610,17 +1603,17 @@ checkPackageId ipi =
     []  -> verror CannotForce ("invalid package identifier: " ++ str)
     _   -> verror CannotForce ("ambiguous package identifier: " ++ str)
 
-checkComponentId :: InstalledPackageInfo -> PackageDBStack -> Bool
+checkUnitId :: InstalledPackageInfo -> PackageDBStack -> Bool
                 -> Validate ()
-checkComponentId ipi db_stack update = do
-  let pk@(ComponentId str) = installedComponentId ipi
-  when (null str) $ verror CannotForce "missing id field"
+checkUnitId ipi db_stack update = do
+  let uid = installedUnitId ipi
+  when (null (display uid)) $ verror CannotForce "missing id field"
   let dups = [ p | p <- allPackagesInStack db_stack,
-                   installedComponentId p == pk ]
+                   installedUnitId p == uid ]
   when (not update && not (null dups)) $
     verror CannotForce $
         "package(s) with this id already exist: " ++
-         unwords (map (display.installedComponentId) dups)
+         unwords (map (display.installedUnitId) dups)
 
 checkDuplicates :: PackageDBStack -> InstalledPackageInfo
                 -> Bool -> Bool-> Validate ()
@@ -1679,16 +1672,16 @@ checkPath url_ok is_dir warn_only thisfield d
           then vwarn msg
           else verror ForceFiles msg
 
-checkDep :: PackageDBStack -> ComponentId -> Validate ()
+checkDep :: PackageDBStack -> UnitId -> Validate ()
 checkDep db_stack pkgid
   | pkgid `elem` pkgids = return ()
   | otherwise = verror ForceAll ("dependency \"" ++ display pkgid
                                  ++ "\" doesn't exist")
   where
         all_pkgs = allPackagesInStack db_stack
-        pkgids = map installedComponentId all_pkgs
+        pkgids = map installedUnitId all_pkgs
 
-checkDuplicateDepends :: [ComponentId] -> Validate ()
+checkDuplicateDepends :: [UnitId] -> Validate ()
 checkDuplicateDepends deps
   | null dups = return ()
   | otherwise = verror ForceAll ("package has duplicate dependencies: " ++
@@ -1725,7 +1718,7 @@ checkExposedModules :: PackageDBStack -> InstalledPackageInfo -> Validate ()
 checkExposedModules db_stack pkg =
   mapM_ checkExposedModule (exposedModules pkg)
   where
-    checkExposedModule (ExposedModule modl reexport _sig) = do
+    checkExposedModule (ExposedModule modl reexport) = do
       let checkOriginal = checkModuleFile pkg modl
           checkReexport = checkOriginalModule "module reexport" db_stack pkg
       maybe checkOriginal checkReexport reexport
@@ -1772,9 +1765,9 @@ checkOriginalModule :: String
                     -> Validate ()
 checkOriginalModule field_name db_stack pkg
     (OriginalModule definingPkgId definingModule) =
-  let mpkg = if definingPkgId == installedComponentId pkg
+  let mpkg = if definingPkgId == installedUnitId pkg
               then Just pkg
-              else PackageIndex.lookupComponentId ipix definingPkgId
+              else PackageIndex.lookupUnitId ipix definingPkgId
   in case mpkg of
       Nothing
            -> verror ForceAll (field_name ++ " refers to a non-existent " ++
@@ -1808,7 +1801,7 @@ checkOriginalModule field_name db_stack pkg
     ipix     = PackageIndex.fromList all_pkgs
 
     isIndirectDependency pkgid = fromMaybe False $ do
-      thispkg  <- graphVertex (installedComponentId pkg)
+      thispkg  <- graphVertex (installedUnitId pkg)
       otherpkg <- graphVertex pkgid
       return (Graph.path depgraph thispkg otherpkg)
     (depgraph, _, graphVertex) =
diff --git a/utils/mkUserGuidePart/Options/Packages.hs b/utils/mkUserGuidePart/Options/Packages.hs
index c6dfa0b86f92..36a7b4898ce2 100644
--- a/utils/mkUserGuidePart/Options/Packages.hs
+++ b/utils/mkUserGuidePart/Options/Packages.hs
@@ -4,8 +4,8 @@ import Types
 
 packagesOptions :: [Flag]
 packagesOptions =
-  [ flag { flagName = "-this-package-key⟨P⟩"
-         , flagDescription = "Compile to be part of package ⟨P⟩"
+  [ flag { flagName = "-this-unit-id⟨P⟩"
+         , flagDescription = "Compile to be part of unit (i.e. package) ⟨P⟩"
          , flagType = DynamicFlag
          }
   , flag { flagName = "-package⟨P⟩"
-- 
GitLab