[commit: haddock] T6018-injective-type-families, adamse-D1033, ghc-head, master, wip/10268, wip/10313, wip/D538, wip/D538-1, wip/D538-2, wip/D538-3, wip/D538-4, wip/D538-5, wip/D538-6, wip/D548-master, wip/D548-master-2, wip/T10483, wip/T9840, wip/api-annot-tweaks-7.10, wip/api-annots-ghc-7.10-3, wip/orf-reboot: Follow changes to TypeAnnot in GHC HEAD (906ac8d)

git at git.haskell.org git at git.haskell.org
Wed Jul 8 08:34:21 UTC 2015


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

On branches: T6018-injective-type-families,adamse-D1033,ghc-head,master,wip/10268,wip/10313,wip/D538,wip/D538-1,wip/D538-2,wip/D538-3,wip/D538-4,wip/D538-5,wip/D538-6,wip/D548-master,wip/D548-master-2,wip/T10483,wip/T9840,wip/api-annot-tweaks-7.10,wip/api-annots-ghc-7.10-3,wip/orf-reboot
Link       : http://git.haskell.org/haddock.git/commitdiff/906ac8d0b1d243ea8a7b6b0d2fa1316e9303d31c

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

commit 906ac8d0b1d243ea8a7b6b0d2fa1316e9303d31c
Author: Alan Zimmerman <alan.zimm at gmail.com>
Date:   Fri Sep 5 18:13:24 2014 -0500

    Follow changes to TypeAnnot in GHC HEAD
    
    Signed-off-by: Austin Seipp <aseipp at pobox.com>
    
    Conflicts:
    	haddock-api/src/Haddock/Convert.hs


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

906ac8d0b1d243ea8a7b6b0d2fa1316e9303d31c
 haddock-api/src/Haddock/Convert.hs          | 10 +++++-----
 haddock-api/src/Haddock/Interface/Rename.hs | 27 +++++++++++++++++++++------
 2 files changed, 26 insertions(+), 11 deletions(-)

diff --git a/haddock-api/src/Haddock/Convert.hs b/haddock-api/src/Haddock/Convert.hs
index 749421c..91581c7 100644
--- a/haddock-api/src/Haddock/Convert.hs
+++ b/haddock-api/src/Haddock/Convert.hs
@@ -85,7 +85,7 @@ tyThingToLHsDecl t = case t of
          , tcdATs = rights atFamDecls
          , tcdATDefs = [] --ignore associated type defaults
          , tcdDocs = [] --we don't have any docs at this point
-         , tcdFVs = placeHolderNames }
+         , tcdFVs = placeHolderNamesTc }
     | otherwise
     -> synifyTyCon Nothing tc >>= allOK . TyClD
 
@@ -135,7 +135,7 @@ synifyAxiom ax@(CoAxiom { co_ax_tc = tc })
   , Just branch <- coAxiomSingleBranch_maybe ax
   = return $ 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
@@ -167,7 +167,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
@@ -203,7 +203,7 @@ synifyTyCon coax tc
           SynDecl { tcdLName = synifyName tc
                   , tcdTyVars = synifyTyVars (tyConTyVars tc)
                   , tcdRhs = synifyType WithinType ty
-                  , tcdFVs = placeHolderNames }
+                  , tcdFVs = placeHolderNamesTc }
         _ -> Left "synifyTyCon: impossible synTyCon"
   | otherwise =
   -- (closed) newtype and data
@@ -246,7 +246,7 @@ synifyTyCon coax tc
  in case lefts consRaw of
   [] -> return $
         DataDecl { tcdLName = name, tcdTyVars = tyvars, tcdDataDefn = defn
-                 , tcdFVs = placeHolderNames }
+                 , tcdFVs = placeHolderNamesTc }
   dataConErrs -> Left $ unlines dataConErrs
 
 -- User beware: it is your responsibility to pass True (use_gadt_syntax)
diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs
index 1cc8c8d..31bb2b9 100644
--- a/haddock-api/src/Haddock/Interface/Rename.hs
+++ b/haddock-api/src/Haddock/Interface/Rename.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE TypeFamilies #-}
 ----------------------------------------------------------------------------
 -- |
 -- Module      :  Haddock.Interface.Rename
@@ -20,6 +21,8 @@ import Haddock.Types
 import Bag (emptyBag)
 import GHC hiding (NoLink)
 import Name
+import NameSet
+import Coercion
 
 import Control.Applicative
 import Control.Monad hiding (mapM)
@@ -176,6 +179,7 @@ renameLKind = renameLType
 renameMaybeLKind :: Maybe (LHsKind Name) -> RnM (Maybe (LHsKind DocName))
 renameMaybeLKind = traverse renameLKind
 
+
 renameType :: HsType Name -> RnM (HsType DocName)
 renameType t = case t of
   HsForAllTy expl tyvars lcontext ltype -> do
@@ -302,17 +306,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
@@ -465,7 +469,7 @@ renameLTyFamInstEqn (L loc (TyFamEqn { tfe_tycon = tc, tfe_pats = pats_w_bndrs,
        ; pats' <- mapM renameLType (hswb_cts pats_w_bndrs)
        ; rhs' <- renameLType rhs
        ; return (L loc (TyFamEqn { tfe_tycon = tc'
-                                 , tfe_pats = pats_w_bndrs { hswb_cts = pats' }
+                                 , tfe_pats = HsWB pats' PlaceHolder PlaceHolder
                                  , tfe_rhs = rhs' })) }
 
 renameLTyFamDefltEqn :: LTyFamDefltEqn Name -> RnM (LTyFamDefltEqn DocName)
@@ -482,7 +486,9 @@ renameDataFamInstD (DataFamInstDecl { dfid_tycon = tc, dfid_pats = pats_w_bndrs,
   = do { tc' <- renameL tc
        ; pats' <- mapM renameLType (hswb_cts pats_w_bndrs)
        ; defn' <- renameDataDefn defn
-       ; return (DataFamInstDecl { dfid_tycon = tc', dfid_pats = pats_w_bndrs { hswb_cts = pats' }
+       ; return (DataFamInstDecl { dfid_tycon = tc'
+                                 , dfid_pats
+                                       = HsWB pats' PlaceHolder PlaceHolder
                                  , dfid_defn = defn', dfid_fvs = placeHolderNames }) }
 
 renameExportItem :: ExportItem Name -> RnM (ExportItem DocName)
@@ -517,3 +523,12 @@ renameSub (n,doc) = do
   n' <- rename n
   doc' <- renameDocForDecl doc
   return (n', doc')
+
+type instance PostRn DocName NameSet  = PlaceHolder
+type instance PostRn DocName Fixity   = PlaceHolder
+type instance PostRn DocName Bool     = PlaceHolder
+type instance PostRn DocName [Name]   = PlaceHolder
+
+type instance PostTc DocName Kind     = PlaceHolder
+type instance PostTc DocName Type     = PlaceHolder
+type instance PostTc DocName Coercion = PlaceHolder



More information about the ghc-commits mailing list