Zubin pushed to branch ghc-9.14 at Glasgow Haskell Compiler / GHC
Commits:
-
0e08b9ae
by Matthew Pickering at 2025-11-04T20:56:40+05:30
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:
| ... | ... | @@ -866,7 +866,7 @@ mkTransZeroDeps = first graphReachability {- module graph is acyclic -} . module |
| 866 | 866 | |
| 867 | 867 | -- | Transitive dependencies, but with the stage that each module is required at.
|
| 868 | 868 | mkStageDeps :: [ModuleGraphNode] -> (ReachabilityIndex StageSummaryNode, (NodeKey, ModuleStage) -> Maybe StageSummaryNode)
|
| 869 | -mkStageDeps = first graphReachability . moduleGraphNodesStages
|
|
| 869 | +mkStageDeps = first cyclicGraphReachability . moduleGraphNodesStages
|
|
| 870 | 870 | |
| 871 | 871 | type ZeroSummaryNode = Node Int ZeroScopeKey
|
| 872 | 872 |
| 1 | +./T26087B.hs: error: [GHC-92213]
|
|
| 2 | + Module graph contains a cycle:
|
|
| 3 | + module ‘main:T26087B’ (./T26087B.hs)
|
|
| 4 | + imports module ‘main:T26087A’ (T26087A.hs)
|
|
| 5 | + which imports module ‘main:T26087B’ (./T26087B.hs)
|
|
| 6 | + |
| 1 | +{-# LANGUAGE ExplicitLevelImports #-}
|
|
| 2 | +module T26087A where
|
|
| 3 | + |
|
| 4 | +import quote T26087B |
| 1 | +{-# LANGUAGE ExplicitLevelImports, TemplateHaskell #-}
|
|
| 2 | +module T26087B where
|
|
| 3 | + |
|
| 4 | +import T26087A |
| ... | ... | @@ -46,7 +46,4 @@ test('SI35', |
| 46 | 46 | compile_and_run,
|
| 47 | 47 | ['-package ghc'])
|
| 48 | 48 | 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'])
|
| 49 | -test('T26090', [], multimod_compile_fail, ['T26090', '-v0'])
|
|
| 50 | -test('ModuleExport', [], multimod_compile_fail, ['ModuleExport', '-v0'])
|
|
| 51 | -test('LevelImportExports', [], makefile_test, [])
|
|
| 52 | -test('DodgyLevelExport', [], multimod_compile, ['DodgyLevelExport', '-v0 -Wdodgy-exports']) |
|
| 49 | +test('T26087', [], multimod_compile_fail, ['T26087A', '']) |