summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorRichard Eisenberg <rae@cs.brynmawr.edu>2018-10-29 10:01:15 -0400
committerRichard Eisenberg <rae@cs.brynmawr.edu>2018-10-29 12:12:48 -0400
commit2adffd854effc0708b9fb268749aceaf3c20a169 (patch)
treeb9ec32482674a7cd2aa791e86fa0de7758fbd3a0
parent731c95f5167246aecd2205743a9b0d8d21bcccf9 (diff)
downloadhaskell-2adffd854effc0708b9fb268749aceaf3c20a169.tar.gz
Test #15076 in dependent/should_compile/T15076*
-rw-r--r--testsuite/tests/dependent/should_compile/T15076.hs13
-rw-r--r--testsuite/tests/dependent/should_compile/T15076.stderr12
-rw-r--r--testsuite/tests/dependent/should_compile/T15076b.hs11
-rw-r--r--testsuite/tests/dependent/should_compile/T15076c.hs16
-rw-r--r--testsuite/tests/dependent/should_compile/all.T3
5 files changed, 55 insertions, 0 deletions
diff --git a/testsuite/tests/dependent/should_compile/T15076.hs b/testsuite/tests/dependent/should_compile/T15076.hs
new file mode 100644
index 0000000000..0890cf9eab
--- /dev/null
+++ b/testsuite/tests/dependent/should_compile/T15076.hs
@@ -0,0 +1,13 @@
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeInType #-}
+{-# LANGUAGE PartialTypeSignatures #-}
+module Bug where
+
+import Data.Kind
+import Data.Proxy
+
+foo :: forall (a :: Type)
+ (f :: forall (x :: a). Proxy x -> Type).
+ Proxy f -> ()
+foo (_ :: _) = ()
diff --git a/testsuite/tests/dependent/should_compile/T15076.stderr b/testsuite/tests/dependent/should_compile/T15076.stderr
new file mode 100644
index 0000000000..43f4772362
--- /dev/null
+++ b/testsuite/tests/dependent/should_compile/T15076.stderr
@@ -0,0 +1,12 @@
+
+T15076.hs:13:11: warning: [-Wpartial-type-signatures (in -Wdefault)]
+ • Found type wildcard ‘_’ standing for ‘Proxy f’
+ Where: ‘f’, ‘a’ are rigid type variables bound by
+ the type signature for:
+ foo :: forall a (f :: forall (x :: a). Proxy x -> *). Proxy f -> ()
+ at T15076.hs:(10,1)-(12,20)
+ • In a pattern type signature: _
+ In the pattern: _ :: _
+ In an equation for ‘foo’: foo (_ :: _) = ()
+ • Relevant bindings include
+ foo :: Proxy f -> () (bound at T15076.hs:13:1)
diff --git a/testsuite/tests/dependent/should_compile/T15076b.hs b/testsuite/tests/dependent/should_compile/T15076b.hs
new file mode 100644
index 0000000000..15fce826c0
--- /dev/null
+++ b/testsuite/tests/dependent/should_compile/T15076b.hs
@@ -0,0 +1,11 @@
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE TypeInType #-}
+module Bug where
+
+import Data.Kind
+import Data.Proxy
+
+foo :: forall (a :: Type)
+ (f :: forall (x :: a). Proxy x -> Type).
+ Proxy f -> ()
+foo _ = ()
diff --git a/testsuite/tests/dependent/should_compile/T15076c.hs b/testsuite/tests/dependent/should_compile/T15076c.hs
new file mode 100644
index 0000000000..b689b5b6f0
--- /dev/null
+++ b/testsuite/tests/dependent/should_compile/T15076c.hs
@@ -0,0 +1,16 @@
+{-# LANGUAGE PolyKinds, MultiParamTypeClasses, GADTs, ScopedTypeVariables,
+ TypeOperators #-}
+{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}
+
+module Super where
+
+import Data.Kind
+import Data.Proxy
+import GHC.Prim
+
+class (a ~ b) => C a b
+data SameKind :: k -> k -> Type where
+ SK :: SameKind a b
+
+bar :: forall (a :: Type) (b :: Type). C a b => Proxy a -> Proxy b -> ()
+bar _ _ = const () (undefined :: forall (x :: a) (y :: b). SameKind x y)
diff --git a/testsuite/tests/dependent/should_compile/all.T b/testsuite/tests/dependent/should_compile/all.T
index 16c6d13ba9..341a44c8f3 100644
--- a/testsuite/tests/dependent/should_compile/all.T
+++ b/testsuite/tests/dependent/should_compile/all.T
@@ -61,3 +61,6 @@ test('T14880-2', normal, compile, [''])
test('T15743', normal, compile, ['-ddump-types -fprint-explicit-foralls'])
test('InferDependency', normal, compile, [''])
test('T15743e', normal, compile, ['-ddump-types -fprint-explicit-foralls'])
+test('T15076', normal, compile, [''])
+test('T15076b', normal, compile, [''])
+test('T15076c', normal, compile, [''])