[commit: ghc] master: Test #15076 in dependent/should_compile/T15076* (2adffd8)
git at git.haskell.org
git at git.haskell.org
Mon Oct 29 16:37:37 UTC 2018
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/2adffd854effc0708b9fb268749aceaf3c20a169/ghc
>---------------------------------------------------------------
commit 2adffd854effc0708b9fb268749aceaf3c20a169
Author: Richard Eisenberg <rae at cs.brynmawr.edu>
Date: Mon Oct 29 10:01:15 2018 -0400
Test #15076 in dependent/should_compile/T15076*
>---------------------------------------------------------------
2adffd854effc0708b9fb268749aceaf3c20a169
.../dependent/should_compile/{T14880-2.hs => T15076.hs} | 10 +++++-----
testsuite/tests/dependent/should_compile/T15076.stderr | 12 ++++++++++++
testsuite/tests/dependent/should_compile/T15076b.hs | 11 +++++++++++
testsuite/tests/dependent/should_compile/T15076c.hs | 16 ++++++++++++++++
testsuite/tests/dependent/should_compile/all.T | 3 +++
5 files changed, 47 insertions(+), 5 deletions(-)
diff --git a/testsuite/tests/dependent/should_compile/T14880-2.hs b/testsuite/tests/dependent/should_compile/T15076.hs
similarity index 51%
copy from testsuite/tests/dependent/should_compile/T14880-2.hs
copy to testsuite/tests/dependent/should_compile/T15076.hs
index e7057a3..0890cf9 100644
--- a/testsuite/tests/dependent/should_compile/T14880-2.hs
+++ b/testsuite/tests/dependent/should_compile/T15076.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE GADTs #-}
+{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE PartialTypeSignatures #-}
@@ -7,7 +7,7 @@ module Bug where
import Data.Kind
import Data.Proxy
-data Foo (x :: Type) :: forall (a :: x). Proxy a -> Type
-
-quux :: forall arg. Proxy (Foo arg) -> ()
-quux (_ :: _) = ()
+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 0000000..43f4772
--- /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 0000000..15fce82
--- /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 0000000..b689b5b
--- /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 16c6d13..341a44c 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, [''])
More information about the ghc-commits
mailing list