[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/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: Haddock changes for T10598 (d73b286)

git at git.haskell.org git at git.haskell.org
Mon Nov 20 21:04:16 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/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/d73b286cb39ad9d02bee4b1a104e817783ceb195

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

commit d73b286cb39ad9d02bee4b1a104e817783ceb195
Author: Ryan Scott <ryan.gl.scott at gmail.com>
Date:   Sun May 29 23:30:27 2016 -0400

    Haddock changes for T10598
    
    See https://ghc.haskell.org/trac/ghc/ticket/10598


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

d73b286cb39ad9d02bee4b1a104e817783ceb195
 haddock-api/src/Haddock/Backends/Hoogle.hs  | 2 +-
 haddock-api/src/Haddock/Convert.hs          | 4 ++--
 haddock-api/src/Haddock/Interface/Create.hs | 5 +++--
 haddock-api/src/Haddock/Interface/Rename.hs | 5 ++++-
 4 files changed, 10 insertions(+), 6 deletions(-)

diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs
index 1c3dea7..48b9744 100644
--- a/haddock-api/src/Haddock/Backends/Hoogle.hs
+++ b/haddock-api/src/Haddock/Backends/Hoogle.hs
@@ -204,7 +204,7 @@ ppSynonym dflags x = [out dflags x]
 
 ppData :: DynFlags -> TyClDecl Name -> [(Name, DocForDecl Name)] -> [String]
 ppData dflags decl@(DataDecl { tcdDataDefn = defn }) subdocs
-    = showData decl{ tcdDataDefn = defn { dd_cons=[],dd_derivs=Nothing }} :
+    = showData decl{ tcdDataDefn = defn { dd_cons=[],dd_derivs=noLoc [] }} :
       concatMap (ppCtor dflags decl subdocs . unL) (dd_cons defn)
     where
 
diff --git a/haddock-api/src/Haddock/Convert.hs b/haddock-api/src/Haddock/Convert.hs
index 41e98c6..4e2ee05 100644
--- a/haddock-api/src/Haddock/Convert.hs
+++ b/haddock-api/src/Haddock/Convert.hs
@@ -153,7 +153,7 @@ synifyTyCon _coax tc
                                       , dd_kindSig = Just (synifyKindSig (tyConKind tc))
                                                -- we have their kind accurately:
                                       , dd_cons = []  -- No constructors
-                                      , dd_derivs = Nothing }
+                                      , dd_derivs = noLoc [] }
            , tcdDataCusk = False
            , tcdFVs = placeHolderNamesTc }
 
@@ -224,7 +224,7 @@ synifyTyCon coax tc
   consRaw = map (synifyDataCon use_gadt_syntax) (tyConDataCons tc)
   cons = rights consRaw
   -- "deriving" doesn't affect the signature, no need to specify any.
-  alg_deriv = Nothing
+  alg_deriv = noLoc []
   defn = HsDataDefn { dd_ND      = alg_nd
                     , dd_ctxt    = alg_ctx
                     , dd_cType   = Nothing
diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs
index 2c8b0b7..2cdc6f8 100644
--- a/haddock-api/src/Haddock/Interface/Create.hs
+++ b/haddock-api/src/Haddock/Interface/Create.hs
@@ -349,8 +349,9 @@ subordinates instMap decl = case decl of
                   , L _ (ConDeclField ns _ doc) <- (unLoc flds)
                   , L _ n <- ns ]
         derivs  = [ (instName, [unL doc], M.empty)
-                  | Just (L _ tys) <- [dd_derivs dd]
-                  , HsIB { hsib_body = L l (HsDocTy _ doc) } <- tys
+                  | HsIB { hsib_body = L l (HsDocTy _ doc) }
+                      <- concatMap (unLoc . deriv_clause_tys . unLoc) $
+                           unLoc $ dd_derivs dd
                   , Just instName <- [M.lookup l instMap] ]
 
 -- | Extract function argument docs from inside types.
diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs
index cf3b72a..fa85ba6 100644
--- a/haddock-api/src/Haddock/Interface/Rename.hs
+++ b/haddock-api/src/Haddock/Interface/Rename.hs
@@ -416,7 +416,8 @@ renameDataDefn (HsDataDefn { dd_ND = nd, dd_ctxt = lcontext, dd_cType = cType
     cons'     <- mapM (mapM renameCon) cons
     -- I don't think we need the derivings, so we return Nothing
     return (HsDataDefn { dd_ND = nd, dd_ctxt = lcontext', dd_cType = cType
-                       , dd_kindSig = k', dd_cons = cons', dd_derivs = Nothing })
+                       , dd_kindSig = k', dd_cons = cons'
+                       , dd_derivs = noLoc [] })
 
 renameCon :: ConDecl Name -> RnM (ConDecl DocName)
 renameCon decl@(ConDeclH98 { con_name = lname, con_qvars = ltyvars
@@ -509,9 +510,11 @@ renameInstD (DataFamInstD { dfid_inst = d }) = do
 
 renameDerivD :: DerivDecl Name -> RnM (DerivDecl DocName)
 renameDerivD (DerivDecl { deriv_type = ty
+                        , deriv_strategy = strat
                         , deriv_overlap_mode = omode }) = do
   ty' <- renameLSigType ty
   return (DerivDecl { deriv_type = ty'
+                    , deriv_strategy = strat
                     , deriv_overlap_mode = omode })
 
 renameClsInstD :: ClsInstDecl Name -> RnM (ClsInstDecl DocName)



More information about the ghc-commits mailing list