[commit: ghc] ghc-8.2: Revert "Fix #13458" (d2f5ef9)
git at git.haskell.org
git at git.haskell.org
Mon Apr 3 02:38:00 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : ghc-8.2
Link : http://ghc.haskell.org/trac/ghc/changeset/d2f5ef97944c43a84459e5017e466d6d707578d3/ghc
>---------------------------------------------------------------
commit d2f5ef97944c43a84459e5017e466d6d707578d3
Author: Ben Gamari <ben at smart-cactus.org>
Date: Sat Apr 1 18:01:22 2017 -0400
Revert "Fix #13458"
This reverts commit 662c64226e302009175abfa7ed196ac905990486.
>---------------------------------------------------------------
d2f5ef97944c43a84459e5017e466d6d707578d3
compiler/simplStg/RepType.hs | 4 ++++
testsuite/tests/typecheck/should_compile/T13458.hs | 11 -----------
testsuite/tests/typecheck/should_compile/all.T | 1 -
3 files changed, 4 insertions(+), 12 deletions(-)
diff --git a/compiler/simplStg/RepType.hs b/compiler/simplStg/RepType.hs
index 91e4285..79b1299 100644
--- a/compiler/simplStg/RepType.hs
+++ b/compiler/simplStg/RepType.hs
@@ -343,6 +343,10 @@ kindPrimRep doc (TyConApp typ [runtime_rep])
kindPrimRep doc ki
= pprPanic "kindPrimRep" (ppr ki $$ doc)
+ -- TODO (RAE): Remove:
+ -- WARN( True, text "kindPrimRep defaulting to LiftedRep on" <+> ppr ki $$ doc )
+ -- [LiftedRep] -- this can happen legitimately for, e.g., Any
+
-- | Take a type of kind RuntimeRep and extract the list of 'PrimRep' that
-- it encodes.
runtimeRepPrimRep :: HasDebugCallStack => SDoc -> Type -> [PrimRep]
diff --git a/testsuite/tests/typecheck/should_compile/T13458.hs b/testsuite/tests/typecheck/should_compile/T13458.hs
deleted file mode 100644
index 9b51378..0000000
--- a/testsuite/tests/typecheck/should_compile/T13458.hs
+++ /dev/null
@@ -1,11 +0,0 @@
-{-# LANGUAGE MagicHash, TypeInType, ScopedTypeVariables #-}
-{-# OPTIONS_GHC -O #-}
-module T13458 where
-import GHC.Exts
-import Data.Kind
-import Unsafe.Coerce
-
-unsafeCoerce' :: forall (r :: RuntimeRep)
- (a :: TYPE r) (b :: TYPE r).
- a -> b
-unsafeCoerce' = unsafeCoerce id
diff --git a/testsuite/tests/typecheck/should_compile/all.T b/testsuite/tests/typecheck/should_compile/all.T
index 33ffc4f..6ceb87d 100644
--- a/testsuite/tests/typecheck/should_compile/all.T
+++ b/testsuite/tests/typecheck/should_compile/all.T
@@ -546,5 +546,4 @@ test('T12926', normal, compile, [''])
test('T13381', normal, compile_fail, [''])
test('T13337', normal, compile, [''])
test('T13343', normal, compile, [''])
-test('T13458', normal, compile, [''])
test('T13474', normal, compile, [''])
More information about the ghc-commits
mailing list