[Git][ghc/ghc][master] Handle the special ghc-prim:GHC.Prim module in the compiler

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Nov 8 00:28:15 UTC 2024



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
d8f8a1c3 by Sylvain Henry at 2024-11-07T19:27:46-05:00
Handle the special ghc-prim:GHC.Prim module in the compiler

Before this patch, some custom hacks were necessary in ghc-prim's
Setup.hs to register the GHC.Prim (virtual) module and in Hadrian to
generate haddocks properly.

In this patch we special-case this module in the compiler itself instead
(which it already is, see ghcPrimIface in GHC.Iface.Load). From
Cabal/Hadrian's perspective GHC.Prim is now just a normal autogenerated
module.

This simplification is worthwhile on its own. It was found while looking
into the work needed for #24453 which aims to merge ghc-prim,
ghc-bignum, and ghc-internal. It's also one step closer to remove
ghc-prim's custom setup.

- - - - -


5 changed files:

- compiler/GHC/Driver/Main.hs
- compiler/GHC/Tc/Module.hs
- hadrian/src/Rules/Documentation.hs
- libraries/ghc-prim/Setup.hs
- libraries/ghc-prim/ghc-prim.cabal


Changes:

=====================================
compiler/GHC/Driver/Main.hs
=====================================
@@ -1215,12 +1215,17 @@ hscDesugarAndSimplify summary (FrontendTypecheck tc_result) tc_warnings mb_old_h
   --
   -- We usually desugar even when we are not generating code, otherwise we
   -- would miss errors thrown by the desugaring (see #10600). The only
-  -- exceptions are when the Module is Ghc.Prim or when it is not a
-  -- HsSrcFile Module.
-  mb_desugar <-
-      if ms_mod summary /= gHC_PRIM && hsc_src == HsSrcFile
-      then Just <$> hscDesugar' (ms_location summary) tc_result
-      else pure Nothing
+  -- exception is when it is not a HsSrcFile module.
+  mb_desugar <- if
+    | hsc_src /= HsSrcFile       -> pure Nothing
+    -- Desugar an empty ghc-prim:GHC.Prim module by filtering out all its
+    -- bindings: the reason is that some of them are invalid (such as top-level
+    -- unlifted ones like void# or proxy#) and cause HsToCore failures.
+    --
+    -- We still need to desugar *something* because the driver and the linkers
+    -- expect a valid object file (.o) to be generated for this module.
+    | ms_mod summary == gHC_PRIM -> Just <$> hscDesugar' (ms_location summary) (tc_result { tcg_binds = [] })
+    | otherwise                  -> Just <$> hscDesugar' (ms_location summary) tc_result
 
   -- Report the warnings from both typechecking and desugar together
   w <- getDiagnostics


=====================================
compiler/GHC/Tc/Module.hs
=====================================
@@ -975,6 +975,13 @@ checkHiBootIface'
   = do  { traceTc "checkHiBootIface" $ vcat
              [ ppr boot_type_env, ppr boot_exports ]
 
+        ; mod <- tcg_mod <$> getGblEnv
+
+        -- don't perform type-checking for ghc-prim:GHC.Prim module.
+        -- The interface (see ghcPrimIface in GHC.Iface.Load) exports entities
+        -- not found in the module code.
+        ; if mod == gHC_PRIM then pure [] else do {
+
         ; gre_env <- getGlobalRdrEnv
 
                 -- Check the exports of the boot module, one by one
@@ -994,7 +1001,7 @@ checkHiBootIface'
 
         ; failIfErrsM
 
-        ; return (fld_prs ++ dfun_prs) }
+        ; return (fld_prs ++ dfun_prs) }}
 
   where
     boot_dfun_names = map idName boot_dfuns


=====================================
hadrian/src/Rules/Documentation.hs
=====================================
@@ -12,10 +12,9 @@ import Hadrian.BuildPath
 import Hadrian.Haskell.Cabal
 import Hadrian.Haskell.Cabal.Type
 
-import Rules.Generate (ghcPrimDependencies)
 import Base
 import Context
-import Expression (getContextData, interpretInContext, (?), package)
+import Expression (getContextData, interpretInContext)
 import Flavour
 import Oracles.ModuleFiles
 import Oracles.Setting (topDirectory)
@@ -287,14 +286,7 @@ buildPackageDocumentation = do
         dep_pkgs <- sequence [pkgConfFile (context { way = haddockWay, Context.package = p})
                              | (p, _) <- haddocks]
 
-        -- `ghc-prim` has a source file for 'GHC.Prim' which is generated just
-        -- for Haddock. We need to 'union' (instead of '++') to avoid passing
-        -- 'GHC.PrimopWrappers' (which unfortunately shows up in both
-        -- `generatedSrcs` and `vanillaSrcs`) to Haddock twice.
-        generatedSrcs <- interpretInContext context (Expression.package ghcPrim ? ghcPrimDependencies)
-        vanillaSrcs <- hsSources context
-        let srcs = vanillaSrcs `union` generatedSrcs
-
+        srcs <- hsSources context
         need $ srcs ++ (map snd haddocks) ++ dep_pkgs
 
         statsFilesDir <- haddockStatsFilesDir


=====================================
libraries/ghc-prim/Setup.hs
=====================================
@@ -19,43 +19,14 @@ import System.Directory
 
 main :: IO ()
 main = do let hooks = simpleUserHooks {
-                  regHook = addPrimModule
-                          $ regHook simpleUserHooks,
                   buildHook = build_primitive_sources
                             $ buildHook simpleUserHooks,
-                  haddockHook = addPrimModuleForHaddock
-                              $ build_primitive_sources
+                  haddockHook = build_primitive_sources
                               $ haddockHook simpleUserHooks }
           defaultMainWithHooks hooks
 
 type Hook a = PackageDescription -> LocalBuildInfo -> UserHooks -> a -> IO ()
 
-addPrimModule :: Hook a -> Hook a
-addPrimModule f pd lbi uhs x =
-    do let -- I'm not sure which one of these we actually need to change.
-           -- It seems bad that there are two.
-           pd' = addPrimModuleToPD pd
-           lpd = addPrimModuleToPD (localPkgDescr lbi)
-           lbi' = lbi { localPkgDescr = lpd }
-       f pd' lbi' uhs x
-
-addPrimModuleForHaddock :: Hook a -> Hook a
-addPrimModuleForHaddock f pd lbi uhs x =
-    do let pc = withPrograms lbi
-           pc' = userSpecifyArgs "haddock" ["GHC/Prim.hs"] pc
-           lbi' = lbi { withPrograms = pc' }
-       f pd lbi' uhs x
-
-addPrimModuleToPD :: PackageDescription -> PackageDescription
-addPrimModuleToPD pd =
-    case library pd of
-    Just lib ->
-        let ems = fromJust (simpleParse "GHC.Prim") : exposedModules lib
-            lib' = lib { exposedModules = ems }
-        in pd { library = Just lib' }
-    Nothing ->
-        error "Expected a library, but none found"
-
 build_primitive_sources :: Hook a -> Hook a
 build_primitive_sources f pd lbi uhs x
  = do when (compilerFlavor (compiler lbi) == GHC) $ do


=====================================
libraries/ghc-prim/ghc-prim.cabal
=====================================
@@ -53,6 +53,7 @@ Library
         GHC.Debug
         GHC.Magic
         GHC.Magic.Dict
+        GHC.Prim
         GHC.Prim.Ext
         GHC.Prim.Panic
         GHC.Prim.Exception
@@ -61,8 +62,9 @@ Library
         GHC.Tuple
         GHC.Types
 
-    virtual-modules:
+    autogen-modules:
         GHC.Prim
+        GHC.PrimopWrappers
 
     -- OS Specific
     if os(windows)



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d8f8a1c387b39d3284597b229916cdd0f957c5c0
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/20241107/92ed133c/attachment-0001.html>


More information about the ghc-commits mailing list