[Git][ghc/ghc][master] Be more eager in TyCon boot validity checking
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Thu Aug 24 20:18:44 UTC 2023
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
1420b8cb by Antoine Leblanc at 2023-08-24T16:18:17-04:00
Be more eager in TyCon boot validity checking
This commit performs boot-file consistency checking for TyCons into
checkValidTyCl. This ensures that we eagerly catch any mismatches,
which prevents the compiler from seeing these inconsistencies and
panicking as a result.
See Note [TyCon boot consistency checking] in GHC.Tc.TyCl.
Fixes #16127
- - - - -
22 changed files:
- compiler/GHC/Tc/TyCl.hs
- compiler/GHC/Tc/TyCl/Utils.hs
- testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr
- + testsuite/tests/rename/should_fail/RnFail059.hs
- + testsuite/tests/rename/should_fail/RnFail059.hs-boot
- + testsuite/tests/rename/should_fail/RnFail059_aux.hs
- testsuite/tests/rename/should_fail/all.T
- testsuite/tests/rename/should_fail/rnfail055.stderr
- + testsuite/tests/rename/should_fail/rnfail059.stderr
- testsuite/tests/roles/should_fail/Roles12.stderr
- testsuite/tests/roles/should_fail/T9204.stderr
- + testsuite/tests/typecheck/T16127/T16127.hs
- + testsuite/tests/typecheck/T16127/T16127.hs-boot
- + testsuite/tests/typecheck/T16127/T16127.stderr
- + testsuite/tests/typecheck/T16127/T16127Helper.hs
- + testsuite/tests/typecheck/T16127/all.T
- testsuite/tests/typecheck/should_fail/T12035.stderr
- testsuite/tests/typecheck/should_fail/T12035j.stderr
- testsuite/tests/typecheck/should_fail/T12042.stderr
- testsuite/tests/typecheck/should_fail/T20588.stderr
- testsuite/tests/typecheck/should_fail/T20588c.stderr
- testsuite/tests/typecheck/should_fail/T3468.stderr
Changes:
=====================================
compiler/GHC/Tc/TyCl.hs
=====================================
@@ -48,6 +48,7 @@ import GHC.Tc.Zonk.TcType
import GHC.Tc.TyCl.Utils
import GHC.Tc.TyCl.Class
import {-# SOURCE #-} GHC.Tc.TyCl.Instance( tcInstDecls1 )
+import {-# SOURCE #-} GHC.Tc.Module( checkBootDeclM )
import GHC.Tc.Deriv (DerivInfo(..))
import GHC.Tc.Gen.HsType
import GHC.Tc.Instance.Class( AssocInstInfo(..) )
@@ -84,6 +85,7 @@ import GHC.Types.Name.Set
import GHC.Types.Name.Env
import GHC.Types.SrcLoc
import GHC.Types.SourceFile
+import GHC.Types.TypeEnv
import GHC.Types.Unique
import GHC.Types.Basic
import qualified GHC.LanguageExtensions as LangExt
@@ -93,6 +95,7 @@ import GHC.Data.Maybe
import GHC.Data.List.SetOps( minusList, equivClasses )
import GHC.Unit
+import GHC.Unit.Module.ModDetails
import GHC.Utils.Outputable
import GHC.Utils.Panic
@@ -209,7 +212,12 @@ tcTyClGroup (TyClGroup { group_tyclds = tyclds
-- Do it before Step 3 (adding implicit things) because the latter
-- expects well-formed TyCons
; traceTc "Starting validity check" (ppr tyclss)
- ; tyclss <- concatMapM checkValidTyCl tyclss
+ ; tyclss <- tcExtendTyConEnv tyclss $
+ -- NB: put the TyCons in the environment for validity checking,
+ -- as we might look them up in checkTyConConsistentWithBoot.
+ -- See Note [TyCon boot consistency checking].
+ concatMapM checkValidTyCl tyclss
+
; traceTc "Done validity check" (ppr tyclss)
; mapM_ (recoverM (return ()) . checkValidRoleAnnots role_annots) tyclss
-- See Note [Check role annotations in a second pass]
@@ -4327,6 +4335,7 @@ checkValidTyCl tc
recoverM recovery_code $
do { traceTc "Starting validity for tycon" (ppr tc)
; checkValidTyCon tc
+ ; checkTyConConsistentWithBoot tc -- See Note [TyCon boot consistency checking]
; traceTc "Done validity for tycon" (ppr tc)
; return [tc] }
where
@@ -4403,6 +4412,49 @@ Some notes:
-- T2 { f1 :: c, f2 :: c, f3 ::Int } :: T
-- Here we do not complain about f1,f2 because they are existential
+-- | Check that a 'TyCon' is consistent with the one in the hs-boot file,
+-- if any.
+--
+-- See Note [TyCon boot consistency checking].
+checkTyConConsistentWithBoot :: TyCon -> TcM ()
+checkTyConConsistentWithBoot tc =
+ do { gbl_env <- getGblEnv
+ ; let name = tyConName tc
+ real_thing = ATyCon tc
+ boot_info = tcg_self_boot gbl_env
+ boot_type_env = case boot_info of
+ NoSelfBoot -> emptyTypeEnv
+ SelfBoot boot_details -> md_types boot_details
+ m_boot_info = lookupTypeEnv boot_type_env name
+ ; case m_boot_info of
+ Nothing -> return ()
+ Just boot_thing -> checkBootDeclM HsBoot boot_thing real_thing
+ }
+
+{- Note [TyCon boot consistency checking]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+We want to throw an error when A.hs and A.hs-boot define a TyCon inconsistently,
+e.g.
+
+ -- A.hs-boot
+ type D :: Type
+ data D
+
+ -- A.hs
+ data D (k :: Type) = MkD
+
+Here A.D and A[boot].D have different kinds, so we must error. In addition, we
+must error eagerly, lest other parts of the compiler witness this inconsistency
+(which was the subject of #16127). To achieve this, we call
+checkTyConIsConsistentWithBoot in checkValidTyCl, which is called in
+GHC.Tc.TyCl.tcTyClGroup.
+
+Note that, when calling checkValidTyCl, we must extend the TyCon environment.
+For example, we could end up comparing the RHS of two type synonym declarations
+to check they are consistent, and these RHS might mention some of the TyCons we
+are validity checking, so they need to be in the environment.
+-}
+
checkValidTyCon :: TyCon -> TcM ()
checkValidTyCon tc
| isPrimTyCon tc -- Happens when Haddock'ing GHC.Prim
=====================================
compiler/GHC/Tc/TyCl/Utils.hs
=====================================
@@ -1,4 +1,3 @@
-
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE TypeFamilies #-}
=====================================
testsuite/tests/indexed-types/should_fail/ClosedFam3.stderr
=====================================
@@ -1,39 +1,42 @@
ClosedFam3.hs-boot:7:1: error: [GHC-15843]
- Type constructor ‘Foo’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type Foo :: * -> *
- type family Foo a where
- Foo Int = Bool
- Foo Double = Char
- Boot file: type Foo :: * -> *
- type family Foo a where
- Foo Int = Bool
- Type family equations do not match:
- The number of equations differs.
+ • Type constructor ‘Foo’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type Foo :: * -> *
+ type family Foo a where
+ Foo Int = Bool
+ Foo Double = Char
+ Boot file: type Foo :: * -> *
+ type family Foo a where
+ Foo Int = Bool
+ Type family equations do not match:
+ The number of equations differs.
+ • In the type family declaration for ‘Foo’
ClosedFam3.hs-boot:10:1: error: [GHC-15843]
- Type constructor ‘Bar’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type Bar :: * -> *
- type family Bar a where
- Bar Int = Bool
- Bar Double = Double
- Boot file: type Bar :: * -> *
- type family Bar a where
- Bar Int = Bool
- Bar Double = Char
- Type family equations do not match:
- The third equations do not match.
- The equation right-hand sides don't match.
+ • Type constructor ‘Bar’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type Bar :: * -> *
+ type family Bar a where
+ Bar Int = Bool
+ Bar Double = Double
+ Boot file: type Bar :: * -> *
+ type family Bar a where
+ Bar Int = Bool
+ Bar Double = Char
+ Type family equations do not match:
+ The third equations do not match.
+ The equation right-hand sides don't match.
+ • In the type family declaration for ‘Bar’
ClosedFam3.hs-boot:15:1: error: [GHC-15843]
- Type constructor ‘Baz’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type Baz :: * -> *
- type family Baz a where
- Baz Int = Bool
- Boot file: type Baz :: forall k. k -> *
- type family Baz a where
- Baz Int = Bool
- The types have different kinds.
+ • Type constructor ‘Baz’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type Baz :: * -> *
+ type family Baz a where
+ Baz Int = Bool
+ Boot file: type Baz :: forall k. k -> *
+ type family Baz a where
+ Baz Int = Bool
+ The types have different kinds.
+ • In the type family declaration for ‘Baz’
=====================================
testsuite/tests/rename/should_fail/RnFail059.hs
=====================================
@@ -0,0 +1,8 @@
+{-# LANGUAGE Haskell2010 #-}
+module RnFail059 where
+
+import RnFail059_aux
+
+-- Id with different type
+f1 :: Int -> Float
+f1 = undefined
=====================================
testsuite/tests/rename/should_fail/RnFail059.hs-boot
=====================================
@@ -0,0 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
+module RnFail059 where
+
+f1 :: Float -> Int
=====================================
testsuite/tests/rename/should_fail/RnFail059_aux.hs
=====================================
@@ -0,0 +1,3 @@
+module RnFail059_aux where
+
+import {-# SOURCE #-} RnFail059
=====================================
testsuite/tests/rename/should_fail/all.T
=====================================
@@ -1,4 +1,3 @@
-
test('rnfail001', normal, compile_fail, [''])
test('rnfail002', normal, compile_fail, [''])
test('rnfail003', normal, compile_fail, [''])
@@ -59,6 +58,7 @@ test('rnfail055', [extra_files(['RnFail055.hs', 'RnFail055.hs-boot', 'RnFail055_
test('rnfail056', normal, compile_fail, [''])
test('rnfail057', normal, compile_fail, [''])
test('rnfail058', normal, compile_fail, [''])
+test('rnfail059', [extra_files(['RnFail059.hs', 'RnFail059.hs-boot', 'RnFail059_aux.hs'])], multimod_compile_fail, ['RnFail059', '-v0'])
test('rn_dup', normal, compile_fail, [''])
test('T495', normal, compile_fail, [''])
=====================================
testsuite/tests/rename/should_fail/rnfail055.stderr
=====================================
@@ -1,121 +1,146 @@
-
RnFail055.hs:2:73: warning: [GHC-53692] [-Wdeprecated-flags (in -Wdefault)]
-XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
RnFail055.hs-boot:2:73: warning: [GHC-53692] [-Wdeprecated-flags (in -Wdefault)]
-XDatatypeContexts is deprecated: It was widely considered a misfeature, and has been removed from the Haskell language.
-RnFail055.hs-boot:5:1: error: [GHC-11890]
- Identifier ‘f1’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: f1 :: Int -> Float
- Boot file: f1 :: Float -> Int
- The two types are different.
-
RnFail055.hs-boot:7:1: error: [GHC-15843]
- Type constructor ‘S1’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type S1 :: * -> * -> *
- type S1 a b = (a, b)
- Boot file: type S1 :: * -> * -> * -> *
- type S1 a b c = (a, b)
- The types have different kinds.
+ • Type constructor ‘S1’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type S1 :: * -> * -> *
+ type S1 a b = (a, b)
+ Boot file: type S1 :: * -> * -> * -> *
+ type S1 a b c = (a, b)
+ The types have different kinds.
+ • In the type synonym declaration for ‘S1’
RnFail055.hs-boot:9:1: error: [GHC-15843]
- Type constructor ‘S2’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type S2 :: * -> * -> *
- type S2 a b = forall a1. (a1, b)
- Boot file: type S2 :: * -> * -> *
- type S2 a b = forall b1. (a, b1)
- The roles do not match.
- NB: roles on abstract types default to ‘representational’ in hs-boot files.
+ • Type constructor ‘S2’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type S2 :: * -> * -> *
+ type S2 a b = forall a1. (a1, b)
+ Boot file: type S2 :: * -> * -> *
+ type S2 a b = forall b1. (a, b1)
+ The roles do not match.
+ NB: roles on abstract types default to ‘representational’ in hs-boot files.
+ • In the type synonym declaration for ‘S2’
RnFail055.hs-boot:13:1: error: [GHC-15843]
- Type constructor ‘T1’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type T1 :: * -> * -> *
- data T1 a b = T1 [b] [a]
- Boot file: type T1 :: * -> * -> *
- data T1 a b = T1 [a] [b]
- The constructors do not match: The types for ‘T1’ differ.
+ • Type constructor ‘T1’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type T1 :: * -> * -> *
+ data T1 a b = T1 [b] [a]
+ Boot file: type T1 :: * -> * -> *
+ data T1 a b = T1 [a] [b]
+ The constructors do not match: The types for ‘T1’ differ.
+ • In the data type declaration for ‘T1’
RnFail055.hs-boot:15:1: error: [GHC-15843]
- Type constructor ‘T2’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type role T2 representational nominal
- type T2 :: * -> * -> *
- data Eq b => T2 a b = T2 a
- Boot file: type role T2 nominal phantom
- type T2 :: * -> * -> *
- data Eq a => T2 a b = T2 a
- The roles do not match.
- NB: roles on abstract types default to ‘representational’ in hs-boot files.
- The datatype contexts do not match.
- The constructors do not match: The types for ‘T2’ differ.
+ • Type constructor ‘T2’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type role T2 representational nominal
+ type T2 :: * -> * -> *
+ data Eq b => T2 a b = T2 a
+ Boot file: type role T2 nominal phantom
+ type T2 :: * -> * -> *
+ data Eq a => T2 a b = T2 a
+ The roles do not match.
+ NB: roles on abstract types default to ‘representational’ in hs-boot files.
+ The datatype contexts do not match.
+ The constructors do not match: The types for ‘T2’ differ.
+ • In the data type declaration for ‘T2’
-RnFail055.hs-boot:17:11: error: [GHC-91999]
- ‘T3’ is exported by the hs-boot file, but not exported by the implementing module.
+RnFail055.hs-boot:17:1: error: [GHC-15843]
+ • Type constructor ‘T3’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type T3 :: *
+ data T3 = T3'
+ Boot file: type T3 :: *
+ data T3 = T3
+ The constructors do not match: The names ‘T3’ and ‘T3'’ differ.
+ • In the data type declaration for ‘T3’
-RnFail055.hs-boot:18:12: error: [GHC-91999]
- ‘T3'’ is exported by the hs-boot file, but not exported by the implementing module.
+RnFail055.hs-boot:18:1: error: [GHC-15843]
+ • Type constructor ‘T3'’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type T3' :: *
+ data T3' = T3
+ Boot file: type T3' :: *
+ data T3' = T3'
+ The constructors do not match: The names ‘T3'’ and ‘T3’ differ.
+ • In the data type declaration for ‘T3'’
RnFail055.hs-boot:22:1: error: [GHC-15843]
- Type constructor ‘T5’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type T5 :: * -> *
- data T5 a = T5 {field5 :: a}
- Boot file: type T5 :: * -> *
- data T5 a = T5 a
- The constructors do not match:
- The record label lists for ‘T5’ differ.
+ • Type constructor ‘T5’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type T5 :: * -> *
+ data T5 a = T5 {field5 :: a}
+ Boot file: type T5 :: * -> *
+ data T5 a = T5 a
+ The constructors do not match:
+ The record label lists for ‘T5’ differ.
+ • In the data type declaration for ‘T5’
RnFail055.hs-boot:24:1: error: [GHC-15843]
- Type constructor ‘T6’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type T6 :: *
- data T6 = T6 Int
- Boot file: type T6 :: *
- data T6 = T6 !Int
- The constructors do not match:
- The strictness annotations for ‘T6’ differ.
+ • Type constructor ‘T6’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type T6 :: *
+ data T6 = T6 Int
+ Boot file: type T6 :: *
+ data T6 = T6 !Int
+ The constructors do not match:
+ The strictness annotations for ‘T6’ differ.
+ • In the data type declaration for ‘T6’
RnFail055.hs-boot:26:1: error: [GHC-15843]
- Type constructor ‘T7’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type role T7 phantom
- type T7 :: * -> *
- data T7 a = forall a1. T7 a1
- Boot file: type T7 :: * -> *
- data T7 a = forall b. T7 a
- The roles do not match.
- NB: roles on abstract types default to ‘representational’ in hs-boot files.
- The constructors do not match: The types for ‘T7’ differ.
+ • Type constructor ‘T7’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type role T7 phantom
+ type T7 :: * -> *
+ data T7 a = forall a1. T7 a1
+ Boot file: type T7 :: * -> *
+ data T7 a = forall b. T7 a
+ The roles do not match.
+ NB: roles on abstract types default to ‘representational’ in hs-boot files.
+ The constructors do not match: The types for ‘T7’ differ.
+ • In the data type declaration for ‘T7’
-RnFail055.hs-boot:28:22: error: [GHC-91999]
- ‘RnFail055.m1’ is exported by the hs-boot file, but not exported by the implementing module.
+RnFail055.hs-boot:28:1: error: [GHC-15843]
+ • Class ‘C1’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type C1 :: * -> * -> Constraint
+ class C1 a b
+ Boot file: type C1 :: * -> * -> Constraint
+ class C1 a b where
+ RnFail055.m1 :: a -> b
+ {-# MINIMAL m1 #-}
+ The class methods do not match:
+ The number of class methods differs.
+ • In the class declaration for ‘C1’
RnFail055.hs-boot:29:1: error: [GHC-15843]
- Class ‘C2’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type C2 :: * -> * -> Constraint
- class C2 a b where
- m2 :: a -> b
- m2' :: a -> b
- {-# MINIMAL m2, m2' #-}
- Boot file: type C2 :: * -> * -> Constraint
- class C2 a b where
- m2 :: a -> b
- {-# MINIMAL m2 #-}
- The class methods do not match:
- The number of class methods differs.
- The MINIMAL pragmas are not compatible.
+ • Class ‘C2’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type C2 :: * -> * -> Constraint
+ class C2 a b where
+ m2 :: a -> b
+ m2' :: a -> b
+ {-# MINIMAL m2, m2' #-}
+ Boot file: type C2 :: * -> * -> Constraint
+ class C2 a b where
+ m2 :: a -> b
+ {-# MINIMAL m2 #-}
+ The class methods do not match:
+ The number of class methods differs.
+ The MINIMAL pragmas are not compatible.
+ • In the class declaration for ‘C2’
RnFail055.hs-boot:30:1: error: [GHC-15843]
- Class ‘C3’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type C3 :: * -> Constraint
- class (Eq a, Ord a) => C3 a
- Boot file: type C3 :: * -> Constraint
- class (Ord a, Eq a) => C3 a
- The superclass constraints do not match.
+ • Class ‘C3’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type C3 :: * -> Constraint
+ class (Eq a, Ord a) => C3 a
+ Boot file: type C3 :: * -> Constraint
+ class (Ord a, Eq a) => C3 a
+ The superclass constraints do not match.
+ • In the class declaration for ‘C3’
=====================================
testsuite/tests/rename/should_fail/rnfail059.stderr
=====================================
@@ -0,0 +1,6 @@
+RnFail059.hs-boot:4:1: error: [GHC-11890]
+ Identifier ‘f1’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: f1 :: Int -> Float
+ Boot file: f1 :: Float -> Int
+ The two types are different.
=====================================
testsuite/tests/roles/should_fail/Roles12.stderr
=====================================
@@ -1,11 +1,12 @@
Roles12.hs:6:1: error: [GHC-15843]
- Type constructor ‘T’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type role T phantom
- type T :: * -> *
- data T a
- Boot file: type T :: * -> *
- data T a
- The roles do not match.
- NB: roles on abstract types default to ‘representational’ in hs-boot files.
+ • Type constructor ‘T’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type role T phantom
+ type T :: * -> *
+ data T a
+ Boot file: type T :: * -> *
+ data T a
+ The roles do not match.
+ NB: roles on abstract types default to ‘representational’ in hs-boot files.
+ • In the data type declaration for ‘T’
=====================================
testsuite/tests/roles/should_fail/T9204.stderr
=====================================
@@ -1,11 +1,12 @@
T9204.hs:7:1: error: [GHC-15843]
- Type constructor ‘D’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type role D phantom
- type D :: * -> *
- data D a
- Boot file: type D :: * -> *
- data D a
- The roles do not match.
- NB: roles on abstract types default to ‘representational’ in hs-boot files.
+ • Type constructor ‘D’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type role D phantom
+ type D :: * -> *
+ data D a
+ Boot file: type D :: * -> *
+ data D a
+ The roles do not match.
+ NB: roles on abstract types default to ‘representational’ in hs-boot files.
+ • In the data type declaration for ‘D’
=====================================
testsuite/tests/typecheck/T16127/T16127.hs
=====================================
@@ -0,0 +1,8 @@
+module T16127 where
+
+import T16127Helper
+
+data E a
+
+g :: E ()
+g = _
=====================================
testsuite/tests/typecheck/T16127/T16127.hs-boot
=====================================
@@ -0,0 +1,3 @@
+module T16127 where
+
+data E s a
=====================================
testsuite/tests/typecheck/T16127/T16127.stderr
=====================================
@@ -0,0 +1,14 @@
+[1 of 3] Compiling T16127[boot] ( T16127.hs-boot, T16127.o-boot )
+[2 of 3] Compiling T16127Helper ( T16127Helper.hs, T16127Helper.o )
+[3 of 3] Compiling T16127 ( T16127.hs, T16127.o )
+
+T16127.hs-boot:3:1: [GHC-15843]
+ Type constructor ‘E’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type role E phantom
+ type E :: forall {k}. k -> *
+ data E a
+ Boot file: type E :: forall {k} {k1}. k -> k1 -> *
+ data E s a
+ The types have different kinds.
+ In the data type declaration for ‘E’
=====================================
testsuite/tests/typecheck/T16127/T16127Helper.hs
=====================================
@@ -0,0 +1,6 @@
+module T16127Helper where
+
+import {-# SOURCE #-} T16127
+
+f :: E () ()
+f = undefined
=====================================
testsuite/tests/typecheck/T16127/all.T
=====================================
@@ -0,0 +1 @@
+test('T16127', normal, multimod_compile_fail, ['T16127', ''])
=====================================
testsuite/tests/typecheck/should_fail/T12035.stderr
=====================================
@@ -1,8 +1,9 @@
T12035.hs-boot:2:1: error: [GHC-15843]
- Type constructor ‘T’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type T :: *
- type T = Bool
- Boot file: type T :: *
- data T
+ • Type constructor ‘T’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type T :: *
+ type T = Bool
+ Boot file: type T :: *
+ data T
+ • In the type synonym declaration for ‘T’
=====================================
testsuite/tests/typecheck/should_fail/T12035j.stderr
=====================================
@@ -1,8 +1,9 @@
T12035.hs-boot:2:1: error: [GHC-15843]
- Type constructor ‘T’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type T :: *
- type T = Bool
- Boot file: type T :: *
- data T
+ • Type constructor ‘T’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type T :: *
+ type T = Bool
+ Boot file: type T :: *
+ data T
+ • In the type synonym declaration for ‘T’
=====================================
testsuite/tests/typecheck/should_fail/T12042.stderr
=====================================
@@ -3,9 +3,10 @@
[3 of 3] Compiling T12042 ( T12042.hs, T12042.o )
T12042.hs-boot:2:1: error: [GHC-15843]
- Type constructor ‘S’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type S :: *
- type S = R
- Boot file: type S :: *
- data S
+ • Type constructor ‘S’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type S :: *
+ type S = R
+ Boot file: type S :: *
+ data S
+ • In the type synonym declaration for ‘S’
=====================================
testsuite/tests/typecheck/should_fail/T20588.stderr
=====================================
@@ -1,29 +1,31 @@
T20588.hs-boot:8:1: error: [GHC-15843]
- Class ‘C’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type C :: * -> Constraint
- class C a where
- meth :: a -> a
- {-# MINIMAL meth #-}
- Boot file: type C :: * -> Constraint
- class C a where
- meth :: a -> a
- {-# MINIMAL meth #-}
- The class methods do not match:
- The default methods associated with ‘meth’ are different.
+ • Class ‘C’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type C :: * -> Constraint
+ class C a where
+ meth :: a -> a
+ {-# MINIMAL meth #-}
+ Boot file: type C :: * -> Constraint
+ class C a where
+ meth :: a -> a
+ {-# MINIMAL meth #-}
+ The class methods do not match:
+ The default methods associated with ‘meth’ are different.
+ • In the class declaration for ‘C’
T20588.hs-boot:11:1: error: [GHC-15843]
- Class ‘D’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type D :: * -> Constraint
- class D a where
- type T :: * -> *
- type family T a
- Default: Int
- Boot file: type D :: * -> Constraint
- class D a where
- type T :: * -> *
- type family T a
- The associated types do not match:
- The types of the second associated type default differ.
+ • Class ‘D’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type D :: * -> Constraint
+ class D a where
+ type T :: * -> *
+ type family T a
+ Default: Int
+ Boot file: type D :: * -> Constraint
+ class D a where
+ type T :: * -> *
+ type family T a
+ The associated types do not match:
+ The types of the second associated type default differ.
+ • In the class declaration for ‘D’
=====================================
testsuite/tests/typecheck/should_fail/T20588c.stderr
=====================================
@@ -1,14 +1,15 @@
T20588c.hs-boot:7:1: error: [GHC-15843]
- Class ‘C’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type C :: * -> Constraint
- class C a where
- meth :: a
- default meth :: Monoid a => a
- Boot file: type C :: * -> Constraint
- class C a where
- meth :: a
- {-# MINIMAL meth #-}
- The class methods do not match:
- The default methods associated with ‘meth’ are different.
+ • Class ‘C’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type C :: * -> Constraint
+ class C a where
+ meth :: a
+ default meth :: Monoid a => a
+ Boot file: type C :: * -> Constraint
+ class C a where
+ meth :: a
+ {-# MINIMAL meth #-}
+ The class methods do not match:
+ The default methods associated with ‘meth’ are different.
+ • In the class declaration for ‘C’
=====================================
testsuite/tests/typecheck/should_fail/T3468.stderr
=====================================
@@ -1,10 +1,11 @@
T3468.hs-boot:3:1: error: [GHC-15843]
- Type constructor ‘Tool’ has conflicting definitions in the module
- and its hs-boot file.
- Main module: type role Tool phantom
- type Tool :: * -> *
- data Tool d = forall a r. F a
- Boot file: type Tool :: *
- data Tool
- The types have different kinds.
+ • Type constructor ‘Tool’ has conflicting definitions in the module
+ and its hs-boot file.
+ Main module: type role Tool phantom
+ type Tool :: * -> *
+ data Tool d = forall a r. F a
+ Boot file: type Tool :: *
+ data Tool
+ The types have different kinds.
+ • In the data type declaration for ‘Tool’
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1420b8cb8a7d6196eec80dc5293864c780379560
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1420b8cb8a7d6196eec80dc5293864c780379560
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230824/2bb3d12f/attachment-0001.html>
More information about the ghc-commits
mailing list