Repository : ssh://darcs.haskell.org//srv/darcs/ghc

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/f27c631a16a17b8ad740d7d28c6ff267fb189c2c

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

commit f27c631a16a17b8ad740d7d28c6ff267fb189c2c
Author: Simon Peyton Jones <[email protected]>
Date:   Wed Aug 29 10:57:48 2012 +0100

    Fix Trac #7196 by adding a case to the desugarer
    
    Pls merge to 7.6

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

 compiler/deSugar/DsBinds.lhs      |   11 ++++++-----
 compiler/typecheck/TcEvidence.lhs |   21 +++++++++++----------
 2 files changed, 17 insertions(+), 15 deletions(-)

diff --git a/compiler/deSugar/DsBinds.lhs b/compiler/deSugar/DsBinds.lhs
index 75680bc..4fa1ec0 100644
--- a/compiler/deSugar/DsBinds.lhs
+++ b/compiler/deSugar/DsBinds.lhs
@@ -844,13 +844,14 @@ ds_tc_coercion subst tc_co
 
     ds_scc :: CvSubst -> SCC EvBind -> CvSubst
     ds_scc subst (AcyclicSCC (EvBind v ev_term))
-      = extendCvSubstAndInScope subst v (ds_ev_term subst ev_term)
+      = extendCvSubstAndInScope subst v (ds_co_term subst ev_term)
     ds_scc _ (CyclicSCC other) = pprPanic "ds_scc:cyclic" (ppr other $$ ppr 
tc_co)
 
-    ds_ev_term :: CvSubst -> EvTerm -> Coercion
-    ds_ev_term subst (EvCoercion tc_co) = ds_tc_coercion subst tc_co
-    ds_ev_term subst (EvId v)           = ds_ev_id subst v
-    ds_ev_term _ other = pprPanic "ds_ev_term" (ppr other $$ ppr tc_co)
+    ds_co_term :: CvSubst -> EvTerm -> Coercion
+    ds_co_term subst (EvCoercion tc_co) = ds_tc_coercion subst tc_co
+    ds_co_term subst (EvId v)           = ds_ev_id subst v
+    ds_co_term subst (EvCast tm co)     = mkCoCast (ds_co_term subst tm) 
(ds_tc_coercion subst co)
+    ds_co_term _ other = pprPanic "ds_co_term" (ppr other $$ ppr tc_co)
 
     ds_ev_id :: CvSubst -> EqVar -> Coercion
     ds_ev_id subst v
diff --git a/compiler/typecheck/TcEvidence.lhs 
b/compiler/typecheck/TcEvidence.lhs
index 6ac351e..1214905 100644
--- a/compiler/typecheck/TcEvidence.lhs
+++ b/compiler/typecheck/TcEvidence.lhs
@@ -490,12 +490,13 @@ data EvLit
 
 \end{code}
 
-Note [Coecion evidence terms]
-~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-Notice that a coercion variable (v :: t1 ~ t2) can be represented as an EvTerm
-in two different ways:
-   EvId v
-   EvCoercion (TcCoVarCo v)
+Note [Coercion evidence terms]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+An evidence term for a coercion, of type (t1 ~ t2), always takes one of 
+these forms:
+   co_tm ::= EvId v
+           | EvCoercion co
+           | EvCast co_tm co
 
 An alternative would be 
 
@@ -506,12 +507,12 @@ An alternative would be
      mkEvCast (EvCoercion c1) c2 = EvCoercion (TcCastCo c1 c2)
      mkEvCast t c = EvCast t c
 
+I don't think it matters much... but maybe we'll find a good reason to
+do one or the other.  But currently we allow any of the three forms.
+
 We do quite often need to get a TcCoercion from an EvTerm; see
-'evTermCoercion'.  Notice that as well as EvId and EvCoercion it may see
-an EvCast.
+'evTermCoercion'.
 
-I don't think it matters much... but maybe we'll find a good reason to
-do one or the other.
 
 Note [EvKindCast] 
 ~~~~~~~~~~~~~~~~~ 



_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to