[commit: haddock] wip/landmine-param-family: Get rid of PlaceHolderNames class (87b2cba)

git at git.haskell.org git at git.haskell.org
Wed Jul 8 08:30:14 UTC 2015


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

On branch  : wip/landmine-param-family
Link       : http://git.haskell.org/haddock.git/commitdiff/87b2cba0850d75b10617327acc3923995fc08399

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

commit 87b2cba0850d75b10617327acc3923995fc08399
Author: Alan Zimmerman <alan.zimm at gmail.com>
Date:   Mon Aug 18 10:30:28 2014 +0200

    Get rid of PlaceHolderNames class


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

87b2cba0850d75b10617327acc3923995fc08399
 src/Haddock/Convert.hs          | 10 +++++-----
 src/Haddock/Interface/Rename.hs | 10 +++++-----
 2 files changed, 10 insertions(+), 10 deletions(-)

diff --git a/src/Haddock/Convert.hs b/src/Haddock/Convert.hs
index dfb0f14..4830639 100644
--- a/src/Haddock/Convert.hs
+++ b/src/Haddock/Convert.hs
@@ -81,7 +81,7 @@ tyThingToLHsDecl t = noLoc $ case t of
          , tcdATs = atFamDecls
          , tcdATDefs = [] --ignore associated type defaults
          , tcdDocs = [] --we don't have any docs at this point
-         , tcdFVs = placeHolderNames }
+         , tcdFVs = placeHolderNamesTc }
     | otherwise
     -> TyClD (synifyTyCon Nothing tc)
 
@@ -118,7 +118,7 @@ synifyAxiom ax@(CoAxiom { co_ax_tc = tc })
   | isOpenSynFamilyTyCon tc
   , Just branch <- coAxiomSingleBranch_maybe ax
   = InstD (TyFamInstD (TyFamInstDecl { tfid_eqn = noLoc $ synifyAxBranch tc branch
-                                     , tfid_fvs = placeHolderNames }))
+                                     , tfid_fvs = placeHolderNamesTc }))
 
   | Just ax' <- isClosedSynFamilyTyCon_maybe tc
   , getUnique ax' == getUnique ax   -- without the getUniques, type error
@@ -148,7 +148,7 @@ synifyTyCon coax tc
                                                -- we have their kind accurately:
                                       , dd_cons = []  -- No constructors
                                       , dd_derivs = Nothing }
-           , tcdFVs = placeHolderNames }
+           , tcdFVs = placeHolderNamesTc }
 
   | isSynFamilyTyCon tc 
   = case synTyConRhs_maybe tc of
@@ -177,7 +177,7 @@ synifyTyCon coax tc
           SynDecl { tcdLName = synifyName tc
                   , tcdTyVars = synifyTyVars (tyConTyVars tc)
                   , tcdRhs = synifyType WithinType ty
-                  , tcdFVs = placeHolderNames }
+                  , tcdFVs = placeHolderNamesTc }
         _ -> error "synifyTyCon: impossible synTyCon"
   | otherwise =
   -- (closed) newtype and data
@@ -217,7 +217,7 @@ synifyTyCon coax tc
                     , dd_cons    = cons 
                     , dd_derivs  = alg_deriv }
  in DataDecl { tcdLName = name, tcdTyVars = tyvars, tcdDataDefn = defn
-             , tcdFVs = placeHolderNames }
+             , tcdFVs = placeHolderNamesTc }
 
 -- User beware: it is your responsibility to pass True (use_gadt_syntax)
 -- for any constructor that would be misrepresented by omitting its
diff --git a/src/Haddock/Interface/Rename.hs b/src/Haddock/Interface/Rename.hs
index 7f1b1ef..c6cea8d 100644
--- a/src/Haddock/Interface/Rename.hs
+++ b/src/Haddock/Interface/Rename.hs
@@ -307,17 +307,17 @@ renameTyClD d = case d of
     decl' <- renameFamilyDecl decl
     return (FamDecl { tcdFam = decl' })
 
-  SynDecl { tcdLName = lname, tcdTyVars = tyvars, tcdRhs = rhs, tcdFVs = fvs } -> do
+  SynDecl { tcdLName = lname, tcdTyVars = tyvars, tcdRhs = rhs, tcdFVs = _fvs } -> do
     lname'    <- renameL lname
     tyvars'   <- renameLTyVarBndrs tyvars
     rhs'     <- renameLType rhs
-    return (SynDecl { tcdLName = lname', tcdTyVars = tyvars', tcdRhs = rhs', tcdFVs = fvs })
+    return (SynDecl { tcdLName = lname', tcdTyVars = tyvars', tcdRhs = rhs', tcdFVs = placeHolderNames })
 
-  DataDecl { tcdLName = lname, tcdTyVars = tyvars, tcdDataDefn = defn, tcdFVs = fvs } -> do
+  DataDecl { tcdLName = lname, tcdTyVars = tyvars, tcdDataDefn = defn, tcdFVs = _fvs } -> do
     lname'    <- renameL lname
     tyvars'   <- renameLTyVarBndrs tyvars
     defn'     <- renameDataDefn defn
-    return (DataDecl { tcdLName = lname', tcdTyVars = tyvars', tcdDataDefn = defn', tcdFVs = fvs })
+    return (DataDecl { tcdLName = lname', tcdTyVars = tyvars', tcdDataDefn = defn', tcdFVs = placeHolderNames })
 
   ClassDecl { tcdCtxt = lcontext, tcdLName = lname, tcdTyVars = ltyvars
             , tcdFDs = lfundeps, tcdSigs = lsigs, tcdATs = ats, tcdATDefs = at_defs } -> do
@@ -457,7 +457,7 @@ renameClsInstD (ClsInstDecl { cid_overlap_mode = omode
                       , cid_sigs = []
                       , cid_tyfam_insts = lATs', cid_datafam_insts = lADTs' })
 
-type instance PostRn DocName NameSet  = NameSet
+type instance PostRn DocName NameSet  = PlaceHolder
 
 renameTyFamInstD :: TyFamInstDecl Name -> RnM (TyFamInstDecl DocName)
 renameTyFamInstD (TyFamInstDecl { tfid_eqn = eqn })



More information about the ghc-commits mailing list