summaryrefslogtreecommitdiff
path: root/testsuite/tests/warnings
diff options
context:
space:
mode:
authorOleg Grenrus <oleg.grenrus@iki.fi>2021-03-21 01:52:07 +0200
committerMarge Bot <ben+marge-bot@smart-cactus.org>2021-03-25 17:36:50 -0400
commit0d5d344d45c200a5e731e7d067598acd2a4f7050 (patch)
tree462b5671404a9011e9609534739ca42ca5de5502 /testsuite/tests/warnings
parentc74bd3daa3468e495714647506cf30cf650d390d (diff)
downloadhaskell-0d5d344d45c200a5e731e7d067598acd2a4f7050.tar.gz
Implement -Wmissing-kind-signatures
Fixes #19564
Diffstat (limited to 'testsuite/tests/warnings')
-rw-r--r--testsuite/tests/warnings/should_compile/T19564a.hs32
-rw-r--r--testsuite/tests/warnings/should_compile/T19564a.stderr36
-rw-r--r--testsuite/tests/warnings/should_compile/T19564b.hs46
-rw-r--r--testsuite/tests/warnings/should_compile/T19564c.hs34
-rw-r--r--testsuite/tests/warnings/should_compile/T19564c.stderr36
-rw-r--r--testsuite/tests/warnings/should_compile/T19564d.hs34
-rw-r--r--testsuite/tests/warnings/should_compile/all.T5
7 files changed, 223 insertions, 0 deletions
diff --git a/testsuite/tests/warnings/should_compile/T19564a.hs b/testsuite/tests/warnings/should_compile/T19564a.hs
new file mode 100644
index 0000000000..462d82cc42
--- /dev/null
+++ b/testsuite/tests/warnings/should_compile/T19564a.hs
@@ -0,0 +1,32 @@
+{-# OPTIONS_GHC -Wmissing-kind-signatures #-}
+{-# LANGUAGE GADTs, PolyKinds, TypeFamilies #-}
+-- without standalone kind signatures or cusks: warnings
+module T19564a where
+
+-- type family
+type family Id x where
+ Id Int = Int
+
+-- class definition
+class Functor f => Alt f where
+ (<!>) :: f a -> f a -> f a
+
+-- type alias
+type Arr a b = a -> b
+type B = Bool
+
+-- Haskell98 data
+data YesNo = Yes | No
+data V2 a = V2 a a
+
+-- GADT
+data Free f a where
+ Pure :: a -> Free f a
+ Ap :: f b -> Free f (b -> a) -> Free f a
+
+-- data family
+data family D1 a
+
+-- associated type family
+class C a where
+ type AT a b
diff --git a/testsuite/tests/warnings/should_compile/T19564a.stderr b/testsuite/tests/warnings/should_compile/T19564a.stderr
new file mode 100644
index 0000000000..f64805fa31
--- /dev/null
+++ b/testsuite/tests/warnings/should_compile/T19564a.stderr
@@ -0,0 +1,36 @@
+
+T19564a.hs:7:1: warning: [-Wmissing-kind-signatures]
+ Top-level type constructor with no standalone kind signature:
+ type Id :: * -> *
+
+T19564a.hs:11:1: warning: [-Wmissing-kind-signatures]
+ Top-level type constructor with no standalone kind signature:
+ type Alt :: (* -> *) -> Constraint
+
+T19564a.hs:15:1: warning: [-Wmissing-kind-signatures]
+ Top-level type constructor with no standalone kind signature:
+ type Arr :: * -> * -> *
+
+T19564a.hs:16:1: warning: [-Wmissing-kind-signatures]
+ Top-level type constructor with no standalone kind signature:
+ type B :: *
+
+T19564a.hs:19:1: warning: [-Wmissing-kind-signatures]
+ Top-level type constructor with no standalone kind signature:
+ type YesNo :: *
+
+T19564a.hs:20:1: warning: [-Wmissing-kind-signatures]
+ Top-level type constructor with no standalone kind signature:
+ type V2 :: * -> *
+
+T19564a.hs:23:1: warning: [-Wmissing-kind-signatures]
+ Top-level type constructor with no standalone kind signature:
+ type Free :: (* -> *) -> * -> *
+
+T19564a.hs:28:1: warning: [-Wmissing-kind-signatures]
+ Top-level type constructor with no standalone kind signature:
+ type D1 :: * -> *
+
+T19564a.hs:31:1: warning: [-Wmissing-kind-signatures]
+ Top-level type constructor with no standalone kind signature:
+ type C :: forall {k}. k -> Constraint
diff --git a/testsuite/tests/warnings/should_compile/T19564b.hs b/testsuite/tests/warnings/should_compile/T19564b.hs
new file mode 100644
index 0000000000..a981e9f61c
--- /dev/null
+++ b/testsuite/tests/warnings/should_compile/T19564b.hs
@@ -0,0 +1,46 @@
+{-# OPTIONS_GHC -Wmissing-kind-signatures #-}
+{-# LANGUAGE GADTs, PolyKinds, TypeFamilies #-}
+-- with kind signatures: no warnings
+module T19564b where
+
+import Data.Kind (Type, Constraint)
+
+-- type family
+type Id :: Type -> Type
+type family Id x where
+ Id Int = Int
+
+-- class definition
+type Alt :: (Type -> Type) -> Constraint
+class Functor f => Alt f where
+ (<!>) :: f a -> f a -> f a
+
+-- type alias
+type Arr :: Type -> Type -> Type
+type Arr a b = a -> b
+
+type B :: Type
+type B = Bool
+
+-- Haskell98 data
+type YesNo :: Type
+data YesNo = Yes | No
+
+type V2 :: Type -> Type
+data V2 a = V2 a a
+
+-- GADT
+type Free :: (Type -> Type) -> (Type -> Type)
+data Free f a where
+ Pure :: a -> Free f a
+ Ap :: f b -> Free f (b -> a) -> Free f a
+
+-- data family
+type D1 :: Type -> Type
+data family D1 a
+
+-- associated type family
+type C :: Type -> Constraint
+class C a where
+ -- is defaulted, doesn't need annotation
+ type AT a b
diff --git a/testsuite/tests/warnings/should_compile/T19564c.hs b/testsuite/tests/warnings/should_compile/T19564c.hs
new file mode 100644
index 0000000000..6f950b7307
--- /dev/null
+++ b/testsuite/tests/warnings/should_compile/T19564c.hs
@@ -0,0 +1,34 @@
+{-# OPTIONS_GHC -Wmissing-kind-signatures #-}
+{-# LANGUAGE GADTs, PolyKinds, TypeFamilies #-}
+-- with cusks but without -XCUSK, warnings
+module T19564c where
+
+import Data.Kind (Type, Constraint)
+
+-- type family
+type family Id (x :: Type) :: Type where
+ Id Int = Int
+
+-- class definition
+class Functor f => Alt (f :: Type -> Type) where
+ (<!>) :: f a -> f a -> f a
+
+-- type alias
+type Arr (a :: Type) (b :: Type) = a -> b :: Type
+type B = Bool :: Type
+
+-- Haskell98 data
+data YesNo = Yes | No
+data V2 (a :: Type) = V2 a a
+
+-- GADT
+data Free (f :: Type -> Type) (a :: Type) where
+ Pure :: a -> Free f a
+ Ap :: f b -> Free f (b -> a) -> Free f a
+
+-- data family
+data family D1 (a :: Type)
+
+-- associated type family
+class C (a :: Type) where
+ type AT a b
diff --git a/testsuite/tests/warnings/should_compile/T19564c.stderr b/testsuite/tests/warnings/should_compile/T19564c.stderr
new file mode 100644
index 0000000000..587ea089fc
--- /dev/null
+++ b/testsuite/tests/warnings/should_compile/T19564c.stderr
@@ -0,0 +1,36 @@
+
+T19564c.hs:9:1: warning: [-Wmissing-kind-signatures]
+ Top-level type constructor with no standalone kind signature:
+ type Id :: * -> *
+
+T19564c.hs:13:1: warning: [-Wmissing-kind-signatures]
+ Top-level type constructor with no standalone kind signature:
+ type Alt :: (* -> *) -> Constraint
+
+T19564c.hs:17:1: warning: [-Wmissing-kind-signatures]
+ Top-level type constructor with no standalone kind signature:
+ type Arr :: * -> * -> *
+
+T19564c.hs:18:1: warning: [-Wmissing-kind-signatures]
+ Top-level type constructor with no standalone kind signature:
+ type B :: *
+
+T19564c.hs:21:1: warning: [-Wmissing-kind-signatures]
+ Top-level type constructor with no standalone kind signature:
+ type YesNo :: *
+
+T19564c.hs:22:1: warning: [-Wmissing-kind-signatures]
+ Top-level type constructor with no standalone kind signature:
+ type V2 :: * -> *
+
+T19564c.hs:25:1: warning: [-Wmissing-kind-signatures]
+ Top-level type constructor with no standalone kind signature:
+ type Free :: (* -> *) -> * -> *
+
+T19564c.hs:30:1: warning: [-Wmissing-kind-signatures]
+ Top-level type constructor with no standalone kind signature:
+ type D1 :: * -> *
+
+T19564c.hs:33:1: warning: [-Wmissing-kind-signatures]
+ Top-level type constructor with no standalone kind signature:
+ type C :: * -> Constraint
diff --git a/testsuite/tests/warnings/should_compile/T19564d.hs b/testsuite/tests/warnings/should_compile/T19564d.hs
new file mode 100644
index 0000000000..599f5bbc6a
--- /dev/null
+++ b/testsuite/tests/warnings/should_compile/T19564d.hs
@@ -0,0 +1,34 @@
+{-# OPTIONS_GHC -Wmissing-kind-signatures #-}
+{-# LANGUAGE GADTs, PolyKinds, TypeFamilies, CUSKs #-}
+-- with -XCUSKs, no warnings
+module T19564c where
+
+import Data.Kind (Type, Constraint)
+
+-- type family
+type family Id (x :: Type) :: Type where
+ Id Int = Int
+
+-- class definition
+class Functor f => Alt (f :: Type -> Type) where
+ (<!>) :: f a -> f a -> f a
+
+-- type alias
+type Arr (a :: Type) (b :: Type) = a -> b :: Type
+type B = Bool :: Type
+
+-- Haskell98 data
+data YesNo = Yes | No
+data V2 (a :: Type) = V2 a a
+
+-- GADT
+data Free (f :: Type -> Type) (a :: Type) where
+ Pure :: a -> Free f a
+ Ap :: f b -> Free f (b -> a) -> Free f a
+
+-- data family
+data family D1 (a :: Type)
+
+-- associated type family
+class C (a :: Type) where
+ type AT a b
diff --git a/testsuite/tests/warnings/should_compile/all.T b/testsuite/tests/warnings/should_compile/all.T
index 7e8668c8d8..f1739aebc3 100644
--- a/testsuite/tests/warnings/should_compile/all.T
+++ b/testsuite/tests/warnings/should_compile/all.T
@@ -38,3 +38,8 @@ test('UnusedPackages', normal, multimod_compile,
['UnusedPackages.hs', '-package=bytestring -package=base -package=process -package=ghc -Wunused-packages'])
test('T18402', normal, compile, [''])
+
+test('T19564a', normal, compile, [''])
+test('T19564b', normal, compile, [''])
+test('T19564c', normal, compile, [''])
+test('T19564d', normal, compile, [''])