Skip to content
Snippets Groups Projects
Commit 1109896c authored by Adam Gundry's avatar Adam Gundry Committed by Marge Bot
Browse files

Make sure HasField use counts for -Wunused-top-binds

This is a small fix that depends on the previous commit, because it
corrected the rnExpr free variable calculation for HsVars which refer
to ambiguous fields. Fixes #19213.
parent 2521b041
No related branches found
No related tags found
No related merge requests found
......@@ -546,7 +546,9 @@ finish_ambiguous_selector lr@(L _ rdr) parent_type
Nothing -> failWithTc (fieldNotInType parent rdr) ;
Just gre ->
-- See Note [Unused name reporting and HasField] in GHC.Tc.Instance.Class
do { addUsedGRE True gre
; keepAlive (greMangledName gre)
; return (greMangledName gre) } } } } }
-- This field name really is ambiguous, so add a suitable "ambiguous
......
......@@ -30,7 +30,7 @@ import GHC.Builtin.Types
import GHC.Builtin.Types.Prim( eqPrimTyCon, eqReprPrimTyCon )
import GHC.Builtin.Names
import GHC.Types.Name.Reader( lookupGRE_FieldLabel )
import GHC.Types.Name.Reader( lookupGRE_FieldLabel, greMangledName )
import GHC.Types.SafeHaskell
import GHC.Types.Name ( Name, pprDefinedAt )
import GHC.Types.Var.Env ( VarEnv )
......@@ -672,6 +672,20 @@ may be solved by a user-supplied HasField instance. Similarly, if we
encounter a HasField constraint where the field is not a literal
string, or does not belong to the type, then we fall back on the
normal constraint solver behaviour.
Note [Unused name reporting and HasField]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
When a HasField constraint is solved by the type-checker, we must record a use
of the corresponding field name, as otherwise it might be reported as unused.
See #19213. We need to call keepAlive to add the name to the tcg_keep set,
which accumulates names used by the constraint solver, as described by
Note [Tracking unused binding and imports] in GHC.Tc.Types.
We need to call addUsedGRE as well because there may be a deprecation warning on
the field, which will be reported by addUsedGRE. But calling addUsedGRE without
keepAlive is not enough, because the field might be defined locally, and
addUsedGRE extends tcg_used_gres with imported GREs only.
-}
-- See Note [HasField instances]
......@@ -721,7 +735,9 @@ matchHasField dflags short_cut clas tys
-- cannot have an existentially quantified type), and
-- it must not be higher-rank.
; if not (isNaughtyRecordSelector sel_id) && isTauTy sel_ty
then do { addUsedGRE True gre
then do { -- See Note [Unused name reporting and HasField]
addUsedGRE True gre
; keepAlive (greMangledName gre)
; return OneInst { cir_new_theta = theta
, cir_mk_ev = mk_ev
, cir_what = BuiltinInstance } }
......
......@@ -680,6 +680,9 @@ We gather three sorts of usage information
Coercible solver updates tcg_keep's TcRef whenever it
encounters a use of `coerce` that crosses newtype boundaries.
(e) Record fields that are used to solve HasField constraints
(see Note [Unused name reporting and HasField] in GHC.Tc.Instance.Class)
The tcg_keep field is used in two distinct ways:
* Desugar.addExportFlagsAndRules. Where things like (a-c) are locally
......
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -Werror=unused-top-binds #-}
module DRFUnused (S(MkS), x, y) where
import GHC.Records
data S = MkS { foo :: Int }
data T = MkT { foo :: Int }
data U = MkU { foo :: Int }
-- Should count as a use of the foo field belonging to T, but not the others.
x = getField @"foo" (MkT 42)
-- Should count as a use of the foo field belonging to U, but not the others.
y = foo (MkU 42 :: U)
DRFUnused.hs:10:16: error: [-Wunused-top-binds (in -Wextra, -Wunused-binds), -Werror=unused-top-binds]
Defined but not used: ‘foo’
......@@ -45,3 +45,4 @@ test('NFS9156', normal, compile_fail, [''])
test('NFSDuplicate', normal, compile_fail, [''])
test('NFSExport', normal, compile_fail, [''])
test('T18999_NoDisambiguateRecordFields', normal, compile_fail, [''])
test('DRFUnused', normal, compile_fail, [''])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment