[Git][ghc/ghc][wip/splice-imports-2024] Some fixes

Matthew Pickering (@mpickering) gitlab at gitlab.haskell.org
Tue Nov 5 12:27:41 UTC 2024



Matthew Pickering pushed to branch wip/splice-imports-2024 at Glasgow Haskell Compiler / GHC


Commits:
b14e2a3a by Matthew Pickering at 2024-11-05T12:27:05+00:00
Some fixes

- - - - -


4 changed files:

- compiler/GHC/Driver/Errors/Ppr.hs
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Linker/Deps.hs
- compiler/GHC/Unit/Module/Graph.hs


Changes:

=====================================
compiler/GHC/Driver/Errors/Ppr.hs
=====================================
@@ -258,7 +258,8 @@ instance Diagnostic DriverMessage where
              go (m:ms) = (text "which imports" <+> ppr_node m) : go ms
 
         ppr_node :: ModuleGraphNode -> SDoc
-        ppr_node (ModuleNode _deps _uids lvl m) = text "module" <+> ppr_ms m <+> text "@"  <> ppr lvl
+        ppr_node (ModuleNode _deps _uids lvl m)
+          = text "module" <+> ppr_ms m <+> if lvl == zeroStage then empty else (text "@"  <> ppr lvl)
         ppr_node (InstantiationNode _uid u) = text "instantiated unit" <+> ppr u
         ppr_node (LinkNode uid _) = pprPanic "LinkNode should not be in a cycle" (ppr uid)
 


=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -1633,9 +1633,11 @@ downsweep_imports hsc_env old_summaries excl_mods allow_dup_roots (root_errs, ro
           -- Add a dependency on the HsBoot file if it exists
           -- This gets passed to the loopImports function which just ignores it if it
           -- can't be found.
-          [(ms_unitid ms, todoStage, NoPkgQual, GWIB (noLoc $ ms_mod_name ms) IsBoot) | NotBoot <- [isBootSummary ms] ] ++
+          [(ms_unitid ms, lvl, NoPkgQual, GWIB (noLoc $ ms_mod_name ms) IsBoot) | NotBoot <- [isBootSummary ms] ] ++
           [(ms_unitid ms, offsetStage lvl st, b, c) | (st, b, c) <- msDeps ms ]
 
+        -- Hacky..
+        offsetStage lvl _ | lvl >= ModuleStage 10 || lvl <= ModuleStage (-10) = lvl
         offsetStage lvl NormalStage = lvl
         offsetStage lvl QuoteStage  = incModuleStage lvl
         offsetStage lvl SpliceStage = decModuleStage lvl
@@ -2027,9 +2029,7 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env unit_state mod_graph
 
     (mg, lookup_node) = moduleGraphNodesZero unit_state mod_graph
 
-    ttMap = mkTransDepsZero unit_state mod_graph
-
-    mk_needed_set roots = pprTrace "ttMap" (ppr ttMap) $ Set.fromList $ map fst $ pprTraceIt "mk_needed_set" $ lefts $ map node_payload $ reachablesG2 mg (map (expectJust "needs_th" . lookup_node) (map Left roots))
+    mk_needed_set roots = Set.fromList $ map fst $ pprTraceIt "mk_needed_set" $ lefts $ map node_payload $ reachablesG2 mg (map (expectJust "needs_th" . lookup_node) (map Left roots))
 
     needs_obj_set, needs_bc_set :: Set.Set ModNodeKeyWithUid
     needs_obj_set = pprTraceIt "res_needs_obj_set" $ mk_needed_set (pprTraceIt "needs_obj_set" need_obj_set)


=====================================
compiler/GHC/Linker/Deps.hs
=====================================
@@ -123,7 +123,6 @@ get_link_deps opts pls maybe_normal_osuf span mods = do
             else do
               (pkgs, mmods) <- unzip <$> mapM get_mod_info all_home_mods
               return (catMaybes mmods, unionManyUniqDSets (init_pkg_set : pkgs))
-      pprTraceM "ld" (ppr (all_home_mods, mods_s, pkgs_s))
 
       let
         -- 2.  Exclude ones already linked


=====================================
compiler/GHC/Unit/Module/Graph.hs
=====================================
@@ -44,9 +44,9 @@ module GHC.Unit.Module.Graph
 
    , moduleGraphNodeUnitId
 
-   , ModNodeKeyWithUid(..)
+    , ModNodeKeyWithUid(..)
 
-   , ModuleStage
+   , ModuleStage(..)
    , zeroStage
    , todoStage
    , moduleStageToThLevel



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b14e2a3aad7fde9e0d39ecd255fc22c5a9c9a915
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/20241105/490b3765/attachment-0001.html>


More information about the ghc-commits mailing list