[commit: ghc] wip/T14880-2-step3: Add test for #14880 (a71f022)

git at git.haskell.org git at git.haskell.org
Mon Sep 17 20:37:31 UTC 2018


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/T14880-2-step3
Link       : http://ghc.haskell.org/trac/ghc/changeset/a71f02265c81c22965999ec2593cf4bec81301ff/ghc

>---------------------------------------------------------------

commit a71f02265c81c22965999ec2593cf4bec81301ff
Author: Tobias Dammers <tdammers at gmail.com>
Date:   Fri Sep 14 13:48:20 2018 +0200

    Add test for #14880


>---------------------------------------------------------------

a71f02265c81c22965999ec2593cf4bec81301ff
 .../tests/dependent/should_compile/{T14880.hs => T14880-2.hs}     | 8 +++-----
 testsuite/tests/dependent/should_compile/all.T                    | 1 +
 2 files changed, 4 insertions(+), 5 deletions(-)

diff --git a/testsuite/tests/dependent/should_compile/T14880.hs b/testsuite/tests/dependent/should_compile/T14880-2.hs
similarity index 52%
copy from testsuite/tests/dependent/should_compile/T14880.hs
copy to testsuite/tests/dependent/should_compile/T14880-2.hs
index 91cfb20..e7057a3 100644
--- a/testsuite/tests/dependent/should_compile/T14880.hs
+++ b/testsuite/tests/dependent/should_compile/T14880-2.hs
@@ -1,6 +1,7 @@
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeInType #-}
+{-# LANGUAGE PartialTypeSignatures #-}
 module Bug where
 
 import Data.Kind
@@ -8,8 +9,5 @@ import Data.Proxy
 
 data Foo (x :: Type) :: forall (a :: x). Proxy a -> Type
 
-data Bar :: Type -> Type where
-    MkBar :: forall x arg.
-             -- Commenting out the line below makes the issue go away
-             Foo arg ~ Foo arg =>
-             Bar x
+quux :: forall arg. Proxy (Foo arg) -> ()
+quux (_ :: _) = ()
diff --git a/testsuite/tests/dependent/should_compile/all.T b/testsuite/tests/dependent/should_compile/all.T
index 5661807..dca19b9 100644
--- a/testsuite/tests/dependent/should_compile/all.T
+++ b/testsuite/tests/dependent/should_compile/all.T
@@ -56,3 +56,4 @@ test('T15419', normal, compile, [''])
 test('T14066h', normal, compile, [''])
 test('T14904', expect_broken(14904), compile, [''])
 test('T14880', normal, compile, [''])
+test('T14880-2', normal, compile, [''])



More information about the ghc-commits mailing list