... |
... |
@@ -547,15 +547,7 @@ rnHsTyKi env tv@(HsTyVar _ ip (L loc rdr_name)) |
547
|
547
|
; this_mod <- getModule
|
548
|
548
|
; when (nameIsLocalOrFrom this_mod name) $
|
549
|
549
|
checkThLocalTyName name
|
550
|
|
- ; when (isDataConName name && not (isKindName name)) $
|
551
|
|
- -- Any use of a promoted data constructor name (that is not
|
552
|
|
- -- specifically exempted by isKindName) is illegal without the use
|
553
|
|
- -- of DataKinds. See Note [Checking for DataKinds] in
|
554
|
|
- -- GHC.Tc.Validity.
|
555
|
|
- checkDataKinds env tv
|
556
|
|
- ; when (isDataConName name && not (isPromoted ip)) $
|
557
|
|
- -- NB: a prefix symbolic operator such as (:) is represented as HsTyVar.
|
558
|
|
- addDiagnostic (TcRnUntickedPromotedThing $ UntickedConstructor Prefix name)
|
|
550
|
+ ; checkPromotedDataConName env tv Prefix ip name
|
559
|
551
|
; return (HsTyVar noAnn ip (L loc $ WithUserRdr rdr_name name), unitFV name) }
|
560
|
552
|
|
561
|
553
|
rnHsTyKi env ty@(HsOpTy _ prom ty1 l_op ty2)
|
... |
... |
@@ -567,8 +559,7 @@ rnHsTyKi env ty@(HsOpTy _ prom ty1 l_op ty2) |
567
|
559
|
; (ty1', fvs2) <- rnLHsTyKi env ty1
|
568
|
560
|
; (ty2', fvs3) <- rnLHsTyKi env ty2
|
569
|
561
|
; res_ty <- mkHsOpTyRn prom (fmap (WithUserRdr op_rdr) l_op') fix ty1' ty2'
|
570
|
|
- ; when (isDataConName op_name && not (isPromoted prom)) $
|
571
|
|
- addDiagnostic (TcRnUntickedPromotedThing $ UntickedConstructor Infix op_name)
|
|
562
|
+ ; checkPromotedDataConName env ty Infix prom op_name
|
572
|
563
|
; return (res_ty, plusFVs [fvs1, fvs2, fvs3]) }
|
573
|
564
|
|
574
|
565
|
rnHsTyKi env (HsParTy _ ty)
|
... |
... |
@@ -1670,6 +1661,30 @@ checkDataKinds env thing |
1670
|
1661
|
type_or_kind | isRnKindLevel env = KindLevel
|
1671
|
1662
|
| otherwise = TypeLevel
|
1672
|
1663
|
|
|
1664
|
+-- | If a 'Name' is that of a promoted data constructor, perform various
|
|
1665
|
+-- validity checks on it.
|
|
1666
|
+checkPromotedDataConName ::
|
|
1667
|
+ RnTyKiEnv ->
|
|
1668
|
+ -- | The type that the 'Name' belongs to. This will always be an 'HsTyVar'
|
|
1669
|
+ -- (for 'Prefix' names) or an 'HsOpTy' (for 'Infix' names).
|
|
1670
|
+ HsType GhcPs ->
|
|
1671
|
+ -- | Whether the type is written 'Prefix' or 'Infix'.
|
|
1672
|
+ LexicalFixity ->
|
|
1673
|
+ -- | Whether the name was written with an explicit promotion tick or not.
|
|
1674
|
+ PromotionFlag ->
|
|
1675
|
+ -- | The name to check.
|
|
1676
|
+ Name ->
|
|
1677
|
+ TcM ()
|
|
1678
|
+checkPromotedDataConName env ty fixity ip name
|
|
1679
|
+ = do when (isDataConName name && not (isKindName name)) $
|
|
1680
|
+ -- Any use of a promoted data constructor name (that is not
|
|
1681
|
+ -- specifically exempted by isKindName) is illegal without the use
|
|
1682
|
+ -- of DataKinds. See Note [Checking for DataKinds] in
|
|
1683
|
+ -- GHC.Tc.Validity.
|
|
1684
|
+ checkDataKinds env ty
|
|
1685
|
+ when (isDataConName name && not (isPromoted ip)) $
|
|
1686
|
+ addDiagnostic (TcRnUntickedPromotedThing $ UntickedConstructor fixity name)
|
|
1687
|
+
|
1673
|
1688
|
warnUnusedForAll :: OutputableBndrFlag flag 'Renamed
|
1674
|
1689
|
=> HsDocContext -> LHsTyVarBndr flag GhcRn -> FreeVars -> TcM ()
|
1675
|
1690
|
warnUnusedForAll doc (L loc tvb) used_names =
|