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

Commits:

3 changed files:

Changes:

  • compiler/GHC/Driver/Make.hs
    ... ... @@ -474,6 +474,10 @@ warnUnusedPackages us dflags mod_graph =
    474 474
                       ui <- lookupUnit us u
    
    475 475
                       -- Which are not explicitly used
    
    476 476
                       guard (Set.notMember (unitId ui) used_args)
    
    477
    +                  -- Exclude units with no exposed modules. This covers packages which only
    
    478
    +                  -- provide C object code or link flags (e.g. system-cxx-std-lib).
    
    479
    +                  -- See #24120.
    
    480
    +                  guard (not $ null $ unitExposedModules ui)
    
    477 481
                       return (unitId ui, unitPackageName ui, unitPackageVersion ui, flag)
    
    478 482
     
    
    479 483
             unusedArgs = sortOn (\(u,_,_,_) -> u) $ mapMaybe resolve (explicitUnits us)
    

  • testsuite/tests/driver/T24120.hs
    1
    +-- | This should not issue an @-Wunused-packages@ warning for @system-cxx-std-lib@.
    
    2
    +module Main where
    
    3
    +
    
    4
    +main :: IO ()
    
    5
    +main = putStrLn "hello world"

  • testsuite/tests/driver/all.T
    ... ... @@ -331,3 +331,4 @@ test('T24839', [unless(arch('x86_64') or arch('aarch64'), skip), extra_files(["t
    331 331
     test('t25150', [extra_files(["t25150"])], multimod_compile, ['Main.hs', '-v0 -working-dir t25150/dir a.c'])
    
    332 332
     test('T25382', normal, makefile_test, [])
    
    333 333
     test('T26018', req_c, makefile_test, [])
    
    334
    +test('T24120', normal, compile, ['-Wunused-packages -hide-all-packages -package base -package system-cxx-std-lib'])