[commit: haddock] wip/ast-annotations-separate: Track changes to hsSyn (691b6de)

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


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

On branch  : wip/ast-annotations-separate
Link       : http://git.haskell.org/haddock.git/commitdiff/691b6de6004e3725ebae5847108a63834c6abe34

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

commit 691b6de6004e3725ebae5847108a63834c6abe34
Author: Alan Zimmerman <alan.zimm at gmail.com>
Date:   Wed Oct 8 23:30:06 2014 +0200

    Track changes to hsSyn


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

691b6de6004e3725ebae5847108a63834c6abe34
 src/Haddock/Backends/Xhtml/Decl.hs | 2 +-
 src/Haddock/Convert.hs             | 2 +-
 src/Haddock/Interface/Create.hs    | 4 ++--
 src/Haddock/Interface/Rename.hs    | 4 ++--
 4 files changed, 6 insertions(+), 6 deletions(-)

diff --git a/src/Haddock/Backends/Xhtml/Decl.hs b/src/Haddock/Backends/Xhtml/Decl.hs
index 304eae8..7d7f9cf 100644
--- a/src/Haddock/Backends/Xhtml/Decl.hs
+++ b/src/Haddock/Backends/Xhtml/Decl.hs
@@ -275,7 +275,7 @@ ppTyFam summary associated links instances fixities loc doc decl splice unicode
     instancesBit
       | FamilyDecl { fdInfo = ClosedTypeFamily eqns } <- decl
       , not summary
-      = subEquations qual $ map (ppTyFamEqn . unLoc) eqns
+      = subEquations qual $ map (ppTyFamEqn . unLoc) (fromCL eqns)
 
       | otherwise
       = ppInstances instances docname unicode qual
diff --git a/src/Haddock/Convert.hs b/src/Haddock/Convert.hs
index 839cfb2..7e4897d 100644
--- a/src/Haddock/Convert.hs
+++ b/src/Haddock/Convert.hs
@@ -156,7 +156,7 @@ synifyTyCon coax tc
         let info = case rhs of
                      OpenSynFamilyTyCon -> OpenTypeFamily
                      ClosedSynFamilyTyCon (CoAxiom { co_ax_branches = branches }) ->
-                       ClosedTypeFamily (brListMap (noLoc . synifyAxBranch tc) branches)
+                       ClosedTypeFamily (toCL $ brListMap (noLoc . synifyAxBranch tc) branches)
                      _ -> error "synifyTyCon: type/data family confusion"
         in FamDecl (FamilyDecl { fdInfo = info
                                , fdLName = synifyName tc
diff --git a/src/Haddock/Interface/Create.hs b/src/Haddock/Interface/Create.hs
index 738f1c9..03b8662 100644
--- a/src/Haddock/Interface/Create.hs
+++ b/src/Haddock/Interface/Create.hs
@@ -711,8 +711,8 @@ fullModuleContents dflags warnings gre (docMap, argMap, subMap, declMap, instMap
     expandSig = foldr f []
       where
         f :: LHsDecl name -> [LHsDecl name] -> [LHsDecl name]
-        f (L l (SigD (TypeSig    names t)))          xs = foldr (\n acc -> L l (SigD (TypeSig    (unitCL n) t))          : acc) xs  $ fromCL names
-        f (L l (SigD (GenericSig names t)))          xs = foldr (\n acc -> L l (SigD (GenericSig (unitCL n) t))          : acc) xs $ fromCL names
+        f (L l (SigD (TypeSig    names t)))          xs = foldr (\n acc -> L l (SigD (TypeSig    (unitCL n) t))          : acc) xs names
+        f (L l (SigD (GenericSig names t)))          xs = foldr (\n acc -> L l (SigD (GenericSig (unitCL n) t))          : acc) xs names
         f x xs = x : xs
 
     mkExportItem :: LHsDecl Name -> ErrMsgGhc (Maybe (ExportItem Name))
diff --git a/src/Haddock/Interface/Rename.hs b/src/Haddock/Interface/Rename.hs
index 0d2e15a..dd2bd73 100644
--- a/src/Haddock/Interface/Rename.hs
+++ b/src/Haddock/Interface/Rename.hs
@@ -403,9 +403,9 @@ renameConDeclFieldField (ConDeclField name t doc) = do
 renameSig :: Sig Name -> RnM (Sig DocName)
 renameSig sig = case sig of
   TypeSig lnames ltype -> do
-    lnames' <- mapM renameL $ fromCL lnames
+    lnames' <- mapM renameL lnames
     ltype' <- renameLType ltype
-    return (TypeSig (toCL lnames') ltype')
+    return (TypeSig lnames' ltype')
   PatSynSig lname args ltype lreq lprov -> do
     lname' <- renameL lname
     args' <- case args of



More information about the ghc-commits mailing list