[commit: ghc] wip/tdammers/T11735-2: Fixed errors introduced by cherry-picking (f3cc973)

git at git.haskell.org git at git.haskell.org
Tue Jan 30 15:48:36 UTC 2018


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

On branch  : wip/tdammers/T11735-2
Link       : http://ghc.haskell.org/trac/ghc/changeset/f3cc973d39743c1fb80c726688f83184455d9296/ghc

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

commit f3cc973d39743c1fb80c726688f83184455d9296
Author: Tobias Dammers <tdammers at gmail.com>
Date:   Tue Jan 30 16:48:00 2018 +0100

    Fixed errors introduced by cherry-picking


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

f3cc973d39743c1fb80c726688f83184455d9296
 compiler/typecheck/TcCanonical.hs | 2 +-
 compiler/typecheck/TcEvidence.hs  | 6 +++---
 compiler/types/Coercion.hs        | 2 +-
 3 files changed, 5 insertions(+), 5 deletions(-)

diff --git a/compiler/typecheck/TcCanonical.hs b/compiler/typecheck/TcCanonical.hs
index ac6b6af..7e7154f 100644
--- a/compiler/typecheck/TcCanonical.hs
+++ b/compiler/typecheck/TcCanonical.hs
@@ -1266,7 +1266,7 @@ canDecomposableTyConAppOK ev eq_rel tc tys1 tys2
         -> do { let ev_co = mkCoVarCo evar
               ; given_evs <- newGivenEvVars loc $
                              [ ( mkPrimEqPredRole r ty1 ty2
-                               , EvCoercion (mkNthCo r i ev_co) )
+                               , evCoercion (mkNthCo r i ev_co) )
                              | (r, ty1, ty2, i) <- zip4 tc_roles tys1 tys2 [0..]
                              , r /= Phantom
                              , not (isCoercionTy ty1) && not (isCoercionTy ty2) ]
diff --git a/compiler/typecheck/TcEvidence.hs b/compiler/typecheck/TcEvidence.hs
index c489d44..d80996e 100644
--- a/compiler/typecheck/TcEvidence.hs
+++ b/compiler/typecheck/TcEvidence.hs
@@ -760,9 +760,9 @@ isEmptyTcEvBinds (TcEvBinds {}) = panic "isEmptyTcEvBinds"
 evTermCoercion :: EvTerm -> TcCoercion
 -- Applied only to EvTerms of type (s~t)
 -- See Note [Coercion evidence terms]
-evTermCoercion (EvId v)        = mkCoVarCo v
-evTermCoercion (EvCoercion co) = co
-evTermCoercion (EvCast tm co)  = mkCoCast Representational (evTermCoercion tm) co
+evTermCoercion (EvExpr (Var v))       = mkCoVarCo v
+evTermCoercion (EvExpr (Coercion co)) = co
+evTermCoercion (EvExpr (Cast tm co))  = mkCoCast Representational (evTermCoercion (EvExpr tm)) co
 evTermCoercion tm = pprPanic "evTermCoercion" (ppr tm)
 
 evVarsOfTerm :: EvTerm -> VarSet
diff --git a/compiler/types/Coercion.hs b/compiler/types/Coercion.hs
index 7fe7792..a5b476a 100644
--- a/compiler/types/Coercion.hs
+++ b/compiler/types/Coercion.hs
@@ -29,7 +29,7 @@ module Coercion (
         mkAxInstLHS, mkUnbranchedAxInstLHS,
         mkPiCo, mkPiCos, mkCoCast,
         mkSymCo, mkTransCo, mkTransAppCo,
-        mkNthCo, mkLRCo,
+        mkNthCo, mkNthCoNoRole, mkLRCo,
         mkInstCo, mkAppCo, mkAppCos, mkTyConAppCo, mkFunCo, mkFunCos,
         mkForAllCo, mkForAllCos, mkHomoForAllCos, mkHomoForAllCos_NoRefl,
         mkPhantomCo,



More information about the ghc-commits mailing list