Skip to content
This repository was archived by the owner on Nov 1, 2018. It is now read-only.

Commit 2adffd8

Browse files
author
Richard Eisenberg
committed
Test #15076 in dependent/should_compile/T15076*
1 parent 731c95f commit 2adffd8

File tree

5 files changed

+55
-0
lines changed

5 files changed

+55
-0
lines changed
Lines changed: 13 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,13 @@
1+
{-# LANGUAGE RankNTypes #-}
2+
{-# LANGUAGE ScopedTypeVariables #-}
3+
{-# LANGUAGE TypeInType #-}
4+
{-# LANGUAGE PartialTypeSignatures #-}
5+
module Bug where
6+
7+
import Data.Kind
8+
import Data.Proxy
9+
10+
foo :: forall (a :: Type)
11+
(f :: forall (x :: a). Proxy x -> Type).
12+
Proxy f -> ()
13+
foo (_ :: _) = ()
Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,12 @@
1+
2+
T15076.hs:13:11: warning: [-Wpartial-type-signatures (in -Wdefault)]
3+
• Found type wildcard ‘_’ standing for ‘Proxy f’
4+
Where: ‘f’, ‘a’ are rigid type variables bound by
5+
the type signature for:
6+
foo :: forall a (f :: forall (x :: a). Proxy x -> *). Proxy f -> ()
7+
at T15076.hs:(10,1)-(12,20)
8+
• In a pattern type signature: _
9+
In the pattern: _ :: _
10+
In an equation for ‘foo’: foo (_ :: _) = ()
11+
• Relevant bindings include
12+
foo :: Proxy f -> () (bound at T15076.hs:13:1)
Lines changed: 11 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,11 @@
1+
{-# LANGUAGE RankNTypes #-}
2+
{-# LANGUAGE TypeInType #-}
3+
module Bug where
4+
5+
import Data.Kind
6+
import Data.Proxy
7+
8+
foo :: forall (a :: Type)
9+
(f :: forall (x :: a). Proxy x -> Type).
10+
Proxy f -> ()
11+
foo _ = ()
Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,16 @@
1+
{-# LANGUAGE PolyKinds, MultiParamTypeClasses, GADTs, ScopedTypeVariables,
2+
TypeOperators #-}
3+
{-# OPTIONS_GHC -fno-warn-redundant-constraints #-}
4+
5+
module Super where
6+
7+
import Data.Kind
8+
import Data.Proxy
9+
import GHC.Prim
10+
11+
class (a ~ b) => C a b
12+
data SameKind :: k -> k -> Type where
13+
SK :: SameKind a b
14+
15+
bar :: forall (a :: Type) (b :: Type). C a b => Proxy a -> Proxy b -> ()
16+
bar _ _ = const () (undefined :: forall (x :: a) (y :: b). SameKind x y)

testsuite/tests/dependent/should_compile/all.T

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -61,3 +61,6 @@ test('T14880-2', normal, compile, [''])
6161
test('T15743', normal, compile, ['-ddump-types -fprint-explicit-foralls'])
6262
test('InferDependency', normal, compile, [''])
6363
test('T15743e', normal, compile, ['-ddump-types -fprint-explicit-foralls'])
64+
test('T15076', normal, compile, [''])
65+
test('T15076b', normal, compile, [''])
66+
test('T15076c', normal, compile, [''])

0 commit comments

Comments
 (0)