[commit: haddock] master: Add support for anchoring signatures in type class declarations. (d761512)

git at git.haskell.org git at git.haskell.org
Wed Jul 8 08:42:39 UTC 2015


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

On branch  : master
Link       : http://git.haskell.org/haddock.git/commitdiff/d761512f239b17f8e9824629595d75aa46e55554

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

commit d761512f239b17f8e9824629595d75aa46e55554
Author: Łukasz Hanuszczak <lukasz.hanuszczak at gmail.com>
Date:   Thu Jul 2 18:53:28 2015 +0200

    Add support for anchoring signatures in type class declarations.


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

d761512f239b17f8e9824629595d75aa46e55554
 haddock-api/src/Haddock/Backends/Hyperlinker/Ast.hs | 5 +++++
 1 file changed, 5 insertions(+)

diff --git a/haddock-api/src/Haddock/Backends/Hyperlinker/Ast.hs b/haddock-api/src/Haddock/Backends/Hyperlinker/Ast.hs
index 4b60ca3..98c9770 100644
--- a/haddock-api/src/Haddock/Backends/Hyperlinker/Ast.hs
+++ b/haddock-api/src/Haddock/Backends/Hyperlinker/Ast.hs
@@ -1,5 +1,7 @@
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE RecordWildCards #-}
+
 
 module Haddock.Backends.Hyperlinker.Ast
     ( enrich
@@ -135,6 +137,7 @@ decls (group, _, _, _) = concatMap ($ group)
     typ (GHC.L _ t) = case t of
         GHC.DataDecl name _ _ _ -> pure . decl $ name
         GHC.FamDecl fam -> pure . decl $ GHC.fdLName fam
+        GHC.ClassDecl{..} -> [decl tcdLName] ++ concatMap sig tcdSigs
         _ -> pure . decl $ GHC.tcdLName t
     fun term = case cast term of
         (Just (GHC.FunBind (GHC.L sspan name) _ _ _ _ _ :: GHC.HsBind GHC.Name))
@@ -152,6 +155,8 @@ decls (group, _, _, _) = concatMap ($ group)
     fld term = case cast term of
         Just field -> map decl $ GHC.cd_fld_names field
         Nothing -> empty
+    sig (GHC.L _ (GHC.TypeSig names _ _)) = map decl names
+    sig _ = []
     decl (GHC.L sspan name) = (sspan, RtkDecl name)
     tyref (GHC.L sspan name) = (sspan, RtkType name)
 



More information about the ghc-commits mailing list