Report deprecated fields bound by record wildcards when used
This commit ensures that we emit the appropriate warnings when a deprecated record field bound by a record wildcard is used. For example: module A where data Foo = Foo {x :: Int, y :: Bool, z :: Char} {-# DEPRECATED x "Don't use x" #-} {-# WARNING y "Don't use y" #-} module B where import A foo (Foo {..}) = x This will cause us to emit a "Don't use x" warning, with location the location of the record wildcard. Note that we don't warn about `y`, because it is unused in the RHS of `foo`. Fixes #23382
Showing
- compiler/GHC/Hs/Utils.hs 98 additions, 38 deletionscompiler/GHC/Hs/Utils.hs
- compiler/GHC/Rename/Bind.hs 1 addition, 1 deletioncompiler/GHC/Rename/Bind.hs
- compiler/GHC/Rename/Env.hs 16 additions, 114 deletionscompiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Expr.hs 1 addition, 1 deletioncompiler/GHC/Rename/Expr.hs
- compiler/GHC/Rename/Pat.hs 5 additions, 7 deletionscompiler/GHC/Rename/Pat.hs
- compiler/GHC/Rename/Utils.hs 150 additions, 6 deletionscompiler/GHC/Rename/Utils.hs
- compiler/GHC/Tc/Gen/Expr.hs 1 addition, 1 deletioncompiler/GHC/Tc/Gen/Expr.hs
- compiler/GHC/Types/Name/Set.hs 3 additions, 1 deletioncompiler/GHC/Types/Name/Set.hs
- libraries/ghc-prim/ghc-prim.cabal 108 additions, 0 deletionslibraries/ghc-prim/ghc-prim.cabal
- testsuite/tests/rename/should_compile/RecordWildCardDeprecation.hs 10 additions, 0 deletions.../tests/rename/should_compile/RecordWildCardDeprecation.hs
- testsuite/tests/rename/should_compile/RecordWildCardDeprecation.stderr 12 additions, 0 deletions...ts/rename/should_compile/RecordWildCardDeprecation.stderr
- testsuite/tests/rename/should_compile/RecordWildCardDeprecation_aux.hs 5 additions, 0 deletions...ts/rename/should_compile/RecordWildCardDeprecation_aux.hs
- testsuite/tests/rename/should_compile/all.T 1 addition, 0 deletionstestsuite/tests/rename/should_compile/all.T
Loading
Please register or sign in to comment