diff options
author | Zubin Duggal <zubin@cmi.ac.in> | 2022-03-12 00:07:56 +0000 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2022-03-23 13:39:39 -0400 |
commit | b91798be48d9fa02610b419ccea15a7dfd663823 (patch) | |
tree | fb87654ccd4a1e92e8c7a15bf454a867460869a3 /compiler/Language/Haskell | |
parent | 52ffd38c610f418ee1d1a549cfdfdaa11794ea40 (diff) | |
download | haskell-b91798be48d9fa02610b419ccea15a7dfd663823.tar.gz |
hi haddock: Lex and store haddock docs in interface files
Names appearing in Haddock docstrings are lexed and renamed like any other names
appearing in the AST. We currently rename names irrespective of the namespace,
so both type and constructor names corresponding to an identifier will appear in
the docstring. Haddock will select a given name as the link destination based on
its own heuristics.
This patch also restricts the limitation of `-haddock` being incompatible with
`Opt_KeepRawTokenStream`.
The export and documenation structure is now computed in GHC and serialised in
.hi files. This can be used by haddock to directly generate doc pages without
reparsing or renaming the source. At the moment the operation of haddock
is not modified, that's left to a future patch.
Updates the haddock submodule with the minimum changes needed.
Diffstat (limited to 'compiler/Language/Haskell')
-rw-r--r-- | compiler/Language/Haskell/Syntax/Decls.hs | 33 | ||||
-rw-r--r-- | compiler/Language/Haskell/Syntax/Type.hs | 4 |
2 files changed, 20 insertions, 17 deletions
diff --git a/compiler/Language/Haskell/Syntax/Decls.hs b/compiler/Language/Haskell/Syntax/Decls.hs index b668d7fbff..64e9a0cc4e 100644 --- a/compiler/Language/Haskell/Syntax/Decls.hs +++ b/compiler/Language/Haskell/Syntax/Decls.hs @@ -7,6 +7,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE UndecidableInstances #-} -- Wrinkle in Note [Trees That Grow] -- in module Language.Haskell.Syntax.Extension {-# LANGUAGE ViewPatterns #-} @@ -150,7 +151,8 @@ data HsDecl p | RuleD (XRuleD p) (RuleDecls p) -- ^ Rule declaration | SpliceD (XSpliceD p) (SpliceDecl p) -- ^ Splice declaration -- (Includes quasi-quotes) - | DocD (XDocD p) (DocDecl) -- ^ Documentation comment declaration + | DocD (XDocD p) (DocDecl p) -- ^ Documentation comment + -- declaration | RoleAnnotD (XRoleAnnotD p) (RoleAnnotDecl p) -- ^Role annotation declaration | XHsDecl !(XXHsDecl p) @@ -1064,8 +1066,8 @@ data ConDecl pass , con_g_args :: HsConDeclGADTDetails pass -- ^ Arguments; never infix , con_res_ty :: LHsType pass -- ^ Result type - , con_doc :: Maybe LHsDocString - -- ^ A possible Haddock comment. + , con_doc :: Maybe (LHsDoc pass) -- ^ A possible Haddock + -- comment. } | ConDeclH98 @@ -1081,8 +1083,7 @@ data ConDecl pass , con_mb_cxt :: Maybe (LHsContext pass) -- ^ User-written context (if any) , con_args :: HsConDeclH98Details pass -- ^ Arguments; can be infix - , con_doc :: Maybe LHsDocString - -- ^ A possible Haddock comment. + , con_doc :: Maybe (LHsDoc pass) -- ^ A possible Haddock comment. } | XConDecl !(XXConDecl pass) @@ -1706,21 +1707,22 @@ pprFullRuleName (L _ (st, n)) = pprWithSourceText st (doubleQuotes $ ftext n) -} -- | Located Documentation comment Declaration -type LDocDecl pass = XRec pass (DocDecl) +type LDocDecl pass = XRec pass (DocDecl pass) -- | Documentation comment Declaration -data DocDecl - = DocCommentNext HsDocString - | DocCommentPrev HsDocString - | DocCommentNamed String HsDocString - | DocGroup Int HsDocString - deriving Data +data DocDecl pass + = DocCommentNext (LHsDoc pass) + | DocCommentPrev (LHsDoc pass) + | DocCommentNamed String (LHsDoc pass) + | DocGroup Int (LHsDoc pass) + +deriving instance (Data pass, Data (IdP pass)) => Data (DocDecl pass) -- Okay, I need to reconstruct the document comments, but for now: -instance Outputable DocDecl where +instance Outputable (DocDecl name) where ppr _ = text "<document comment>" -docDeclDoc :: DocDecl -> HsDocString +docDeclDoc :: DocDecl pass -> LHsDoc pass docDeclDoc (DocCommentNext d) = d docDeclDoc (DocCommentPrev d) = d docDeclDoc (DocCommentNamed _ d) = d @@ -1751,9 +1753,10 @@ data WarnDecls pass = Warnings { wd_ext :: XWarnings pass type LWarnDecl pass = XRec pass (WarnDecl pass) -- | Warning pragma Declaration -data WarnDecl pass = Warning (XWarning pass) [LIdP pass] WarningTxt +data WarnDecl pass = Warning (XWarning pass) [LIdP pass] (WarningTxt pass) | XWarnDecl !(XXWarnDecl pass) + {- ************************************************************************ * * diff --git a/compiler/Language/Haskell/Syntax/Type.hs b/compiler/Language/Haskell/Syntax/Type.hs index 10c2c03b48..e7c35f93c1 100644 --- a/compiler/Language/Haskell/Syntax/Type.hs +++ b/compiler/Language/Haskell/Syntax/Type.hs @@ -841,7 +841,7 @@ data HsType pass -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | HsDocTy (XDocTy pass) - (LHsType pass) LHsDocString -- A documented type + (LHsType pass) (LHsDoc pass) -- A documented type -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : None -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation @@ -1046,7 +1046,7 @@ data ConDeclField pass -- Record fields have Haddock docs on them cd_fld_names :: [LFieldOcc pass], -- ^ See Note [ConDeclField passs] cd_fld_type :: LBangType pass, - cd_fld_doc :: Maybe LHsDocString } + cd_fld_doc :: Maybe (LHsDoc pass)} -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation |