[Git][ghc/ghc][master] Reject infix promoted data constructors without DataKinds

Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 13250d97 by Ryan Scott at 2025-08-26T09:31:59-04:00 Reject infix promoted data constructors without DataKinds In the rename, make sure to apply the same `DataKinds` checks for both `HsTyVar` (for prefix promoted data constructors) and `HsOpTy` (for infix promoted data constructors) alike. Fixes #26318. - - - - - 5 changed files: - compiler/GHC/Rename/HsType.hs - docs/users_guide/9.16.1-notes.rst - + testsuite/tests/typecheck/should_fail/T26318.hs - + testsuite/tests/typecheck/should_fail/T26318.stderr - testsuite/tests/typecheck/should_fail/all.T Changes: ===================================== compiler/GHC/Rename/HsType.hs ===================================== @@ -547,15 +547,7 @@ rnHsTyKi env tv@(HsTyVar _ ip (L loc rdr_name)) ; this_mod <- getModule ; when (nameIsLocalOrFrom this_mod name) $ checkThLocalTyName name - ; when (isDataConName name && not (isKindName name)) $ - -- Any use of a promoted data constructor name (that is not - -- specifically exempted by isKindName) is illegal without the use - -- of DataKinds. See Note [Checking for DataKinds] in - -- GHC.Tc.Validity. - checkDataKinds env tv - ; when (isDataConName name && not (isPromoted ip)) $ - -- NB: a prefix symbolic operator such as (:) is represented as HsTyVar. - addDiagnostic (TcRnUntickedPromotedThing $ UntickedConstructor Prefix name) + ; checkPromotedDataConName env tv Prefix ip name ; return (HsTyVar noAnn ip (L loc $ WithUserRdr rdr_name name), unitFV name) } rnHsTyKi env ty@(HsOpTy _ prom ty1 l_op ty2) @@ -567,8 +559,7 @@ rnHsTyKi env ty@(HsOpTy _ prom ty1 l_op ty2) ; (ty1', fvs2) <- rnLHsTyKi env ty1 ; (ty2', fvs3) <- rnLHsTyKi env ty2 ; res_ty <- mkHsOpTyRn prom (fmap (WithUserRdr op_rdr) l_op') fix ty1' ty2' - ; when (isDataConName op_name && not (isPromoted prom)) $ - addDiagnostic (TcRnUntickedPromotedThing $ UntickedConstructor Infix op_name) + ; checkPromotedDataConName env ty Infix prom op_name ; return (res_ty, plusFVs [fvs1, fvs2, fvs3]) } rnHsTyKi env (HsParTy _ ty) @@ -1670,6 +1661,30 @@ checkDataKinds env thing type_or_kind | isRnKindLevel env = KindLevel | otherwise = TypeLevel +-- | If a 'Name' is that of a promoted data constructor, perform various +-- validity checks on it. +checkPromotedDataConName :: + RnTyKiEnv -> + -- | The type that the 'Name' belongs to. This will always be an 'HsTyVar' + -- (for 'Prefix' names) or an 'HsOpTy' (for 'Infix' names). + HsType GhcPs -> + -- | Whether the type is written 'Prefix' or 'Infix'. + LexicalFixity -> + -- | Whether the name was written with an explicit promotion tick or not. + PromotionFlag -> + -- | The name to check. + Name -> + TcM () +checkPromotedDataConName env ty fixity ip name + = do when (isDataConName name && not (isKindName name)) $ + -- Any use of a promoted data constructor name (that is not + -- specifically exempted by isKindName) is illegal without the use + -- of DataKinds. See Note [Checking for DataKinds] in + -- GHC.Tc.Validity. + checkDataKinds env ty + when (isDataConName name && not (isPromoted ip)) $ + addDiagnostic (TcRnUntickedPromotedThing $ UntickedConstructor fixity name) + warnUnusedForAll :: OutputableBndrFlag flag 'Renamed => HsDocContext -> LHsTyVarBndr flag GhcRn -> FreeVars -> TcM () warnUnusedForAll doc (L loc tvb) used_names = ===================================== docs/users_guide/9.16.1-notes.rst ===================================== @@ -11,6 +11,11 @@ for specific guidance on migrating programs to this release. Language ~~~~~~~~ +- Fix a bug introduced in GHC 9.10 where GHC would erroneously accept infix uses + of promoted data constructors without enabling :extension:`DataKinds`. As a + result, you may need to enable :extension:`DataKinds` in code that did not + previously require it. + Compiler ~~~~~~~~ ===================================== testsuite/tests/typecheck/should_fail/T26318.hs ===================================== @@ -0,0 +1,15 @@ +{-# LANGUAGE GHC2021 #-} +{-# LANGUAGE NoDataKinds #-} +module T26318 where + +class C1 l +instance C1 (x : xs) + +class C2 l +instance C2 (x ': xs) + +class C3 l +instance C3 ((:) x xs) + +class C4 l +instance C4 ('(:) x xs) ===================================== testsuite/tests/typecheck/should_fail/T26318.stderr ===================================== @@ -0,0 +1,20 @@ +T26318.hs:6:16: error: [GHC-68567] + Illegal type: ‘x : xs’ + Suggested fix: + Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) + +T26318.hs:9:16: error: [GHC-68567] + Illegal type: ‘x ': xs’ + Suggested fix: + Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) + +T26318.hs:12:14: error: [GHC-68567] + Illegal type: ‘(:)’ + Suggested fix: + Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) + +T26318.hs:15:14: error: [GHC-68567] + Illegal type: ‘'(:)’ + Suggested fix: + Perhaps you intended to use the ‘DataKinds’ extension (implied by ‘UnliftedDatatypes’) + ===================================== testsuite/tests/typecheck/should_fail/all.T ===================================== @@ -741,3 +741,4 @@ test('T25325', normal, compile_fail, ['']) test('T25004', normal, compile_fail, ['']) test('T25004k', normal, compile_fail, ['']) test('T26004', normal, compile_fail, ['']) +test('T26318', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/13250d97c76b163262af3d1c2b88a224... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/13250d97c76b163262af3d1c2b88a224... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Marge Bot (@marge-bot)