[Git][ghc/ghc][wip/T23536-teo] Make template-haskell a stage1 package
Teo Camarasu (@teo)
gitlab at gitlab.haskell.org
Thu Apr 4 10:22:59 UTC 2024
Teo Camarasu pushed to branch wip/T23536-teo at Glasgow Haskell Compiler / GHC
Commits:
840fe186 by Teo Camarasu at 2024-04-04T11:22:50+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.
In order to accomplish this we now compile stage0 packages using
the boot compiler's version of template-haskell.
This means that there are now two versions of template-haskell in play:
the boot compiler's version, and the in-tree version.
When compiling the stage1 compiler, we have to pick a version of
template-haskell to use.
During bootstrapping we want to use the same version as the final
compiler. This forces the in-tree version. We are only able to use the
internal interpreter with stage2 onwards. Yet, we could still use the
external interpreter.
The external interpreter runs splices in another process. Queries and
results are seralised. This reduces our compatibility requirements from
ABI compatibility with the internal interpreter to mere serialisation
compatibility. We may compile GHC against another library to what the
external interpreter is compiled against so long as it has exactly the
same serialisation of template-haskell types.
This opens up the strategy pursued in this patch.
When compiling the stage1 compiler we vendor the template-haskell and
ghc-boot-th libraries through ghc-boot and use these to define the Template
Haskell interface for the external interpreter. Note that at this point
we also have the template-haskell and ghc-boot-th packages in our
transitive dependency closure from the boot compiler, and some packages
like containers have dependencies on these to define Lift instances.
Then the external interpreter should be compiled against the regular
template-haskell library from the source tree. As this will have the
same serialised interface as what we vendor in ghc-boot, we can then
run splices.
GHC stage2 is compiled as normal as well against the template-haskell
library from the source tree.
Resolves #23536
- - - - -
10 changed files:
- compiler/ghc.cabal.in
- hadrian/src/Rules/Dependencies.hs
- hadrian/src/Rules/ToolArgs.hs
- hadrian/src/Settings/Default.hs
- hadrian/src/Settings/Packages.hs
- libraries/ghc-boot/ghc-boot.cabal.in
- libraries/ghci/ghci.cabal.in
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- libraries/template-haskell/vendored-filepath/System/FilePath/Posix.hs
- libraries/template-haskell/vendored-filepath/System/FilePath/Windows.hs
Changes:
=====================================
compiler/ghc.cabal.in
=====================================
@@ -115,7 +115,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.*,
=====================================
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/ToolArgs.hs
=====================================
@@ -158,7 +158,6 @@ toolTargets = [ binary
-- , ghc -- # depends on ghc library
-- , runGhc -- # depends on ghc library
, ghcBoot
- , ghcBootTh
, ghcPlatform
, ghcToolchain
, ghcToolchainBin
@@ -172,7 +171,6 @@ toolTargets = [ binary
, mtl
, parsec
, time
- , templateHaskell
, text
, transformers
, semaphoreCompat
=====================================
hadrian/src/Settings/Default.hs
=====================================
@@ -93,7 +93,6 @@ stage0Packages = do
, ghc
, runGhc
, ghcBoot
- , ghcBootTh
, ghcPlatform
, ghcHeap
, ghcToolchain
@@ -108,7 +107,6 @@ stage0Packages = do
, parsec
, semaphoreCompat
, time
- , templateHaskell
, text
, transformers
, unlit
@@ -143,6 +141,7 @@ stage1Packages = do
, deepseq
, exceptions
, ghc
+ , ghcBootTh
, ghcBignum
, ghcCompact
, ghcExperimental
@@ -156,6 +155,7 @@ stage1Packages = do
, pretty
, rts
, semaphoreCompat
+ , templateHaskell
, stm
, unlit
, xhtml
=====================================
hadrian/src/Settings/Packages.hs
=====================================
@@ -121,6 +121,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-th")
+
--------------------------------- ghci ---------------------------------
, package ghci ? mconcat
[
=====================================
libraries/ghc-boot/ghc-boot.cabal.in
=====================================
@@ -35,6 +35,11 @@ source-repository head
location: https://gitlab.haskell.org/ghc/ghc.git
subdir: libraries/ghc-boot
+Flag bootstrap-th
+ Description: Enable if we are bootstrapping template-haskell, and hence want to depend on both the in-tree and boot `template-haskell` lib
+ Default: False
+ Manual: True
+
Library
default-language: Haskell2010
other-extensions: DeriveGeneric, RankNTypes, ScopedTypeVariables
@@ -56,13 +61,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 +79,49 @@ Library
filepath >= 1.3 && < 1.6,
deepseq >= 1.4 && < 1.6,
ghc-platform >= 0.1,
- ghc-boot-th == @ProjectVersionMunged@
+ if flag(bootstrap-th)
+ cpp-options: -DBOOTSTRAP_TH
+ build-depends:
+ ghc-prim
+ , pretty
+ -- we vendor ghc-boot-th and template-haskell while bootstrapping TH.
+ -- This is to avoid having two copies of ghc-boot-th and template-haskell
+ -- in the build graph: one from the boot compiler and the in-tree one.
+ hs-source-dirs: . ../ghc-boot-th ../template-haskell ../template-haskell/vendored-filepath
+ exposed-modules:
+ GHC.LanguageExtensions.Type
+ , GHC.ForeignSrcLang.Type
+ , GHC.Lexeme
+ , Language.Haskell.TH
+ , Language.Haskell.TH.Lib
+ , Language.Haskell.TH.Ppr
+ , Language.Haskell.TH.PprLib
+ , Language.Haskell.TH.Quote
+ , Language.Haskell.TH.Syntax
+ , Language.Haskell.TH.LanguageExtensions
+ , Language.Haskell.TH.CodeDo
+ , Language.Haskell.TH.Lib.Internal
+
+ other-modules:
+ Language.Haskell.TH.Lib.Map
+ , System.FilePath
+ , System.FilePath.Posix
+ , System.FilePath.Windows
+ else
+ hs-source-dirs: .
+ build-depends:
+ ghc-boot-th == @ProjectVersionMunged@
+ , template-haskell == 2.22.0.0
+ -- reexport modules from ghc-boot-th and template-haskell so that packages
+ -- don't have to import all of ghc-boot, ghc-boot-th and template-haskell.
+ -- It makes the dependency graph easier to understand and to refactor
+ -- and reduces the amount of cabal flags we need to use for bootstrapping TH.
+ reexported-modules:
+ GHC.LanguageExtensions.Type
+ , GHC.ForeignSrcLang.Type
+ , GHC.Lexeme
+ , Language.Haskell.TH
+ , Language.Haskell.TH.Syntax
if !os(windows)
build-depends:
unix >= 2.7 && < 2.9
=====================================
libraries/ghci/ghci.cabal.in
=====================================
@@ -84,7 +84,6 @@ library
filepath >= 1.4 && < 1.6,
ghc-boot == @ProjectVersionMunged@,
ghc-heap == @ProjectVersionMunged@,
- template-haskell == 2.22.*,
transformers >= 0.5 && < 0.7
if !os(windows)
=====================================
libraries/template-haskell/Language/Haskell/TH/Syntax.hs
=====================================
@@ -34,49 +34,54 @@ 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.Char ( isAlpha, isAlphaNum, isUpper )
import Data.Int
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
+#ifdef BOOTSTRAP_TH
+import GHC.Types (TYPE, RuntimeRep(..), Levity(..))
+#else
+import Control.Monad (liftM)
+import Data.Char (ord)
+import qualified Data.Fixed as Fixed
+import GHC.Prim ( Int#, Word#, Char#, Double#, Float#, Addr# )
+import GHC.Types ( Int(..), Word(..), Char(..), Double(..), Float(..),
+ TYPE, RuntimeRep(..), Levity(..) )
+import GHC.CString ( unpackCString# )
+import GHC.ForeignPtr (ForeignPtr(..), ForeignPtrContents(..))
+import Data.Void ( Void, absurd )
+import Numeric.Natural
import Data.Array.Byte (ByteArray(..))
import GHC.Exts
( ByteArray#, unsafeFreezeByteArray#, copyAddrToByteArray#, newByteArray#
, isByteArrayPinned#, isTrue#, sizeofByteArray#, unsafeCoerce#, byteArrayContents#
, copyByteArray#, newPinnedByteArray#)
-import GHC.ForeignPtr (ForeignPtr(..), ForeignPtrContents(..))
import GHC.ST (ST(..), runST)
+#endif
-----------------------------------------------------
--
@@ -1018,6 +1023,7 @@ class Lift (t :: TYPE r) where
liftTyped :: Quote m => t -> Code m t
+#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 +1390,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/vendored-filepath/System/FilePath/Posix.hs
=====================================
@@ -102,6 +102,7 @@ module System.FilePath.Posix
)
where
+import Prelude
import Data.Char(toLower, toUpper, isAsciiLower, isAsciiUpper)
import Data.Maybe(isJust)
import Data.List(stripPrefix, isSuffixOf)
=====================================
libraries/template-haskell/vendored-filepath/System/FilePath/Windows.hs
=====================================
@@ -102,6 +102,7 @@ module System.FilePath.Windows
)
where
+import Prelude
import Data.Char(toLower, toUpper, isAsciiLower, isAsciiUpper)
import Data.Maybe(isJust)
import Data.List(stripPrefix, isSuffixOf)
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/840fe186f95e24b9a8e690af1fd78b6dfaaff475
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/840fe186f95e24b9a8e690af1fd78b6dfaaff475
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/20240404/c5c44d52/attachment-0001.html>
More information about the ghc-commits
mailing list