[Git][ghc/ghc][master] Implementation of the Deprecated Instances proposal #575

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Tue Aug 1 18:47:06 UTC 2023



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


Commits:
d2bedffd by Bartłomiej Cieślar at 2023-08-01T14:46:40-04:00
Implementation of the Deprecated Instances proposal #575

This commit implements the ability to deprecate certain instances,
which causes the compiler to emit the desired deprecation message
whenever they are instantiated. For example:

  module A where
  class C t where
  instance {-# DEPRECATED "dont use" #-} C Int where

  module B where
  import A
  f :: C t => t
  f = undefined
  g :: Int
  g = f -- "dont use" emitted here

The implementation is as follows:
  - In the parser, we parse deprecations/warnings attached to instances:

      instance {-# DEPRECATED "msg" #-} Show X
      deriving instance {-# WARNING "msg2" #-} Eq Y

    (Note that non-standalone deriving instance declarations do not support
    this mechanism.)

  - We store the resulting warning message in `ClsInstDecl` (respectively, `DerivDecl`).
    In `GHC.Tc.TyCl.Instance.tcClsInstDecl` (respectively, `GHC.Tc.Deriv.Utils.newDerivClsInst`),
    we pass on that information to `ClsInst` (and eventually store it in `IfaceClsInst` too).

  - Finally, when we solve a constraint using such an instance, in
    `GHC.Tc.Instance.Class.matchInstEnv`, we emit the appropriate warning
    that was stored in `ClsInst`.
    Note that we only emit a warning when the instance is used in a different module
    than it is defined, which keeps the behaviour in line with the deprecation of
    top-level identifiers.

Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com>

- - - - -


30 changed files:

- compiler/GHC/Core/InstEnv.hs
- compiler/GHC/Hs.hs
- compiler/GHC/Hs/Decls.hs
- compiler/GHC/Hs/ImpExp.hs
- compiler/GHC/Iface/Make.hs
- compiler/GHC/Iface/Syntax.hs
- compiler/GHC/IfaceToCore.hs
- compiler/GHC/Parser.y
- compiler/GHC/Parser/PostProcess.hs
- compiler/GHC/Rename/Env.hs
- compiler/GHC/Rename/Module.hs
- compiler/GHC/Rename/Names.hs
- compiler/GHC/Tc/Deriv.hs
- compiler/GHC/Tc/Deriv/Utils.hs
- compiler/GHC/Tc/Errors/Ppr.hs
- compiler/GHC/Tc/Errors/Types.hs
- compiler/GHC/Tc/Gen/Export.hs
- compiler/GHC/Tc/Instance/Class.hs
- compiler/GHC/Tc/Solver/Dict.hs
- compiler/GHC/Tc/TyCl/Instance.hs
- compiler/GHC/Tc/Types/Origin.hs
- compiler/GHC/Tc/Utils/Instantiate.hs
- compiler/GHC/ThToHs.hs
- compiler/GHC/Unit/Module/Warnings.hs
- docs/users_guide/exts/pragmas.rst
- testsuite/tests/haddock/should_compile_flag_haddock/T17544.stderr
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/printer/Makefile
- + testsuite/tests/printer/PprInstanceWarn.hs
- testsuite/tests/printer/all.T


The diff was not included because it is too large.


View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d2bedffdc07b766f01dfcd4fc73a3859305814f3

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d2bedffdc07b766f01dfcd4fc73a3859305814f3
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230801/0881035a/attachment.html>


More information about the ghc-commits mailing list