Matthew Pickering pushed to branch wip/t26087 at Glasgow Haskell Compiler / GHC

Commits:

5 changed files:

Changes:

  • compiler/GHC/Unit/Module/Graph.hs
    ... ... @@ -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
     
    

  • testsuite/tests/splice-imports/T26087.stderr
    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
    +

  • testsuite/tests/splice-imports/T26087A.hs
    1
    +{-# LANGUAGE ExplicitLevelImports #-}
    
    2
    +module T26087A where
    
    3
    +
    
    4
    +import quote T26087B

  • testsuite/tests/splice-imports/T26087B.hs
    1
    +{-# LANGUAGE ExplicitLevelImports, TemplateHaskell #-}
    
    2
    +module T26087B where
    
    3
    +
    
    4
    +import T26087A

  • testsuite/tests/splice-imports/all.T
    ... ... @@ -46,3 +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('T26087', [], multimod_compile_fail, ['T26087A', ''])