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
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:
... | ... | @@ -4787,6 +4787,7 @@ checkValidTyCl tc |
4787 | 4787 | = setSrcSpan (getSrcSpan tc) $
|
4788 | 4788 | addTyConCtxt tc $
|
4789 | 4789 | recoverM recovery_code $
|
4790 | + checkNoErrs $
|
|
4790 | 4791 | do { traceTc "Starting validity for tycon" (ppr tc)
|
4791 | 4792 | ; checkValidTyCon tc
|
4792 | 4793 | ; checkTyConConsistentWithBoot tc -- See Note [TyCon boot consistency checking]
|
... | ... | @@ -4991,7 +4992,7 @@ checkValidTyCon tc |
4991 | 4992 | check_fields ((label, con1) :| other_fields)
|
4992 | 4993 | -- These fields all have the same name, but are from
|
4993 | 4994 | -- different constructors in the data type
|
4994 | - = recoverM (return ()) $ mapM_ checkOne other_fields
|
|
4995 | + = mapM_ checkOne other_fields
|
|
4995 | 4996 | -- Check that all the fields in the group have the same type
|
4996 | 4997 | -- NB: this check assumes that all the constructors of a given
|
4997 | 4998 | -- data type use the same type variables
|
... | ... | @@ -5001,8 +5002,9 @@ checkValidTyCon tc |
5001 | 5002 | lbl = flLabel label
|
5002 | 5003 | |
5003 | 5004 | checkOne (_, con2) -- Do it both ways to ensure they are structurally identical
|
5004 | - = do { checkFieldCompat lbl con1 con2 res1 res2 fty1 fty2
|
|
5005 | - ; checkFieldCompat lbl con2 con1 res2 res1 fty2 fty1 }
|
|
5005 | + = traverse addErrTc $ firstJust
|
|
5006 | + (checkFieldCompat lbl con1 con2 res1 res2 fty1 fty2)
|
|
5007 | + (checkFieldCompat lbl con2 con1 res2 res1 fty2 fty1)
|
|
5006 | 5008 | where
|
5007 | 5009 | res2 = dataConOrigResTy con2
|
5008 | 5010 | fty2 = dataConFieldType con2 lbl
|
... | ... | @@ -5027,10 +5029,13 @@ checkPartialRecordField all_cons fld |
5027 | 5029 | inst_tys = dataConResRepTyArgs con1
|
5028 | 5030 | |
5029 | 5031 | checkFieldCompat :: FieldLabelString -> DataCon -> DataCon
|
5030 | - -> Type -> Type -> Type -> Type -> TcM ()
|
|
5032 | + -> Type -> Type -> Type -> Type -> Maybe TcRnMessage
|
|
5031 | 5033 | checkFieldCompat fld con1 con2 res1 res2 fty1 fty2
|
5032 | - = do { checkTc (isJust mb_subst1) (TcRnCommonFieldResultTypeMismatch con1 con2 fld)
|
|
5033 | - ; checkTc (isJust mb_subst2) (TcRnCommonFieldTypeMismatch con1 con2 fld) }
|
|
5034 | + = if isNothing mb_subst1
|
|
5035 | + then Just $ TcRnCommonFieldResultTypeMismatch con1 con2 fld
|
|
5036 | + else if isNothing mb_subst2
|
|
5037 | + then Just $ TcRnCommonFieldTypeMismatch con1 con2 fld
|
|
5038 | + else Nothing
|
|
5034 | 5039 | where
|
5035 | 5040 | mb_subst1 = tcMatchTy res1 res2
|
5036 | 5041 | mb_subst2 = tcMatchTyX (expectJust mb_subst1) fty1 fty2
|
... | ... | @@ -2,10 +2,3 @@ CommonFieldTypeMismatch.hs:3:1: error: [GHC-91827] |
2 | 2 | • Constructors A1 and A2 give different types for field ‘fld’
|
3 | 3 | • In the data type declaration for ‘A’
|
4 | 4 | |
5 | -CommonFieldTypeMismatch.hs:4:8: error: [GHC-83865]
|
|
6 | - • Couldn't match type ‘[Char]’ with ‘Int’
|
|
7 | - Expected: Int
|
|
8 | - Actual: String
|
|
9 | - • In the expression: fld
|
|
10 | - In an equation for ‘fld’: fld A2 {fld = fld} = fld
|
|
11 | - |
1 | 1 | {-# LANGUAGE Haskell2010 #-}
|
2 | 2 | {-# LANGUAGE TypeFamilies #-}
|
3 | 3 | {-# LANGUAGE UnicodeSyntax #-}
|
4 | +{-# LANGUAGE AllowAmbiguousTypes #-}
|
|
4 | 5 | module T12803a where
|
5 | 6 | |
6 | 7 | type Constrd a = Num a ⇒ a
|
1 | - |
|
2 | -T12083a.hs:6:1: error: [GHC-91510]
|
|
1 | +T12083a.hs:7:1: error: [GHC-91510]
|
|
3 | 2 | • Illegal qualified type: Num a => a
|
4 | 3 | • In the type synonym declaration for ‘Constrd’
|
5 | 4 | Suggested fix:
|
6 | 5 | Perhaps you intended to use the ‘RankNTypes’ extension (implied by ‘ImpredicativeTypes’)
|
7 | 6 | |
8 | -T12083a.hs:10:26: error: [GHC-25709]
|
|
7 | +T12083a.hs:11:26: error: [GHC-25709]
|
|
9 | 8 | • Data constructor ‘ExistentiallyLost’ has existential type variables, a context, or a specialised result type
|
10 | 9 | ExistentiallyLost :: forall u. TC u => u -> ExistentiallyLost
|
11 | 10 | • In the definition of data constructor ‘ExistentiallyLost’
|
12 | 11 | In the data type declaration for ‘ExistentiallyLost’
|
13 | 12 | Suggested fix:
|
14 | 13 | Enable any of the following extensions: ‘ExistentialQuantification’ or ‘GADTs’
|
14 | + |
1 | 1 | {-# LANGUAGE MultiParamTypeClasses #-}
|
2 | +{-# LANGUAGE AllowAmbiguousTypes #-}
|
|
2 | 3 | module T9739 where
|
3 | 4 | |
4 | 5 | class Class3 a => Class1 a where
|
1 | - |
|
2 | -T9739.hs:4:1: error: [GHC-29210]
|
|
1 | +T9739.hs:5:1: error: [GHC-29210]
|
|
3 | 2 | • Superclass cycle for ‘Class1’
|
4 | 3 | one of whose superclasses is ‘Class3’
|
5 | 4 | one of whose superclasses is ‘Class1’
|
... | ... | @@ -7,10 +6,11 @@ T9739.hs:4:1: error: [GHC-29210] |
7 | 6 | Suggested fix:
|
8 | 7 | Perhaps you intended to use the ‘UndecidableSuperClasses’ extension
|
9 | 8 | |
10 | -T9739.hs:9:1: error: [GHC-29210]
|
|
9 | +T9739.hs:10:1: error: [GHC-29210]
|
|
11 | 10 | • Superclass cycle for ‘Class3’
|
12 | 11 | one of whose superclasses is ‘Class1’
|
13 | 12 | one of whose superclasses is ‘Class3’
|
14 | 13 | • In the class declaration for ‘Class3’
|
15 | 14 | Suggested fix:
|
16 | 15 | Perhaps you intended to use the ‘UndecidableSuperClasses’ extension
|
16 | + |