[commit: ghc] wip/rae: Fix #11246. (f0c31a6)

git at git.haskell.org git at git.haskell.org
Mon Feb 15 15:38:51 UTC 2016


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

On branch  : wip/rae
Link       : http://ghc.haskell.org/trac/ghc/changeset/f0c31a6b54c6a26eae4c1f576ddca04488034ff9/ghc

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

commit f0c31a6b54c6a26eae4c1f576ddca04488034ff9
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Wed Feb 10 09:09:26 2016 -0500

    Fix #11246.
    
    Previously, the definition of Any was just plain wrong. I'm surprised
    anything was actually working!


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

f0c31a6b54c6a26eae4c1f576ddca04488034ff9
 compiler/prelude/TysPrim.hs                        | 2 +-
 testsuite/tests/typecheck/should_compile/T11246.hs | 5 +++++
 testsuite/tests/typecheck/should_compile/all.T     | 1 +
 3 files changed, 7 insertions(+), 1 deletion(-)

diff --git a/compiler/prelude/TysPrim.hs b/compiler/prelude/TysPrim.hs
index d1e42d5..26a20c3 100644
--- a/compiler/prelude/TysPrim.hs
+++ b/compiler/prelude/TysPrim.hs
@@ -920,7 +920,7 @@ anyTy :: Type
 anyTy = mkTyConTy anyTyCon
 
 anyTyCon :: TyCon
-anyTyCon = mkFamilyTyCon anyTyConName kind [kKiVar] Nothing
+anyTyCon = mkFamilyTyCon anyTyConName kind [] Nothing
                          (ClosedSynFamilyTyCon Nothing)
                          Nothing
                          NotInjective
diff --git a/testsuite/tests/typecheck/should_compile/T11246.hs b/testsuite/tests/typecheck/should_compile/T11246.hs
new file mode 100644
index 0000000..afe8975
--- /dev/null
+++ b/testsuite/tests/typecheck/should_compile/T11246.hs
@@ -0,0 +1,5 @@
+module T11246 where
+
+import GHC.Exts
+
+type Key a = Any
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index f7c5644..ec948dd 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -505,3 +505,4 @@ test('T11397', normal, compile, [''])
 test('T11458', normal, compile, [''])
 test('T11524', normal, compile, [''])
 test('T11552', normal, compile, [''])
+test('T11246', normal, compile, [''])



More information about the ghc-commits mailing list