
Sjoerd Visscher pushed to branch wip/T18570 at Glasgow Haskell Compiler / GHC Commits: 17c678ec by Sjoerd Visscher at 2025-06-30T15:25:34+02:00 Fix field type mismatch error handling - - - - - 6 changed files: - compiler/GHC/Tc/TyCl.hs - testsuite/tests/typecheck/should_fail/CommonFieldTypeMismatch.stderr - testsuite/tests/typecheck/should_fail/T12083a.hs - testsuite/tests/typecheck/should_fail/T12083a.stderr - testsuite/tests/typecheck/should_fail/T9739.hs - testsuite/tests/typecheck/should_fail/T9739.stderr Changes: ===================================== compiler/GHC/Tc/TyCl.hs ===================================== @@ -4787,6 +4787,7 @@ checkValidTyCl tc = setSrcSpan (getSrcSpan tc) $ addTyConCtxt tc $ recoverM recovery_code $ + checkNoErrs $ do { traceTc "Starting validity for tycon" (ppr tc) ; checkValidTyCon tc ; checkTyConConsistentWithBoot tc -- See Note [TyCon boot consistency checking] @@ -4991,7 +4992,7 @@ checkValidTyCon tc check_fields ((label, con1) :| other_fields) -- These fields all have the same name, but are from -- different constructors in the data type - = recoverM (return ()) $ mapM_ checkOne other_fields + = mapM_ checkOne other_fields -- Check that all the fields in the group have the same type -- NB: this check assumes that all the constructors of a given -- data type use the same type variables @@ -5001,8 +5002,9 @@ checkValidTyCon tc lbl = flLabel label checkOne (_, con2) -- Do it both ways to ensure they are structurally identical - = do { checkFieldCompat lbl con1 con2 res1 res2 fty1 fty2 - ; checkFieldCompat lbl con2 con1 res2 res1 fty2 fty1 } + = traverse addErrTc $ firstJust + (checkFieldCompat lbl con1 con2 res1 res2 fty1 fty2) + (checkFieldCompat lbl con2 con1 res2 res1 fty2 fty1) where res2 = dataConOrigResTy con2 fty2 = dataConFieldType con2 lbl @@ -5027,10 +5029,13 @@ checkPartialRecordField all_cons fld inst_tys = dataConResRepTyArgs con1 checkFieldCompat :: FieldLabelString -> DataCon -> DataCon - -> Type -> Type -> Type -> Type -> TcM () + -> Type -> Type -> Type -> Type -> Maybe TcRnMessage checkFieldCompat fld con1 con2 res1 res2 fty1 fty2 - = do { checkTc (isJust mb_subst1) (TcRnCommonFieldResultTypeMismatch con1 con2 fld) - ; checkTc (isJust mb_subst2) (TcRnCommonFieldTypeMismatch con1 con2 fld) } + = if isNothing mb_subst1 + then Just $ TcRnCommonFieldResultTypeMismatch con1 con2 fld + else if isNothing mb_subst2 + then Just $ TcRnCommonFieldTypeMismatch con1 con2 fld + else Nothing where mb_subst1 = tcMatchTy res1 res2 mb_subst2 = tcMatchTyX (expectJust mb_subst1) fty1 fty2 ===================================== testsuite/tests/typecheck/should_fail/CommonFieldTypeMismatch.stderr ===================================== @@ -2,10 +2,3 @@ CommonFieldTypeMismatch.hs:3:1: error: [GHC-91827] • Constructors A1 and A2 give different types for field ‘fld’ • In the data type declaration for ‘A’ -CommonFieldTypeMismatch.hs:4:8: error: [GHC-83865] - • Couldn't match type ‘[Char]’ with ‘Int’ - Expected: Int - Actual: String - • In the expression: fld - In an equation for ‘fld’: fld A2 {fld = fld} = fld - ===================================== testsuite/tests/typecheck/should_fail/T12083a.hs ===================================== @@ -1,6 +1,7 @@ {-# LANGUAGE Haskell2010 #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UnicodeSyntax #-} +{-# LANGUAGE AllowAmbiguousTypes #-} module T12803a where type Constrd a = Num a ⇒ a ===================================== testsuite/tests/typecheck/should_fail/T12083a.stderr ===================================== @@ -1,14 +1,14 @@ - -T12083a.hs:6:1: error: [GHC-91510] +T12083a.hs:7:1: error: [GHC-91510] • Illegal qualified type: Num a => a • In the type synonym declaration for ‘Constrd’ Suggested fix: Perhaps you intended to use the ‘RankNTypes’ extension (implied by ‘ImpredicativeTypes’) -T12083a.hs:10:26: error: [GHC-25709] +T12083a.hs:11:26: error: [GHC-25709] • Data constructor ‘ExistentiallyLost’ has existential type variables, a context, or a specialised result type ExistentiallyLost :: forall u. TC u => u -> ExistentiallyLost • In the definition of data constructor ‘ExistentiallyLost’ In the data type declaration for ‘ExistentiallyLost’ Suggested fix: Enable any of the following extensions: ‘ExistentialQuantification’ or ‘GADTs’ + ===================================== testsuite/tests/typecheck/should_fail/T9739.hs ===================================== @@ -1,4 +1,5 @@ {-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE AllowAmbiguousTypes #-} module T9739 where class Class3 a => Class1 a where ===================================== testsuite/tests/typecheck/should_fail/T9739.stderr ===================================== @@ -1,5 +1,4 @@ - -T9739.hs:4:1: error: [GHC-29210] +T9739.hs:5:1: error: [GHC-29210] • Superclass cycle for ‘Class1’ one of whose superclasses is ‘Class3’ one of whose superclasses is ‘Class1’ @@ -7,10 +6,11 @@ T9739.hs:4:1: error: [GHC-29210] Suggested fix: Perhaps you intended to use the ‘UndecidableSuperClasses’ extension -T9739.hs:9:1: error: [GHC-29210] +T9739.hs:10:1: error: [GHC-29210] • Superclass cycle for ‘Class3’ one of whose superclasses is ‘Class1’ one of whose superclasses is ‘Class3’ • In the class declaration for ‘Class3’ Suggested fix: Perhaps you intended to use the ‘UndecidableSuperClasses’ extension + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/17c678ec195acbad05742013cd335546... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/17c678ec195acbad05742013cd335546... You're receiving this email because of your account on gitlab.haskell.org.