summaryrefslogtreecommitdiff
path: root/testsuite/tests/gadt
diff options
context:
space:
mode:
authorVladislav Zavialov <vlad.z.4096@gmail.com>2018-10-15 13:52:12 -0400
committerBen Gamari <ben@smart-cactus.org>2018-10-15 19:24:16 -0400
commit165d3d5ddaecc7dbe7f5ac051834a7619463efb0 (patch)
tree6ae7967d95ddc071a6dda7e3307f4a16cbf2229f /testsuite/tests/gadt
parent058c2813d882266309e8045af7a72eedecbf2dbb (diff)
downloadhaskell-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/gadt')
-rw-r--r--testsuite/tests/gadt/Gadt23_AST.hs4
-rw-r--r--testsuite/tests/gadt/Session.hs4
-rw-r--r--testsuite/tests/gadt/T14320.hs8
-rw-r--r--testsuite/tests/gadt/T9380.hs7
-rw-r--r--testsuite/tests/gadt/gadt20.hs6
-rw-r--r--testsuite/tests/gadt/gadt22.hs3
-rw-r--r--testsuite/tests/gadt/gadt8.hs4
-rw-r--r--testsuite/tests/gadt/josef.hs4
-rw-r--r--testsuite/tests/gadt/karl1.hs4
-rw-r--r--testsuite/tests/gadt/karl2.hs6
10 files changed, 34 insertions, 16 deletions
diff --git a/testsuite/tests/gadt/Gadt23_AST.hs b/testsuite/tests/gadt/Gadt23_AST.hs
index 75b07c7611..f1014a6a88 100644
--- a/testsuite/tests/gadt/Gadt23_AST.hs
+++ b/testsuite/tests/gadt/Gadt23_AST.hs
@@ -2,9 +2,11 @@
module Gadt23_AST where
+import Data.Kind (Type)
+
data Exp_;
-data AST :: * -> * -> * where
+data AST :: Type -> Type -> Type where
Var :: String -> AST Exp_ tag
Tag :: tag -> AST a tag -> AST a tag
diff --git a/testsuite/tests/gadt/Session.hs b/testsuite/tests/gadt/Session.hs
index 4403b6f869..2a9b3da6ef 100644
--- a/testsuite/tests/gadt/Session.hs
+++ b/testsuite/tests/gadt/Session.hs
@@ -4,6 +4,8 @@
module Main where
+import Data.Kind (Type)
+
data Zero = Zero
deriving (Show)
@@ -16,7 +18,7 @@ class TyNum a where
instance TyNum Zero where
instance (TyNum p) => TyNum (Succ p) where
-data List :: * -> * -> * where
+data List :: Type -> Type -> Type where
Nil :: List a Zero
Cons :: (TyNum p) => a -> List a p -> List a (Succ p)
diff --git a/testsuite/tests/gadt/T14320.hs b/testsuite/tests/gadt/T14320.hs
index 4acd4c8f63..77c68ee92e 100644
--- a/testsuite/tests/gadt/T14320.hs
+++ b/testsuite/tests/gadt/T14320.hs
@@ -2,14 +2,16 @@
module T14320
where
-data Exp :: * where
+import Data.Kind (Type)
+
+data Exp :: Type where
Lit :: (Int -> Exp)
-newtype TypedExp :: * -> * where
+newtype TypedExp :: Type -> Type where
TEGood :: forall a . (Exp -> (TypedExp a))
-- The only difference here is that the type is wrapped in parentheses,
-- but GHC 8.0.1 rejects this program
--
-newtype TypedExpToo :: * -> * where
+newtype TypedExpToo :: Type -> Type where
TEBad :: (forall a . (Exp -> (TypedExpToo a)))
diff --git a/testsuite/tests/gadt/T9380.hs b/testsuite/tests/gadt/T9380.hs
index 99dfab8477..9a2d0f7354 100644
--- a/testsuite/tests/gadt/T9380.hs
+++ b/testsuite/tests/gadt/T9380.hs
@@ -4,6 +4,7 @@
{-# LANGUAGE GADTs #-}
module Main where
+import Data.Kind (Type)
import Foreign
import Unsafe.Coerce
@@ -13,11 +14,11 @@ newtype S (a :: M) = S Int
data SomeS = forall a . SomeS (S a)
-data V0 :: M -> * where
+data V0 :: M -> Type where
V0A :: Int -> V0 A
V0B :: Double -> V0 B
-data V1 :: M -> * where
+data V1 :: M -> Type where
V1A :: Int -> V1 A
V1B :: Double -> V1 B
V1a :: () -> V1 a
@@ -65,4 +66,4 @@ test2 =
main = do
test0 -- no output at all
test1 -- A
- test2 -- O_o \ No newline at end of file
+ test2 -- O_o
diff --git a/testsuite/tests/gadt/gadt20.hs b/testsuite/tests/gadt/gadt20.hs
index c754831ce5..f2f4503c31 100644
--- a/testsuite/tests/gadt/gadt20.hs
+++ b/testsuite/tests/gadt/gadt20.hs
@@ -6,10 +6,12 @@
module Foo where
-data Pair :: (* -> *) -> * where
+import Data.Kind (Type)
+
+data Pair :: (Type -> Type) -> Type where
Pair :: a b -> b -> Pair a
-data Sel :: * -> * where
+data Sel :: Type -> Type where
A :: Sel Bool
B :: Sel Integer
diff --git a/testsuite/tests/gadt/gadt22.hs b/testsuite/tests/gadt/gadt22.hs
index 67d17c7a67..2bd6b74e44 100644
--- a/testsuite/tests/gadt/gadt22.hs
+++ b/testsuite/tests/gadt/gadt22.hs
@@ -8,6 +8,7 @@
module Expr where
+import qualified Data.Kind as K (Type)
import Data.Set (Set)
data Type a where
@@ -15,7 +16,7 @@ data Type a where
TypeSet :: Ord a => Type a -> Type (Set a)
TypeFun :: Type a -> Type b -> Type (a -> b)
-data Expr :: * -> * where
+data Expr :: K.Type -> K.Type where
Const :: Type a -> a -> Expr a
data DynExpr = forall a. DynExpr (Expr a)
diff --git a/testsuite/tests/gadt/gadt8.hs b/testsuite/tests/gadt/gadt8.hs
index ebd8b04c49..ba5ecaa603 100644
--- a/testsuite/tests/gadt/gadt8.hs
+++ b/testsuite/tests/gadt/gadt8.hs
@@ -6,7 +6,9 @@
-- kind signatures
module ShouldCompile where
-data Expr :: * -> * where {
+import Data.Kind (Type)
+
+data Expr :: Type -> Type where {
EInt :: Int -> Expr Int ;
EBool :: Bool -> Expr Bool ;
EIf :: (Expr Bool) -> (Expr a) -> (Expr a) -> Expr a ;
diff --git a/testsuite/tests/gadt/josef.hs b/testsuite/tests/gadt/josef.hs
index 34bd41ba3f..818a6dd20d 100644
--- a/testsuite/tests/gadt/josef.hs
+++ b/testsuite/tests/gadt/josef.hs
@@ -18,6 +18,8 @@
module Bug where
+import Data.Kind (Type)
+
class Category arr where
idA :: arr a a
comp :: arr a b -> arr b c -> arr a c
@@ -51,7 +53,7 @@ data V prod env t where
Z :: V prod (prod env t) t
S :: V prod env t -> V prod (prod env x) t
-data Lambda terminal (exp :: * -> * -> *) prod env t where
+data Lambda terminal (exp :: Type -> Type -> Type) prod env t where
Unit :: Lambda foo exp prod env foo
Var :: V prod env t -> Lambda terminal exp prod env t
{- Lam :: Lambda terminal exp prod (prod env a) t
diff --git a/testsuite/tests/gadt/karl1.hs b/testsuite/tests/gadt/karl1.hs
index b671db7cd3..e201a711f6 100644
--- a/testsuite/tests/gadt/karl1.hs
+++ b/testsuite/tests/gadt/karl1.hs
@@ -6,7 +6,9 @@
module Expr1 where
-data Expr :: * -> * where -- Not a GADT at all
+import Data.Kind (Type)
+
+data Expr :: Type -> Type where -- Not a GADT at all
Const :: Show a => a -> Expr a
-- Note the Show constraint here
Var :: Var a -> Expr a
diff --git a/testsuite/tests/gadt/karl2.hs b/testsuite/tests/gadt/karl2.hs
index aa96d689d7..1f46df37ee 100644
--- a/testsuite/tests/gadt/karl2.hs
+++ b/testsuite/tests/gadt/karl2.hs
@@ -5,11 +5,13 @@ module Expr0 where
-- See Trac #301
-- This one *does* use GADTs (Fct)
-data Expr :: * -> * where
+import Data.Kind (Type)
+
+data Expr :: Type -> Type where
Const :: Show a => a -> Expr a
Apply :: Fct a b -> Expr a -> Expr b
-data Fct :: * -> * -> * where
+data Fct :: Type -> Type -> Type where
Succ :: Fct Int Int
EqZero :: Fct Int Bool
Add :: Fct Int (Int -> Int)