[commit: ghc] master: Comments on TrieMap and unifier. (cc071ec)

git at git.haskell.org git at git.haskell.org
Thu Dec 4 08:24:47 UTC 2014


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

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

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

commit cc071ecfab52396e7ecf54eb69abef57c3a63626
Author: Edward Z. Yang <ezyang at cs.stanford.edu>
Date:   Thu Dec 4 00:23:57 2014 -0800

    Comments on TrieMap and unifier.
    
    Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>


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

cc071ecfab52396e7ecf54eb69abef57c3a63626
 compiler/coreSyn/TrieMap.hs |  7 +++++++
 compiler/types/Unify.hs     | 15 ++++++++++++++-
 2 files changed, 21 insertions(+), 1 deletion(-)

diff --git a/compiler/coreSyn/TrieMap.hs b/compiler/coreSyn/TrieMap.hs
index 57f360e..aa9172b 100644
--- a/compiler/coreSyn/TrieMap.hs
+++ b/compiler/coreSyn/TrieMap.hs
@@ -784,6 +784,13 @@ lookupCME :: CmEnv -> Var -> Maybe BoundVar
 lookupCME (CME { cme_env = env }) v = lookupVarEnv env v
 
 --------- Variable binders -------------
+
+-- | A 'BndrMap' is a 'TypeMap' which allows us to distinguish between
+-- binding forms whose binders have different types.  For example,
+-- if we are doing a 'TrieMap' lookup on @\(x :: Int) -> ()@, we should
+-- not pick up an entry in the 'TrieMap' for @\(x :: Bool) -> ()@:
+-- we can disambiguate this by matching on the type (or kind, if this
+-- a binder in a type) of the binder.
 type BndrMap = TypeMap
 
 lkBndr :: CmEnv -> Var -> BndrMap a -> Maybe a
diff --git a/compiler/types/Unify.hs b/compiler/types/Unify.hs
index 82fdad5..02d3792 100644
--- a/compiler/types/Unify.hs
+++ b/compiler/types/Unify.hs
@@ -87,7 +87,7 @@ tcMatchTy tmpls ty1 ty2
     menv     = ME { me_tmpls = tmpls, me_env = mkRnEnv2 in_scope }
     in_scope = mkInScopeSet (tmpls `unionVarSet` tyVarsOfType ty2)
         -- We're assuming that all the interesting
-        -- tyvars in tys1 are in tmpls
+        -- tyvars in ty1 are in tmpls
 
 tcMatchTys :: TyVarSet          -- Template tyvars
            -> [Type]            -- Template
@@ -139,6 +139,15 @@ ruleMatchTyX menv subst ty1 ty2 = match menv subst ty1 ty2      -- Rename for ex
 
 -- Now the internals of matching
 
+-- | Workhorse matching function.  Our goal is to find a substitution
+-- on all of the template variables (specified by @me_tmpls menv@) such
+-- that @ty1@ and @ty2@ unify.  This substitution is accumulated in @subst at .
+-- If a variable is not a template variable, we don't attempt to find a
+-- substitution for it; it must match exactly on both sides.  Furthermore,
+-- only @ty1@ can have template variables.
+--
+-- This function handles binders, see 'RnEnv2' for more details on
+-- how that works.
 match :: MatchEnv       -- For the most part this is pushed downwards
       -> TvSubstEnv     -- Substitution so far:
                         --   Domain is subset of template tyvars
@@ -160,6 +169,10 @@ match menv subst (TyVarTy tv1) ty2
   | tv1' `elemVarSet` me_tmpls menv
   = if any (inRnEnvR rn_env) (varSetElems (tyVarsOfType ty2))
     then Nothing        -- Occurs check
+                        -- ezyang: Is this really an occurs check?  It seems
+                        -- to just reject matching \x. A against \x. x (maintaining
+                        -- the invariant that the free vars of the range of @subst@
+                        -- are a subset of the in-scope set in @me_env menv at .)
     else do { subst1 <- match_kind menv subst (tyVarKind tv1) (typeKind ty2)
                         -- Note [Matching kinds]
             ; return (extendVarEnv subst1 tv1' ty2) }



More information about the ghc-commits mailing list