[commit: ghc] master: Comments and white space (0be7c2c)

git at git.haskell.org git at git.haskell.org
Thu Jul 31 14:49:54 UTC 2014


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/0be7c2cf1aa7c7747d27fb985e032ea2eeeb718e/ghc

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

commit 0be7c2cf1aa7c7747d27fb985e032ea2eeeb718e
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Jul 28 14:21:04 2014 +0100

    Comments and white space


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

0be7c2cf1aa7c7747d27fb985e032ea2eeeb718e
 compiler/types/FamInstEnv.lhs | 28 +++++++++++++++-------------
 compiler/types/TyCon.lhs      | 16 +++++++++++-----
 2 files changed, 26 insertions(+), 18 deletions(-)

diff --git a/compiler/types/FamInstEnv.lhs b/compiler/types/FamInstEnv.lhs
index fcf7cb4..870113f 100644
--- a/compiler/types/FamInstEnv.lhs
+++ b/compiler/types/FamInstEnv.lhs
@@ -644,7 +644,7 @@ lookupFamInstEnvConflicts envs fam_inst@(FamInst { fi_axiom = new_axiom })
                   (ppr tpl_tvs <+> ppr tpl_tys) )
                 -- Unification will break badly if the variables overlap
                 -- They shouldn't because we allocate separate uniques for them
-         if compatibleBranches (coAxiomSingleBranch old_axiom) (new_branch)
+         if compatibleBranches (coAxiomSingleBranch old_axiom) new_branch
            then Nothing
            else Just noSubst
       -- Note [Family instance overlap conflicts]
@@ -672,7 +672,7 @@ Note [Family instance overlap conflicts]
 -- Might be a one-way match or a unifier
 type MatchFun =  FamInst                -- The FamInst template
               -> TyVarSet -> [Type]     --   fi_tvs, fi_tys of that FamInst
-              -> [Type]                         -- Target to match against
+              -> [Type]                 -- Target to match against
               -> Maybe TvSubst
 
 lookup_fam_inst_env'          -- The worker, local to this module
@@ -732,9 +732,9 @@ lookup_fam_inst_env           -- The worker, local to this module
 
 -- Precondition: the tycon is saturated (or over-saturated)
 
-lookup_fam_inst_env match_fun (pkg_ie, home_ie) fam tys =
-    lookup_fam_inst_env' match_fun home_ie fam tys ++
-    lookup_fam_inst_env' match_fun pkg_ie  fam tys
+lookup_fam_inst_env match_fun (pkg_ie, home_ie) fam tys
+  =  lookup_fam_inst_env' match_fun home_ie fam tys
+  ++ lookup_fam_inst_env' match_fun pkg_ie  fam tys
 
 \end{code}
 
@@ -750,16 +750,18 @@ which you can't do in Haskell!):
 
 Then looking up (F (Int,Bool) Char) will return a FamInstMatch
      (FPair, [Int,Bool,Char])
-
 The "extra" type argument [Char] just stays on the end.
 
-Because of eta-reduction of data family instances (see
-Note [Eta reduction for data family axioms] in TcInstDecls), we must
-handle data families and type families separately here. All instances
-of a type family must have the same arity, so we can precompute the split
-between the match_tys and the overflow tys. This is done in pre_rough_split_tys.
-For data instances, though, we need to re-split for each instance, because
-the breakdown might be different.
+We handle data families and type families separately here:
+
+ * For type  families, all instances of a type family must have the
+   same arity, so we can precompute the split between the match_tys
+   and the overflow tys. This is done in pre_rough_split_tys.
+
+ * For data families instances, though, we need to re-split for each
+   instance, because the breakdown might be different for each
+   instance.  Why?  Because of eta reduction; see Note [Eta reduction
+   for data family axioms]
 
 \begin{code}
 
diff --git a/compiler/types/TyCon.lhs b/compiler/types/TyCon.lhs
index c39f9d1..a500a62 100644
--- a/compiler/types/TyCon.lhs
+++ b/compiler/types/TyCon.lhs
@@ -183,6 +183,9 @@ See also Note [Wrappers for data instance tycons] in MkId.lhs
   It has an AlgTyConParent of
         FamInstTyCon T [Int] ax_ti
 
+* The axiom ax_ti may be eta-reduced; see
+  Note [Eta reduction for data family axioms] in TcInstDcls
+
 * The data contructor T2 has a wrapper (which is what the
   source-level "T2" invokes):
 
@@ -576,11 +579,14 @@ data TyConParent
   --  3) A 'CoTyCon' identifying the representation
   --  type with the type instance family
   | FamInstTyCon          -- See Note [Data type families]
-        (CoAxiom Unbranched)  -- The coercion constructor,
-                              -- always of kind   T ty1 ty2 ~ R:T a b c
-                              -- where T is the family TyCon,
-                              -- and R:T is the representation TyCon (ie this one)
-                              -- and a,b,c are the tyConTyVars of this TyCon
+        (CoAxiom Unbranched)  -- The coercion axiom.
+               -- Generally of kind   T ty1 ty2 ~ R:T a b c
+               -- where T is the family TyCon,
+               -- and R:T is the representation TyCon (ie this one)
+               -- and a,b,c are the tyConTyVars of this TyCon
+               --
+               -- BUT may be eta-reduced; see TcInstDcls
+               --     Note [Eta reduction for data family axioms]
 
           -- Cached fields of the CoAxiom, but adjusted to
           -- use the tyConTyVars of this TyCon



More information about the ghc-commits mailing list