[Git][ghc/ghc][wip/T23536-teo] Make template-haskell a stage1 package

Teo Camarasu (@teo) gitlab at gitlab.haskell.org
Fri Apr 12 08:53:32 UTC 2024



Teo Camarasu pushed to branch wip/T23536-teo at Glasgow Haskell Compiler / GHC


Commits:
b06519e2 by Teo Camarasu at 2024-04-12T09:52:24+01:00
Make template-haskell a stage1 package

Promoting template-haskell from a stage0 to a stage1 package means that
we can much more easily refactor template-haskell.

We implement this by duplicating the in-tree `template-haskell`.
A new `template-haskell-next` library is autogenerated to mirror `template-haskell`
`stage1:ghc` to depend on the new interface of the library including the
`Binary` instances without adding an explicit dependency on `template-haskell`.

This is controlled by the `bootstrap-th` cabal flag

When building `template-haskell` modules as part of this vendoring we do
not have access to quote syntax, so we cannot use variable quote
notation (`'Just`). So we either replace these with hand-written `Name`s
or hide the code behind CPP.

We can remove the `th_hack` from hadrian, which was required when
building stage0 packages using the in-tree `template-haskell` library.

For more details see Note [Bootstrapping Template Haskell].

Resolves #23536

Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com>
Co-Authored-By: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org>

- - - - -


15 changed files:

- .gitignore
- compiler/GHC/Tc/Gen/Splice.hs
- compiler/ghc.cabal.in
- hadrian/src/Packages.hs
- hadrian/src/Rules/Dependencies.hs
- hadrian/src/Rules/Generate.hs
- hadrian/src/Rules/ToolArgs.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Packages.hs
- libffi-tarballs
- libraries/ghc-boot-th/ghc-boot-th.cabal.in
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghci/ghci.cabal.in
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- libraries/template-haskell/template-haskell.cabal.in


Changes:

=====================================
.gitignore
=====================================
@@ -166,6 +166,7 @@ _darcs/
 /libraries/ghc-boot/ghc-boot.cabal
 /libraries/ghc-boot-th/GNUmakefile
 /libraries/ghc-boot-th/ghc-boot-th.cabal
+/libraries/ghc-boot-th-next/ghc-boot-th-next.cabal
 /libraries/ghc-boot-th/ghc.mk
 /libraries/ghc-heap/ghc-heap.cabal
 /libraries/ghci/GNUmakefile
@@ -182,6 +183,7 @@ _darcs/
 /libraries/synopsis.png
 /libraries/stamp/
 /libraries/template-haskell/template-haskell.cabal
+/libraries/template-haskell-next/template-haskell-next.cabal
 /linter.log
 /mk/are-validating.mk
 /mk/build.mk


=====================================
compiler/GHC/Tc/Gen/Splice.hs
=====================================
@@ -2916,3 +2916,116 @@ tcGetInterp = do
    case hsc_interp hsc_env of
       Nothing -> liftIO $ throwIO (InstallationError "Template haskell requires a target code interpreter")
       Just i  -> pure i
+
+-- Note [Bootstrapping Template Haskell]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+-- Staged Metaprogramming as implemented in Template Haskell introduces a whole
+-- new dimension of staging to the already staged bootstrapping process.
+-- The `template-haskell` library plays a crucial role in this process.
+--
+-- Nomenclature:
+--
+--   boot/stage0 compiler: An already released compiler used to compile GHC
+--   stage(N+1) compiler: The result of compiling GHC from source with stage(N)
+--       Recall that any code compiled by the stage1 compiler should be binary
+--       identical to the same code compiled by later stages.
+--   boot TH: the `template-haskell` that comes with (and is linked to) the
+--       boot/stage0 compiler
+--   in-tree TH: the `template-haskell` library that lives in GHC's repository.
+--       Recall that building in-tree TH with the stage1 compiler yields a binary
+--       that is identical to the in-tree TH compiled by stage2.
+--   boot library: A library such as bytestring or containers that GHC depends on.
+--       CONFUSINGLY, we build these libraries with the boot compiler as well as
+--       the stage1 compiler; thus the "boot" in boot library does not refer to a
+--       stage.
+--
+-- Here is how we bootstrap `template-haskell` in tandem with GHC:
+--
+--  1. Link the stage1 compiler against the boot TH library.
+--  2. When building the stage1 compiler, build a CPP'd version of the in-tree
+--     TH using the boot compiler under a different package-id,
+--     `template-haskell-next`, and build stage1 GHC against that.
+--  3. Build the in-tree TH with the stage1 compiler.
+--  4. Build and link the stage2 compiler against the in-tree TH.
+--
+-- Observations:
+--
+--  A. The vendoring in (2) means that the fully qualified name of the in-tree TH
+--     AST will be, e.g., `template-haskell-next:...VarE`, not `template-haskell:...VarE`.
+--     That is OK, because we need it just for the `Binary` instance and to
+--     convert TH ASTs returned by splices into the Hs AST, both of which do not
+--     depend on the fully qualified name of the type to serialise! Importantly,
+--     Note [Hard-wiring in-tree template-haskell for desugaring quotes] is
+--     unaffected, because the desugaring refers to names in the in-tree TH
+--     library, which is built in the next stage, stage1, and later.
+--
+-- (Rejected) alternative designs:
+--
+--  1b. Build the in-tree TH with the stage0 compiler and link the stage1 compiler
+--      against it. This is what we did until Apr 24 and it is problematic (#23536):
+--        * (It rules out using TH in GHC, for example to derive GHC.Core.Map types,
+--           because the boot compiler expects the boot TH AST in splices, but, e.g.,
+--           splice functions in GHC.Core.Map.TH would return the in-tree TH AST.
+--           However, at the moment, we are not using TH in GHC anyway.)
+--        * Ultimately, we must link the stage1 compiler against a
+--          single version of template-haskell.
+--            (Beyond the fact that doing otherwise would invite even
+--            more "which `template-haskell` is this" confusion, it
+--            would also result in confusing linker errors: see for
+--            example #21981.  In principle we could likely lift this
+--            restriction with more aggressive name mangling, but the
+--            knock-on effects of doing so are unexplored.)
+--        * If the single version is the in-tree TH, we have to recompile all boot
+--          libraries (e.g. bytestring, containers) with this new TH version.
+--        * But the boot libraries must *not* be built against a non-boot TH version.
+--          The reason is Note [Hard-wiring in-tree template-haskell for desugaring quotes]:
+--          The boot compiler will desugar quotes wrt. names in the boot TH version.
+--          A quote like `[| unsafePackLenLiteral |]` in bytestring will desugar
+--          to `varE (mkNameS "unsafePackLenLiteral")`, and all
+--          those smart constructors refer to locations in *boot TH*, because that
+--          is all that the boot GHC knows about.
+--          If the in-tree TH were to move or rename the definition of
+--          `mkNameS`, the boot compiler would report a linker error when
+--          compiling bytestring.
+--        * (Stopping to use quotes in bytestring is no solution, either, because
+--           the `Lift` type class is wired-in as well.
+--           Only remaining option: provide an entirely TH-less variant of every
+--           boot library. That would place a huge burden on maintainers and is
+--           thus rejected.)
+--        * We have thus made it impossible to refactor in-tree TH.
+--          This problem was discussed in #23536.
+--  1c. Do not build the stage1 compiler against any template-haskell library.
+--      This is viable because no splices need to be run as part of the
+--      bootstrapping process, so we could CPP away all the code in the stage1
+--      compiler that refers to template-haskell types. However,
+--        * it is not so simple either: a surprising example is GHC.Tc.Errors.Types
+--          where we would need to replace all TH types with dummy types.
+--          (We *cannot* simply CPP away TH-specific error constructors because
+--          that affects binary compatibility with the stage2 compiler.)
+--        * we would still need to vendor the updated Extension enum, so even
+--          though we had to use a lot of CPP, we still end up depending on names
+--          that are not present in the stage2 compiler.
+--        * this design would never allow us to use TH in GHC's code base, for
+--          example in GHC.Core.Map.
+--      It seems simpler just to depend on a template-haskell library in a fake
+--      namespace.
+--  2b. Alternatively vendor the parts relevant to serialising
+--      the (new, in-tree) TH AST into `ghc-boot`, thus shadowing definitions in the
+--      implicitly linked boot TH.
+--        * We found that this led to quite a bit of duplication in the
+--          `ghc-boot` cabal file.
+
+-- Note [Hard-wiring in-tree template-haskell for desugaring quotes]
+-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+-- To desugar Template Haskell quotes, GHC needs to wire in a bunch of Names in the
+-- `template-haskell` library as Note [Known-key names], in GHC.Builtin.Names.TH.
+-- Consider
+-- > foo :: Q Exp
+-- > foo = [| unwords ["hello", "world"] |]
+-- this desugars to Core that looks like this
+-- > varE (mkNameS "unwords") `appE` listE [litE (stringE "hello"), litE (stringE "world")]
+-- And all these smart constructors are known-key.
+-- NB: Since the constructors are known-key, it is impossible to link this program
+-- against another template-haskell library in which, e.g., `varE` was moved into a
+-- different module. So effectively, GHC is hard-wired against the in-tree
+-- template-haskell library.


=====================================
compiler/ghc.cabal.in
=====================================
@@ -82,6 +82,15 @@ Flag hadrian-stage0
     Default: False
     Manual: True
 
+Flag bootstrap
+        Description:
+          Enabled when building the stage1 compiler in order to vendor the in-tree
+          `template-haskell` library (including its dependency `ghc-boot-th`), while
+          allowing dependencies to depend on the boot `template-haskell` library.
+          See Note [Bootstrapping Template Haskell]
+        Default: False
+        Manual: True
+
 Library
     Default-Language: GHC2021
     Exposed: False
@@ -115,7 +124,6 @@ Library
                    containers >= 0.6.2.1 && < 0.8,
                    array      >= 0.1 && < 0.6,
                    filepath   >= 1   && < 1.6,
-                   template-haskell == 2.22.*,
                    hpc        >= 0.6 && < 0.8,
                    transformers >= 0.5 && < 0.7,
                    exceptions == 0.10.*,
@@ -125,6 +133,13 @@ Library
                    ghc-heap   == @ProjectVersionMunged@,
                    ghci == @ProjectVersionMunged@
 
+    if flag(bootstrap)
+      Build-Depends:
+        template-haskell-next 
+    else
+      Build-Depends:
+        template-haskell      == 2.22.*
+
     if os(windows)
         Build-Depends: Win32  >= 2.3 && < 2.15
     else


=====================================
hadrian/src/Packages.hs
=====================================
@@ -4,12 +4,12 @@ module Packages (
     array, base, binary, bytestring, cabal, cabalSyntax, checkPpr,
     checkExact, countDeps,
     compareSizes, compiler, containers, deepseq, deriveConstants, directory, dumpDecls,
-    exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh, ghcPlatform,
+    exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh, ghcBootThNext, ghcPlatform,
     ghcCompact, ghcConfig, ghcExperimental, ghcHeap, ghcInternal, ghci, ghciWrapper, ghcPkg, ghcPrim,
     ghcToolchain, ghcToolchainBin, haddock, haskeline,
     hsc2hs, hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, iservProxy,
     libffi, mtl, osString, parsec, pretty, primitive, process, remoteIserv, rts,
-    runGhc, semaphoreCompat, stm, templateHaskell, terminfo, text, time, timeout,
+    runGhc, semaphoreCompat, stm, templateHaskell, templateHaskellNext, terminfo, text, time, timeout,
     transformers, unlit, unix, win32, xhtml,
     lintersCommon, lintNotes, lintCodes, lintCommitMsg, lintSubmoduleRefs, lintWhitespace,
     ghcPackages, isGhcPackage,
@@ -37,11 +37,11 @@ ghcPackages :: [Package]
 ghcPackages =
     [ array, base, binary, bytestring, cabalSyntax, cabal, checkPpr, checkExact, countDeps
     , compareSizes, compiler, containers, deepseq, deriveConstants, directory, dumpDecls
-    , exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh, ghcPlatform
+    , exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh, ghcBootThNext, ghcPlatform
     , ghcCompact, ghcConfig, ghcExperimental, ghcHeap, ghcInternal, ghci, ghciWrapper, ghcPkg, ghcPrim
     , ghcToolchain, ghcToolchainBin, haddock, haskeline, hsc2hs
     , hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, libffi, mtl, osString
-    , parsec, pretty, process, rts, runGhc, stm, semaphoreCompat, templateHaskell
+    , parsec, pretty, process, rts, runGhc, stm, semaphoreCompat, templateHaskell, templateHaskellNext
     , terminfo, text, time, transformers, unlit, unix, win32, xhtml
     , timeout
     , lintersCommon
@@ -54,7 +54,7 @@ isGhcPackage = (`elem` ghcPackages)
 -- | Package definitions, see 'Package'.
 array, base, binary, bytestring, cabalSyntax, cabal, checkPpr, checkExact, countDeps,
   compareSizes, compiler, containers, deepseq, deriveConstants, directory, dumpDecls,
-  exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh, ghcPlatform,
+  exceptions, filepath, genapply, genprimopcode, ghc, ghcBignum, ghcBoot, ghcBootTh, ghcBootThNext, ghcPlatform,
   ghcCompact, ghcConfig, ghcExperimental, ghcHeap, ghci, ghcInternal, ghciWrapper, ghcPkg, ghcPrim,
   ghcToolchain, ghcToolchainBin, haddock, haskeline, hsc2hs,
   hp2ps, hpc, hpcBin, integerGmp, integerSimple, iserv, iservProxy, remoteIserv, libffi, mtl,
@@ -87,6 +87,7 @@ ghc                 = prg  "ghc-bin"         `setPath` "ghc"
 ghcBignum           = lib  "ghc-bignum"
 ghcBoot             = lib  "ghc-boot"
 ghcBootTh           = lib  "ghc-boot-th"
+ghcBootThNext       = lib  "ghc-boot-th-next"
 ghcPlatform         = lib  "ghc-platform"
 ghcCompact          = lib  "ghc-compact"
 ghcConfig           = prg  "ghc-config"      `setPath` "testsuite/ghc-config"
@@ -123,6 +124,7 @@ runGhc              = util "runghc"
 semaphoreCompat     = lib  "semaphore-compat"
 stm                 = lib  "stm"
 templateHaskell     = lib  "template-haskell"
+templateHaskellNext = lib  "template-haskell-next"
 terminfo            = lib  "terminfo"
 text                = lib  "text"
 time                = lib  "time"


=====================================
hadrian/src/Rules/Dependencies.hs
=====================================
@@ -35,7 +35,10 @@ extra_dependencies =
 
   where
     th_internal = (templateHaskell, "Language.Haskell.TH.Lib.Internal")
-    dep (p1, m1) (p2, m2) s = do
+    dep (p1, m1) (p2, m2) s =
+      -- We use the boot compiler's `template-haskell` library when building stage0,
+      -- so we don't need to register dependencies.
+      if isStage0 s then pure [] else do
         let context = Context s p1 (error "extra_dependencies: way not set") (error "extra_dependencies: iplace not set")
         ways <- interpretInContext context getLibraryWays
         mapM (\way -> (,) <$> path s way p1 m1 <*> path s way p2 m2) (S.toList ways)


=====================================
hadrian/src/Rules/Generate.hs
=====================================
@@ -307,14 +307,18 @@ escapedPkgName = map f . pkgName
     f '-'   = '_'
     f other = other
 
-templateRule :: FilePath -> Interpolations -> Rules ()
-templateRule outPath interps = do
+templateRuleFrom :: FilePath -> FilePath -> Interpolations -> Rules ()
+templateRuleFrom inPath outPath interps = do
     outPath %> \_ -> do
-        s <- readFile' (outPath <.> "in")
+        s <- readFile' inPath
         result <- runInterpolations interps s
         writeFile' outPath result
         putSuccess ("| Successfully generated " ++ outPath ++ " from its template")
 
+templateRule :: FilePath -> Interpolations -> Rules ()
+templateRule outPath =
+  templateRuleFrom (outPath <.> "in") outPath
+
 templateRules :: Rules ()
 templateRules = do
   templateRule "compiler/ghc.cabal" $ projectVersion
@@ -324,11 +328,31 @@ templateRules = do
   templateRule "utils/remote-iserv/remote-iserv.cabal" $ projectVersion
   templateRule "utils/runghc/runghc.cabal" $ projectVersion
   templateRule "libraries/ghc-boot/ghc-boot.cabal" $ projectVersion
-  templateRule "libraries/ghc-boot-th/ghc-boot-th.cabal" $ projectVersion
+  templateRule "libraries/ghc-boot-th/ghc-boot-th.cabal" $ mconcat
+    [ projectVersion
+    , interpolateVar "Suffix" $ pure ""
+    , interpolateVar "SourceRoot" $ pure "."
+    ]
+  templateRuleFrom "libraries/ghc-boot-th/ghc-boot-th.cabal.in"
+                   "libraries/ghc-boot-th-next/ghc-boot-th-next.cabal" $ mconcat
+    [ projectVersion
+    , interpolateVar "Suffix" $ pure "-next"
+    , interpolateVar "SourceRoot" $ pure "../ghc-boot-th"
+    ]
   templateRule "libraries/ghci/ghci.cabal" $ projectVersion
   templateRule "libraries/ghc-heap/ghc-heap.cabal" $ projectVersion
   templateRule "utils/ghc-pkg/ghc-pkg.cabal" $ projectVersion
-  templateRule "libraries/template-haskell/template-haskell.cabal" $ projectVersion
+  templateRule "libraries/template-haskell/template-haskell.cabal" $ mconcat
+    [ projectVersion
+    , interpolateVar "Suffix" $ pure ""
+    , interpolateVar "SourceRoot" $ pure "."
+    ]
+  templateRuleFrom "libraries/template-haskell/template-haskell.cabal.in"
+                   "libraries/template-haskell-next/template-haskell-next.cabal" $ mconcat
+    [ projectVersion
+    , interpolateVar "Suffix" $ pure "-next"
+    , interpolateVar "SourceRoot" $ pure "../template-haskell"
+    ]
   templateRule "libraries/prologue.txt" $ packageVersions
   templateRule "rts/include/ghcversion.h" $ mconcat
     [ interpolateSetting "ProjectVersionInt" ProjectVersionInt


=====================================
hadrian/src/Rules/ToolArgs.hs
=====================================
@@ -85,25 +85,13 @@ multiSetup pkg_s = do
       need (srcs ++ gens)
       let rexp m = ["-reexported-module", m]
       let hidir = root </> "interfaces" </> pkgPath p
-      writeFile' (resp_file root p) (intercalate "\n" (th_hack arg_list
+      writeFile' (resp_file root p) (intercalate "\n" (arg_list
                                                       ++  modules cd
                                                       ++ concatMap rexp (reexportModules cd)
                                                       ++ ["-outputdir", hidir]))
       return (resp_file root p)
 
 
-    -- The template-haskell package is compiled with -this-unit-id=template-haskell but
-    -- everything which depends on it depends on `-package-id-template-haskell-2.17.0.0`
-    -- and so the logic for detetecting which home-units depend on what is defeated.
-    -- The workaround here is just to rewrite all the `-package-id` arguments to
-    -- point to `template-haskell` instead which works for the multi-repl case.
-    -- See #20887
-    th_hack :: [String] -> [String]
-    th_hack ((isPrefixOf "-package-id template-haskell" -> True) : xs) = "-package-id" : "template-haskell" : xs
-    th_hack (x:xs) = x : th_hack xs
-    th_hack [] = []
-
-
 toolRuleBody :: FilePath -> Action ()
 toolRuleBody fp = do
   mm <- dirMap
@@ -158,7 +146,7 @@ toolTargets = [ binary
               -- , ghc     -- # depends on ghc library
               -- , runGhc  -- # depends on ghc library
               , ghcBoot
-              , ghcBootTh
+              , ghcBootThNext
               , ghcPlatform
               , ghcToolchain
               , ghcToolchainBin
@@ -172,7 +160,7 @@ toolTargets = [ binary
               , mtl
               , parsec
               , time
-              , templateHaskell
+              , templateHaskellNext
               , text
               , transformers
               , semaphoreCompat


=====================================
hadrian/src/Settings/Default.hs
=====================================
@@ -93,7 +93,7 @@ stage0Packages = do
              , ghc
              , runGhc
              , ghcBoot
-             , ghcBootTh
+             , ghcBootThNext
              , ghcPlatform
              , ghcHeap
              , ghcToolchain
@@ -108,7 +108,7 @@ stage0Packages = do
              , parsec
              , semaphoreCompat
              , time
-             , templateHaskell
+             , templateHaskellNext
              , text
              , transformers
              , unlit
@@ -127,6 +127,10 @@ stage1Packages = do
           -- but not win32/unix because it depends on cross-compilation target
           | p == win32        = False
           | p == unix         = False
+          -- These packages are only needed for bootstrapping.
+          -- See Note [Bootstrapping Template Haskell]
+          | p == templateHaskellNext = False
+          | p == ghcBootThNext = False
           | otherwise         = True
 
     libraries0 <- filter good_stage0_package <$> stage0Packages
@@ -143,6 +147,7 @@ stage1Packages = do
         , deepseq
         , exceptions
         , ghc
+        , ghcBootTh
         , ghcBignum
         , ghcCompact
         , ghcExperimental
@@ -156,6 +161,7 @@ stage1Packages = do
         , pretty
         , rts
         , semaphoreCompat
+        , templateHaskell
         , stm
         , unlit
         , xhtml


=====================================
hadrian/src/Settings/Packages.hs
=====================================
@@ -87,6 +87,7 @@ packageArgs = do
             -- We do it through a cabal flag in ghc.cabal
             , stageVersion < makeVersion [9,8,1] ? arg "+hadrian-stage0"
             , flag StaticLibzstd `cabalFlag` "static-libzstd"
+            , stage0 `cabalFlag` "bootstrap"
             ]
 
           , builder (Haddock BuildPackage) ? arg ("--optghc=-I" ++ path) ]
@@ -121,6 +122,10 @@ packageArgs = do
           , builder (Cc CompileC) ? (not <$> flag CcLlvmBackend) ?
             input "**/cbits/atomic.c"  ? arg "-Wno-sync-nand" ]
 
+        -------------------------------- ghcBoot ------------------------------
+        , package ghcBoot ?
+            builder (Cabal Flags) ? (stage0 `cabalFlag` "bootstrap")
+
         --------------------------------- ghci ---------------------------------
         , package ghci ? mconcat
           [
@@ -151,9 +156,12 @@ packageArgs = do
           -- compiler comes with the same versions as the one we are building.
           --
             builder (Cabal Setup) ? cabalExtraDirs ffiIncludeDir ffiLibraryDir
-          , builder (Cabal Flags) ? ifM stage0
-              (andM [cross, bootCross] `cabalFlag` "internal-interpreter")
-              (arg "internal-interpreter")
+          , builder (Cabal Flags) ? mconcat
+            [ ifM stage0
+                (andM [cross, bootCross] `cabalFlag` "internal-interpreter")
+                (arg "internal-interpreter")
+            , stage0 `cabalFlag` "bootstrap"
+            ]
 
           ]
 
@@ -178,6 +186,10 @@ packageArgs = do
         , package haddock ?
           builder (Cabal Flags) ? arg "in-ghc-tree"
 
+        ---------------------------- template-haskell --------------------------
+        , package templateHaskellNext ?
+            builder (Cabal Flags) ? stage0 `cabalFlag` "bootstrap"
+
         ---------------------------------- text --------------------------------
         , package text ? mconcat
           -- Disable SIMDUTF by default due to packaging difficulties


=====================================
libffi-tarballs
=====================================
@@ -1 +1 @@
-Subproject commit 89a9b01c5647c8f0d3899435b99df690f582e9f1
+Subproject commit 5624fd5c8bbce8432cd3c0b0ea92d152a1bba047


=====================================
libraries/ghc-boot-th/ghc-boot-th.cabal.in
=====================================
@@ -1,8 +1,8 @@
--- WARNING: ghc-boot-th.cabal is automatically generated from
--- ghc-boot-th.cabal.in by ../../configure.  Make sure you are editing
--- ghc-boot-th.cabal.in, not ghc-boot-th.cabal.
+-- WARNING: ghc-boot-th at Suffix@.cabal is automatically generated from
+-- ghc-boot-th at Suffix@.cabal.in by ../../configure.  Make sure you are editing
+-- ghc-boot-th at Suffix@.cabal.in, not ghc-boot-th at Suffix@.cabal.
 
-name:           ghc-boot-th
+name:           ghc-boot-th at Suffix@
 version:        @ProjectVersionMunged@
 license:        BSD3
 license-file:   LICENSE
@@ -27,6 +27,7 @@ source-repository head
     subdir:   libraries/ghc-boot-th
 
 Library
+    hs-source-dirs: @SourceRoot@
     default-language: Haskell2010
     other-extensions: DeriveGeneric
     default-extensions: NoImplicitPrelude


=====================================
libraries/ghc-boot/ghc-boot.cabal.in
=====================================
@@ -35,6 +35,15 @@ source-repository head
     location: https://gitlab.haskell.org/ghc/ghc.git
     subdir:   libraries/ghc-boot
 
+Flag bootstrap
+        Description:
+          Enabled when building the stage1 compiler in order to vendor the in-tree
+          `template-haskell` library (including its dependency `ghc-boot-th`), while
+          allowing dependencies to depend on the boot `template-haskell` library.
+          See Note [Bootstrapping Template Haskell]
+        Default: False
+        Manual: True
+
 Library
     default-language: Haskell2010
     other-extensions: DeriveGeneric, RankNTypes, ScopedTypeVariables
@@ -56,13 +65,6 @@ Library
             GHC.UniqueSubdir
             GHC.Version
 
-    -- reexport modules from ghc-boot-th so that packages don't have to import
-    -- both ghc-boot and ghc-boot-th. It makes the dependency graph easier to
-    -- understand and to refactor.
-    reexported-modules:
-              GHC.LanguageExtensions.Type
-            , GHC.ForeignSrcLang.Type
-            , GHC.Lexeme
 
     -- reexport platform modules from ghc-platform
     reexported-modules:
@@ -81,7 +83,22 @@ Library
                    filepath   >= 1.3 && < 1.6,
                    deepseq    >= 1.4 && < 1.6,
                    ghc-platform >= 0.1,
-                   ghc-boot-th == @ProjectVersionMunged@
+
+    -- reexport modules from ghc-boot-th so that packages
+    -- don't have to import all of ghc-boot and ghc-boot-th.
+    -- It makes the dependency graph easier to understand.
+    reexported-modules:
+            GHC.LanguageExtensions.Type
+          , GHC.ForeignSrcLang.Type
+          , GHC.Lexeme
+
+    if flag(bootstrap)
+      build-depends:
+              ghc-boot-th-next    == @ProjectVersionMunged@
+    else
+      build-depends:
+              ghc-boot-th         == @ProjectVersionMunged@
+
     if !os(windows)
         build-depends:
                    unix       >= 2.7 && < 2.9


=====================================
libraries/ghci/ghci.cabal.in
=====================================
@@ -22,6 +22,15 @@ Flag internal-interpreter
     Default: False
     Manual: True
 
+Flag bootstrap
+        Description:
+          Enabled when building the stage1 compiler in order to vendor the in-tree
+          `template-haskell` library (including its dependency `ghc-boot-th`), while
+          allowing dependencies to depend on the boot `template-haskell` library.
+          See Note [Bootstrapping Template Haskell]
+        Default: False
+        Manual: True
+
 source-repository head
     type:     git
     location: https://gitlab.haskell.org/ghc/ghc.git
@@ -84,8 +93,14 @@ library
         filepath         >= 1.4 && < 1.6,
         ghc-boot         == @ProjectVersionMunged@,
         ghc-heap         == @ProjectVersionMunged@,
-        template-haskell == 2.22.*,
         transformers     >= 0.5 && < 0.7
 
+    if flag(bootstrap)
+      build-depends:
+            template-haskell-next == 2.22.*
+    else
+      build-depends:
+            template-haskell      == 2.22.*
+
     if !os(windows)
         Build-Depends: unix >= 2.7 && < 2.9


=====================================
libraries/template-haskell/Language/Haskell/TH/Syntax.hs
=====================================
@@ -34,49 +34,52 @@ module Language.Haskell.TH.Syntax
     -- $infix
     ) where
 
-import qualified Data.Fixed as Fixed
+import Prelude
 import Data.Data hiding (Fixity(..))
 import Data.IORef
 import System.IO.Unsafe ( unsafePerformIO )
 import System.FilePath
 import GHC.IO.Unsafe    ( unsafeDupableInterleaveIO )
-import Control.Monad (liftM)
 import Control.Monad.IO.Class (MonadIO (..))
 import Control.Monad.Fix (MonadFix (..))
-import Control.Applicative (Applicative(..))
 import Control.Exception (BlockedIndefinitelyOnMVar (..), catch, throwIO)
 import Control.Exception.Base (FixIOException (..))
 import Control.Concurrent.MVar (newEmptyMVar, readMVar, putMVar)
 import System.IO        ( hPutStrLn, stderr )
-import Data.Char        ( isAlpha, isAlphaNum, isUpper, ord )
-import Data.Int
+import Data.Char        ( isAlpha, isAlphaNum, isUpper )
 import Data.List.NonEmpty ( NonEmpty(..) )
-import Data.Void        ( Void, absurd )
 import Data.Word
-import Data.Ratio
-import GHC.CString      ( unpackCString# )
 import GHC.Generics     ( Generic )
-import GHC.Types        ( Int(..), Word(..), Char(..), Double(..), Float(..),
-                          TYPE, RuntimeRep(..), Levity(..), Multiplicity (..) )
 import qualified Data.Kind as Kind (Type)
-import GHC.Prim         ( Int#, Word#, Char#, Double#, Float#, Addr# )
 import GHC.Ptr          ( Ptr, plusPtr )
 import GHC.Lexeme       ( startsVarSym, startsVarId )
 import GHC.ForeignSrcLang.Type
 import Language.Haskell.TH.LanguageExtensions
-import Numeric.Natural
 import Prelude hiding (Applicative(..))
 import Foreign.ForeignPtr
 import Foreign.C.String
 import Foreign.C.Types
+import GHC.Types        (TYPE, RuntimeRep(..), Levity(..))
 
+#ifndef BOOTSTRAP_TH
+import Control.Monad (liftM)
 import Data.Array.Byte (ByteArray(..))
+import Data.Char (ord)
+import Data.Int
+import Data.Ratio
+import Data.Void        ( Void, absurd )
+import GHC.CString      ( unpackCString# )
 import GHC.Exts
   ( ByteArray#, unsafeFreezeByteArray#, copyAddrToByteArray#, newByteArray#
   , isByteArrayPinned#, isTrue#, sizeofByteArray#, unsafeCoerce#, byteArrayContents#
   , copyByteArray#, newPinnedByteArray#)
 import GHC.ForeignPtr (ForeignPtr(..), ForeignPtrContents(..))
+import GHC.Prim         ( Int#, Word#, Char#, Double#, Float#, Addr# )
 import GHC.ST (ST(..), runST)
+import GHC.Types        ( Int(..), Word(..), Char(..), Double(..), Float(..))
+import Numeric.Natural
+import qualified Data.Fixed as Fixed
+#endif
 
 -----------------------------------------------------
 --
@@ -1018,6 +1021,8 @@ class Lift (t :: TYPE r) where
   liftTyped :: Quote m => t -> Code m t
 
 
+-- See Note [Bootstrapping Template Haskell]
+#ifndef BOOTSTRAP_TH
 -- If you add any instances here, consider updating test th/TH_Lift
 instance Lift Integer where
   liftTyped x = unsafeCodeCoerce (lift x)
@@ -1384,10 +1389,11 @@ rightName = 'Right
 
 nonemptyName :: Name
 nonemptyName = '(:|)
+#endif
 
 oneName, manyName :: Name
-oneName  = 'One
-manyName = 'Many
+oneName  = mkNameG DataName "ghc-prim" "GHC.Types" "One"
+manyName = mkNameG DataName "ghc-prim" "GHC.Types" "Many"
 
 -----------------------------------------------------
 --


=====================================
libraries/template-haskell/template-haskell.cabal.in
=====================================
@@ -1,8 +1,8 @@
--- WARNING: template-haskell.cabal is automatically generated from template-haskell.cabal.in by
+-- WARNING: template-haskell at Suffix@.cabal is automatically generated from ../template-haskell/template-haskell.cabal.in by
 -- ../../configure.  Make sure you are editing template-haskell.cabal.in, not
--- template-haskell.cabal.
+-- template-haskell at Suffix@.cabal.
 
-name:           template-haskell
+name:           template-haskell at Suffix@
 version:        2.22.0.0
 -- NOTE: Don't forget to update ./changelog.md
 license:        BSD3
@@ -20,6 +20,15 @@ description:
     See <http://www.haskell.org/haskellwiki/Template_Haskell> for more
     information.
 
+Flag bootstrap
+        Description:
+          Enabled when building the stage1 compiler in order to vendor the in-tree
+          `template-haskell` library (including its dependency `ghc-boot-th`), while
+          allowing dependencies to depend on the boot `template-haskell` library.
+          See Note [Bootstrapping Template Haskell]
+        Default: False
+        Manual: True
+
 extra-source-files: changelog.md
 
 source-repository head
@@ -56,7 +65,7 @@ Library
 
     build-depends:
         base        >= 4.11 && < 4.21,
-        ghc-boot-th == @ProjectVersionMunged@,
+        ghc-boot-th at Suffix@ == @ProjectVersionMunged@,
         ghc-prim,
         pretty      == 1.1.*
 
@@ -64,12 +73,15 @@ Library
       System.FilePath
       System.FilePath.Posix
       System.FilePath.Windows
-    hs-source-dirs: ./vendored-filepath .
+    hs-source-dirs: @SourceRoot@/vendored-filepath @SourceRoot@
     default-extensions:
       ImplicitPrelude
 
     ghc-options: -Wall
 
-    -- We need to set the unit ID to template-haskell (without a
-    -- version number) as it's magic.
-    ghc-options: -this-unit-id template-haskell
+    if flag(bootstrap)
+        cpp-options: -DBOOTSTRAP_TH
+    else
+        -- We need to set the unit ID to template-haskell (without a
+        -- version number) as it's magic.
+        ghc-options: -this-unit-id template-haskell



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b06519e2ece645ffa9e80b7b6a43ddd2e6e840ab

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b06519e2ece645ffa9e80b7b6a43ddd2e6e840ab
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20240412/4577f2c4/attachment-0001.html>


More information about the ghc-commits mailing list