diff options
author | Vladislav Zavialov <vlad.z.4096@gmail.com> | 2018-10-15 13:52:12 -0400 |
---|---|---|
committer | Ben Gamari <ben@smart-cactus.org> | 2018-10-15 19:24:16 -0400 |
commit | 165d3d5ddaecc7dbe7f5ac051834a7619463efb0 (patch) | |
tree | 6ae7967d95ddc071a6dda7e3307f4a16cbf2229f /testsuite/tests/parser/should_compile | |
parent | 058c2813d882266309e8045af7a72eedecbf2dbb (diff) | |
download | haskell-165d3d5ddaecc7dbe7f5ac051834a7619463efb0.tar.gz |
Enable -Wcompat=error in the testsuite
Enabling -Werror=compat in the testsuite allows us to easily see the
impact that a new warning has on code. It also means that in the period
between adding the warning and making the actual breaking change, all
new test cases that are being added to the testsuite will be
forwards-compatible. This is good because it will make the actual
breaking change contain less irrelevant testsuite updates.
Things that -Wcompat warns about are things that are going to break in
the future, so we can be proactive and keep our testsuite
forwards-compatible.
This patch consists of two main changes:
* Add `TEST_HC_OPTS += -Werror=compat` to the testsuite configuration.
* Fix all broken test cases.
Test Plan: Validate
Reviewers: hvr, goldfire, bgamari, simonpj, RyanGlScott
Reviewed By: goldfire, RyanGlScott
Subscribers: rwbarton, carter
GHC Trac Issues: #15278
Differential Revision: https://phabricator.haskell.org/D5200
Diffstat (limited to 'testsuite/tests/parser/should_compile')
7 files changed, 162 insertions, 120 deletions
diff --git a/testsuite/tests/parser/should_compile/DumpRenamedAst.hs b/testsuite/tests/parser/should_compile/DumpRenamedAst.hs index bf3e372461..c617febd40 100644 --- a/testsuite/tests/parser/should_compile/DumpRenamedAst.hs +++ b/testsuite/tests/parser/should_compile/DumpRenamedAst.hs @@ -1,18 +1,20 @@ {-# LANGUAGE DataKinds, GADTs, PolyKinds, RankNTypes, TypeOperators, - TypeFamilies, StarIsType #-} + TypeFamilies #-} module DumpRenamedAst where +import Data.Kind (Type) + data Peano = Zero | Succ Peano type family Length (as :: [k]) :: Peano where Length (a : as) = Succ (Length as) Length '[] = Zero -data family Nat :: k -> k -> * +data family Nat :: k -> k -> Type -- Ensure that the `k` in the type pattern and `k` in the kind signature have -- the same binding site. -newtype instance Nat (a :: k -> *) :: (k -> *) -> * where +newtype instance Nat (a :: k -> Type) :: (k -> Type) -> Type where Nat :: (forall xx. f xx -> g xx) -> Nat f g main = putStrLn "hello" diff --git a/testsuite/tests/parser/should_compile/DumpRenamedAst.stderr b/testsuite/tests/parser/should_compile/DumpRenamedAst.stderr index d27e6d96e0..f20c450a9a 100644 --- a/testsuite/tests/parser/should_compile/DumpRenamedAst.stderr +++ b/testsuite/tests/parser/should_compile/DumpRenamedAst.stderr @@ -10,39 +10,39 @@ [((,) (NonRecursive) {Bag(Located (HsBind Name)): - [({ DumpRenamedAst.hs:18:1-23 } + [({ DumpRenamedAst.hs:20:1-23 } (FunBind {NameSet: []} - ({ DumpRenamedAst.hs:18:1-4 } + ({ DumpRenamedAst.hs:20:1-4 } {Name: DumpRenamedAst.main}) (MG (NoExt) - ({ DumpRenamedAst.hs:18:1-23 } - [({ DumpRenamedAst.hs:18:1-23 } + ({ DumpRenamedAst.hs:20:1-23 } + [({ DumpRenamedAst.hs:20:1-23 } (Match (NoExt) (FunRhs - ({ DumpRenamedAst.hs:18:1-4 } + ({ DumpRenamedAst.hs:20:1-4 } {Name: DumpRenamedAst.main}) (Prefix) (NoSrcStrict)) [] (GRHSs (NoExt) - [({ DumpRenamedAst.hs:18:6-23 } + [({ DumpRenamedAst.hs:20:6-23 } (GRHS (NoExt) [] - ({ DumpRenamedAst.hs:18:8-23 } + ({ DumpRenamedAst.hs:20:8-23 } (HsApp (NoExt) - ({ DumpRenamedAst.hs:18:8-15 } + ({ DumpRenamedAst.hs:20:8-15 } (HsVar (NoExt) - ({ DumpRenamedAst.hs:18:8-15 } + ({ DumpRenamedAst.hs:20:8-15 } {Name: System.IO.putStrLn}))) - ({ DumpRenamedAst.hs:18:17-23 } + ({ DumpRenamedAst.hs:20:17-23 } (HsLit (NoExt) (HsString @@ -59,13 +59,13 @@ [] [(TyClGroup (NoExt) - [({ DumpRenamedAst.hs:6:1-30 } + [({ DumpRenamedAst.hs:8:1-30 } (DataDecl (DataDeclRn (True) {NameSet: [{Name: DumpRenamedAst.Peano}]}) - ({ DumpRenamedAst.hs:6:6-10 } + ({ DumpRenamedAst.hs:8:6-10 } {Name: DumpRenamedAst.Peano}) (HsQTvs (HsQTvsRn @@ -81,10 +81,10 @@ []) (Nothing) (Nothing) - [({ DumpRenamedAst.hs:6:14-17 } + [({ DumpRenamedAst.hs:8:14-17 } (ConDeclH98 (NoExt) - ({ DumpRenamedAst.hs:6:14-17 } + ({ DumpRenamedAst.hs:8:14-17 } {Name: DumpRenamedAst.Zero}) ({ <no location info> } (False)) @@ -93,21 +93,21 @@ (PrefixCon []) (Nothing))) - ,({ DumpRenamedAst.hs:6:21-30 } + ,({ DumpRenamedAst.hs:8:21-30 } (ConDeclH98 (NoExt) - ({ DumpRenamedAst.hs:6:21-24 } + ({ DumpRenamedAst.hs:8:21-24 } {Name: DumpRenamedAst.Succ}) ({ <no location info> } (False)) [] (Nothing) (PrefixCon - [({ DumpRenamedAst.hs:6:26-30 } + [({ DumpRenamedAst.hs:8:26-30 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:6:26-30 } + ({ DumpRenamedAst.hs:8:26-30 } {Name: DumpRenamedAst.Peano})))]) (Nothing)))] ({ <no location info> } @@ -116,131 +116,131 @@ []) ,(TyClGroup (NoExt) - [({ DumpRenamedAst.hs:8:1-39 } + [({ DumpRenamedAst.hs:10:1-39 } (FamDecl (NoExt) (FamilyDecl (NoExt) (ClosedTypeFamily (Just - [({ DumpRenamedAst.hs:9:3-36 } + [({ DumpRenamedAst.hs:11:3-36 } (HsIB [{Name: a} ,{Name: as}] (FamEqn (NoExt) - ({ DumpRenamedAst.hs:9:3-8 } + ({ DumpRenamedAst.hs:11:3-8 } {Name: DumpRenamedAst.Length}) - [({ DumpRenamedAst.hs:9:10-17 } + [({ DumpRenamedAst.hs:11:10-17 } (HsParTy (NoExt) - ({ DumpRenamedAst.hs:9:11-16 } + ({ DumpRenamedAst.hs:11:11-16 } (HsOpTy (NoExt) - ({ DumpRenamedAst.hs:9:11 } + ({ DumpRenamedAst.hs:11:11 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:9:11 } + ({ DumpRenamedAst.hs:11:11 } {Name: a}))) - ({ DumpRenamedAst.hs:9:13 } + ({ DumpRenamedAst.hs:11:13 } {Name: :}) - ({ DumpRenamedAst.hs:9:15-16 } + ({ DumpRenamedAst.hs:11:15-16 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:9:15-16 } + ({ DumpRenamedAst.hs:11:15-16 } {Name: as})))))))] (Prefix) - ({ DumpRenamedAst.hs:9:21-36 } + ({ DumpRenamedAst.hs:11:21-36 } (HsAppTy (NoExt) - ({ DumpRenamedAst.hs:9:21-24 } + ({ DumpRenamedAst.hs:11:21-24 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:9:21-24 } + ({ DumpRenamedAst.hs:11:21-24 } {Name: DumpRenamedAst.Succ}))) - ({ DumpRenamedAst.hs:9:26-36 } + ({ DumpRenamedAst.hs:11:26-36 } (HsParTy (NoExt) - ({ DumpRenamedAst.hs:9:27-35 } + ({ DumpRenamedAst.hs:11:27-35 } (HsAppTy (NoExt) - ({ DumpRenamedAst.hs:9:27-32 } + ({ DumpRenamedAst.hs:11:27-32 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:9:27-32 } + ({ DumpRenamedAst.hs:11:27-32 } {Name: DumpRenamedAst.Length}))) - ({ DumpRenamedAst.hs:9:34-35 } + ({ DumpRenamedAst.hs:11:34-35 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:9:34-35 } + ({ DumpRenamedAst.hs:11:34-35 } {Name: as})))))))))))) - ,({ DumpRenamedAst.hs:10:3-24 } + ,({ DumpRenamedAst.hs:12:3-24 } (HsIB [] (FamEqn (NoExt) - ({ DumpRenamedAst.hs:10:3-8 } + ({ DumpRenamedAst.hs:12:3-8 } {Name: DumpRenamedAst.Length}) - [({ DumpRenamedAst.hs:10:10-12 } + [({ DumpRenamedAst.hs:12:10-12 } (HsExplicitListTy (NoExt) (Promoted) []))] (Prefix) - ({ DumpRenamedAst.hs:10:21-24 } + ({ DumpRenamedAst.hs:12:21-24 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:10:21-24 } + ({ DumpRenamedAst.hs:12:21-24 } {Name: DumpRenamedAst.Zero}))))))])) - ({ DumpRenamedAst.hs:8:13-18 } + ({ DumpRenamedAst.hs:10:13-18 } {Name: DumpRenamedAst.Length}) (HsQTvs (HsQTvsRn [{Name: k}] {NameSet: []}) - [({ DumpRenamedAst.hs:8:21-29 } + [({ DumpRenamedAst.hs:10:21-29 } (KindedTyVar (NoExt) - ({ DumpRenamedAst.hs:8:21-22 } + ({ DumpRenamedAst.hs:10:21-22 } {Name: as}) - ({ DumpRenamedAst.hs:8:27-29 } + ({ DumpRenamedAst.hs:10:27-29 } (HsListTy (NoExt) - ({ DumpRenamedAst.hs:8:28 } + ({ DumpRenamedAst.hs:10:28 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:8:28 } + ({ DumpRenamedAst.hs:10:28 } {Name: k})))))))]) (Prefix) - ({ DumpRenamedAst.hs:8:32-39 } + ({ DumpRenamedAst.hs:10:32-39 } (KindSig (NoExt) - ({ DumpRenamedAst.hs:8:35-39 } + ({ DumpRenamedAst.hs:10:35-39 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:8:35-39 } + ({ DumpRenamedAst.hs:10:35-39 } {Name: DumpRenamedAst.Peano}))))) (Nothing))))] [] []) ,(TyClGroup (NoExt) - [({ DumpRenamedAst.hs:12:1-30 } + [({ DumpRenamedAst.hs:14:1-33 } (FamDecl (NoExt) (FamilyDecl (NoExt) (DataFamily) - ({ DumpRenamedAst.hs:12:13-15 } + ({ DumpRenamedAst.hs:14:13-15 } {Name: DumpRenamedAst.Nat}) (HsQTvs (HsQTvsRn @@ -249,34 +249,36 @@ []}) []) (Prefix) - ({ DumpRenamedAst.hs:12:17-30 } + ({ DumpRenamedAst.hs:14:17-33 } (KindSig (NoExt) - ({ DumpRenamedAst.hs:12:20-30 } + ({ DumpRenamedAst.hs:14:20-33 } (HsFunTy (NoExt) - ({ DumpRenamedAst.hs:12:20 } + ({ DumpRenamedAst.hs:14:20 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:12:20 } + ({ DumpRenamedAst.hs:14:20 } {Name: k}))) - ({ DumpRenamedAst.hs:12:25-30 } + ({ DumpRenamedAst.hs:14:25-33 } (HsFunTy (NoExt) - ({ DumpRenamedAst.hs:12:25 } + ({ DumpRenamedAst.hs:14:25 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:12:25 } + ({ DumpRenamedAst.hs:14:25 } {Name: k}))) - ({ DumpRenamedAst.hs:12:30 } - (HsStarTy + ({ DumpRenamedAst.hs:14:30-33 } + (HsTyVar (NoExt) - (False))))))))) + (NotPromoted) + ({ DumpRenamedAst.hs:14:30-33 } + {Name: GHC.Types.Type}))))))))) (Nothing))))] [] - [({ DumpRenamedAst.hs:(15,1)-(16,45) } + [({ DumpRenamedAst.hs:(17,1)-(18,45) } (DataFamInstD (NoExt) (DataFamInstDecl @@ -285,33 +287,35 @@ ,{Name: a}] (FamEqn (NoExt) - ({ DumpRenamedAst.hs:15:18-20 } + ({ DumpRenamedAst.hs:17:18-20 } {Name: DumpRenamedAst.Nat}) - [({ DumpRenamedAst.hs:15:22-34 } + [({ DumpRenamedAst.hs:17:22-37 } (HsParTy (NoExt) - ({ DumpRenamedAst.hs:15:23-33 } + ({ DumpRenamedAst.hs:17:23-36 } (HsKindSig (NoExt) - ({ DumpRenamedAst.hs:15:23 } + ({ DumpRenamedAst.hs:17:23 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:15:23 } + ({ DumpRenamedAst.hs:17:23 } {Name: a}))) - ({ DumpRenamedAst.hs:15:28-33 } + ({ DumpRenamedAst.hs:17:28-36 } (HsFunTy (NoExt) - ({ DumpRenamedAst.hs:15:28 } + ({ DumpRenamedAst.hs:17:28 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:15:28 } + ({ DumpRenamedAst.hs:17:28 } {Name: k}))) - ({ DumpRenamedAst.hs:15:33 } - (HsStarTy + ({ DumpRenamedAst.hs:17:33-36 } + (HsTyVar (NoExt) - (False)))))))))] + (NotPromoted) + ({ DumpRenamedAst.hs:17:33-36 } + {Name: GHC.Types.Type})))))))))] (Prefix) (HsDataDefn (NoExt) @@ -320,35 +324,39 @@ []) (Nothing) (Just - ({ DumpRenamedAst.hs:15:39-51 } + ({ DumpRenamedAst.hs:17:42-60 } (HsFunTy (NoExt) - ({ DumpRenamedAst.hs:15:39-46 } + ({ DumpRenamedAst.hs:17:42-52 } (HsParTy (NoExt) - ({ DumpRenamedAst.hs:15:40-45 } + ({ DumpRenamedAst.hs:17:43-51 } (HsFunTy (NoExt) - ({ DumpRenamedAst.hs:15:40 } + ({ DumpRenamedAst.hs:17:43 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:15:40 } + ({ DumpRenamedAst.hs:17:43 } {Name: k}))) - ({ DumpRenamedAst.hs:15:45 } - (HsStarTy + ({ DumpRenamedAst.hs:17:48-51 } + (HsTyVar (NoExt) - (False))))))) - ({ DumpRenamedAst.hs:15:51 } - (HsStarTy + (NotPromoted) + ({ DumpRenamedAst.hs:17:48-51 } + {Name: GHC.Types.Type}))))))) + ({ DumpRenamedAst.hs:17:57-60 } + (HsTyVar (NoExt) - (False)))))) - [({ DumpRenamedAst.hs:16:3-45 } + (NotPromoted) + ({ DumpRenamedAst.hs:17:57-60 } + {Name: GHC.Types.Type})))))) + [({ DumpRenamedAst.hs:18:3-45 } (ConDeclGADT (NoExt) - [({ DumpRenamedAst.hs:16:3-5 } + [({ DumpRenamedAst.hs:18:3-5 } {Name: DumpRenamedAst.Nat})] - ({ DumpRenamedAst.hs:16:10-45 } + ({ DumpRenamedAst.hs:18:10-45 } (False)) (HsQTvs (HsQTvsRn @@ -359,73 +367,73 @@ []) (Nothing) (PrefixCon - [({ DumpRenamedAst.hs:16:10-34 } + [({ DumpRenamedAst.hs:18:10-34 } (HsParTy (NoExt) - ({ DumpRenamedAst.hs:16:11-33 } + ({ DumpRenamedAst.hs:18:11-33 } (HsForAllTy (NoExt) - [({ DumpRenamedAst.hs:16:18-19 } + [({ DumpRenamedAst.hs:18:18-19 } (UserTyVar (NoExt) - ({ DumpRenamedAst.hs:16:18-19 } + ({ DumpRenamedAst.hs:18:18-19 } {Name: xx})))] - ({ DumpRenamedAst.hs:16:22-33 } + ({ DumpRenamedAst.hs:18:22-33 } (HsFunTy (NoExt) - ({ DumpRenamedAst.hs:16:22-25 } + ({ DumpRenamedAst.hs:18:22-25 } (HsAppTy (NoExt) - ({ DumpRenamedAst.hs:16:22 } + ({ DumpRenamedAst.hs:18:22 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:16:22 } + ({ DumpRenamedAst.hs:18:22 } {Name: f}))) - ({ DumpRenamedAst.hs:16:24-25 } + ({ DumpRenamedAst.hs:18:24-25 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:16:24-25 } + ({ DumpRenamedAst.hs:18:24-25 } {Name: xx}))))) - ({ DumpRenamedAst.hs:16:30-33 } + ({ DumpRenamedAst.hs:18:30-33 } (HsAppTy (NoExt) - ({ DumpRenamedAst.hs:16:30 } + ({ DumpRenamedAst.hs:18:30 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:16:30 } + ({ DumpRenamedAst.hs:18:30 } {Name: g}))) - ({ DumpRenamedAst.hs:16:32-33 } + ({ DumpRenamedAst.hs:18:32-33 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:16:32-33 } + ({ DumpRenamedAst.hs:18:32-33 } {Name: xx})))))))))))]) - ({ DumpRenamedAst.hs:16:39-45 } + ({ DumpRenamedAst.hs:18:39-45 } (HsAppTy (NoExt) - ({ DumpRenamedAst.hs:16:39-43 } + ({ DumpRenamedAst.hs:18:39-43 } (HsAppTy (NoExt) - ({ DumpRenamedAst.hs:16:39-41 } + ({ DumpRenamedAst.hs:18:39-41 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:16:39-41 } + ({ DumpRenamedAst.hs:18:39-41 } {Name: DumpRenamedAst.Nat}))) - ({ DumpRenamedAst.hs:16:43 } + ({ DumpRenamedAst.hs:18:43 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:16:43 } + ({ DumpRenamedAst.hs:18:43 } {Name: f}))))) - ({ DumpRenamedAst.hs:16:45 } + ({ DumpRenamedAst.hs:18:45 } (HsTyVar (NoExt) (NotPromoted) - ({ DumpRenamedAst.hs:16:45 } + ({ DumpRenamedAst.hs:18:45 } {Name: g}))))) (Nothing)))] ({ <no location info> } @@ -450,7 +458,30 @@ (False) (True) (Nothing) - (Nothing)))] + (Nothing))) + ,({ DumpRenamedAst.hs:6:1-23 } + (ImportDecl + (NoExt) + (NoSourceText) + ({ DumpRenamedAst.hs:6:8-16 } + {ModuleName: Data.Kind}) + (Nothing) + (False) + (False) + (False) + (False) + (Nothing) + (Just + ((,) + (False) + ({ DumpRenamedAst.hs:6:18-23 } + [({ DumpRenamedAst.hs:6:19-22 } + (IEThingAbs + (NoExt) + ({ DumpRenamedAst.hs:6:19-22 } + (IEName + ({ DumpRenamedAst.hs:6:19-22 } + {Name: GHC.Types.Type})))))])))))] (Nothing) (Nothing))) diff --git a/testsuite/tests/parser/should_compile/T10379.hs b/testsuite/tests/parser/should_compile/T10379.hs index eb231c4415..aa62d17233 100644 --- a/testsuite/tests/parser/should_compile/T10379.hs +++ b/testsuite/tests/parser/should_compile/T10379.hs @@ -1,4 +1,5 @@ {-# LANGUAGE KindSignatures, GADTs, DataKinds #-} +{-# OPTIONS -Wno-star-is-type #-} module Foo where data Foo1 :: [*] -> * where diff --git a/testsuite/tests/parser/should_compile/T13747.hs b/testsuite/tests/parser/should_compile/T13747.hs index 749d8d2fc4..670005c756 100644 --- a/testsuite/tests/parser/should_compile/T13747.hs +++ b/testsuite/tests/parser/should_compile/T13747.hs @@ -3,11 +3,13 @@ module T13747 where +import Data.Kind (Type) + class C a where - type family TC a :: * + type family TC a :: Type class D a where - data family TD a :: * + data family TD a :: Type instance C Int where type instance TC Int = Int diff --git a/testsuite/tests/parser/should_compile/read026.hs b/testsuite/tests/parser/should_compile/read026.hs index 0605ca054d..5fc89f3df6 100644 --- a/testsuite/tests/parser/should_compile/read026.hs +++ b/testsuite/tests/parser/should_compile/read026.hs @@ -1,5 +1,7 @@ module ShouldCompile where +import Prelude hiding ((<>)) + (<>) :: (a -> Maybe b) -> (b -> Maybe c) -> (a -> Maybe c) (m1 <> m2) a1 = case m1 a1 of Nothing -> Nothing diff --git a/testsuite/tests/parser/should_compile/read050.hs b/testsuite/tests/parser/should_compile/read050.hs index d991bb01c7..9934310958 100644 --- a/testsuite/tests/parser/should_compile/read050.hs +++ b/testsuite/tests/parser/should_compile/read050.hs @@ -3,5 +3,7 @@ module Foo where -data Foo (a :: *) = Foo a +import Data.Kind (Type) + +data Foo (a :: Type) = Foo a diff --git a/testsuite/tests/parser/should_compile/read051.hs b/testsuite/tests/parser/should_compile/read051.hs index 3e95241862..6a4d3444e9 100644 --- a/testsuite/tests/parser/should_compile/read051.hs +++ b/testsuite/tests/parser/should_compile/read051.hs @@ -3,5 +3,7 @@ module Foo where -data Foo (a :: *) = Foo a +import Data.Kind (Type) + +data Foo (a :: Type) = Foo a |