[commit: ghc] wip/rae: Fix #9788 by giving `coerce` the right type. (92544d6)

git at git.haskell.org git at git.haskell.org
Tue Nov 11 15:06:46 UTC 2014


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

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

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

commit 92544d6363182b23baea5a5f5ee769c026a11080
Author: Richard Eisenberg <eir at cis.upenn.edu>
Date:   Mon Nov 10 20:41:38 2014 -0500

    Fix #9788 by giving `coerce` the right type.
    
    No test case added, as the original mistake is just one level
    up from a typo.


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

92544d6363182b23baea5a5f5ee769c026a11080
 compiler/basicTypes/MkId.lhs                | 19 ++++++++-----------
 testsuite/tests/ghci/scripts/ghci059.stdout |  4 +---
 2 files changed, 9 insertions(+), 14 deletions(-)

diff --git a/compiler/basicTypes/MkId.lhs b/compiler/basicTypes/MkId.lhs
index 9fc728b..b32a2b7 100644
--- a/compiler/basicTypes/MkId.lhs
+++ b/compiler/basicTypes/MkId.lhs
@@ -1146,17 +1146,14 @@ coerceId = pcMiscPrelId coerceName ty info
   where
     info = noCafIdInfo `setInlinePragInfo` alwaysInlinePragma
                        `setUnfoldingInfo`  mkCompulsoryUnfolding rhs
-    kv = kKiVar
-    k = mkTyVarTy kv
-    a:b:_ = tyVarList k
-    [aTy,bTy] = map mkTyVarTy [a,b]
-    eqRTy     = mkTyConApp coercibleTyCon  [k, aTy, bTy]
-    eqRPrimTy = mkTyConApp eqReprPrimTyCon [k, aTy, bTy]
-    ty   = mkForAllTys [kv, a, b] (mkFunTys [eqRTy, aTy] bTy)
-
-    [eqR,x,eq] = mkTemplateLocals [eqRTy, aTy,eqRPrimTy]
-    rhs = mkLams [kv,a,b,eqR,x] $
-          mkWildCase (Var eqR) eqRTy bTy $
+    eqRTy     = mkTyConApp coercibleTyCon  [liftedTypeKind, alphaTy, betaTy]
+    eqRPrimTy = mkTyConApp eqReprPrimTyCon [liftedTypeKind, alphaTy, betaTy]
+    ty        = mkForAllTys [alphaTyVar, betaTyVar] $
+                mkFunTys [eqRTy, alphaTy] betaTy
+
+    [eqR,x,eq] = mkTemplateLocals [eqRTy, alphaTy, eqRPrimTy]
+    rhs = mkLams [alphaTyVar, betaTyVar, eqR, x] $
+          mkWildCase (Var eqR) eqRTy betaTy $
           [(DataAlt coercibleDataCon, [eq], Cast (Var x) (CoVarCo eq))]
 \end{code}
 
diff --git a/testsuite/tests/ghci/scripts/ghci059.stdout b/testsuite/tests/ghci/scripts/ghci059.stdout
index ffc893f..6b2c8f8 100644
--- a/testsuite/tests/ghci/scripts/ghci059.stdout
+++ b/testsuite/tests/ghci/scripts/ghci059.stdout
@@ -1,6 +1,4 @@
 type role Coercible representational representational
 class Coercible (a :: k) (b :: k)
   	-- Defined in ‘GHC.Types’
-coerce ::
-  forall (k :: BOX) (a :: k) (b :: k). Coercible a b => a -> b
-  	-- Defined in ‘GHC.Prim’
+coerce :: Coercible a b => a -> b 	-- Defined in ‘GHC.Prim’



More information about the ghc-commits mailing list