diff --git a/README b/README
index 43c7fb88e5455c1c64d8dc710d6f7db478d9e3ce..daad5757657c88044976de9cd28323118630f59b 100644
--- a/README
+++ b/README
@@ -1,188 +1,8 @@
-This page documents some cleanups that I (Sylvain Henry) would like to perform on GHC's code base.
+ghc-api-compat
+==============
 
-== Why?
+We are in the process of [renaming GHC
+modules](https://gitlab.haskell.org/ghc/ghc/issues/13009).
 
-* Make the code more beginner friendly
-  * Avoid acronyms
-  * Hierarchical modules help in understanding the compiler structure
-  * Try to correctly name things:
-    * e.g. the "type checker" doesn't only check types, hence maybe we should call it "type system" or split it (e.g. Deriver, TypeChecker, etc.)
-    * Avoid meaningless codename (e.g. backpack, hoopl)
-* Make the compiler more modular
-  * Allow easier reuse (with the GHC API)
-  * Make the compiler easier to debug
-  * Make adding new passes/optimisations easier
-  * Allow easier and faster testing (testing per component instead of testing the whole pipeline)
-  * Allow new more interactive frontends (step-run each compiler pass and show IR, stats, etc.)
-  * Allow profile guided optimizations (passes count and order, etc.)
-
-== Step 1: introduce basic module hierarchy
-
-Implement the [wiki:ModuleDependencies/Hierarchical proposal for hierarchical module structure in GHC] (#13009).
-
-It consists only in renaming/moving modules.
-
-Compared to the original proposal, I have:
-* Put IRs into GHC.IR and compilers into GHC.Compiler
-* changed GHC.Types into GHC.Data and GHC.Entity as the former is misleading (from a GHC API user point of view)
-* split GHC.Typecheck into GHC.IR.Haskell.{TypeChecker,Deriver}
-* split GHC.Utils into GHC.Utils and GHC.Data (e.g., Bag is in Data, not Utils)
-* etc.
-
-Tree logic:
-* IR: intermediate representations. Each one contains its syntax and stuff manipulating it
-    * Haskell
-        * Syntax
-        * Parser, Lexer, Printer
-        * Analyser
-        * TypeChecker, Renamer, Deriver
-    * Core
-        * Syntax
-        * Analyser
-        * Transformer.{Simplifier,Specialiser,Vectoriser,WorkerWrapper,FloatIn,FloatOut,CommonSubExpr, etc.}
-    * Cmm
-        * Syntax
-        * Analyser
-        * Parser, Lexer, Printer
-        * Transformer.{CommonBlockElim,ConstantFolder,Dataflow,ShortCutter,Sinker}
-    * Stg
-        * Syntax
-        * Analyser
-        * Transformer.{CommonSubExpr,CostCentreCollecter,Unariser}
-    * ByteCode.{Assembler,Linker...}
-    * Interface.{Loader,Renamer,TypeChecker, Transformer.Tidier}
-    * Llvm.{Syntax, Printer}
-* Compiler: converters between representations
-    * HaskellToCore
-    * CoreToStg
-    * StgToCmm
-    * CmmToAsm
-    * CmmToLlvm
-    * CoreToByteCode
-    * CoreToInterface
-    * CmmToC
-    * TemplateToHaskell
-* Entity: entities shared by different phases of the compiler (Class, Id, Name, Unique, etc.)
-* Builtin: builtin stuff
-    * Primitive.{Types,Operations}: primitives
-    * Names, Types, Uniques: other wired-in stuff
-* Program: GHC-the-program (command-line parser, etc.) and its modes
-    * Driver.{Phases,Pipeline}
-    * Backpack
-    * Make, MakeDepend
-* Interactive: interactive stuff (debugger, closure inspection, interpreter, etc.)
-* Data: data structures (Bag, Tree, etc.)
-* Config: GHC configuration
-    * HostPlatform: host platform info
-    * Flags: dynamic configuration (DynFlags)
-    * Build: generated at build time
-* Packages: package management stuff
-* RTS: interaction with the runtime system (closure and table representation)
-* Utils: utility code or code that doesn't easily belong to another directory (e.g., Outputable, SysTools, Elf, Finder, etc.)
-* Plugin: modules to import to write compiler plugins
-
-Actual renaming: see CodeBaseCleanup/ModuleRenaming
-
-Issues:
-* name clashes: some modules in `base` (e.g. GHC.Desugar) and `ghc-prim` (e.g. GHC.Types) use the same GHC prefix
-  * maybe we should put all GHC extensions to base under GHC.Exts.* or GHC.Base.*
-  * use GHC.Builtin.Primitive.* prefix in ghc-prim?
-
-TODO in the future:
-* Fix comments:
-  * Several references to Note "Remote Template Haskell" (supposedly in libraries/ghci/GHCi/TH.hs) but it doesn't exist. Maybe replaced by Note "Remote GHCi"? 
-  * Undefined reference to "fill_in in PrelPack.hs" from GHC.Entity.Id
-  * Undefined reference to CgConTbls.hs from GHC.Compiler.StgToCmm.Binding
-  * Undefined reference to PprMach.hs from GHC.Compiler.CmmToAsm.PIC
-  * Undefined reference to Renaming.hs from GHC.IR.Core.Transformer.Substitution
-  * Undefined reference to simplStg/SRT.hs from GHC.IR.Cmm.Transformer.InfoTableBuilder
-  * Undefined reference to codeGen/CodeGen.hs from GHC.Compiler.HaskellToCore.Foreign.Declaration
-  * Undefined reference to RegArchBase.hs from GHC.Compiler.CmmToAsm.Register.Allocator.Graph.ArchX86
-  * Undefined reference to MachRegs*.hs and MachRegs.hs from GHC.Compiler.CmmToAsm.Register.Allocator.Graph.ArchBase
-* Binutils 2.17 is from 2011. Maybe we could remove the Hack in GHC.Compiler.CmmToAsm.X86.CodeGen
-* Rename CAF into "static thunk"?
-* put notes files (e.g. profiling-notes, *.tex files) into actual notes or in the wiki
-* Fix traces of RnHsSyn that doesn't exist anymore
-* References to "NCG" should be replaced with reference to "CmmToAsm compiler"
-* Foreign export stubs are generated in GHC.Compiler.HaskellToCore.Foreign.Declaration...
-* Tests still reflect the old hierarchy (e.g., simplCore/should_compile) but renaming them could break other tools
-
-
-
-Questions:
-* Why don't we use the mangled selector name ($sel:foo:MkT) in every cases (not only when we have -XDuplicateRecordFields) instead of using the ambiguous one (foo)?
-  * Incidentally, partially answered yesterday (2017-06-12) on ticket #13352
-  
-
-== Step 2: split and edit some modules
-
-Some modules contain a lot of (unrelated) stuff. We should split them.
-
-* GHC.Utils (previously compiler/utils/Util.hs) contains a lot of stuff that should be split
-  * Compiler configuration (ghciSupported, etc.): GHC.Config
-  * List operations: GHC.Data.List{.Sort,.Fold}
-  * Transitive closure: GHC.Data.Graph?
-  * Edit distance and fuzzy match: GHC.Utils.FuzzyMatch?
-  * Shared globals between GHC package instances: GHC.Utils.SharedGlobals?
-  * Command-line parser: GHC.Utils.CmdLine
-  * exactLog2 (Integer): GHC.Data.Integer (why isn't it in base?)
-  * Read helpers (rational, maybe, etc.): GHC.Utils.Read?
-  * doesDirNameExist, getModificationUTCTime: GHC.Utils.FilePath
-  * hSetTranslit: GHC.Utils.Handle.Encoding
-  * etc.
-* Split GHC.Types (was HscTypes) as it contains a lot of unrelated things
-  * ModGuts/ModDetails/ModIface: move to GHC.Data.Module.*
-  * Usage/Dependencies: move to GHC.Data.Module.Usage/Dependencies
-* GHC.Data.*: split
-  * Split OccEnv from OccName (to harmonize with GHC.Data.Name.Env)?
-  * Split ModuleEnv/ModuleSet from Module?
-* Split GHC.Data.Types (was TyCoRep)?
-  * Contains many data types (TyThing, Coercion, Type, Kind, etc.)
-* Split PrettyPrint from GHC.Syntax.{Type,Expr,etc.}
-* Split GHC.IR.Core.Transform.{Simplify,SimplUtils,etc.}
-* Split GHC.Rename.ImportExport (e.g., contains "warnMissingSignature")
-* Put cmmToCmm optimisations from GHC.Compilers.CmmToAsm into GHC.IR.Cmm.Transform
-* Split type-checker solvers (class lookup, givens, wanted, etc.) (was TcSimplify, TcInteract, etc.)
-* Module name GHC.Compilers.StgToCmm.Layout seems dubious: split and rename?
-
-Some function/type names should be modified:
-
-* Rename codeGen function into stgToCmm
-* Rename nativeCodeGen into cmmToAsm
-* Rename ORdList (in GHC.Data.Tree.OrdList) into TreeSomething? (misleading)
-* CorePrep (prepare Core for codegen) could use a more explicit name
-* Maybe rename GHC.Data.RepType
-* Maybe rename OccName/RdrName/Name/Id to make them more explicit (may become obsolete with "trees that grow" patch)
-  * OccName: NSName (NameSpacedName)
-  * RdrName: ParsedName
-  * Name: UniqueName
-  * Id: TypedName
-
-
-
-
-== Step 3: clearly separate GHC-the-program and GHC's API
-
-* Make the GHC API purer
-
-=== Abstract file loading (i.e. pluggable Finder)
-
-Currently the Finder assumes that a filesystem exists into which it can find some packages/modules.
-
-I would like to add support for module sources that are only available in memory or that can be retrieved from elsewhere (network, etc.).
-
-Something similar to Java's class loaders.
-
-=== Abstract error reporting and logging (i.e. pluggable Logger)
-
-Allow new frontends (using GHC API) to use HTML reporting, etc.
-
-* Avoid dumping to the filesystem and/or stdout/stderr
-* Use data types instead of raw SDoc reports
-
-
-=== Step 4: clearly separate phases
-
-* split DynFlags to only pass the required info to each pass
-    * e.g. only the required hooks
-* use data types to report phase statistics, intermediate representations, etc.
+This package aims to make the transition easier by mapping old module names to
+newer module names.
diff --git a/ghc-api-compat.cabal b/ghc-api-compat.cabal
index 656a2877ec78d03158c5a1757e54537305ba5454..84d72c11c9243964be67718eaf7e3a4f5a15f0cb 100644
--- a/ghc-api-compat.cabal
+++ b/ghc-api-compat.cabal
@@ -1,12 +1,12 @@
 name:                ghc-api-compat
-version:             8.2
+version:             8.6
 synopsis:            Provide GHC-API compatibility with older GHC versions
--- description:         
+-- description:
 license:             BSD3
 license-file:        LICENSE
 author:              Sylvain Henry
 maintainer:          sylvain@haskus.fr
--- copyright:           
+-- copyright:
 category:            Development
 build-type:          Simple
 extra-source-files:  ChangeLog.md
@@ -14,472 +14,167 @@ cabal-version:       >=1.22
 
 library
    build-depends:
-      ghc >= 8.3
+      ghc >= 8.10
    hs-source-dirs:      src
    default-language:    Haskell2010
 
    reexported-modules:
-        GHC
-      , GHC.Builtin.Names                                               as  PrelNames
-      , GHC.Builtin.Names.TemplateHaskell                               as  THNames
-      , GHC.Builtin.Primitive.Operations                                as  PrimOp
-      , GHC.Builtin.Primitive.Types                                     as  TysPrim
-      , GHC.Builtin.TypeNats                                            as  TcTypeNats
-      , GHC.Builtin.Types                                               as  TysWiredIn
-      , GHC.Builtin.Uniques                                             as  KnownUniques
-      , GHC.Builtin.Util                                                as  PrelInfo
-      , GHC.ByteCode.Assembler                                          as  ByteCodeAsm
-      , GHC.ByteCode.InfoTable                                          as  ByteCodeItbls
-      , GHC.ByteCode.Instruction                                        as  ByteCodeInstr
-      , GHC.ByteCode.Linker                                             as  ByteCodeLink
-      , GHC.ByteCode.Types                                              as  ByteCodeTypes
-      , GHC.Cmm.CommonBlockElim                                         as  CmmCommonBLockElim
-      , GHC.Cmm.ConstantFolder                                          as  CmmOpt
-      , GHC.Cmm.Dataflow                                                as  Hoopl
-      , GHC.Cmm.Dataflow.Block                                          as  Hoopl.Block
-      , GHC.Cmm.Dataflow.Collections                                    as  Hoopl.Collections
-      , GHC.Cmm.Dataflow.Graph                                          as  Hoopl.Graph
-      , GHC.Cmm.Dataflow.Label                                          as  Hoopl.Label
-      , GHC.Cmm.Dataflow.Unique                                         as  Hoopl.Unique
-      , GHC.Cmm.InfoTableBuilder                                        as  CmmBuildInfoTables
-      , GHC.Cmm.LayoutStack                                             as  CmmLayoutStack
-      , GHC.Cmm.Lexer                                                   as  CmmLex
-      , GHC.Cmm.Lint                                                    as  CmmLint
-      , GHC.Cmm.Liveness                                                as  CmmLive
-      , GHC.Cmm.Parser                                                  as  CmmParse
-      , GHC.Cmm.Parser.Monad                                            as  CmmMonad
-      , GHC.Cmm.Pipeline                                                as  CmmPipeline
-      , GHC.Cmm.Printer                                                 as  PprCmm
-      , GHC.Cmm.Printer.Declaration                                     as  PprCmmDecl
-      , GHC.Cmm.Printer.Expression                                      as  PprCmmExpr
-      , GHC.Cmm.ProcPoint                                               as  CmmProcPoint
-      , GHC.Cmm.Shortcutter                                             as  CmmContFlowOpt
-      , GHC.Cmm.Sinker                                                  as  CmmSink
-      , GHC.Cmm.Switch                                                  as  CmmSwitch
-      , GHC.Cmm.Switch.Implement                                        as  CmmImplementSwitchPlans
-      , GHC.Cmm.Syntax                                                  as  Cmm
-      , GHC.Cmm.Syntax.BlockId                                          as  BlockId
-      , GHC.Cmm.Syntax.CallConvention                                   as  CmmCallConv
-      , GHC.Cmm.Syntax.DebugBlock                                       as  Debug
-      , GHC.Cmm.Syntax.Expression                                       as  CmmExpr
-      , GHC.Cmm.Syntax.Graph                                            as  MkGraph
-      , GHC.Cmm.Syntax.MachinePrimOps                                   as  CmmMachOp
-      , GHC.Cmm.Syntax.Node                                             as  CmmNode
-      , GHC.Cmm.Syntax.Type                                             as  CmmType
-      , GHC.CmmToAsm                                                    as  AsmCodeGen
-      , GHC.CmmToAsm.Dwarf                                              as  Dwarf
-      , GHC.CmmToAsm.Dwarf.Constants                                    as  Dwarf.Constants
-      , GHC.CmmToAsm.Dwarf.Types                                        as  Dwarf.Types
-      , GHC.CmmToAsm.Format                                             as  Format
-      , GHC.CmmToAsm.Instruction                                        as  Instruction
-      , GHC.CmmToAsm.Monad                                              as  NCGMonad
-      , GHC.CmmToAsm.PIC                                                as  PIC
-      , GHC.CmmToAsm.PPC.CodeGen                                        as  PPC.CodeGen
-      , GHC.CmmToAsm.PPC.Cond                                           as  PPC.Cond
-      , GHC.CmmToAsm.PPC.Instr                                          as  PPC.Instr
-      , GHC.CmmToAsm.PPC.Ppr                                            as  PPC.Ppr
-      , GHC.CmmToAsm.PPC.RegInfo                                        as  PPC.RegInfo
-      , GHC.CmmToAsm.PPC.Regs                                           as  PPC.Regs
-      , GHC.CmmToAsm.PrettyPrint                                        as  PprBase
-      , GHC.CmmToAsm.RegAlloc.Graph.ArchBase                            as  RegAlloc.Graph.ArchBase
-      , GHC.CmmToAsm.RegAlloc.Graph.ArchX86                             as  RegAlloc.Graph.ArchX86
-      , GHC.CmmToAsm.RegAlloc.Graph.Coalesce                            as  RegAlloc.Graph.Coalesce
-      , GHC.CmmToAsm.RegAlloc.Graph.Main                                as  RegAlloc.Graph.Main
-      , GHC.CmmToAsm.RegAlloc.Graph.Spill                               as  RegAlloc.Graph.Spill
-      , GHC.CmmToAsm.RegAlloc.Graph.SpillClean                          as  RegAlloc.Graph.SpillClean
-      , GHC.CmmToAsm.RegAlloc.Graph.SpillCost                           as  RegAlloc.Graph.SpillCost
-      , GHC.CmmToAsm.RegAlloc.Graph.Stats                               as  RegAlloc.Graph.Stats
-      , GHC.CmmToAsm.RegAlloc.Graph.TrivColorable                       as  RegAlloc.Graph.TrivColorable
-      , GHC.CmmToAsm.RegAlloc.Linear.Base                               as  RegAlloc.Linear.Base
-      , GHC.CmmToAsm.RegAlloc.Linear.FreeRegs                           as  RegAlloc.Linear.FreeRegs
-      , GHC.CmmToAsm.RegAlloc.Linear.JoinToTargets                      as  RegAlloc.Linear.JoinToTargets
-      , GHC.CmmToAsm.RegAlloc.Linear.Main                               as  RegAlloc.Linear.Main
-      , GHC.CmmToAsm.RegAlloc.Linear.PPC.FreeRegs                       as  RegAlloc.Linear.PPC.FreeRegs
-      , GHC.CmmToAsm.RegAlloc.Linear.SPARC.FreeRegs                     as  RegAlloc.Linear.SPARC.FreeRegs
-      , GHC.CmmToAsm.RegAlloc.Linear.StackMap                           as  RegAlloc.Linear.StackMap
-      , GHC.CmmToAsm.RegAlloc.Linear.State                              as  RegAlloc.Linear.State
-      , GHC.CmmToAsm.RegAlloc.Linear.Stats                              as  RegAlloc.Linear.Stats
-      , GHC.CmmToAsm.RegAlloc.Linear.X86_64.FreeRegs                    as  RegAlloc.Linear.X86_64.FreeRegs
-      , GHC.CmmToAsm.RegAlloc.Linear.X86.FreeRegs                       as  RegAlloc.Linear.X86.FreeRegs
-      , GHC.CmmToAsm.RegAlloc.Liveness                                  as  RegAlloc.Liveness
-      , GHC.CmmToAsm.Register                                           as  Reg
-      , GHC.CmmToAsm.Register.Class                                     as  RegClass
-      , GHC.CmmToAsm.Register.Target                                    as  TargetReg
-      , GHC.CmmToAsm.SPARC.AddrMode                                     as  SPARC.AddrMode
-      , GHC.CmmToAsm.SPARC.Base                                         as  SPARC.Base
-      , GHC.CmmToAsm.SPARC.CodeGen.Amode                                as  SPARC.CodeGen.Amode
-      , GHC.CmmToAsm.SPARC.CodeGen                                      as  SPARC.CodeGen
-      , GHC.CmmToAsm.SPARC.CodeGen.Base                                 as  SPARC.CodeGen.Base
-      , GHC.CmmToAsm.SPARC.CodeGen.CondCode                             as  SPARC.CodeGen.CondCode
-      , GHC.CmmToAsm.SPARC.CodeGen.Expand                               as  SPARC.CodeGen.Expand
-      , GHC.CmmToAsm.SPARC.CodeGen.Gen32                                as  SPARC.CodeGen.Gen32
-      , GHC.CmmToAsm.SPARC.CodeGen.Gen64                                as  SPARC.CodeGen.Gen64
-      , GHC.CmmToAsm.SPARC.CodeGen.Sanity                               as  SPARC.CodeGen.Sanity
-      , GHC.CmmToAsm.SPARC.Cond                                         as  SPARC.Cond
-      , GHC.CmmToAsm.SPARC.Imm                                          as  SPARC.Imm
-      , GHC.CmmToAsm.SPARC.Instr                                        as  SPARC.Instr
-      , GHC.CmmToAsm.SPARC.Ppr                                          as  SPARC.Ppr
-      , GHC.CmmToAsm.SPARC.Regs                                         as  SPARC.Regs
-      , GHC.CmmToAsm.SPARC.ShortcutJump                                 as  SPARC.ShortcutJump
-      , GHC.CmmToAsm.SPARC.Stack                                        as  SPARC.Stack
-      , GHC.CmmToAsm.X86.CodeGen                                        as  X86.CodeGen
-      , GHC.CmmToAsm.X86.Cond                                           as  X86.Cond
-      , GHC.CmmToAsm.X86.Instr                                          as  X86.Instr
-      , GHC.CmmToAsm.X86.Ppr                                            as  X86.Ppr
-      , GHC.CmmToAsm.X86.RegInfo                                        as  X86.RegInfo
-      , GHC.CmmToAsm.X86.Regs                                           as  X86.Regs
-      , GHC.CmmToC                                                      as  PprC
-      , GHC.CmmToLlvm                                                   as  Llvm
-      , GHC.CmmToLlvm.CodeGen                                           as  LlvmCodeGen
-      , GHC.CmmToLlvm.CodeGen.Base                                      as  LlvmCodeGen.Base
-      , GHC.CmmToLlvm.CodeGen.Data                                      as  LlvmCodeGen.Data
-      , GHC.CmmToLlvm.CodeGen.PrettyPrint                               as  LlvmCodeGen.Ppr
-      , GHC.CmmToLlvm.CodeGen.Proc                                      as  LlvmCodeGen.CodeGen
-      , GHC.CmmToLlvm.CodeGen.Regs                                      as  LlvmCodeGen.Regs
-      , GHC.CmmToLlvm.Fixup                                             as  LlvmMangler
-      , GHC.Cmm.Util                                                    as  CmmUtils
-      , GHC.Config.Constants                                            as  Constants
-      , GHC.Config.Flags                                                as  DynFlags
-      , GHC.Config.Flags.Fingerprint                                    as  FlagChecker
-      , GHC.Config.Hooks                                                as  Hooks
-      , GHC.Config.HostPlatform                                         as  PlatformConstants
-      , GHC.Core.Arity                                                  as  CoreArity
-      , GHC.Core.CallArity                                              as  CallArity
-      , GHC.Core.CommonSubExpr                                          as  CSE
-      , GHC.Core.ConstantFold                                           as  PrelRules
-      , GHC.Core.Demand                                                 as  DmdAnal
-      , GHC.Core.FloatIn                                                as  FloatIn
-      , GHC.Core.FloatOut                                               as  FloatOut
-      , GHC.Core.FreeVars                                               as  CoreFVs
-      , GHC.Core.Inliner                                                as  CoreUnfold
-      , GHC.Core.LevelSet                                               as  SetLevels
-      , GHC.Core.LiberateCase                                           as  LiberateCase
-      , GHC.Core.Lint                                                   as  CoreLint
-      , GHC.Core.Monad                                                  as  CoreMonad
-      , GHC.Core.Occurence                                              as  OccurAnal
-      , GHC.Core.Pipeline                                               as  SimplCore
-      , GHC.Core.Prepare                                                as  CorePrep
-      , GHC.Core.Printer                                                as  PprCore
-      , GHC.Core.Rules                                                  as  Rules
-      , GHC.Core.SimpleOpt                                              as  CoreOpt
-      , GHC.Core.Simplify                                               as  Simplify
-      , GHC.Core.Simplify.Environment                                   as  SimplEnv
-      , GHC.Core.Simplify.Monad                                         as  SimplMonad
-      , GHC.Core.Simplify.Util                                          as  SimplUtils
-      , GHC.Core.Specialise                                             as  Specialise
-      , GHC.Core.Specialise.Constructor                                 as  SpecConstr
-      , GHC.Core.StaticArgument                                         as  SAT
-      , GHC.Core.Stats                                                  as  CoreStats
-      , GHC.Core.Subst                                                  as  CoreSubst
-      , GHC.Core.Syntax                                                 as  CoreSyn
-      , GHC.Core.Syntax.Force                                           as  CoreSeq
-      , GHC.Core.Syntax.Make                                            as  MkCore
-      , GHC.Core.Tidy                                                   as  CoreTidy
-      , GHC.CoreToByteCode                                              as  ByteCodeGen
-      , GHC.CoreToInterface                                             as  ToIface
-      , GHC.CoreToStg                                                   as  CoreToStg
-      , GHC.CoreTypes.Annotation                                        as  Annotations
-      , GHC.CoreTypes.Available                                         as  Avail
-      , GHC.CoreTypes.Base                                              as  HscTypes
-      , GHC.CoreTypes.BasicTypes                                        as  BasicTypes
-      , GHC.CoreTypes.CLabel                                            as  CLabel
-      , GHC.CoreTypes.Class                                             as  Class
-      , GHC.CoreTypes.Coercion                                          as  Coercion
-      , GHC.CoreTypes.Coercion.Axiom                                    as  CoAxiom
-      , GHC.CoreTypes.Coercion.Optimise                                 as  OptCoercion
-      , GHC.CoreTypes.ConLike                                           as  ConLike
-      , GHC.CoreTypes.CostCentre                                        as  CostCentre
-      , GHC.CoreTypes.CostCentre.Init                                   as  ProfInit
-      , GHC.CoreTypes.DataCon                                           as  DataCon
-      , GHC.CoreTypes.Demand                                            as  Demand
-      , GHC.CoreTypes.FamilyInstance                                    as  FamInstEnv
-      , GHC.CoreTypes.FieldLabel                                        as  FieldLabel
-      , GHC.CoreTypes.ForeignCall                                       as  ForeignCall
-      , GHC.CoreTypes.Id                                                as  Id
-      , GHC.CoreTypes.Id.Info                                           as  IdInfo
-      , GHC.CoreTypes.Id.Make                                           as  MkId
-      , GHC.CoreTypes.Instance                                          as  InstEnv
-      , GHC.CoreTypes.Kind                                              as  Kind
-      , GHC.CoreTypes.Literal                                           as  Literal
-      , GHC.CoreTypes.Module                                            as  Module
-      , GHC.CoreTypes.Name                                              as  Name
-      , GHC.CoreTypes.Name.Cache                                        as  NameCache
-      , GHC.CoreTypes.Name.Environment                                  as  NameEnv
-      , GHC.CoreTypes.Name.Set                                          as  NameSet
-      , GHC.CoreTypes.NameShape                                         as  NameShape
-      , GHC.CoreTypes.OccName                                           as  OccName
-      , GHC.CoreTypes.PatternSynonym                                    as  PatSyn
-      , GHC.CoreTypes.RdrName                                           as  RdrName
-      , GHC.CoreTypes.RepType                                           as  RepType
-      , GHC.CoreTypes.SrcLoc                                            as  SrcLoc
-      , GHC.CoreTypes.TyCon                                             as  TyCon
-      , GHC.CoreTypes.Type                                              as  Type
-      , GHC.CoreTypes.Type.Internal                                     as  TyCoRep
-      , GHC.CoreTypes.Type.Unify                                        as  Unify
-      , GHC.CoreTypes.Var                                               as  Var
-      , GHC.CoreTypes.Var.Environment                                   as  VarEnv
-      , GHC.CoreTypes.Var.Free                                          as  FV
-      , GHC.CoreTypes.Var.Set                                           as  VarSet
-      , GHC.CoreTypes.Var.UndirectedGraph                               as  UnVarGraph
-      , GHC.Core.Util                                                   as  CoreUtils
-      , GHC.Core.Vectorise                                              as  Vectorise
-      , GHC.Core.Vectorise.Builtins                                     as  Vectorise.Builtins
-      , GHC.Core.Vectorise.Builtins.Base                                as  Vectorise.Builtins.Base
-      , GHC.Core.Vectorise.Builtins.Initialise                          as  Vectorise.Builtins.Initialise
-      , GHC.Core.Vectorise.Convert                                      as  Vectorise.Convert
-      , GHC.Core.Vectorise.Env                                          as  Vectorise.Env
-      , GHC.Core.Vectorise.Exp                                          as  Vectorise.Exp
-      , GHC.Core.Vectorise.Generic.Description                          as  Vectorise.Generic.Description
-      , GHC.Core.Vectorise.Generic.PADict                               as  Vectorise.Generic.PADict
-      , GHC.Core.Vectorise.Generic.PAMethods                            as  Vectorise.Generic.PAMethods
-      , GHC.Core.Vectorise.Generic.PData                                as  Vectorise.Generic.PData
-      , GHC.Core.Vectorise.Monad                                        as  Vectorise.Monad
-      , GHC.Core.Vectorise.Monad.Base                                   as  Vectorise.Monad.Base
-      , GHC.Core.Vectorise.Monad.Global                                 as  Vectorise.Monad.Global
-      , GHC.Core.Vectorise.Monad.InstEnv                                as  Vectorise.Monad.InstEnv
-      , GHC.Core.Vectorise.Monad.Local                                  as  Vectorise.Monad.Local
-      , GHC.Core.Vectorise.Monad.Naming                                 as  Vectorise.Monad.Naming
-      , GHC.Core.Vectorise.Type.Classify                                as  Vectorise.Type.Classify
-      , GHC.Core.Vectorise.Type.Env                                     as  Vectorise.Type.Env
-      , GHC.Core.Vectorise.Type.TyConDecl                               as  Vectorise.Type.TyConDecl
-      , GHC.Core.Vectorise.Type.Type                                    as  Vectorise.Type.Type
-      , GHC.Core.Vectorise.Util                                         as  Vectorise.Utils
-      , GHC.Core.Vectorise.Util.Base                                    as  Vectorise.Utils.Base
-      , GHC.Core.Vectorise.Util.Closure                                 as  Vectorise.Utils.Closure
-      , GHC.Core.Vectorise.Util.Hoisting                                as  Vectorise.Utils.Hoisting
-      , GHC.Core.Vectorise.Util.PADict                                  as  Vectorise.Utils.PADict
-      , GHC.Core.Vectorise.Util.Poly                                    as  Vectorise.Utils.Poly
-      , GHC.Core.Vectorise.Var                                          as  Vectorise.Var
-      , GHC.Core.WorkerWrap                                             as  WorkWrap
-      , GHC.Core.WorkerWrap.Util                                        as  WwLib
-      , GHC.Data.Bag                                                    as  Bag
-      , GHC.Data.Bitmap                                                 as  Bitmap
-      , GHC.Data.BoolFormula                                            as  BooleanFormula
-      , GHC.Data.Char.Classification                                    as  Ctype
-      , GHC.Data.Char.Encoding                                          as  Encoding
-      , GHC.Data.EnumSet                                                as  EnumSet
-      , GHC.Data.FastMutableInt                                         as  FastMutInt
-      , GHC.Data.FastString                                             as  FastString
-      , GHC.Data.FastString.Environment                                 as  FastStringEnv
-      , GHC.Data.FiniteMap                                              as  FiniteMap
-      , GHC.Data.Graph.Base                                             as  GraphBase
-      , GHC.Data.Graph.Color                                            as  GraphColor
-      , GHC.Data.Graph.Directed                                         as  Digraph
-      , GHC.Data.Graph.Operations                                       as  GraphOps
-      , GHC.Data.Graph.PrettyPrint                                      as  GraphPpr
-      , GHC.Data.List.SetOps                                            as  ListSetOps
-      , GHC.Data.Maybe                                                  as  Maybes
-      , GHC.Data.OrdList                                                as  OrdList
-      , GHC.Data.Pair                                                   as  Pair
-      , GHC.Data.Stream                                                 as  Stream
-      , GHC.Data.StringBuffer                                           as  StringBuffer
-      , GHC.Data.TrieMap                                                as  TrieMap
-      , GHC.Data.UniqueDFM                                              as  UniqDFM
-      , GHC.Data.UniqueDSet                                             as  UniqDSet
-      , GHC.Data.UniqueFM                                               as  UniqFM
-      , GHC.Data.UniqueMap                                              as  UniqMap
-      , GHC.Data.UniqueSet                                              as  UniqSet
-      , GHC.Data.UniqueSupply                                           as  UniqSupply
-      , GHC.Driver.Backpack.Main                                        as  DriverBkp
-      , GHC.Driver.Backpack.Syntax                                      as  BkpSyn
-      , GHC.Driver.CmdLineParser                                        as  CmdLineParser
-      , GHC.Driver.CodeOutput                                           as  CodeOutput
-      , GHC.Driver.Finder                                               as  Finder
-      , GHC.Driver.Main                                                 as  HscMain
-      , GHC.Driver.Make                                                 as  GhcMake
-      , GHC.Driver.MakeDepend                                           as  DriverMkDepend
-      , GHC.Driver.Phases                                               as  DriverPhases
-      , GHC.Driver.Pipeline                                             as  DriverPipeline
-      , GHC.Driver.Pipeline.Monad                                       as  PipelineMonad
-      , GHC.Haskell.Derive.BasicClasses                                 as  TcGenDeriv
-      , GHC.Haskell.Derive.Constraints                                  as  TcDerivInfer
-      , GHC.Haskell.Derive.Functor                                      as  TcGenFunctor
-      , GHC.Haskell.Derive.Generic                                      as  TcGenGenerics
-      , GHC.Haskell.Derive.Typeable                                     as  TcTypeable
-      , GHC.Haskell.Derive.Util                                         as  TcDerivUtils
-      , GHC.Haskell.Lexer                                               as  Lexer
-      , GHC.Haskell.Parser                                              as  Parser
-      , GHC.Haskell.Parser.HeaderInfo                                   as  HeaderInfo
-      , GHC.Haskell.Parser.Syntax                                       as  RdrHsSyn
-      , GHC.Haskell.Parser.Util                                         as  HaddockUtils
-      , GHC.Haskell.Printer.Dump                                        as  HsDumpAst
-      , GHC.Haskell.Rename                                              as  RnSource
-      , GHC.Haskell.Rename.Bind                                         as  RnBinds
-      , GHC.Haskell.Rename.Documentation                                as  RnHsDoc
-      , GHC.Haskell.Rename.Environment                                  as  RnEnv
-      , GHC.Haskell.Rename.Expression                                   as  RnExpr
-      , GHC.Haskell.Rename.Fixity                                       as  RnFixity
-      , GHC.Haskell.Rename.ImportExport                                 as  RnNames
-      , GHC.Haskell.Rename.Pattern                                      as  RnPat
-      , GHC.Haskell.Rename.Splice                                       as  RnSplice
-      , GHC.Haskell.Rename.Type                                         as  RnTypes
-      , GHC.Haskell.Rename.Util                                         as  RnUtils
-      , GHC.Haskell.Rename.Util.Unbound                                 as  RnUnbound
-      , GHC.Haskell.Stats                                               as  HscStats
-      , GHC.Syntax.Annotation                                           as  ApiAnnotation
-      , GHC.Syntax                                                      as  HsSyn
-      , GHC.Syntax.Bind                                                 as  HsBinds
-      , GHC.Syntax.Declaration                                          as  HsDecls
-      , GHC.Syntax.Documentation                                        as  HsDoc
-      , GHC.Syntax.Expression                                           as  HsExpr
-      , GHC.Syntax.Extension                                            as  HsExtension
-      , GHC.Syntax.ImportExport                                         as  HsImpExp
-      , GHC.Syntax.Literal                                              as  HsLit
-      , GHC.Syntax.Pattern                                              as  HsPat
-      , GHC.Syntax.PlaceHolder                                          as  PlaceHolder
-      , GHC.Syntax.Type                                                 as  HsTypes
-      , GHC.Haskell.Template                                            as  Convert
-      , GHC.HaskellToCore.Arrow                                         as  DsArrows
-      , GHC.HaskellToCore                                               as  Desugar
-      , GHC.HaskellToCore.Bind                                          as  DsBinds
-      , GHC.HaskellToCore.Coverage                                      as  Coverage
-      , GHC.HaskellToCore.Expression                                    as  DsExpr
-      , GHC.HaskellToCore.Foreign.Call                                  as  DsCCall
-      , GHC.HaskellToCore.Foreign.Declaration                           as  DsForeign
-      , GHC.HaskellToCore.GuardedRHS                                    as  DsGRHSs
-      , GHC.HaskellToCore.ListComp                                      as  DsListComp
-      , GHC.HaskellToCore.Match                                         as  Match
-      , GHC.HaskellToCore.Match.Check                                   as  Check
-      , GHC.HaskellToCore.Match.Constructor                             as  MatchCon
-      , GHC.HaskellToCore.Match.Expression                              as  PmExpr
-      , GHC.HaskellToCore.Match.Literal                                 as  MatchLit
-      , GHC.HaskellToCore.Match.TermEqOracle                            as  TmOracle
-      , GHC.HaskellToCore.Monad                                         as  DsMonad
-      , GHC.HaskellToCore.Splice                                        as  DsMeta
-      , GHC.HaskellToCore.Usage                                         as  DsUsage
-      , GHC.HaskellToCore.Util                                          as  DsUtils
-      , GHC.TypeCheck.Annotation                                        as  TcAnnotations
-      , GHC.TypeCheck.Arrow                                             as  TcArrows
-      , GHC.TypeCheck.Bind                                              as  TcBinds
-      , GHC.TypeCheck.Class                                             as  TcClassDcl
-      , GHC.TypeCheck.Default                                           as  TcDefaults
-      , GHC.TypeCheck.Deriving                                          as  TcDeriv
-      , GHC.TypeCheck.Environment                                       as  TcEnv
-      , GHC.TypeCheck.Error                                             as  TcErrors
-      , GHC.TypeCheck.Evidence                                          as  TcEvidence
-      , GHC.TypeCheck.Export                                            as  TcRnExports
-      , GHC.TypeCheck.Expression                                        as  TcExpr
-      , GHC.TypeCheck.FamilyInstance                                    as  FamInst
-      , GHC.TypeCheck.Foreign                                           as  TcForeign
-      , GHC.TypeCheck.FunctionalDependency                              as  FunDeps
-      , GHC.TypeCheck.Instance                                          as  TcInstDcls
-      , GHC.TypeCheck.Instantiation                                     as  Inst
-      , GHC.TypeCheck.Match                                             as  TcMatches
-      , GHC.TypeCheck.Module                                            as  TcRnDriver
-      , GHC.TypeCheck.ModuleSignature                                   as  TcBackpack
-      , GHC.TypeCheck.Monad                                             as  TcRnMonad
-      , GHC.TypeCheck.Pattern                                           as  TcPat
-      , GHC.TypeCheck.PatternSynonym                                    as  TcPatSyn
-      , GHC.TypeCheck.Rule                                              as  TcRules
-      , GHC.TypeCheck.Signature                                         as  TcSigs
-      , GHC.TypeCheck.Simplify                                          as  TcSimplify
-      , GHC.TypeCheck.Solver.Canonicalise                               as  TcCanonical
-      , GHC.TypeCheck.Solver.Flatten                                    as  TcFlatten
-      , GHC.TypeCheck.Solver.Interact                                   as  TcInteract
-      , GHC.TypeCheck.Solver.Monad                                      as  TcSMonad
-      , GHC.TypeCheck.Splice                                            as  TcSplice
-      , GHC.TypeCheck.Syntax                                            as  TcHsSyn
-      , GHC.TypeCheck.Type                                              as  TcHsType
-      , GHC.TypeCheck.TypeDecl                                          as  TcTyClsDecls
-      , GHC.TypeCheck.TypeDeclUtil                                      as  TcTyDecls
-      , GHC.TypeCheck.Unify                                             as  TcUnify
-      , GHC.TypeCheck.Util                                              as  TcRnTypes
-      , GHC.TypeCheck.Util.CoreType                                     as  TcType
-      , GHC.TypeCheck.Util.Monadic                                      as  TcMType
-      , GHC.TypeCheck.Validity                                          as  TcValidity
-      , GHC.Haskell.Util                                                as  HsUtils
-      , GHC.Interactive.ClosureInspect                                  as  RtClosureInspect
-      , GHC.Interactive.Debugger                                        as  Debugger
-      , GHC.Interactive.Debugger.Util                                   as  DebuggerUtils
-      , GHC.Interactive.DynamicLoading                                  as  DynamicLoading
-      , GHC.Interactive.Eval                                            as  InteractiveEval
-      , GHC.Interactive.Interpreter                                     as  GHCi
-      , GHC.Interactive.Linker                                          as  Linker
-      , GHC.Interactive.Types                                           as  InteractiveEvalTypes
-      , GHC.Interface.Binary                                            as  BinIface
-      , GHC.Interface.BuildTypeAndClass                                 as  BuildTyCl
-      , GHC.Interface.Environment                                       as  IfaceEnv
-      , GHC.Interface.Load                                              as  LoadIface
-      , GHC.Interface.Rename                                            as  RnModIface
-      , GHC.Interface.Syntax                                            as  IfaceSyn
-      , GHC.Interface.Tidy                                              as  TidyPgm
-      , GHC.Interface.Type                                              as  IfaceType
-      , GHC.Interface.TypeCheck                                         as  TcIface
-      , GHC.Interface.Util                                              as  MkIface
-      , GHC.Llvm.MetaData                                               as  Llvm.MetaData
-      , GHC.Llvm.Printer                                                as  Llvm.PpLlvm
-      , GHC.Llvm.Syntax                                                 as  Llvm.AbsSyn
-      , GHC.Llvm.Types                                                  as  Llvm.Types
-      , GHC.Monad                                                       as  GhcMonad
-      , GHC.Packages                                                    as  Packages
-      , GHC.Packages.PackageConfig                                      as  PackageConfig
-      , GHC.Plugin                                                      as  GhcPlugins
-      , GHC.Plugin.TypeChecker                                          as  TcPluginM
-      , GHC.Plugin.Types                                                as  Plugins
-      , GHC.RTS.InfoTable                                               as  CmmInfo
-      , GHC.RTS.Storage                                                 as  SMRep
-      , GHC.Stg.CommonSubExpr                                           as  StgCse
-      , GHC.Stg.CostCentreCollect                                       as  SCCfinal
-      , GHC.Stg.Lint                                                    as  StgLint
-      , GHC.Stg.Pipeline                                                as  SimplStg
-      , GHC.Stg.Stats                                                   as  StgStats
-      , GHC.Stg.Syntax                                                  as  StgSyn
-      , GHC.StgToCmm.ArgRep                                             as  StgCmmArgRep
-      , GHC.StgToCmm                                                    as  StgCmm
-      , GHC.StgToCmm.Bind                                               as  StgCmmBind
-      , GHC.StgToCmm.Closure                                            as  StgCmmClosure
-      , GHC.StgToCmm.Constructor                                        as  StgCmmCon
-      , GHC.StgToCmm.Coverage                                           as  StgCmmHpc
-      , GHC.StgToCmm.Environment                                        as  StgCmmEnv
-      , GHC.StgToCmm.Expression                                         as  StgCmmExpr
-      , GHC.StgToCmm.ForeignCall                                        as  StgCmmForeign
-      , GHC.StgToCmm.Heap                                               as  StgCmmHeap
-      , GHC.StgToCmm.Layout                                             as  StgCmmLayout
-      , GHC.StgToCmm.Monad                                              as  StgCmmMonad
-      , GHC.StgToCmm.Monad.Extended                                     as  StgCmmExtCode
-      , GHC.StgToCmm.PrimOp                                             as  StgCmmPrim
-      , GHC.StgToCmm.Profiling                                          as  StgCmmProf
-      , GHC.StgToCmm.Profiling.Ticky                                    as  StgCmmTicky
-      , GHC.StgToCmm.Util                                               as  StgCmmUtils
-      , GHC.Stg.Unarise                                                 as  UnariseStg
-      , GHC.Stg.Util                                                    as  CgUtils
-      , GHC.Util                                                        as  Util
-      , GHC.Util.Assembler                                              as  AsmUtils
-      , GHC.Util.Binary                                                 as  Binary
-      , GHC.Util.Binary.Fingerprint                                     as  BinFingerprint
-      , GHC.Util.CodeGen.Platform.ARM64                                 as  CodeGen.Platform.ARM64
-      , GHC.Util.CodeGen.Platform.ARM                                   as  CodeGen.Platform.ARM
-      , GHC.Util.CodeGen.Platform                                       as  CodeGen.Platform
-      , GHC.Util.CodeGen.Platform.NoRegs                                as  CodeGen.Platform.NoRegs
-      , GHC.Util.CodeGen.Platform.PPC                                   as  CodeGen.Platform.PPC
-      , GHC.Util.CodeGen.Platform.PPC_Darwin                            as  CodeGen.Platform.PPC_Darwin
-      , GHC.Util.CodeGen.Platform.SPARC                                 as  CodeGen.Platform.SPARC
-      , GHC.Util.CodeGen.Platform.X86_64                                as  CodeGen.Platform.X86_64
-      , GHC.Util.CodeGen.Platform.X86                                   as  CodeGen.Platform.X86
-      , GHC.Util.CodeGen.Primitive                                      as  CPrim
-      , GHC.Util.CodeGen.StaticPtrTable                                 as  StaticPtrTable
-      , GHC.Util.Elf                                                    as  Elf
-      , GHC.Util.Error                                                  as  ErrUtils
-      , GHC.Util.Exception                                              as  Exception
-      , GHC.Util.FileCleanup                                            as  FileCleanup
-      , GHC.Util.Fingerprint                                            as  Fingerprint
-      , GHC.Util.Handle.BufferedWrite                                   as  BufWrite
-      , GHC.Util.IO.Unsafe                                              as  FastFunctions
-      , GHC.Util.Json                                                   as  Json
-      , GHC.Util.Lexeme                                                 as  Lexeme
-      , GHC.Util.Monad                                                  as  MonadUtils
-      , GHC.Util.Monad.IOEnv                                            as  IOEnv
-      , GHC.Util.Monad.ListT                                            as  ListT
-      , GHC.Util.Monad.State                                            as  State
-      , GHC.Util.Outputable                                             as  Outputable
-      , GHC.Util.Panic                                                  as  Panic
-      , GHC.Util.Platform                                               as  Platform
-      , GHC.Util.PrettyPrint                                            as  Pretty
-      , GHC.Util.PrettyPrint.Colour                                     as  PprColour
-      , GHC.Util.PrettyPrint.TyThing                                    as  PprTyThing
-      , GHC.Util.SysTools                                               as  SysTools
-      , GHC.Util.SysTools.Terminal                                      as  SysTools.Terminal
-      , GHC.Util.SysTools.ExtraObj                                      as  SysTools.ExtraObj
-      , GHC.Util.SysTools.Info                                          as  SysTools.Info
-      , GHC.Util.SysTools.Process                                       as  SysTools.Process
-      , GHC.Util.SysTools.Tasks                                         as  SysTools.Tasks
+
+        GHC.Hs.Annotation              as ApiAnnotation
+      , GHC.Hs.Binds                   as HsBinds
+      , GHC.Hs.Decls                   as HsDecls
+      , GHC.Hs.Doc                     as HsDoc
+      , GHC.Hs.Dump                    as HsDumpAst
+      , GHC.Hs.Expr                    as HsExpr
+      , GHC.Hs.Extension               as HsExtension
+      , GHC.Hs                         as HsSyn
+      , GHC.Hs.ImpExp                  as HsImpExp
+      , GHC.Hs.Instances               as HsInstances
+      , GHC.Hs.Lit                     as HsLit
+      , GHC.Hs.Pat                     as HsPat
+      , GHC.Hs.PlaceHolder             as PlaceHolder
+      , GHC.Hs.Types                   as HsTypes
+      , GHC.Hs.Utils                   as HsUtils
+      , GHC.Hs.Stats                   as HscStats
+
+      , GHC.Platform.ARM64             as CodeGen.Platform.ARM64
+      , GHC.Platform.ARM               as CodeGen.Platform.ARM
+      , GHC.Platform.NoRegs            as CodeGen.Platform.NoRegs
+      , GHC.Platform.PPC               as CodeGen.Platform.PPC
+      , GHC.Platform.Regs              as CodeGen.Platform
+      , GHC.Platform.SPARC             as CodeGen.Platform.SPARC
+      , GHC.Platform.X86_64            as CodeGen.Platform.X86_64
+      , GHC.Platform.X86               as CodeGen.Platform.X86
+
+      , GHC.StgToCmm.ArgRep            as StgCmmArgRep
+      , GHC.StgToCmm.Bind              as StgCmmBind
+      , GHC.StgToCmm.CgUtils           as CgUtils
+      , GHC.StgToCmm.Closure           as StgCmmClosure
+      , GHC.StgToCmm.DataCon           as StgCmmCon
+      , GHC.StgToCmm.Env               as StgCmmEnv
+      , GHC.StgToCmm.Expr              as StgCmmExpr
+      , GHC.StgToCmm.ExtCode           as StgCmmExtCode
+      , GHC.StgToCmm.Foreign           as StgCmmForeign
+      , GHC.StgToCmm.Heap              as StgCmmHeap
+      , GHC.StgToCmm.Hpc               as StgCmmHpc
+      , GHC.StgToCmm                   as StgCmm
+      , GHC.StgToCmm.Layout            as StgCmmLayout
+      , GHC.StgToCmm.Monad             as StgCmmMonad
+      , GHC.StgToCmm.Prim              as StgCmmPrim
+      , GHC.StgToCmm.Prof              as StgCmmProf
+      , GHC.StgToCmm.Ticky             as StgCmmTicky
+      , GHC.StgToCmm.Utils             as StgCmmUtils
+
+      , GHC.ThToHs                     as Convert
+
+      , GHC.Rename.Binds               as RnBinds
+      , GHC.Rename.Env                 as RnEnv
+      , GHC.Rename.Expr                as RnExpr
+      , GHC.Rename.Fixity              as RnFixity
+      , GHC.Rename.Doc                 as RnHsDoc
+      , GHC.Rename.Names               as RnNames
+      , GHC.Rename.Pat                 as RnPat
+      , GHC.Rename.Source              as RnSource
+      , GHC.Rename.Splice              as RnSplice
+      , GHC.Rename.Types               as RnTypes
+      , GHC.Rename.Unbound             as RnUnbound
+      , GHC.Rename.Utils               as RnUtils
+
+      , GHC.Types.RepType              as RepType
+
+      , GHC.Cmm.BlockId                as BlockId
+      , GHC.Cmm.CLabel                 as CLabel
+      , GHC.Cmm.CallConv               as CmmCallConv
+      , GHC.Cmm.CommonBlockElim        as CmmCommonBlockElim
+      , GHC.Cmm.ContFlowOpt            as CmmContFlowOpt
+      , GHC.Cmm.Expr                   as CmmExpr
+      , GHC.Cmm                        as Cmm
+      , GHC.Cmm.Switch                 as CmmSwitch
+      , GHC.Cmm.Switch.Implement       as CmmImplementSwitchPlans
+      , GHC.Cmm.Info                   as CmmInfo
+      , GHC.Cmm.Info.Build             as CmmBuildInfoTables
+      , GHC.Cmm.LayoutStack            as CmmLayoutStack
+      , GHC.Cmm.Lint                   as CmmLint
+      , GHC.Cmm.Liveness               as CmmLive
+      , GHC.Cmm.MachOp                 as CmmMachOp
+      , GHC.Cmm.Monad                  as CmmMonad
+      , GHC.Cmm.Node                   as CmmNode
+      , GHC.Cmm.Opt                    as CmmOpt
+      , GHC.Cmm.Pipeline               as CmmPipeline
+      , GHC.Cmm.ProcPoint              as CmmProcPoint
+      , GHC.Cmm.Sink                   as CmmSink
+      , GHC.Cmm.Type                   as CmmType
+      , GHC.Cmm.Utils                  as CmmUtils
+      , GHC.Cmm.DebugBlock             as Debug
+      , GHC.Cmm.Dataflow.Block         as Hoopl.Block
+      , GHC.Cmm.Dataflow.Collections   as Hoopl.Collections
+      , GHC.Cmm.Dataflow               as Hoopl.Dataflow
+      , GHC.Cmm.Dataflow.Graph         as Hoopl.Graph
+      , GHC.Cmm.Dataflow.Label         as Hoopl.Label
+      , GHC.Cmm.Graph                  as MkGraph
+      , GHC.Cmm.Ppr.Decl               as PprCmmDecl
+      , GHC.Cmm.Ppr.Expr               as PprCmmExpr
+      , GHC.Cmm.Ppr                    as PprCmm
+      , GHC.Cmm.Lexer                  as CmmLex
+      , GHC.Cmm.Parser                 as CmmParse
+
+      , GHC.CmmToC                     as PprC
+
+      , GHC.HsToCore.PmCheck           as Check
+      , GHC.HsToCore.PmCheck.Oracle    as PmOracle
+      , GHC.HsToCore.PmCheck.Ppr       as PmPpr
+      , GHC.HsToCore.PmCheck.Types     as PmTypes
+
+      , GHC.HsToCore                   as Desugar
+      , GHC.HsToCore.Coverage          as Coverage
+      , GHC.HsToCore.Arrows            as DsArrows
+      , GHC.HsToCore.Binds             as DsBinds
+      , GHC.HsToCore.ForeignCall       as DsCCall
+      , GHC.HsToCore.Expr              as DsExpr
+      , GHC.HsToCore.ForeignCallDecl   as DsForeign
+      , GHC.HsToCore.GuardedRHSs       as DsGRHSs
+      , GHC.HsToCore.ListComp          as DsListComp
+      , GHC.HsToCore.Splice            as DsMeta
+      , GHC.HsToCore.Monad             as DsMonad
+      , GHC.HsToCore.Usage             as DsUsage
+      , GHC.HsToCore.Utils             as DsUtils
+      , GHC.HsToCore.Docs              as ExtractDocs
+      , GHC.HsToCore.Match             as Match
+      , GHC.HsToCore.Match.Constructor as MatchCon
+      , GHC.HsToCore.Match.Literal     as MatchLit
+
+      , GHC.Stg.Pipeline               as SimplStg
+      , GHC.Stg.CSE                    as StgCse
+      , GHC.Stg.Stats                  as StgStats
+      , GHC.Stg.Unarise                as UnariseStg
+      , GHC.Stg.FVs                    as StgFVs
+      , GHC.Stg.Lint                   as StgLint
+      , GHC.Stg.Subst                  as StgSubst
+      , GHC.Stg.Syntax                 as StgSyn
+
+      , GHC.Stg.Lift                   as StgLiftLams
+      , GHC.Stg.Lift.Analysis          as StgLiftLams.Analysis
+      , GHC.Stg.Lift.Monad             as StgLiftLams.LiftM
+
+      , GHC.CoreToStg                  as CoreToStg
+      , GHC.CoreToStg.Prep             as CorePrep
+
+      , GHC.Iface.Binary               as BinIface
+      , GHC.Iface.Env                  as IfaceEnv
+      , GHC.Iface.Syntax               as IfaceSyn
+      , GHC.Iface.Type                 as IfaceType
+      , GHC.Iface.Load                 as LoadIface
+      , GHC.Iface.Utils                as MkIface
+      , GHC.Iface.Rename               as RnModIface
+      , GHC.Iface.Tidy                 as TidyPgm
+
+      , GHC.Iface.Ext.Ast              as HieAst
+      , GHC.Iface.Ext.Binary           as HieBin
+      , GHC.Iface.Ext.Debug            as HieDebug
+      , GHC.Iface.Ext.Types            as HieTypes
+      , GHC.Iface.Ext.Utils            as HieUtils
+
+      , GHC.IfaceToCore                as TcIface
+      , GHC.CoreToIface                as ToIface
+
+      , GHC.Data.Bitmap                as Bitmap