[Git][ghc/ghc][wip/backports-9.14] level imports: Fix infinite loop with cyclic module imports
Zubin pushed to branch wip/backports-9.14 at Glasgow Haskell Compiler / GHC Commits: 0e08b9ae by Matthew Pickering at 2025-11-04T20:56:40+05:30 level imports: Fix infinite loop with cyclic module imports I didn't anticipate that downsweep would run before we checked for cyclic imports. Therefore we need to use the reachability function which handles cyclic graphs. Fixes #26087 (cherry picked from commit 8b731e3c900291655a767123bcda55eddd63920c) - - - - - 5 changed files: - compiler/GHC/Unit/Module/Graph.hs - + testsuite/tests/splice-imports/T26087.stderr - + testsuite/tests/splice-imports/T26087A.hs - + testsuite/tests/splice-imports/T26087B.hs - testsuite/tests/splice-imports/all.T Changes: ===================================== compiler/GHC/Unit/Module/Graph.hs ===================================== @@ -866,7 +866,7 @@ mkTransZeroDeps = first graphReachability {- module graph is acyclic -} . module -- | Transitive dependencies, but with the stage that each module is required at. mkStageDeps :: [ModuleGraphNode] -> (ReachabilityIndex StageSummaryNode, (NodeKey, ModuleStage) -> Maybe StageSummaryNode) -mkStageDeps = first graphReachability . moduleGraphNodesStages +mkStageDeps = first cyclicGraphReachability . moduleGraphNodesStages type ZeroSummaryNode = Node Int ZeroScopeKey ===================================== testsuite/tests/splice-imports/T26087.stderr ===================================== @@ -0,0 +1,6 @@ +./T26087B.hs: error: [GHC-92213] + Module graph contains a cycle: + module ‘main:T26087B’ (./T26087B.hs) + imports module ‘main:T26087A’ (T26087A.hs) + which imports module ‘main:T26087B’ (./T26087B.hs) + ===================================== testsuite/tests/splice-imports/T26087A.hs ===================================== @@ -0,0 +1,4 @@ +{-# LANGUAGE ExplicitLevelImports #-} +module T26087A where + +import quote T26087B ===================================== testsuite/tests/splice-imports/T26087B.hs ===================================== @@ -0,0 +1,4 @@ +{-# LANGUAGE ExplicitLevelImports, TemplateHaskell #-} +module T26087B where + +import T26087A ===================================== testsuite/tests/splice-imports/all.T ===================================== @@ -46,7 +46,4 @@ test('SI35', compile_and_run, ['-package ghc']) test('SI36', [extra_files(["SI36_A.hs", "SI36_B1.hs", "SI36_B2.hs", "SI36_B3.hs", "SI36_C1.hs", "SI36_C2.hs", "SI36_C3.hs"])], multimod_compile_fail, ['SI36', '-v0']) -test('T26090', [], multimod_compile_fail, ['T26090', '-v0']) -test('ModuleExport', [], multimod_compile_fail, ['ModuleExport', '-v0']) -test('LevelImportExports', [], makefile_test, []) -test('DodgyLevelExport', [], multimod_compile, ['DodgyLevelExport', '-v0 -Wdodgy-exports']) +test('T26087', [], multimod_compile_fail, ['T26087A', '']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0e08b9aee6ce58fe7099f14ac1d7deaf... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0e08b9aee6ce58fe7099f14ac1d7deaf... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Zubin (@wz1000)