summaryrefslogtreecommitdiff
path: root/testsuite/tests/simplCore/should_compile/T15517a.hs
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/simplCore/should_compile/T15517a.hs
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/simplCore/should_compile/T15517a.hs')
-rw-r--r--testsuite/tests/simplCore/should_compile/T15517a.hs19
1 files changed, 10 insertions, 9 deletions
diff --git a/testsuite/tests/simplCore/should_compile/T15517a.hs b/testsuite/tests/simplCore/should_compile/T15517a.hs
index 28ca664969..2c8f6c4b32 100644
--- a/testsuite/tests/simplCore/should_compile/T15517a.hs
+++ b/testsuite/tests/simplCore/should_compile/T15517a.hs
@@ -9,16 +9,17 @@
{-# LANGUAGE TypeOperators #-}
module T15517a () where
+import Data.Kind (Type)
import Data.Proxy
-newtype Rep (ki :: kon -> *) (phi :: Nat -> *) (code :: [[Atom kon]])
+newtype Rep (ki :: kon -> Type) (phi :: Nat -> Type) (code :: [[Atom kon]])
= Rep (NS (PoA ki phi) code)
-data NA :: (kon -> *) -> (Nat -> *) -> Atom kon -> * where
+data NA :: (kon -> Type) -> (Nat -> Type) -> Atom kon -> Type where
NA_I :: (IsNat k) => phi k -> NA ki phi (I k)
NA_K :: ki k -> NA ki phi (K k)
-data NP :: (k -> *) -> [k] -> * where
+data NP :: (k -> Type) -> [k] -> Type where
NP0 :: NP p '[]
(:*) :: p x -> NP p xs -> NP p (x : xs)
@@ -32,33 +33,33 @@ instance IsNat n => IsNat (S n) where
proxyUnsuc :: Proxy (S n) -> Proxy n
proxyUnsuc _ = Proxy
-type PoA (ki :: kon -> *) (phi :: Nat -> *) = NP (NA ki phi)
+type PoA (ki :: kon -> Type) (phi :: Nat -> Type) = NP (NA ki phi)
data Atom kon
= K kon
| I Nat
data Nat = S Nat | Z
-data SNat :: Nat -> * where
+data SNat :: Nat -> Type where
SZ :: SNat Z
SS :: SNat n -> SNat (S n)
data Kon = KInt
-data Singl (kon :: Kon) :: * where
+data Singl (kon :: Kon) :: Type where
SInt :: Int -> Singl KInt
type family Lkup (n :: Nat) (ks :: [k]) :: k where
Lkup Z (k : ks) = k
Lkup (S n) (k : ks) = Lkup n ks
-data El :: [*] -> Nat -> * where
+data El :: [Type] -> Nat -> Type where
El :: IsNat ix => Lkup ix fam -> El fam ix
-data NS :: (k -> *) -> [k] -> * where
+data NS :: (k -> Type) -> [k] -> Type where
There :: NS p xs -> NS p (x : xs)
Here :: p x -> NS p (x : xs)
-class Family (ki :: kon -> *) (fam :: [*]) (codes :: [[[Atom kon]]])
+class Family (ki :: kon -> Type) (fam :: [Type]) (codes :: [[[Atom kon]]])
| fam -> ki codes , ki codes -> fam where
sfrom' :: SNat ix -> El fam ix -> Rep ki (El fam) (Lkup ix codes)