[Git][ghc/ghc][master] Switch from HscSource to IsBootInterface for module lookup in GhcMake

Marge Bot gitlab at gitlab.haskell.org
Wed Jun 24 02:47:43 UTC 2020



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


Commits:
809caedf by John Ericson at 2020-06-23T22:47:37-04:00
Switch from HscSource to IsBootInterface for module lookup in GhcMake

We look up modules by their name, and not their contents. There is no
way to separately reference a signature vs regular module; you get what
you get. Only boot files can be referenced indepenently with `import {-#
SOURCE #-}`.

- - - - -


1 changed file:

- compiler/GHC/Driver/Make.hs


Changes:

=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -1917,7 +1917,7 @@ reachableBackwards mod summaries
   = [ node_payload node | node <- reachableG (transposeG graph) root ]
   where -- the rest just sets up the graph:
         (graph, lookup_node) = moduleGraphNodes False summaries
-        root  = expectJust "reachableBackwards" (lookup_node HsBootFile mod)
+        root  = expectJust "reachableBackwards" (lookup_node IsBoot mod)
 
 -- ---------------------------------------------------------------------------
 --
@@ -1960,7 +1960,7 @@ topSortModuleGraph drop_hs_boot_nodes module_graph mb_root_mod
             -- the specified module.  We do this by building a graph with
             -- the full set of nodes, and determining the reachable set from
             -- the specified node.
-            let root | Just node <- lookup_node HsSrcFile root_mod
+            let root | Just node <- lookup_node NotBoot root_mod
                      , graph `hasVertexG` node
                      = node
                      | otherwise
@@ -1976,21 +1976,18 @@ summaryNodeSummary :: SummaryNode -> ModSummary
 summaryNodeSummary = node_payload
 
 moduleGraphNodes :: Bool -> [ModSummary]
-  -> (Graph SummaryNode, HscSource -> ModuleName -> Maybe SummaryNode)
+  -> (Graph SummaryNode, IsBootInterface -> ModuleName -> Maybe SummaryNode)
 moduleGraphNodes drop_hs_boot_nodes summaries =
   (graphFromEdgedVerticesUniq nodes, lookup_node)
   where
     numbered_summaries = zip summaries [1..]
 
-    lookup_node :: HscSource -> ModuleName -> Maybe SummaryNode
+    lookup_node :: IsBootInterface -> ModuleName -> Maybe SummaryNode
     lookup_node hs_src mod = Map.lookup
-      GWIB
-        { gwib_mod = mod
-        , gwib_isBoot = hscSourceToIsBoot hs_src
-        }
+      (GWIB { gwib_mod = mod, gwib_isBoot = hs_src })
       node_map
 
-    lookup_key :: HscSource -> ModuleName -> Maybe Int
+    lookup_key :: IsBootInterface -> ModuleName -> Maybe Int
     lookup_key hs_src mod = fmap summaryNodeKey (lookup_node hs_src mod)
 
     node_map :: NodeMap SummaryNode
@@ -2010,11 +2007,11 @@ moduleGraphNodes drop_hs_boot_nodes summaries =
              -- Drop the hi-boot ones if told to do so
             , not (isBootSummary s == IsBoot && drop_hs_boot_nodes)
             , let out_keys = out_edge_keys hs_boot_key (map unLoc (ms_home_srcimps s)) ++
-                             out_edge_keys HsSrcFile   (map unLoc (ms_home_imps s)) ++
+                             out_edge_keys NotBoot     (map unLoc (ms_home_imps s)) ++
                              (-- see [boot-edges] below
                               if drop_hs_boot_nodes || ms_hsc_src s == HsBootFile
                               then []
-                              else case lookup_key HsBootFile (ms_mod_name s) of
+                              else case lookup_key IsBoot (ms_mod_name s) of
                                     Nothing -> []
                                     Just k  -> [k]) ]
 
@@ -2027,10 +2024,10 @@ moduleGraphNodes drop_hs_boot_nodes summaries =
     -- most up to date information.
 
     -- Drop hs-boot nodes by using HsSrcFile as the key
-    hs_boot_key | drop_hs_boot_nodes = HsSrcFile
-                | otherwise          = HsBootFile
+    hs_boot_key | drop_hs_boot_nodes = NotBoot -- is regular mod or signature
+                | otherwise          = IsBoot
 
-    out_edge_keys :: HscSource -> [ModuleName] -> [Int]
+    out_edge_keys :: IsBootInterface -> [ModuleName] -> [Int]
     out_edge_keys hi_boot ms = mapMaybe (lookup_key hi_boot) ms
         -- If we want keep_hi_boot_nodes, then we do lookup_key with
         -- IsBoot; else False



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/809caedffe489931efa8c96a60eaed6d7ff739b9
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/20200623/36ecf568/attachment-0001.html>


More information about the ghc-commits mailing list