[commit: haddock] alexbiehl-patch-1, ghc-head, ghc-head1, haddock-quick, headdock-library-1.4.5, ie_avails, master, pr-filter-maps, pr/cabal-desc, travis, v2.18, wip-located-module-as, wip/D2418, wip/T12942, wip/T13163, wip/T3384, wip/embelleshed-rdr, wip/new-tree-one-param, wip/rae, wip/remove-frames, wip/remove-frames1, wip/revert-ttg-2017-11-20, wip/ttg-2017-10-13, wip/ttg-2017-10-31, wip/ttg-2017-11-06, wip/ttg2-2017-11-10, wip/ttg3-2017-11-12, wip/ttg4-constraints-2017-11-13: Follow changes to LHsSigWcType (09054c2)

git at git.haskell.org git at git.haskell.org
Mon Nov 20 21:03:25 UTC 2017


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

On branches: alexbiehl-patch-1,ghc-head,ghc-head1,haddock-quick,headdock-library-1.4.5,ie_avails,master,pr-filter-maps,pr/cabal-desc,travis,v2.18,wip-located-module-as,wip/D2418,wip/T12942,wip/T13163,wip/T3384,wip/embelleshed-rdr,wip/new-tree-one-param,wip/rae,wip/remove-frames,wip/remove-frames1,wip/revert-ttg-2017-11-20,wip/ttg-2017-10-13,wip/ttg-2017-10-31,wip/ttg-2017-11-06,wip/ttg2-2017-11-10,wip/ttg3-2017-11-12,wip/ttg4-constraints-2017-11-13
Link       : http://git.haskell.org/haddock.git/commitdiff/09054c2c6ac346b19d0dec9a43956fcea1c272fb

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

commit 09054c2c6ac346b19d0dec9a43956fcea1c272fb
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Mon Jun 13 18:26:03 2016 +0100

    Follow changes to LHsSigWcType


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

09054c2c6ac346b19d0dec9a43956fcea1c272fb
 haddock-api/src/Haddock/Backends/Xhtml/Decl.hs  | 4 +---
 haddock-api/src/Haddock/Convert.hs              | 2 +-
 haddock-api/src/Haddock/Interface/Rename.hs     | 4 ++--
 haddock-api/src/Haddock/Interface/Specialize.hs | 4 ++--
 haddock-api/src/Haddock/Utils.hs                | 2 +-
 5 files changed, 7 insertions(+), 9 deletions(-)

diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
index e6dfce6..d32c6d1 100644
--- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
+++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs
@@ -646,10 +646,8 @@ ppInstanceSigs :: LinksInfo -> Splice -> Unicode -> Qualification
 ppInstanceSigs links splice unicode qual sigs = do
     TypeSig lnames typ <- sigs
     let names = map unLoc lnames
-        L loc rtyp = get_type typ
+        L loc rtyp = hsSigWcType typ
     return $ ppSimpleSig links splice unicode qual loc names rtyp
-    where
-      get_type = hswc_body . hsib_body
 
 
 lookupAnySubdoc :: Eq id1 => id1 -> [(id1, DocForDecl id2)] -> DocForDecl id2
diff --git a/haddock-api/src/Haddock/Convert.hs b/haddock-api/src/Haddock/Convert.hs
index 71a8119..ecc26b9 100644
--- a/haddock-api/src/Haddock/Convert.hs
+++ b/haddock-api/src/Haddock/Convert.hs
@@ -357,7 +357,7 @@ synifySigType s ty = mkEmptyImplicitBndrs (synifyType s ty)
 
 synifySigWcType :: SynifyTypeState -> Type -> LHsSigWcType Name
 -- Ditto (see synifySigType)
-synifySigWcType s ty = mkEmptyImplicitBndrs (mkEmptyWildCardBndrs (synifyType s ty))
+synifySigWcType s ty = mkEmptyWildCardBndrs (mkEmptyImplicitBndrs (synifyType s ty))
 
 synifyPatSynSigType :: PatSyn -> LHsSigType Name
 -- Ditto (see synifySigType)
diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs
index 1f3f2aa..ab23ce3 100644
--- a/haddock-api/src/Haddock/Interface/Rename.hs
+++ b/haddock-api/src/Haddock/Interface/Rename.hs
@@ -179,7 +179,7 @@ renameLSigType :: LHsSigType Name -> RnM (LHsSigType DocName)
 renameLSigType = renameImplicit renameLType
 
 renameLSigWcType :: LHsSigWcType Name -> RnM (LHsSigWcType DocName)
-renameLSigWcType = renameImplicit (renameWc renameLType)
+renameLSigWcType = renameWc (renameImplicit renameLType)
 
 renameLKind :: LHsKind Name -> RnM (LHsKind DocName)
 renameLKind = renameLType
@@ -573,7 +573,7 @@ renameWc :: (in_thing -> RnM out_thing)
 renameWc rn_thing (HsWC { hswc_body = thing })
   = do { thing' <- rn_thing thing
        ; return (HsWC { hswc_body = thing'
-                      , hswc_wcs = PlaceHolder, hswc_ctx = Nothing }) }
+                      , hswc_wcs = PlaceHolder }) }
 
 renameDocInstance :: DocInstance Name -> RnM (DocInstance DocName)
 renameDocInstance (inst, idoc, L l n) = do
diff --git a/haddock-api/src/Haddock/Interface/Specialize.hs b/haddock-api/src/Haddock/Interface/Specialize.hs
index ab719fe..198bc4f 100644
--- a/haddock-api/src/Haddock/Interface/Specialize.hs
+++ b/haddock-api/src/Haddock/Interface/Specialize.hs
@@ -81,10 +81,10 @@ specializeSig :: forall name . (Eq name, DataId name, SetName name)
               -> Sig name
               -> Sig name
 specializeSig bndrs typs (TypeSig lnames typ) =
-    TypeSig lnames (typ { hsib_body = (hsib_body typ) { hswc_body = noLoc typ'}})
+    TypeSig lnames (typ { hswc_body = (hswc_body typ) { hsib_body = noLoc typ'}})
   where
     true_type :: HsType name
-    true_type = unLoc (hswc_body (hsib_body typ))
+    true_type = unLoc (hsSigWcType typ)
     typ' :: HsType name
     typ' = rename fv . sugar $ specializeTyVarBndrs bndrs typs true_type
     fv = foldr Set.union Set.empty . map freeVariables $ typs
diff --git a/haddock-api/src/Haddock/Utils.hs b/haddock-api/src/Haddock/Utils.hs
index 58a7ef9..da87990 100644
--- a/haddock-api/src/Haddock/Utils.hs
+++ b/haddock-api/src/Haddock/Utils.hs
@@ -129,7 +129,7 @@ mkMeta x = emptyMetaDoc { _doc = x }
 mkEmptySigWcType :: LHsType Name -> LHsSigWcType Name
 -- Dubious, because the implicit binders are empty even
 -- though the type might have free varaiables
-mkEmptySigWcType ty = mkEmptyImplicitBndrs (mkEmptyWildCardBndrs ty)
+mkEmptySigWcType ty = mkEmptyWildCardBndrs (mkEmptyImplicitBndrs ty)
 
 addClassContext :: Name -> LHsQTyVars Name -> LSig Name -> LSig Name
 -- Add the class context to a class-op signature



More information about the ghc-commits mailing list