[Git][ghc/ghc][master] driver: Don't lose track of nodes when we fail to resolve cycles
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Fri Dec 8 10:48:34 UTC 2023
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
8db8d2fd by Zubin Duggal at 2023-12-08T05:47:54-05:00
driver: Don't lose track of nodes when we fail to resolve cycles
The nodes that take part in a cycle should include both hs-boot and hs files,
but when we fail to resolve a cycle, we were only counting the nodes from the
graph without boot files.
Fixes #24196
- - - - -
6 changed files:
- compiler/GHC/Driver/Make.hs
- + testsuite/tests/driver/T24196/T24196.stderr
- + testsuite/tests/driver/T24196/T24196A.hs
- + testsuite/tests/driver/T24196/T24196A.hs-boot
- + testsuite/tests/driver/T24196/T24196B.hs
- + testsuite/tests/driver/T24196/all.T
Changes:
=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -608,7 +608,7 @@ createBuildPlan mod_graph maybe_top_mod =
-- Now perform another toposort but just with these nodes and relevant hs-boot files.
-- The result should be acyclic, if it's not, then there's an unresolved cycle in the graph.
mresolved_cycle = collapseSCC (topSortWithBoot nodes)
- in acyclic ++ [maybe (UnresolvedCycle nodes) ResolvedCycle mresolved_cycle] ++ toBuildPlan sccs []
+ in acyclic ++ [either UnresolvedCycle ResolvedCycle mresolved_cycle] ++ toBuildPlan sccs []
(mg, lookup_node) = moduleGraphNodes False (mgModSummaries' mod_graph)
trans_deps_map = allReachable mg (mkNodeKey . node_payload)
@@ -639,12 +639,12 @@ createBuildPlan mod_graph maybe_top_mod =
get_boot_module m = case m of ModuleNode _ ms | HsSrcFile <- ms_hsc_src ms -> lookupModuleEnv boot_modules (ms_mod ms); _ -> Nothing
-- Any cycles should be resolved now
- collapseSCC :: [SCC ModuleGraphNode] -> Maybe [(Either ModuleGraphNode ModuleGraphNodeWithBootFile)]
+ collapseSCC :: [SCC ModuleGraphNode] -> Either [ModuleGraphNode] [(Either ModuleGraphNode ModuleGraphNodeWithBootFile)]
-- Must be at least two nodes, as we were in a cycle
- collapseSCC [AcyclicSCC node1, AcyclicSCC node2] = Just [toNodeWithBoot node1, toNodeWithBoot node2]
+ collapseSCC [AcyclicSCC node1, AcyclicSCC node2] = Right [toNodeWithBoot node1, toNodeWithBoot node2]
collapseSCC (AcyclicSCC node : nodes) = (toNodeWithBoot node :) <$> collapseSCC nodes
-- Cyclic
- collapseSCC _ = Nothing
+ collapseSCC nodes = Left (flattenSCCs nodes)
toNodeWithBoot :: ModuleGraphNode -> Either ModuleGraphNode ModuleGraphNodeWithBootFile
toNodeWithBoot mn =
=====================================
testsuite/tests/driver/T24196/T24196.stderr
=====================================
@@ -0,0 +1,4 @@
+Module graph contains a cycle:
+ module ‘T24196A’ (./T24196A.hs-boot)
+ imports module ‘T24196B’ (T24196B.hs)
+ which imports module ‘T24196A’ (./T24196A.hs-boot)
=====================================
testsuite/tests/driver/T24196/T24196A.hs
=====================================
@@ -0,0 +1 @@
+module T24196A where
=====================================
testsuite/tests/driver/T24196/T24196A.hs-boot
=====================================
@@ -0,0 +1,3 @@
+module T24196A where
+
+import T24196B
=====================================
testsuite/tests/driver/T24196/T24196B.hs
=====================================
@@ -0,0 +1,3 @@
+module T24196B where
+
+import {-# SOURCE #-} T24196A
=====================================
testsuite/tests/driver/T24196/all.T
=====================================
@@ -0,0 +1 @@
+test('T24196', extra_files(['T24196A.hs','T24196A.hs-boot','T24196B.hs']), multimod_compile_fail, ['T24196B',''])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8db8d2fd1c881032b1b360c032b6d9d072c11723
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8db8d2fd1c881032b1b360c032b6d9d072c11723
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/20231208/ce23548e/attachment-0001.html>
More information about the ghc-commits
mailing list