[commit: ghc] master: Use IfLclName instead of OccName in IfaceEqSpec (6e8861c)

git at git.haskell.org git at git.haskell.org
Tue Jun 3 16:12:35 UTC 2014


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

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

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

commit 6e8861c913a4bb6ae68a57a4f3a148235905f9ee
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Tue Jun 3 14:23:48 2014 +0100

    Use IfLclName instead of OccName in IfaceEqSpec
    
    The type variables in the IfaceEqSpec of a data constructor are really
    ordinarly *occurrences*, so they should be IfLclNames just like any
    other type variable occurence.


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

6e8861c913a4bb6ae68a57a4f3a148235905f9ee
 compiler/iface/IfaceSyn.lhs  | 6 +++---
 compiler/iface/IfaceType.lhs | 2 +-
 compiler/iface/MkIface.lhs   | 5 ++---
 compiler/iface/TcIface.lhs   | 4 ++--
 4 files changed, 8 insertions(+), 9 deletions(-)

diff --git a/compiler/iface/IfaceSyn.lhs b/compiler/iface/IfaceSyn.lhs
index c8e7ea8..6af5bbe 100644
--- a/compiler/iface/IfaceSyn.lhs
+++ b/compiler/iface/IfaceSyn.lhs
@@ -16,7 +16,7 @@ module IfaceSyn (
         module IfaceType,
 
         IfaceDecl(..), IfaceSynTyConRhs(..), IfaceClassOp(..), IfaceAT(..), 
-        IfaceConDecl(..), IfaceConDecls(..),
+        IfaceConDecl(..), IfaceConDecls(..), IfaceEqSpec,
         IfaceExpr(..), IfaceAlt, IfaceLetBndr(..),
         IfaceBinding(..), IfaceConAlt(..),
         IfaceIdInfo(..), IfaceIdDetails(..), IfaceUnfolding(..),
@@ -405,7 +405,7 @@ data IfaceConDecl
         ifConStricts :: [IfaceBang]}            -- Empty (meaning all lazy),
                                                 -- or 1-1 corresp with arg tys
 
-type IfaceEqSpec = [(OccName,IfaceType)]
+type IfaceEqSpec = [(IfLclName,IfaceType)]
 
 instance HasOccName IfaceConDecl where
   occName = ifConOcc
@@ -1183,7 +1183,7 @@ pprIfaceDecl ss (IfaceData { ifName = tycon, ifCType = ctype,
     mk_user_con_res_ty univ_tvs eq_spec
       = (filterOut done_univ_tv univ_tvs, sdocWithDynFlags pp_res_ty)
       where
-        gadt_env = mkFsEnv [(occNameFS occ, ty) | (occ,ty) <- eq_spec]
+        gadt_env = mkFsEnv eq_spec
         done_univ_tv (tv,_) = isJust (lookupFsEnv gadt_env tv)
 
         pp_res_ty dflags
diff --git a/compiler/iface/IfaceType.lhs b/compiler/iface/IfaceType.lhs
index 4a19264..c55edc6 100644
--- a/compiler/iface/IfaceType.lhs
+++ b/compiler/iface/IfaceType.lhs
@@ -15,7 +15,7 @@ module IfaceType (
         IfaceContext, IfaceBndr(..), IfaceTvBndr, IfaceIdBndr,
 
         -- Conversion from Type -> IfaceType
-        toIfaceType, toIfaceTypes, toIfaceKind,
+        toIfaceType, toIfaceTypes, toIfaceKind, toIfaceTyVar,
         toIfaceContext, toIfaceBndr, toIfaceIdBndr,
         toIfaceTvBndrs, toIfaceTyCon, toIfaceTyCon_name,
         toIfaceTcArgs,
diff --git a/compiler/iface/MkIface.lhs b/compiler/iface/MkIface.lhs
index e01097e..21a8047 100644
--- a/compiler/iface/MkIface.lhs
+++ b/compiler/iface/MkIface.lhs
@@ -1646,7 +1646,7 @@ tyConToIfaceDecl env tycon
                     ifConWrapper = isJust (dataConWrapId_maybe data_con),
                     ifConUnivTvs = toIfaceTvBndrs univ_tvs',
                     ifConExTvs   = toIfaceTvBndrs ex_tvs',
-                    ifConEqSpec  = to_eq_spec eq_spec,
+                    ifConEqSpec  = map to_eq_spec eq_spec,
                     ifConCtxt    = tidyToIfaceContext env2 theta,
                     ifConArgTys  = map (tidyToIfaceType env2) arg_tys,
                     ifConFields  = map getOccName
@@ -1659,8 +1659,7 @@ tyConToIfaceDecl env tycon
           -- data constructor is fully standalone
           (env1, univ_tvs') = tidyTyVarBndrs emptyTidyEnv univ_tvs
           (env2, ex_tvs')   = tidyTyVarBndrs env1 ex_tvs
-          to_eq_spec spec = [ (getOccName (tidyTyVar env2 tv), tidyToIfaceType env2 ty)
-                            | (tv,ty) <- spec]
+          to_eq_spec (tv,ty) = (toIfaceTyVar (tidyTyVar env2 tv), tidyToIfaceType env2 ty)
 
 toIfaceBang :: TidyEnv -> HsBang -> IfaceBang
 toIfaceBang _    HsNoBang            = IfNoBang
diff --git a/compiler/iface/TcIface.lhs b/compiler/iface/TcIface.lhs
index e5da356..e4a415a 100644
--- a/compiler/iface/TcIface.lhs
+++ b/compiler/iface/TcIface.lhs
@@ -673,11 +673,11 @@ tcIfaceDataCons tycon_name tycon _ if_cons
     tc_strict (IfUnpackCo if_co) = do { co <- tcIfaceCo if_co
                                       ; return (HsUnpack (Just co)) }
 
-tcIfaceEqSpec :: [(OccName, IfaceType)] -> IfL [(TyVar, Type)]
+tcIfaceEqSpec :: IfaceEqSpec -> IfL [(TyVar, Type)]
 tcIfaceEqSpec spec
   = mapM do_item spec
   where
-    do_item (occ, if_ty) = do { tv <- tcIfaceTyVar (occNameFS occ)
+    do_item (occ, if_ty) = do { tv <- tcIfaceTyVar occ
                               ; ty <- tcIfaceType if_ty
                               ; return (tv,ty) }
 \end{code}



More information about the ghc-commits mailing list