From 5d45da4898f7e8e7a1637b4cd473c393063034a0 Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Mon, 25 Feb 2019 21:53:56 -0800 Subject: Fix standalone deriving docs Docs on standalone deriving decls for classes with associated types should be associated with the class instance, not the associated type instance. Fixes #1033 --- haddock-api/src/Haddock/Interface/Create.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) (limited to 'haddock-api/src/Haddock/Interface/Create.hs') diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index a4408434..146c3cc8 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -132,8 +132,8 @@ createInterface tm flags modMap instIfaceMap = do fixMap = mkFixMap group_ (decls, _) = unzip declsWithDocs localInsts = filter (nameIsLocalOrFrom sem_mdl) - $ map getName instances - ++ map getName fam_instances + $ map getName fam_instances + ++ map getName instances -- Locations of all TH splices splices = [ l | L l (SpliceD _ _) <- hsmodDecls hsm ] -- cgit v1.2.3 From dc78937c638d9e1e4f4cfd18f90ecf79d8649c06 Mon Sep 17 00:00:00 2001 From: Alan Zimmerman Date: Sat, 26 Jan 2019 21:45:59 +0200 Subject: Matching changes in GHC for #16236 (cherry picked from commit 3ee6526d4ae7bf4deb7cd1caf24b3d7355573576) --- haddock-api/src/Haddock/Backends/LaTeX.hs | 6 +++--- haddock-api/src/Haddock/Backends/Xhtml/Decl.hs | 4 ++-- haddock-api/src/Haddock/Interface/Create.hs | 6 +++--- haddock-api/src/Haddock/Interface/Rename.hs | 4 ++-- 4 files changed, 10 insertions(+), 10 deletions(-) (limited to 'haddock-api/src/Haddock/Interface/Create.hs') diff --git a/haddock-api/src/Haddock/Backends/LaTeX.hs b/haddock-api/src/Haddock/Backends/LaTeX.hs index cc096a7a..c62a9311 100644 --- a/haddock-api/src/Haddock/Backends/LaTeX.hs +++ b/haddock-api/src/Haddock/Backends/LaTeX.hs @@ -1029,9 +1029,9 @@ ppCtxType unicode ty = ppr_mono_ty (reparenTypePrec PREC_CTX ty) unicode ppLHsTypeArg :: Bool -> LHsTypeArg DocNameI -> LaTeX ppLHsTypeArg unicode (HsValArg ty) = ppLParendType unicode ty -ppLHsTypeArg unicode (HsTypeArg ki) = atSign unicode <> - ppLParendType unicode ki -ppLHsTypeArg _ (HsArgPar _) = text "" +ppLHsTypeArg unicode (HsTypeArg _ ki) = atSign unicode <> + ppLParendType unicode ki +ppLHsTypeArg _ (HsArgPar _) = text "" ppHsTyVarBndr :: Bool -> HsTyVarBndr DocNameI -> LaTeX ppHsTyVarBndr _ (UserTyVar _ (L _ name)) = ppDocName name diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs index 56a79d57..40d630b0 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs @@ -1135,8 +1135,8 @@ ppFunLhType unicode qual emptyCtxts ty = ppr_mono_ty (reparenTypePrec PREC_FUN ppLHsTypeArg :: Unicode -> Qualification -> HideEmptyContexts -> LHsTypeArg DocNameI -> Html ppLHsTypeArg unicode qual emptyCtxts (HsValArg ty) = ppLParendType unicode qual emptyCtxts ty -ppLHsTypeArg unicode qual emptyCtxts (HsTypeArg ki) = atSign unicode <> - ppLParendType unicode qual emptyCtxts ki +ppLHsTypeArg unicode qual emptyCtxts (HsTypeArg _ ki) = atSign unicode <> + ppLParendType unicode qual emptyCtxts ki ppLHsTypeArg _ _ _ (HsArgPar _) = toHtml "" ppHsTyVarBndr :: Unicode -> Qualification -> HsTyVarBndr DocNameI -> Html ppHsTyVarBndr _ qual (UserTyVar _ (L _ name)) = diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index d89efb5a..463411b4 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -1140,7 +1140,7 @@ extractPatternSyn nm t tvs cons = | otherwise = foldl' (\x y -> noLoc (mkAppTyArg x y)) (noLoc (HsTyVar noExt NotPromoted (noLoc t))) tvs where mkAppTyArg :: LHsType GhcRn -> LHsTypeArg GhcRn -> HsType GhcRn mkAppTyArg f (HsValArg ty) = HsAppTy noExt f ty - mkAppTyArg f (HsTypeArg ki) = HsAppKindTy noExt f ki + mkAppTyArg f (HsTypeArg l ki) = HsAppKindTy l f ki mkAppTyArg f (HsArgPar _) = HsParTy noExt f extractRecSel :: Name -> Name -> [LHsTypeArg GhcRn] -> [LConDecl GhcRn] @@ -1162,8 +1162,8 @@ extractRecSel nm t tvs (L _ con : rest) = | otherwise = foldl' (\x y -> noLoc (mkAppTyArg x y)) (noLoc (HsTyVar noExt NotPromoted (noLoc t))) tvs where mkAppTyArg :: LHsType GhcRn -> LHsTypeArg GhcRn -> HsType GhcRn mkAppTyArg f (HsValArg ty) = HsAppTy noExt f ty - mkAppTyArg f (HsTypeArg ki) = HsAppKindTy noExt f ki - mkAppTyArg f (HsArgPar _) = HsParTy noExt f + mkAppTyArg f (HsTypeArg l ki) = HsAppKindTy l f ki + mkAppTyArg f (HsArgPar _) = HsParTy noExt f -- | Keep export items with docs. pruneExportItems :: [ExportItem GhcRn] -> [ExportItem GhcRn] diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs index 88238f04..ceea2444 100644 --- a/haddock-api/src/Haddock/Interface/Rename.hs +++ b/haddock-api/src/Haddock/Interface/Rename.hs @@ -186,8 +186,8 @@ renameLType = mapM renameType renameLTypeArg :: LHsTypeArg GhcRn -> RnM (LHsTypeArg DocNameI) renameLTypeArg (HsValArg ty) = do { ty' <- renameLType ty ; return $ HsValArg ty' } -renameLTypeArg (HsTypeArg ki) = do { ki' <- renameLKind ki - ; return $ HsTypeArg ki' } +renameLTypeArg (HsTypeArg l ki) = do { ki' <- renameLKind ki + ; return $ HsTypeArg l ki' } renameLTypeArg (HsArgPar sp) = return $ HsArgPar sp renameLSigType :: LHsSigType GhcRn -> RnM (LHsSigType DocNameI) -- cgit v1.2.3 From 9bbcd3859c9ea08b75e6964490e75236f4a73454 Mon Sep 17 00:00:00 2001 From: Alexis King Date: Mon, 30 Sep 2019 20:12:42 -0500 Subject: Fix the ignore-exports option (#1082) The `ignore-exports` option has been broken since #688, as mentioned in https://github.com/haskell/haddock/pull/766#issue-172505043. This PR fixes it. --- haddock-api/src/Haddock/Interface/Create.hs | 9 ++--- html-test/Main.hs | 6 ---- html-test/ref/IgnoreExports.html | 54 +++++++++++++++++++++++++---- html-test/src/IgnoreExports.hs | 5 ++- 4 files changed, 56 insertions(+), 18 deletions(-) (limited to 'haddock-api/src/Haddock/Interface/Create.hs') diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index 463411b4..dd1d4eb3 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -83,8 +83,9 @@ createInterface tm flags modMap instIfaceMap = do (TcGblEnv { tcg_rdr_env = gre , tcg_warns = warnings - , tcg_exports = all_exports + , tcg_exports = all_exports0 }, md) = tm_internals_ tm + all_local_avails = gresToAvailInfo . filter isLocalGRE . globalRdrEnvElts $ gre -- The 'pkgName' is necessary to decide what package to mention in "@since" -- annotations. Not having it is not fatal though. @@ -111,9 +112,9 @@ createInterface tm flags modMap instIfaceMap = do let declsWithDocs = topDecls group_ exports0 = fmap (map (first unLoc)) mayExports - exports - | OptIgnoreExports `elem` opts = Nothing - | otherwise = exports0 + (all_exports, exports) + | OptIgnoreExports `elem` opts = (all_local_avails, Nothing) + | otherwise = (all_exports0, exports0) unrestrictedImportedMods -- module re-exports are only possible with diff --git a/html-test/Main.hs b/html-test/Main.hs index 26eefe4a..36e56d9a 100755 --- a/html-test/Main.hs +++ b/html-test/Main.hs @@ -54,12 +54,6 @@ ingoredTests = -- we need a reliable way to deduplicate here. -- Happens since PR #688. "B" - - -- ignore-exports flag broke with PR #688. We use - -- the Avails calculated by GHC now. Probably - -- requires a change to GHC to "ignore" a modules - -- export list reliably. - , "IgnoreExports" ] checkIgnore :: FilePath -> Bool diff --git a/html-test/ref/IgnoreExports.html b/html-test/ref/IgnoreExports.html index eed12c00..8b3390ae 100644 --- a/html-test/ref/IgnoreExports.html +++ b/html-test/ref/IgnoreExports.html @@ -4,12 +4,14 @@ />IgnoreExportsSynopsis

Documentation

data Foo #

documentation for Foo

Constructors

Bar

Documentation for Bar

+> \ No newline at end of file diff --git a/html-test/src/IgnoreExports.hs b/html-test/src/IgnoreExports.hs index 0321ad02..edb7c4c1 100644 --- a/html-test/src/IgnoreExports.hs +++ b/html-test/src/IgnoreExports.hs @@ -1,5 +1,8 @@ {-# OPTIONS_HADDOCK ignore-exports #-} -module IgnoreExports (foo) where +module IgnoreExports (Foo, foo) where + +-- | documentation for Foo +data Foo = Bar -- ^ Documentation for Bar -- | documentation for foo foo :: Int -- cgit v1.2.3 From 5bef8bd8a72465a0abb1753a8bbeb94634a9d698 Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Sun, 22 Mar 2020 11:46:42 -0400 Subject: Clean up warnings * unused imports * imports of `Data.List` without import lists * missing `CompatPrelude` file in `.cabal` --- haddock-api/src/Haddock/Backends/Hoogle.hs | 3 +-- haddock-api/src/Haddock/Backends/LaTeX.hs | 9 +------- haddock-api/src/Haddock/Backends/Xhtml/Decl.hs | 1 - .../src/Haddock/Backends/Xhtml/DocMarkup.hs | 2 +- haddock-api/src/Haddock/Interface.hs | 2 +- .../src/Haddock/Interface/AttachInstances.hs | 2 +- haddock-api/src/Haddock/Interface/Create.hs | 2 +- haddock-api/src/Haddock/Interface/LexParseRn.hs | 2 +- haddock-api/src/Haddock/Interface/Rename.hs | 2 -- haddock-api/src/Haddock/InterfaceFile.hs | 2 +- haddock-api/src/Haddock/Utils.hs | 1 - haddock-api/src/Haddock/Utils/Json.hs | 2 +- haddock-library/haddock-library.cabal | 26 ++++++++++------------ haddock.cabal | 1 + 14 files changed, 22 insertions(+), 35 deletions(-) (limited to 'haddock-api/src/Haddock/Interface/Create.hs') diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs index 1f98ef9c..b38d4047 100644 --- a/haddock-api/src/Haddock/Backends/Hoogle.hs +++ b/haddock-api/src/Haddock/Backends/Hoogle.hs @@ -27,10 +27,9 @@ import Haddock.Utils hiding (out) import GHC import Outputable -import NameSet import Data.Char -import Data.List +import Data.List (isPrefixOf, intercalate) import Data.Maybe import Data.Version diff --git a/haddock-api/src/Haddock/Backends/LaTeX.hs b/haddock-api/src/Haddock/Backends/LaTeX.hs index f2fb1041..63b12a14 100644 --- a/haddock-api/src/Haddock/Backends/LaTeX.hs +++ b/haddock-api/src/Haddock/Backends/LaTeX.hs @@ -38,7 +38,7 @@ import System.FilePath import Data.Char import Control.Monad import Data.Maybe -import Data.List +import Data.List ( sort ) import Prelude hiding ((<>)) import Haddock.Doc (combineDocumentation) @@ -517,12 +517,6 @@ ppSubSigLike unicode typ argDocs subdocs leader = do_args 0 leader typ gadtOpen = char '{' -ppForAllSeparator :: Bool -> ForallVisFlag -> LaTeX -ppForAllSeparator unicode fvf = - case fvf of - ForallVis -> text "\\ " <> arrow unicode - ForallInvis -> dot - ppTypeSig :: [Name] -> HsType DocNameI -> Bool -> LaTeX ppTypeSig nms ty unicode = hsep (punctuate comma $ map ppSymName nms) @@ -1063,7 +1057,6 @@ ppForAllPart unicode tvs fvf = hsep (forallSymbol unicode : tvs') <> fv ForallVis -> text "\\ " <> arrow unicode ForallInvis -> dot - ppr_mono_lty :: LHsType DocNameI -> Bool -> LaTeX ppr_mono_lty ty unicode = ppr_mono_ty (unLoc ty) unicode diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs index c7ae15ca..b450dc94 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs @@ -36,7 +36,6 @@ import Text.XHtml hiding ( name, title, p, quote ) import BasicTypes (PromotionFlag(..), isPromoted) import GHC hiding (LexicalFixity(..)) -import qualified GHC import GHC.Exts import Name import BooleanFormula diff --git a/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs b/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs index edab4b16..0d7accfc 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs @@ -19,7 +19,7 @@ module Haddock.Backends.Xhtml.DocMarkup ( docElement, docSection, docSection_, ) where -import Data.List +import Data.List (intersperse) import Documentation.Haddock.Markup import Haddock.Backends.Xhtml.Names import Haddock.Backends.Xhtml.Utils diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index c2c0d733..24568235 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -44,7 +44,7 @@ import Haddock.Utils import Control.Monad import Control.Exception (evaluate) -import Data.List +import Data.List (foldl', isPrefixOf, nub) import qualified Data.Map as Map import qualified Data.Set as Set import Text.Printf diff --git a/haddock-api/src/Haddock/Interface/AttachInstances.hs b/haddock-api/src/Haddock/Interface/AttachInstances.hs index 35f24ee5..685dca01 100644 --- a/haddock-api/src/Haddock/Interface/AttachInstances.hs +++ b/haddock-api/src/Haddock/Interface/AttachInstances.hs @@ -21,7 +21,7 @@ import Haddock.GhcUtils import Control.Applicative ((<|>)) import Control.Arrow hiding ((<+>)) -import Data.List +import Data.List (sortBy) import Data.Ord (comparing) import Data.Maybe ( maybeToList, mapMaybe, fromMaybe ) import qualified Data.Map as Map diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index d5cbdaf5..b182a615 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -32,7 +32,7 @@ import Data.Bifunctor import Data.Bitraversable import qualified Data.Map as M import Data.Map (Map) -import Data.List +import Data.List (find, foldl', sortBy) import Data.Maybe import Data.Ord import Control.Applicative diff --git a/haddock-api/src/Haddock/Interface/LexParseRn.hs b/haddock-api/src/Haddock/Interface/LexParseRn.hs index 0b40ed3c..08a3c0f8 100644 --- a/haddock-api/src/Haddock/Interface/LexParseRn.hs +++ b/haddock-api/src/Haddock/Interface/LexParseRn.hs @@ -22,7 +22,7 @@ module Haddock.Interface.LexParseRn import Control.Arrow import Control.Monad import Data.Functor (($>)) -import Data.List +import Data.List (maximumBy, (\\)) import Data.Ord import Documentation.Haddock.Doc (metaDocConcat) import DynFlags (languageExtensions) diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs index 72d063dc..0b122b07 100644 --- a/haddock-api/src/Haddock/Interface/Rename.hs +++ b/haddock-api/src/Haddock/Interface/Rename.hs @@ -22,14 +22,12 @@ import Haddock.Types import Bag (emptyBag) import GHC hiding (NoLink) import Name -import Outputable ( panic ) import RdrName (RdrName(Exact)) import TysWiredIn (eqTyCon_RDR) import Control.Applicative import Control.Arrow ( first ) import Control.Monad hiding (mapM) -import Data.List import qualified Data.Map as Map hiding ( Map ) import Prelude hiding (mapM) diff --git a/haddock-api/src/Haddock/InterfaceFile.hs b/haddock-api/src/Haddock/InterfaceFile.hs index b5be311a..3ce2fabb 100644 --- a/haddock-api/src/Haddock/InterfaceFile.hs +++ b/haddock-api/src/Haddock/InterfaceFile.hs @@ -26,7 +26,7 @@ import Haddock.Utils hiding (out) import Control.Monad import Data.Array import Data.IORef -import Data.List +import Data.List (mapAccumR) import qualified Data.Map as Map import Data.Map (Map) import Data.Word diff --git a/haddock-api/src/Haddock/Utils.hs b/haddock-api/src/Haddock/Utils.hs index 79673365..3eb702c9 100644 --- a/haddock-api/src/Haddock/Utils.hs +++ b/haddock-api/src/Haddock/Utils.hs @@ -65,7 +65,6 @@ import BasicTypes ( PromotionFlag(..) ) import Exception (ExceptionMonad) import GHC import Name -import Outputable ( panic ) import Control.Monad ( liftM ) import Data.Char ( isAlpha, isAlphaNum, isAscii, ord, chr ) diff --git a/haddock-api/src/Haddock/Utils/Json.hs b/haddock-api/src/Haddock/Utils/Json.hs index e3c3dddc..2270a547 100644 --- a/haddock-api/src/Haddock/Utils/Json.hs +++ b/haddock-api/src/Haddock/Utils/Json.hs @@ -19,7 +19,7 @@ import Data.Char import Data.Int import Data.String import Data.Word -import Data.List +import Data.List (intersperse) import Data.Monoid import Data.ByteString.Builder (Builder) diff --git a/haddock-library/haddock-library.cabal b/haddock-library/haddock-library.cabal index e58fe2ef..294ef5be 100644 --- a/haddock-library/haddock-library.cabal +++ b/haddock-library/haddock-library.cabal @@ -59,22 +59,20 @@ test-suite spec type: exitcode-stdio-1.0 main-is: Spec.hs hs-source-dirs: - test - src - - cpp-options: - -DTEST + test + src other-modules: - Documentation.Haddock.Doc - Documentation.Haddock.Markup - Documentation.Haddock.Parser - Documentation.Haddock.Parser.Monad - Documentation.Haddock.Parser.Util - Documentation.Haddock.Parser.UtilSpec - Documentation.Haddock.ParserSpec - Documentation.Haddock.Types - Documentation.Haddock.Parser.Identifier + CompatPrelude + Documentation.Haddock.Doc + Documentation.Haddock.Markup + Documentation.Haddock.Parser + Documentation.Haddock.Parser.Monad + Documentation.Haddock.Parser.Util + Documentation.Haddock.Parser.UtilSpec + Documentation.Haddock.ParserSpec + Documentation.Haddock.Types + Documentation.Haddock.Parser.Identifier build-depends: , base-compat ^>= 0.9.3 || ^>= 0.11.0 diff --git a/haddock.cabal b/haddock.cabal index 92fe249e..425ed454 100644 --- a/haddock.cabal +++ b/haddock.cabal @@ -87,6 +87,7 @@ executable haddock transformers other-modules: + CompatPrelude Documentation.Haddock.Parser Documentation.Haddock.Parser.Monad Documentation.Haddock.Parser.Identifier -- cgit v1.2.3 From b33e4bebce0fb98acfc2c1f5efc370e95a061c86 Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Sat, 28 Mar 2020 12:28:48 -0400 Subject: Use `unLoc`/`noLoc` from GHC instead of `unL`/`reL` * `unL` is already defined by GHC as `unLoc` * `reL` is already defined by GHC as `noLoc` (in a safer way too!) * Condense `setOutputDir` and add a about exporting from GHC Fixes #978 --- haddock-api/src/Haddock/Backends/Hoogle.hs | 24 ++++++------ haddock-api/src/Haddock/Backends/LaTeX.hs | 2 +- haddock-api/src/Haddock/Backends/Xhtml/Decl.hs | 4 +- haddock-api/src/Haddock/GhcUtils.hs | 53 ++++++++++---------------- haddock-api/src/Haddock/Interface/Create.hs | 18 ++++----- 5 files changed, 44 insertions(+), 57 deletions(-) (limited to 'haddock-api/src/Haddock/Interface/Create.hs') diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs index b4a605f2..63acb465 100644 --- a/haddock-api/src/Haddock/Backends/Hoogle.hs +++ b/haddock-api/src/Haddock/Backends/Hoogle.hs @@ -82,7 +82,7 @@ dropHsDocTy = f f (HsOpTy x a b c) = HsOpTy x (g a) b (g c) f (HsParTy x a) = HsParTy x (g a) f (HsKindSig x a b) = HsKindSig x (g a) b - f (HsDocTy _ a _) = f $ unL a + f (HsDocTy _ a _) = f $ unLoc a f x = x outHsType :: (OutputableBndrId p) @@ -215,7 +215,7 @@ ppSynonym dflags x = [out dflags x] ppData :: DynFlags -> TyClDecl GhcRn -> [(Name, DocForDecl Name)] -> [String] ppData dflags decl@(DataDecl { tcdDataDefn = defn }) subdocs = showData decl{ tcdDataDefn = defn { dd_cons=[],dd_derivs=noLoc [] }} : - concatMap (ppCtor dflags decl subdocs . unL) (dd_cons defn) + concatMap (ppCtor dflags decl subdocs . unLoc) (dd_cons defn) where -- GHC gives out "data Bar =", we want to delete the equals. @@ -244,22 +244,22 @@ ppCtor dflags dat subdocs con@ConDeclH98 {} [out dflags (map (extFieldOcc . unLoc) $ cd_fld_names r) `typeSig` [resType, cd_fld_type r]] | r <- map unLoc recs] - funs = foldr1 (\x y -> reL $ HsFunTy noExtField x y) - apps = foldl1 (\x y -> reL $ HsAppTy noExtField x y) + funs = foldr1 (\x y -> noLoc $ HsFunTy noExtField x y) + apps = foldl1 (\x y -> noLoc $ HsAppTy noExtField x y) - typeSig nm flds = operator nm ++ " :: " ++ outHsType dflags (unL $ funs flds) + typeSig nm flds = operator nm ++ " :: " ++ outHsType dflags (unLoc $ funs flds) -- We print the constructors as comma-separated list. See GHC -- docs for con_names on why it is a list to begin with. - name = commaSeparate dflags . map unL $ getConNames con + name = commaSeparate dflags . map unLoc $ getConNames con - resType = let c = HsTyVar noExtField NotPromoted (reL (tcdName dat)) + resType = let c = HsTyVar noExtField NotPromoted (noLoc (tcdName dat)) as = map (tyVarBndr2Type . unLoc) (hsQTvExplicit $ tyClDeclTyVars dat) - in apps (map reL (c : as)) + in apps (map noLoc (c : as)) tyVarBndr2Type :: HsTyVarBndr GhcRn -> HsType GhcRn tyVarBndr2Type (UserTyVar _ n) = HsTyVar noExtField NotPromoted n - tyVarBndr2Type (KindedTyVar _ n k) = HsKindSig noExtField (reL (HsTyVar noExtField NotPromoted n)) k + tyVarBndr2Type (KindedTyVar _ n k) = HsKindSig noExtField (noLoc (HsTyVar noExtField NotPromoted n)) k tyVarBndr2Type (XTyVarBndr nec) = noExtCon nec ppCtor dflags _dat subdocs con@(ConDeclGADT { }) @@ -267,8 +267,8 @@ ppCtor dflags _dat subdocs con@(ConDeclGADT { }) where f = [typeSig name (getGADTConTypeG con)] - typeSig nm ty = operator nm ++ " :: " ++ outHsType dflags (unL ty) - name = out dflags $ map unL $ getConNames con + typeSig nm ty = operator nm ++ " :: " ++ outHsType dflags (unLoc ty) + name = out dflags $ map unLoc $ getConNames con ppCtor _ _ _ (XConDecl nec) = noExtCon nec ppFixity :: DynFlags -> (Name, Fixity) -> [String] @@ -298,7 +298,7 @@ docWith dflags header d mkSubdoc :: DynFlags -> Located Name -> [(Name, DocForDecl Name)] -> [String] -> [String] mkSubdoc dflags n subdocs s = concatMap (ppDocumentation dflags) getDoc ++ s where - getDoc = maybe [] (return . fst) (lookup (unL n) subdocs) + getDoc = maybe [] (return . fst) (lookup (unLoc n) subdocs) data Tag = TagL Char [Tags] | TagP Tags | TagPre Tags | TagInline String Tags | Str String deriving Show diff --git a/haddock-api/src/Haddock/Backends/LaTeX.hs b/haddock-api/src/Haddock/Backends/LaTeX.hs index d52c136f..647812f9 100644 --- a/haddock-api/src/Haddock/Backends/LaTeX.hs +++ b/haddock-api/src/Haddock/Backends/LaTeX.hs @@ -624,7 +624,7 @@ ppClassDecl instances doc subdocs text "\\haddockpremethods{}" <> emph (text "Associated Types") $$ vcat [ ppFamDecl True (fst doc) [] (FamDecl noExtField decl) True | L _ decl <- ats - , let name = unL . fdLName $ decl + , let name = unLoc . fdLName $ decl doc = lookupAnySubdoc name subdocs ] diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs index 25669ca7..ef0ba1b6 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs @@ -492,7 +492,7 @@ ppShortClassDecl summary links (ClassDecl { tcdCtxt = lctxt, tcdLName = lname, t +++ shortSubDecls False ( [ ppAssocType summary links doc at [] splice unicode pkg qual | at <- ats - , let doc = lookupAnySubdoc (unL $ fdLName $ unL at) subdocs ] ++ + , let doc = lookupAnySubdoc (unLoc $ fdLName $ unLoc at) subdocs ] ++ -- ToDo: add associated type defaults @@ -544,7 +544,7 @@ ppClassDecl summary links instances fixities loc d subdocs <+> subDefaults (maybeToList defTys) | at <- ats - , let name = unL . fdLName $ unL at + , let name = unLoc . fdLName $ unLoc at doc = lookupAnySubdoc name subdocs subfixs = filter ((== name) . fst) fixities defTys = (declElem . ppDefaultAssocTy name) <$> lookupDAT name diff --git a/haddock-api/src/Haddock/GhcUtils.hs b/haddock-api/src/Haddock/GhcUtils.hs index f600997a..923516b6 100644 --- a/haddock-api/src/Haddock/GhcUtils.hs +++ b/haddock-api/src/Haddock/GhcUtils.hs @@ -319,8 +319,8 @@ restrictCons names decls = [ L p d | L p (Just d) <- map (fmap keep) decls ] case con_args d of PrefixCon _ -> Just d RecCon fields - | all field_avail (unL fields) -> Just d - | otherwise -> Just (d { con_args = PrefixCon (field_types (map unL (unL fields))) }) + | all field_avail (unLoc fields) -> Just d + | otherwise -> Just (d { con_args = PrefixCon (field_types (map unLoc (unLoc fields))) }) -- if we have *all* the field names available, then -- keep the record declaration. Otherwise degrade to -- a constructor declaration. This isn't quite right, but @@ -340,7 +340,7 @@ restrictDecls names = mapMaybe (filterLSigNames (`elem` names)) restrictATs :: [Name] -> [LFamilyDecl GhcRn] -> [LFamilyDecl GhcRn] -restrictATs names ats = [ at | at <- ats , unL (fdLName (unL at)) `elem` names ] +restrictATs names ats = [ at | at <- ats , unLoc (fdLName (unLoc at)) `elem` names ] ------------------------------------------------------------------------------- @@ -443,18 +443,6 @@ reparenConDeclField (ConDeclField x n t d) = ConDeclField x n (reparenLType t) d reparenConDeclField c@XConDeclField{} = c -------------------------------------------------------------------------------- --- * Located -------------------------------------------------------------------------------- - - -unL :: Located a -> a -unL (L _ x) = x - - -reL :: a -> Located a -reL = L undefined - ------------------------------------------------------------------------------- -- * NamedThing instances ------------------------------------------------------------------------------- @@ -475,17 +463,17 @@ class Parent a where instance Parent (ConDecl GhcRn) where children con = case con_args con of - RecCon fields -> map (extFieldOcc . unL) $ - concatMap (cd_fld_names . unL) (unL fields) + RecCon fields -> map (extFieldOcc . unLoc) $ + concatMap (cd_fld_names . unLoc) (unLoc fields) _ -> [] instance Parent (TyClDecl GhcRn) where children d - | isDataDecl d = map unL $ concatMap (getConNames . unL) + | isDataDecl d = map unLoc $ concatMap (getConNames . unLoc) $ (dd_cons . tcdDataDefn) $ d | isClassDecl d = - map (unL . fdLName . unL) (tcdATs d) ++ - [ unL n | L _ (TypeSig _ ns _) <- tcdSigs d, n <- ns ] + map (unLoc . fdLName . unLoc) (tcdATs d) ++ + [ unLoc n | L _ (TypeSig _ ns _) <- tcdSigs d, n <- ns ] | otherwise = [] @@ -495,13 +483,13 @@ family = getName &&& children familyConDecl :: ConDecl GHC.GhcRn -> [(Name, [Name])] -familyConDecl d = zip (map unL (getConNames d)) (repeat $ children d) +familyConDecl d = zip (map unLoc (getConNames d)) (repeat $ children d) -- | A mapping from the parent (main-binder) to its children and from each -- child to its grand-children, recursively. families :: TyClDecl GhcRn -> [(Name, [Name])] families d - | isDataDecl d = family d : concatMap (familyConDecl . unL) (dd_cons (tcdDataDefn d)) + | isDataDecl d = family d : concatMap (familyConDecl . unLoc) (dd_cons (tcdDataDefn d)) | isClassDecl d = [family d] | otherwise = [] @@ -546,17 +534,16 @@ minimalDef n = do -- * DynFlags ------------------------------------------------------------------------------- - -setObjectDir, setHiDir, setHieDir, setStubDir, setOutputDir :: String -> DynFlags -> DynFlags -setObjectDir f d = d{ objectDir = Just f} -setHiDir f d = d{ hiDir = Just f} -setHieDir f d = d{ hieDir = Just f} -setStubDir f d = d{ stubDir = Just f - , includePaths = addGlobalInclude (includePaths d) [f] } - -- -stubdir D adds an implicit -I D, so that gcc can find the _stub.h file - -- \#included from the .hc file when compiling with -fvia-C. -setOutputDir f = setObjectDir f . setHiDir f . setHieDir f . setStubDir f - +-- TODO: use `setOutputDir` from GHC +setOutputDir :: FilePath -> DynFlags -> DynFlags +setOutputDir dir dynFlags = + dynFlags { objectDir = Just dir + , hiDir = Just dir + , hieDir = Just dir + , stubDir = Just dir + , includePaths = addGlobalInclude (includePaths dynFlags) [dir] + , dumpDir = Just dir + } ------------------------------------------------------------------------------- -- * 'StringBuffer' and 'ByteString' diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index b182a615..af006d03 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -461,14 +461,14 @@ subordinates instMap decl = case decl of dataSubs :: HsDataDefn GhcRn -> [(Name, [HsDocString], Map Int HsDocString)] dataSubs dd = constrs ++ fields ++ derivs where - cons = map unL $ (dd_cons dd) - constrs = [ (unL cname, maybeToList $ fmap unL $ con_doc c, conArgDocs c) + cons = map unLoc $ (dd_cons dd) + constrs = [ (unLoc cname, maybeToList $ fmap unLoc $ con_doc c, conArgDocs c) | c <- cons, cname <- getConNames c ] - fields = [ (extFieldOcc n, maybeToList $ fmap unL doc, M.empty) + fields = [ (extFieldOcc n, maybeToList $ fmap unLoc doc, M.empty) | RecCon flds <- map getConArgs cons , L _ (ConDeclField _ ns _ doc) <- (unLoc flds) , L _ n <- ns ] - derivs = [ (instName, [unL doc], M.empty) + derivs = [ (instName, [unLoc doc], M.empty) | (l, doc) <- mapMaybe (extract_deriv_ty . hsib_body) $ concatMap (unLoc . deriv_clause_tys . unLoc) $ unLoc $ dd_derivs dd @@ -585,13 +585,13 @@ sortByLoc = sortBy (comparing getLoc) -- | Filter out declarations that we don't handle in Haddock filterDecls :: [(LHsDecl a, doc)] -> [(LHsDecl a, doc)] -filterDecls = filter (isHandled . unL . fst) +filterDecls = filter (isHandled . unLoc . fst) where isHandled (ForD _ (ForeignImport {})) = True isHandled (TyClD {}) = True isHandled (InstD {}) = True isHandled (DerivD {}) = True - isHandled (SigD _ d) = isUserLSig (reL d) + isHandled (SigD _ d) = isUserLSig (noLoc d) isHandled (ValD {}) = True -- we keep doc declarations to be able to get at named docs isHandled (DocD {}) = True @@ -677,7 +677,7 @@ mkExportItems return [ExportDoc doc] lookupExport (IEDocNamed _ str, _) = liftErrMsg $ - findNamedDoc str [ unL d | d <- decls ] >>= \case + findNamedDoc str [ unLoc d | d <- decls ] >>= \case Nothing -> return [] Just docStr -> do doc <- processDocStringParas dflags pkgName gre docStr @@ -725,13 +725,13 @@ availExportItem is_sig modMap thisMod semMod warnings exportedNames export <- hiValExportItem dflags t l doc (l `elem` splices) $ M.lookup t fixMap return [export] (ds, docs_) | decl : _ <- filter (not . isValD . unLoc) ds -> - let declNames = getMainDeclBinder (unL decl) + let declNames = getMainDeclBinder (unLoc decl) in case () of _ -- We should not show a subordinate by itself if any of its -- parents is also exported. See note [1]. | t `notElem` declNames, - Just p <- find isExported (parents t $ unL decl) -> + Just p <- find isExported (parents t $ unLoc decl) -> do liftErrMsg $ tell [ "Warning: " ++ moduleString thisMod ++ ": " ++ pretty dflags (nameOccName t) ++ " is exported separately but " ++ -- cgit v1.2.3 From 8d83110789def9207463a035fa766b78ebf5fdd9 Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Wed, 15 Apr 2020 09:21:09 -0400 Subject: Prune docstrings that are never rendered When first creating a Haddock interface, trim `ifaceDocMap` and `ifaceArgMap` to not include docstrings that can never appear in the final output. Besides checking with GHC which names are exported, we also need to keep all the docs attached to instance declarations (it is much tougher to detect when an instance is fully private). This change means: * slightly smaller interface files (7% reduction on boot libs) * slightly less work to do processing docstrings that aren't used * no warnings in Haddock's output about private docstrings (see #1070) I've tested manually that this does not affect any of the boot library generated docs (the only change in output was some small re-ordering in a handful of instance lists). This should mean no docstrings have been incorrectly dropped. --- haddock-api/src/Haddock/Interface/Create.hs | 17 +++++++++++++++-- 1 file changed, 15 insertions(+), 2 deletions(-) (limited to 'haddock-api/src/Haddock/Interface/Create.hs') diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index af006d03..f29f576e 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -31,6 +31,7 @@ import Haddock.Interface.LexParseRn import Data.Bifunctor import Data.Bitraversable import qualified Data.Map as M +import qualified Data.Set as S import Data.Map (Map) import Data.List (find, foldl', sortBy) import Data.Maybe @@ -165,6 +166,18 @@ createInterface tm flags modMap instIfaceMap = do modWarn <- liftErrMsg (moduleWarning dflags gre warnings) + -- Prune the docstring 'Map's to keep only docstrings that are not private. + -- + -- Besides all the names that GHC has told us this module exports, we also + -- keep the docs for locally defined class instances. This is more names than + -- we need, but figuring out which instances are fully private is tricky. + -- + -- We do this pruning to avoid having to rename, emit warnings, and save + -- docstrings which will anyways never be rendered. + let !localVisibleNames = S.fromList (localInsts ++ exportedNames) + !prunedDocMap = M.restrictKeys docMap localVisibleNames + !prunedArgMap = M.restrictKeys argMap localVisibleNames + return $! Interface { ifaceMod = mdl , ifaceIsSig = is_sig @@ -173,8 +186,8 @@ createInterface tm flags modMap instIfaceMap = do , ifaceDoc = Documentation mbDoc modWarn , ifaceRnDoc = Documentation Nothing Nothing , ifaceOptions = opts - , ifaceDocMap = docMap - , ifaceArgMap = argMap + , ifaceDocMap = prunedDocMap + , ifaceArgMap = prunedArgMap , ifaceRnDocMap = M.empty , ifaceRnArgMap = M.empty , ifaceExportItems = prunedExportItems -- cgit v1.2.3 From 83f0fa0b6218c34898337bf41072ee5fedec1bde Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Wed, 15 Apr 2020 09:56:55 -0400 Subject: Don't warn about missing links in miminal sigs When renaming the Haddock interface, never emit warnings when renaming a minimal signature. Also added some documention around `renameInterface`. Minimal signatures intentionally include references to potentially un-exported methods (see the discussion in #330), so it is expected that they will not always have a link destination. On the principle that warnings should always be resolvable, this shouldn't produce a warning. See #1070. --- haddock-api/src/Haddock/Interface/Create.hs | 6 +++--- haddock-api/src/Haddock/Interface/Rename.hs | 15 ++++++++++++++- 2 files changed, 17 insertions(+), 4 deletions(-) (limited to 'haddock-api/src/Haddock/Interface/Create.hs') diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index f29f576e..0f24afaa 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -188,10 +188,10 @@ createInterface tm flags modMap instIfaceMap = do , ifaceOptions = opts , ifaceDocMap = prunedDocMap , ifaceArgMap = prunedArgMap - , ifaceRnDocMap = M.empty - , ifaceRnArgMap = M.empty + , ifaceRnDocMap = M.empty -- Filled in `renameInterface` + , ifaceRnArgMap = M.empty -- Filled in `renameInterface` , ifaceExportItems = prunedExportItems - , ifaceRnExportItems = [] + , ifaceRnExportItems = [] -- Filled in `renameInterface` , ifaceExports = exportedNames , ifaceVisibleExports = visibleNames , ifaceDeclMap = declMap diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs index ce3878b8..97f128d7 100644 --- a/haddock-api/src/Haddock/Interface/Rename.hs +++ b/haddock-api/src/Haddock/Interface/Rename.hs @@ -31,6 +31,14 @@ import Control.Monad hiding (mapM) import qualified Data.Map as Map hiding ( Map ) import Prelude hiding (mapM) +-- | Traverse docstrings and ASTs in the Haddock interface, renaming 'Name' to +-- 'DocName'. +-- +-- What this really boils down to is: for each 'Name', figure out which of the +-- modules that export the name is the preferred place to link to. +-- +-- The renamed output gets written into fields in the Haddock interface record +-- that were previously left empty. renameInterface :: DynFlags -> LinkEnv -> Bool -> Interface -> ErrMsgM Interface renameInterface dflags renamingEnv warnings iface = @@ -128,6 +136,11 @@ lookupRn name = RnM $ \lkp -> (False,maps_to) -> (maps_to, (name :)) (True, maps_to) -> (maps_to, id) +-- | Look up a 'Name' in the renaming environment, but don't warn if you don't +-- find the name. Prefer to use 'lookupRn' whenever possible. +lookupRnNoWarn :: Name -> RnM DocName +lookupRnNoWarn name = RnM $ \lkp -> (snd (lkp name), id) + -- | Run the renamer action using lookup in a 'LinkEnv' as the lookup function. -- Returns the renamed value along with a list of `Name`'s that could not be -- renamed because they weren't in the environment. @@ -532,7 +545,7 @@ renameSig sig = case sig of lnames' <- mapM renameL lnames return $ FixSig noExtField (FixitySig noExtField lnames' fixity) MinimalSig _ src (L l s) -> do - s' <- traverse renameL s + s' <- traverse (traverse lookupRnNoWarn) s return $ MinimalSig noExtField src (L l s') -- we have filtered out all other kinds of signatures in Interface.Create _ -> error "expected TypeSig" -- cgit v1.2.3 From 5bc5016a14bc872a8315cddc629f8171a9ccd62e Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Tue, 21 Apr 2020 10:53:28 -0400 Subject: Fallback to `hiDecl` when `extractDecl` fails Sometimes, the declaration being exported is a subdecl (for instance, a record accessor getting exported at the top-level). For these cases, Haddock has to find a way to produce some synthetic sensible top-level declaration. This is done with `extractDecl`. As is shown by #1067, this is sometimes impossible to do just at a syntactic level (for instance when the subdecl is re-exported). In these cases, the only sensible thing to do is to try to reify a declaration based on a GHC `TyThing` via `hiDecl`. --- haddock-api/src/Haddock/Interface/Create.hs | 114 +++++++++++++++++----------- html-test/ref/Bug1067A.html | 114 ++++++++++++++++++++++++++++ html-test/ref/Bug1067B.html | 84 ++++++++++++++++++++ html-test/src/Bug1067A.hs | 9 +++ html-test/src/Bug1067B.hs | 4 + 5 files changed, 280 insertions(+), 45 deletions(-) create mode 100644 html-test/ref/Bug1067A.html create mode 100644 html-test/ref/Bug1067B.html create mode 100644 html-test/src/Bug1067A.hs create mode 100644 html-test/src/Bug1067B.hs (limited to 'haddock-api/src/Haddock/Interface/Create.hs') diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index 0f24afaa..5a58e1ac 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -793,11 +793,24 @@ availExportItem is_sig modMap thisMod semMod warnings exportedNames _ -> return [] + -- Tries 'extractDecl' first then falls back to 'hiDecl' if that fails + availDecl :: Name -> LHsDecl GhcRn -> ErrMsgGhc (LHsDecl GhcRn) + availDecl declName parentDecl = + case extractDecl declMap declName parentDecl of + Right d -> pure d + Left err -> do + synifiedDeclOpt <- hiDecl dflags declName + case synifiedDeclOpt of + Just synifiedDecl -> pure synifiedDecl + Nothing -> O.pprPanic "availExportItem" (O.text err) + availExportDecl :: AvailInfo -> LHsDecl GhcRn -> (DocForDecl Name, [(Name, DocForDecl Name)]) -> ErrMsgGhc [ ExportItem GhcRn ] availExportDecl avail decl (doc, subs) | availExportsDecl avail = do + extractedDecl <- availDecl (availName avail) decl + -- bundled pattern synonyms only make sense if the declaration is -- exported (otherwise there would be nothing to bundle to) bundledPatSyns <- findBundledPatterns avail @@ -813,8 +826,7 @@ availExportItem is_sig modMap thisMod semMod warnings exportedNames ] return [ ExportDecl { - expItemDecl = restrictTo (fmap fst subs) - (extractDecl declMap (availName avail) decl) + expItemDecl = restrictTo (fmap fst subs) extractedDecl , expItemPats = bundledPatSyns , expItemMbDoc = doc , expItemSubDocs = subs @@ -824,18 +836,18 @@ availExportItem is_sig modMap thisMod semMod warnings exportedNames } ] - | otherwise = - return [ ExportDecl { - expItemDecl = extractDecl declMap sub decl + | otherwise = for subs $ \(sub, sub_doc) -> do + extractedDecl <- availDecl sub decl + + return ( ExportDecl { + expItemDecl = extractedDecl , expItemPats = [] , expItemMbDoc = sub_doc , expItemSubDocs = [] , expItemInstances = [] , expItemFixities = [ (sub, f) | Just f <- [M.lookup sub fixMap] ] , expItemSpliced = False - } - | (sub, sub_doc) <- subs - ] + } ) exportedNameSet = mkNameSet exportedNames isExported n = elemNameSet n exportedNameSet @@ -910,6 +922,7 @@ semToIdMod this_uid m | Module.isHoleModule m = mkModule this_uid (moduleName m) | otherwise = m +-- | Reify a declaration from the GHC internal 'TyThing' representation. hiDecl :: DynFlags -> Name -> ErrMsgGhc (Maybe (LHsDecl GhcRn)) hiDecl dflags t = do mayTyThing <- liftGhcToErrMsgGhc $ lookupName t @@ -1053,20 +1066,30 @@ fullModuleContents is_sig modMap pkgName thisMod semMod warnings gre exportedNam isSigD (L _ SigD{}) = True isSigD _ = False + -- | Sometimes the declaration we want to export is not the "main" declaration: -- it might be an individual record selector or a class method. In these -- cases we have to extract the required declaration (and somehow cobble -- together a type signature for it...). -extractDecl :: DeclMap -> Name -> LHsDecl GhcRn -> LHsDecl GhcRn +-- +-- This function looks through the declarations in this module to try to find +-- the one with the right name. +extractDecl + :: DeclMap -- ^ all declarations in the file + -> Name -- ^ name of the declaration to extract + -> LHsDecl GhcRn -- ^ parent declaration + -> Either ErrMsg (LHsDecl GhcRn) extractDecl declMap name decl - | name `elem` getMainDeclBinder (unLoc decl) = decl + | name `elem` getMainDeclBinder (unLoc decl) = pure decl | otherwise = case unLoc decl of - TyClD _ d@ClassDecl {} -> + TyClD _ d@ClassDecl { tcdLName = L _ clsNm + , tcdSigs = clsSigs + , tcdATs = clsATs } -> let matchesMethod = [ lsig - | lsig <- tcdSigs d + | lsig <- clsSigs , ClassOpSig _ False _ _ <- pure $ unLoc lsig -- Note: exclude `default` declarations (see #505) , name `elem` sigName lsig @@ -1074,51 +1097,54 @@ extractDecl declMap name decl matchesAssociatedType = [ lfam_decl - | lfam_decl <- tcdATs d + | lfam_decl <- clsATs , name == unLoc (fdLName (unLoc lfam_decl)) ] -- TODO: document fixity in case (matchesMethod, matchesAssociatedType) of - ([s0], _) -> let (n, tyvar_names) = (tcdName d, tyClDeclTyVars d) - L pos sig = addClassContext n tyvar_names s0 - in L pos (SigD noExtField sig) - (_, [L pos fam_decl]) -> L pos (TyClD noExtField (FamDecl noExtField fam_decl)) + ([s0], _) -> let tyvar_names = tyClDeclTyVars d + L pos sig = addClassContext clsNm tyvar_names s0 + in pure (L pos (SigD noExtField sig)) + (_, [L pos fam_decl]) -> pure (L pos (TyClD noExtField (FamDecl noExtField fam_decl))) ([], []) | Just (famInstDecl:_) <- M.lookup name declMap -> extractDecl declMap name famInstDecl - _ -> O.pprPanic "extractDecl" (O.text "Ambiguous decl for" O.<+> O.ppr name O.<+> O.text "in class:" - O.$$ O.nest 4 (O.ppr d) - O.$$ O.text "Matches:" - O.$$ O.nest 4 (O.ppr matchesMethod O.<+> O.ppr matchesAssociatedType)) - TyClD _ d@DataDecl {} -> - let (n, tyvar_tys) = (tcdName d, lHsQTyVarsToTypes (tyClDeclTyVars d)) - in if isDataConName name - then SigD noExtField <$> extractPatternSyn name n (map HsValArg tyvar_tys) (dd_cons (tcdDataDefn d)) - else SigD noExtField <$> extractRecSel name n (map HsValArg tyvar_tys) (dd_cons (tcdDataDefn d)) + _ -> Left (concat [ "Ambiguous decl for ", getOccString name + , " in class ", getOccString clsNm ]) + + TyClD _ d@DataDecl { tcdLName = L _ dataNm + , tcdDataDefn = HsDataDefn { dd_cons = dataCons } } -> do + let ty_args = map HsValArg (lHsQTyVarsToTypes (tyClDeclTyVars d)) + lsig <- if isDataConName name + then extractPatternSyn name dataNm ty_args dataCons + else extractRecSel name dataNm ty_args dataCons + pure (SigD noExtField <$> lsig) + TyClD _ FamDecl {} | isValName name , Just (famInst:_) <- M.lookup name declMap -> extractDecl declMap name famInst InstD _ (DataFamInstD _ (DataFamInstDecl (HsIB { hsib_body = - FamEqn { feqn_tycon = L _ n - , feqn_pats = tys - , feqn_rhs = defn }}))) -> - if isDataConName name - then SigD noExtField <$> extractPatternSyn name n tys (dd_cons defn) - else SigD noExtField <$> extractRecSel name n tys (dd_cons defn) + FamEqn { feqn_tycon = L _ famName + , feqn_pats = ty_args + , feqn_rhs = HsDataDefn { dd_cons = dataCons } }}))) -> do + lsig <- if isDataConName name + then extractPatternSyn name famName ty_args dataCons + else extractRecSel name famName ty_args dataCons + pure (SigD noExtField <$> lsig) InstD _ (ClsInstD _ ClsInstDecl { cid_datafam_insts = insts }) | isDataConName name -> let matches = [ d' | L _ d'@(DataFamInstDecl (HsIB { hsib_body = - FamEqn { feqn_rhs = dd + FamEqn { feqn_rhs = HsDataDefn { dd_cons = dataCons } } })) <- insts - , name `elem` map unLoc (concatMap (getConNames . unLoc) (dd_cons dd)) + , name `elem` map unLoc (concatMap (getConNames . unLoc) dataCons) ] in case matches of [d0] -> extractDecl declMap name (noLoc (InstD noExtField (DataFamInstD noExtField d0))) - _ -> error "internal: extractDecl (ClsInstD)" + _ -> Left "internal: extractDecl (ClsInstD)" | otherwise -> let matches = [ d' | L _ d'@(DataFamInstDecl (HsIB { hsib_body = d })) <- insts @@ -1130,16 +1156,14 @@ extractDecl declMap name decl ] in case matches of [d0] -> extractDecl declMap name (noLoc . InstD noExtField $ DataFamInstD noExtField d0) - _ -> error "internal: extractDecl (ClsInstD)" - _ -> O.pprPanic "extractDecl" $ - O.text "Unhandled decl for" O.<+> O.ppr name O.<> O.text ":" - O.$$ O.nest 4 (O.ppr decl) + _ -> Left "internal: extractDecl (ClsInstD)" + _ -> Left ("extractDecl: Unhandled decl for " ++ getOccString name) -extractPatternSyn :: Name -> Name -> [LHsTypeArg GhcRn] -> [LConDecl GhcRn] -> LSig GhcRn +extractPatternSyn :: Name -> Name -> [LHsTypeArg GhcRn] -> [LConDecl GhcRn] -> Either ErrMsg (LSig GhcRn) extractPatternSyn nm t tvs cons = case filter matches cons of - [] -> error "extractPatternSyn: constructor pattern not found" - con:_ -> extract <$> con + [] -> Left "extractPatternSyn: constructor pattern not found" + con:_ -> pure (extract <$> con) where matches :: LConDecl GhcRn -> Bool matches (L _ con) = nm `elem` (unLoc <$> getConNames con) @@ -1170,13 +1194,13 @@ extractPatternSyn nm t tvs cons = mkAppTyArg f (HsArgPar _) = HsParTy noExtField f extractRecSel :: Name -> Name -> [LHsTypeArg GhcRn] -> [LConDecl GhcRn] - -> LSig GhcRn -extractRecSel _ _ _ [] = error "extractRecSel: selector not found" + -> Either ErrMsg (LSig GhcRn) +extractRecSel _ _ _ [] = Left "extractRecSel: selector not found" extractRecSel nm t tvs (L _ con : rest) = case getConArgs con of RecCon (L _ fields) | ((l,L _ (ConDeclField _ _nn ty _)) : _) <- matching_fields fields -> - L l (TypeSig noExtField [noLoc nm] (mkEmptySigWcType (noLoc (HsFunTy noExtField data_ty (getBangType ty))))) + pure (L l (TypeSig noExtField [noLoc nm] (mkEmptySigWcType (noLoc (HsFunTy noExtField data_ty (getBangType ty)))))) _ -> extractRecSel nm t tvs rest where matching_fields :: [LConDeclField GhcRn] -> [(SrcSpan, LConDeclField GhcRn)] diff --git a/html-test/ref/Bug1067A.html b/html-test/ref/Bug1067A.html new file mode 100644 index 00000000..96b8d495 --- /dev/null +++ b/html-test/ref/Bug1067A.html @@ -0,0 +1,114 @@ +Bug1067A
Safe HaskellSafe-Inferred

Bug1067A

Synopsis

Documentation

data Foo where #

A foo

Bundled Patterns

pattern P :: Foo

A pattern

diff --git a/html-test/ref/Bug1067B.html b/html-test/ref/Bug1067B.html new file mode 100644 index 00000000..f3bf821a --- /dev/null +++ b/html-test/ref/Bug1067B.html @@ -0,0 +1,84 @@ +Bug1067B
Safe HaskellSafe-Inferred

Bug1067B

Synopsis

Documentation

pattern P :: Foo #

A pattern

diff --git a/html-test/src/Bug1067A.hs b/html-test/src/Bug1067A.hs new file mode 100644 index 00000000..57ab60b0 --- /dev/null +++ b/html-test/src/Bug1067A.hs @@ -0,0 +1,9 @@ +{-# language PatternSynonyms #-} +module Bug1067A ( Foo(P) ) where + +-- | A foo +data Foo = Foo + +-- | A pattern +pattern P :: Foo +pattern P = Foo diff --git a/html-test/src/Bug1067B.hs b/html-test/src/Bug1067B.hs new file mode 100644 index 00000000..f1a814df --- /dev/null +++ b/html-test/src/Bug1067B.hs @@ -0,0 +1,4 @@ +{-# language PatternSynonyms #-} +module Bug1067B ( pattern P ) where + +import Bug1067A -- cgit v1.2.3 From 7240b69e3444e40546c7a17855eed2e5ab8a0816 Mon Sep 17 00:00:00 2001 From: Xia Li-yao Date: Tue, 8 Dec 2020 10:43:05 -0500 Subject: Add dangling changes from branches ghc-8.6 and ghc-8.8 (#1243) * Fix multiple typos and inconsistencies in doc/markup.rst Note: I noticed some overlap with #1112 from @wygulmage and #1081 from @parsonsmatt after creating these proposed changes - mea culpa for not looking at the open PRs sooner. * Fix #1113 If no Signatures, no section of index.html * Change the formatting of missing link destinations The current formatting of the missing link destination does not really help user to understand the reasons of the missing link. To address this, I've changed the formatting in two ways: - the missing link symbol name is now fully qualified. This way you immediately know which haskell module cannot be linked. It is then easier to understand why this module does not have documentation (hidden module or broken documentation). - one line per missing link, that's more readable now that symbol name can be longer due to qualification. For example, before haddock was listing missing symbol such as: ``` could not find link destinations for: Word8 Word16 mapMaybe ``` Now it is listed as: ``` could not find link destinations for: - Data.Word.Word8 - Data.Word.Word16 - Data.Maybe.mapMaybe ``` * Add `--ignore-link-symbol` command line argument This argument can be used multiples time. A missing link to a symbol listed by `--ignore-link-symbol` won't trigger "missing link" warning. * Forbid spaces in anchors (#1148) * Improve error messages with context information (#1060) Co-authored-by: Matt Audesse Co-authored-by: Mike Pilgrem Co-authored-by: Guillaume Bouchard Co-authored-by: Pepe Iborra --- doc/markup.rst | 77 ++++++++++++---------- haddock-api/src/Haddock/Backends/Xhtml.hs | 1 + haddock-api/src/Haddock/Interface.hs | 2 +- haddock-api/src/Haddock/Interface/Create.hs | 27 +++++--- haddock-api/src/Haddock/Interface/Rename.hs | 16 +++-- haddock-api/src/Haddock/Options.hs | 10 ++- haddock-api/src/Haddock/Types.hs | 22 ++++++- .../src/Documentation/Haddock/Parser.hs | 2 +- haddock-library/src/Documentation/Haddock/Types.hs | 2 +- .../test/Documentation/Haddock/ParserSpec.hs | 9 ++- 10 files changed, 111 insertions(+), 57 deletions(-) (limited to 'haddock-api/src/Haddock/Interface/Create.hs') diff --git a/doc/markup.rst b/doc/markup.rst index 178a6865..8935b765 100644 --- a/doc/markup.rst +++ b/doc/markup.rst @@ -131,7 +131,7 @@ or like this: :: b -- ^ This is the documentation for the argument of type 'b' There is one edge case that is handled differently: only one ``-- ^`` -annotation occuring after the constructor and all its arguments is +annotation occurring after the constructor and all its arguments is applied to the constructor, not its last argument: :: data T a b @@ -156,8 +156,8 @@ Alternative layout styles are generally accepted by Haddock - for example doc comments can appear before or after the comma in separated lists such as the list of record fields above. -In case that more than one constructor exports a field with the same -name, the documentation attached to the first occurence of the field +In cases where more than one constructor exports a field with the same +name, the documentation attached to the first occurrence of the field will be used, even if a comment is not present. :: data T a = A { someField :: a -- ^ Doc for someField of A @@ -165,7 +165,7 @@ will be used, even if a comment is not present. :: | B { someField :: a -- ^ Doc for someField of B } -In the above example, all occurences of ``someField`` in the +In the above example, all occurrences of ``someField`` in the documentation are going to be documented with ``Doc for someField of A``. Note that Haddock versions 2.14.0 and before would join up documentation of each field and render the result. The @@ -238,7 +238,7 @@ module documentation example and then talk about the fields. :: All fields are optional but they must be in order if they do appear. Multi-line fields are accepted but the consecutive lines have to start -indented more than their label. If your label is indented one space as +indented more than their label. If your label is indented one space, as is often the case with the ``--`` syntax, the consecutive lines have to start at two spaces at the very least. For example, above we saw a multiline ``Copyright`` field: :: @@ -250,7 +250,7 @@ multiline ``Copyright`` field: :: ... -} -That could equivalently be written as :: +That could equivalently be written as: :: -- | ... -- Copyright: @@ -258,14 +258,14 @@ That could equivalently be written as :: -- Someone Else, 2014 -- ... -or as :: +or as: :: -- | ... -- Copyright: (c) Some Person, 2013 -- Someone Else, 2014 -- ... -but not as :: +but not as: :: -- | ... -- Copyright: (c) Some Person, 2013 @@ -352,7 +352,7 @@ Documentation Structure Examples We now give several examples that produce similar results and illustrate most of the structural markup features. The first two -example use an export list, but the third example does not. +examples use an export list, but the third example does not. The first example, using an export list with :ref:`section-headings` and inline section descriptions: :: @@ -362,7 +362,7 @@ and inline section descriptions: :: -- -- | There is a "smart" importer, 'readImage', that determines -- the image format from the file extension, and several - -- "dumb" format-specific importers that decode the file at + -- "dumb" format-specific importers that decode the file as -- the specified type. readImage , readPngImage @@ -417,7 +417,7 @@ defined elsewhere (the ``$imageImporters``; see :ref:`named-chunks`): -- -- There is a "smart" importer, 'readImage', that determines the -- image format from the file extension, and several "dumb" - -- format-specific importers that decode the file at the specified + -- format-specific importers that decode the file as the specified -- type. -- | Read an image, guessing the format from the file name. @@ -450,7 +450,7 @@ The third example, without an export list: :: -- -- There is a "smart" importer, 'readImage', that determines the -- image format from the file extension, and several "dumb" - -- format-specific importers that decode the file at the specified + -- format-specific importers that decode the file as the specified -- type. -- | Read an image, guessing the format from the file name. @@ -522,11 +522,11 @@ create stable links, you can add an explicit anchor (see This will create an HTML anchor ``#g:classes`` to the section. The alternative style of placing the commas at the beginning of each -line is also supported. e.g.: :: +line is also supported, e.g.: :: module Foo ( -- * Classes - , C(..) + C(..) -- * Types -- ** A data type , T @@ -539,7 +539,7 @@ line is also supported. e.g.: :: When not using an export list, you may insert section headers in the module body. Such section headers associate with all entities -declaried up until the next section header. For example: :: +declared up until the next section header. For example: :: module Foo where @@ -614,7 +614,7 @@ re-exporting module. It is often desirable to include a chunk of documentation which is not attached to any particular Haskell declaration, for example, when giving summary documentation for a group of related definitions (see -:ref:`structure-examples`). In addition to including such documenation +:ref:`structure-examples`). In addition to including such documentation chunks at the top of the file, as part of the :ref:`module-description`, you can also associate them with :ref:`section-headings`. @@ -668,14 +668,14 @@ headings, depending on whether you are using an export list or not: -- Here is a large chunk of documentation which may be referred to by -- the name $doc. - Just like with entity declariations when not using an export list, + Just like with entity declarations when not using an export list, named chunks of documentation are associated with the preceding section header here, or with the implicit top-level documentation section if there is no preceding section header. **Warning**: the form used in the first bullet above, where the chunk is not named, *does not work* when you aren't using an - export list. For example :: + export list. For example: :: module Foo where @@ -686,7 +686,7 @@ headings, depending on whether you are using an export list or not: -- | The fooifier. foo :: ... - will result in ``Some documentation not ...`` being attached to + will result in ``Some documentation not ...`` being attached to the *next* entity declaration, here ``foo``, in addition to any other documentation that next entity already has! @@ -756,7 +756,7 @@ type in ``C`` will therefore point locally to ``C.T``. Module Attributes ----------------- -Certain attributes may be specified for each module which affects the +Certain attributes may be specified for each module which affect the way that Haddock generates documentation for that module. Attributes are specified in a comma-separated list in an ``{-# OPTIONS_HADDOCK ... #-}`` pragma at the top of the module, either @@ -807,7 +807,7 @@ Markup Haddock understands certain textual cues inside documentation annotations that tell it how to render the documentation. The cues (or -“markup”) have been designed to be simple and mnemonic in ASCII so that +“markup”) have been designed to be simple and mnemonic in ASCII so the programmer doesn't have to deal with heavyweight annotations when editing documentation comments. @@ -820,8 +820,8 @@ comment. Special Characters ~~~~~~~~~~~~~~~~~~ -The following characters have special meanings in documentation -comments: ``\``, ``/``, ``'``, `````, ``"``, ``@``, ``<``, ``$``, ``#``. To insert a +The following characters have special meanings in documentation comments: +``\``, ``/``, ``'``, `````, ``"``, ``@``, ``<``, ``$``, ``#``. To insert a literal occurrence of one of these special characters, precede it with a backslash (``\``). @@ -839,7 +839,7 @@ Character References Although Haskell source files may contain any character from the Unicode character set, the encoding of these characters as bytes varies between -systems, so that only source files restricted to the ASCII character set +systems. Consequently, only source files restricted to the ASCII character set are portable. Other characters may be specified in character and string literals using Haskell character escapes. To represent such characters in documentation comments, Haddock supports SGML-style numeric character @@ -926,10 +926,11 @@ If ``M.T`` is not otherwise in scope, then Haddock will simply emit a link pointing to the entity ``T`` exported from module ``M`` (without checking to see whether either ``M`` or ``M.T`` exist). -Since values and types live in different namespaces in Haskell, it is -possible for a reference such as ``'X'`` to be ambiguous. In such a case, -Haddock defaults to pointing to the type. The ambiguity can be overcome by explicitly specifying a namespace, by way of a ``v`` (for value) or ``t`` -(for type) immediately before the link: :: +Since values and types live in different namespaces in Haskell, it is possible +for a reference such as ``'X'`` to be ambiguous. In such a case, Haddock +defaults to pointing to the type. The ambiguity can be overcome by explicitly +specifying a namespace, by way of a ``v`` (for value) or ``t`` (for type) +immediately before the link: :: -- | An implicit reference to 'X', the type constructor -- An explicit reference to v'X', the data constructor @@ -986,7 +987,7 @@ Itemized and Enumerated Lists A bulleted item is represented by preceding a paragraph with either “``*``” or “``-``”. A sequence of bulleted paragraphs is rendered as an -itemized list in the generated documentation, eg.: :: +itemized list in the generated documentation, e.g.: :: -- | This is a bulleted list: -- @@ -1025,7 +1026,7 @@ You can have more than one line of content in a list element: :: You can even nest whole paragraphs inside of list elements. The rules are 4 spaces for each indentation level. You're required to use a -newline before such nested paragraph: :: +newline before such nested paragraphs: :: {-| * Beginning of list @@ -1112,7 +1113,7 @@ followed by the URL enclosed in regular parentheses, for example: :: [some link](http://example.com) -The link text is used as a descriptive text for the URL, if the output +The link text is used as a description for the URL if the output format supports it. Images @@ -1125,8 +1126,8 @@ like this: :: ![image description](pathtoimage.png) If the output format supports it, the image will be rendered inside the -documentation. The image description is used as relpacement text and/or -image title. +documentation. The image description is used as replacement text and/or +an image title. Mathematics / LaTeX ~~~~~~~~~~~~~~~~~~~ @@ -1146,7 +1147,13 @@ the mathematics via `MathJax `__. Grid Tables ~~~~~~~~~~~ -Inspired by reSTs grid tables Haddock supports a complete table representation via a grid-like "ASCII art". Grid tables are described with a visual grid made up of the characters "-", "=", "|", and "+". The hyphen ("-") is used for horizontal lines (row separators). The equals sign ("=") may be used to separate optional header rows from the table body. The vertical bar ("|") is used for vertical lines (column separators). The plus sign ("+") is used for intersections of horizontal and vertical lines. :: +Inspired by reSTs grid tables, Haddock supports a complete table representation +via grid-like "ASCII art". Grid tables are described with a visual grid made +up of the characters "-", "=", "|", and "+". The hyphen ("-") is used for +horizontal lines (row separators). The equals sign ("=") may be used to +separate optional header rows from the table body. The vertical bar ("|") is +used for vertical lines (column separators). The plus sign ("+") is used for +intersections of horizontal and vertical lines. :: -- | This is a grid table: -- @@ -1240,7 +1247,7 @@ Since ^^^^^ ``@since`` annotation can be used to convey information about when the -function was introduced or when it has changed in the way significant to +function was introduced or when it has changed in a way significant to the user. ``@since`` is a paragraph-level element. While multiple such annotations are not an error, only the one to appear in the comment last will be used. ``@since`` has to be followed with a version number, no diff --git a/haddock-api/src/Haddock/Backends/Xhtml.hs b/haddock-api/src/Haddock/Backends/Xhtml.hs index 4e87d0be..f80a9c05 100644 --- a/haddock-api/src/Haddock/Backends/Xhtml.hs +++ b/haddock-api/src/Haddock/Backends/Xhtml.hs @@ -307,6 +307,7 @@ ppPrologue pkg qual title (Just doc) = ppSignatureTree :: Maybe Package -> Qualification -> [ModuleTree] -> Html +ppSignatureTree _ _ [] = mempty ppSignatureTree pkg qual ts = divModuleList << (sectionName << "Signatures" +++ mkNodeList pkg qual [] "n" ts) diff --git a/haddock-api/src/Haddock/Interface.hs b/haddock-api/src/Haddock/Interface.hs index 66e0bedc..d1e1dae1 100644 --- a/haddock-api/src/Haddock/Interface.hs +++ b/haddock-api/src/Haddock/Interface.hs @@ -111,7 +111,7 @@ processModules verbosity modules flags extIfaces = do let warnings = Flag_NoWarnings `notElem` flags dflags <- getDynFlags let (interfaces'', msgs) = - runWriter $ mapM (renameInterface dflags links warnings) interfaces' + runWriter $ mapM (renameInterface dflags (ignoredSymbols flags) links warnings) interfaces' liftIO $ mapM_ putStrLn msgs return (interfaces'', homeLinks) diff --git a/haddock-api/src/Haddock/Interface/Create.hs b/haddock-api/src/Haddock/Interface/Create.hs index 5a58e1ac..d554eeb3 100644 --- a/haddock-api/src/Haddock/Interface/Create.hs +++ b/haddock-api/src/Haddock/Interface/Create.hs @@ -39,6 +39,7 @@ import Data.Ord import Control.Applicative import Control.Monad import Data.Traversable +import GHC.Stack (HasCallStack) import Avail hiding (avail) import qualified Avail @@ -58,16 +59,21 @@ import FastString ( unpackFS, bytesFS ) import BasicTypes ( StringLiteral(..), SourceText(..), PromotionFlag(..) ) import qualified Outputable as O +mkExceptionContext :: TypecheckedModule -> String +mkExceptionContext = + ("creating Haddock interface for " ++) . moduleNameString . ms_mod_name . pm_mod_summary . tm_parsed_module -- | Use a 'TypecheckedModule' to produce an 'Interface'. -- To do this, we need access to already processed modules in the topological -- sort. That's what's in the 'IfaceMap'. -createInterface :: TypecheckedModule +createInterface :: HasCallStack + => TypecheckedModule -> [Flag] -- Boolean flags -> IfaceMap -- Locally processed modules -> InstIfaceMap -- External, already installed interfaces -> ErrMsgGhc Interface -createInterface tm flags modMap instIfaceMap = do +createInterface tm flags modMap instIfaceMap = + withExceptionContext (mkExceptionContext tm) $ do let ms = pm_mod_summary . tm_parsed_module $ tm mi = moduleInfo tm @@ -207,7 +213,6 @@ createInterface tm flags modMap instIfaceMap = do , ifaceDynFlags = dflags } - -- | Given all of the @import M as N@ declarations in a package, -- create a mapping from the module identity of M, to an alias N -- (if there are multiple aliases, we pick the last one.) This @@ -652,7 +657,8 @@ collectDocs = go Nothing [] -- We create the export items even if the module is hidden, since they -- might be useful when creating the export items for other modules. mkExportItems - :: Bool -- is it a signature + :: HasCallStack + => Bool -- is it a signature -> IfaceMap -> Maybe Package -- this package -> Module -- this module @@ -711,7 +717,8 @@ mkExportItems availExportItem is_sig modMap thisMod semMod warnings exportedNames maps fixMap splices instIfaceMap dflags avail -availExportItem :: Bool -- is it a signature +availExportItem :: HasCallStack + => Bool -- is it a signature -> IfaceMap -> Module -- this module -> Module -- semantic module @@ -804,7 +811,7 @@ availExportItem is_sig modMap thisMod semMod warnings exportedNames Just synifiedDecl -> pure synifiedDecl Nothing -> O.pprPanic "availExportItem" (O.text err) - availExportDecl :: AvailInfo -> LHsDecl GhcRn + availExportDecl :: HasCallStack => AvailInfo -> LHsDecl GhcRn -> (DocForDecl Name, [(Name, DocForDecl Name)]) -> ErrMsgGhc [ ExportItem GhcRn ] availExportDecl avail decl (doc, subs) @@ -1075,7 +1082,8 @@ fullModuleContents is_sig modMap pkgName thisMod semMod warnings gre exportedNam -- This function looks through the declarations in this module to try to find -- the one with the right name. extractDecl - :: DeclMap -- ^ all declarations in the file + :: HasCallStack + => DeclMap -- ^ all declarations in the file -> Name -- ^ name of the declaration to extract -> LHsDecl GhcRn -- ^ parent declaration -> Either ErrMsg (LHsDecl GhcRn) @@ -1159,10 +1167,11 @@ extractDecl declMap name decl _ -> Left "internal: extractDecl (ClsInstD)" _ -> Left ("extractDecl: Unhandled decl for " ++ getOccString name) -extractPatternSyn :: Name -> Name -> [LHsTypeArg GhcRn] -> [LConDecl GhcRn] -> Either ErrMsg (LSig GhcRn) +extractPatternSyn :: HasCallStack => Name -> Name -> [LHsTypeArg GhcRn] -> [LConDecl GhcRn] -> Either ErrMsg (LSig GhcRn) extractPatternSyn nm t tvs cons = case filter matches cons of - [] -> Left "extractPatternSyn: constructor pattern not found" + [] -> Left . O.showSDocUnsafe $ + O.text "constructor pattern " O.<+> O.ppr nm O.<+> O.text "not found in type" O.<+> O.ppr t con:_ -> pure (extract <$> con) where matches :: LConDecl GhcRn -> Bool diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs index 97f128d7..b4ff31e5 100644 --- a/haddock-api/src/Haddock/Interface/Rename.hs +++ b/haddock-api/src/Haddock/Interface/Rename.hs @@ -29,6 +29,7 @@ import Control.Applicative import Control.Arrow ( first ) import Control.Monad hiding (mapM) import qualified Data.Map as Map hiding ( Map ) +import qualified Data.Set as Set import Prelude hiding (mapM) -- | Traverse docstrings and ASTs in the Haddock interface, renaming 'Name' to @@ -39,8 +40,8 @@ import Prelude hiding (mapM) -- -- The renamed output gets written into fields in the Haddock interface record -- that were previously left empty. -renameInterface :: DynFlags -> LinkEnv -> Bool -> Interface -> ErrMsgM Interface -renameInterface dflags renamingEnv warnings iface = +renameInterface :: DynFlags -> [String] -> LinkEnv -> Bool -> Interface -> ErrMsgM Interface +renameInterface _dflags ignoredSymbols renamingEnv warnings iface = -- first create the local env, where every name exported by this module -- is mapped to itself, and everything else comes from the global renaming @@ -75,8 +76,15 @@ renameInterface dflags renamingEnv warnings iface = -- Note that since the renamed AST represents equality constraints as -- @HasOpTy t1 eqTyCon_RDR t2@ (and _not_ as @HsEqTy t1 t2@), we need to -- manually filter out 'eqTyCon_RDR' (aka @~@). - strings = [ pretty dflags n + + qualifiedName n = (moduleNameString $ moduleName $ nameModule n) <> "." <> getOccString n + + ignoreSet = Set.fromList ignoredSymbols + + strings = [ qualifiedName n + | n <- missingNames + , not (qualifiedName n `Set.member` ignoreSet) , not (isSystemName n) , not (isBuiltInSyntax n) , Exact n /= eqTyCon_RDR @@ -88,7 +96,7 @@ renameInterface dflags renamingEnv warnings iface = unless (OptHide `elem` ifaceOptions iface || null strings || not warnings) $ tell ["Warning: " ++ moduleString (ifaceMod iface) ++ ": could not find link destinations for:\n"++ - unwords (" " : strings) ] + intercalate "\n\t- " ("" : strings) ] return $ iface { ifaceRnDoc = finalModuleDoc, ifaceRnDocMap = rnDocMap, diff --git a/haddock-api/src/Haddock/Options.hs b/haddock-api/src/Haddock/Options.hs index 510810b0..8a18a60d 100644 --- a/haddock-api/src/Haddock/Options.hs +++ b/haddock-api/src/Haddock/Options.hs @@ -36,7 +36,8 @@ module Haddock.Options ( readIfaceArgs, optPackageName, optPackageVersion, - modulePackageInfo + modulePackageInfo, + ignoredSymbols ) where @@ -108,6 +109,7 @@ data Flag | Flag_PackageVersion String | Flag_Reexport String | Flag_SinceQualification String + | Flag_IgnoreLinkSymbol String deriving (Eq, Show) @@ -219,7 +221,9 @@ options backwardsCompat = Option [] ["package-version"] (ReqArg Flag_PackageVersion "VERSION") "version of the package being documented in usual x.y.z.w format", Option [] ["since-qual"] (ReqArg Flag_SinceQualification "QUAL") - "package qualification of @since, one of\n'always' (default) or 'only-external'" + "package qualification of @since, one of\n'always' (default) or 'only-external'", + Option [] ["ignore-link-symbol"] (ReqArg Flag_IgnoreLinkSymbol "SYMBOL") + "name of a symbol which does not trigger a warning in case of link issue" ] @@ -336,6 +340,8 @@ verbosity flags = Left e -> throwE e Right v -> v +ignoredSymbols :: [Flag] -> [String] +ignoredSymbols flags = [ symbol | Flag_IgnoreLinkSymbol symbol <- flags ] ghcFlags :: [Flag] -> [String] ghcFlags flags = [ option | Flag_OptGhc option <- flags ] diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs index ec76fb72..c2cf08bb 100644 --- a/haddock-api/src/Haddock/Types.hs +++ b/haddock-api/src/Haddock/Types.hs @@ -39,6 +39,7 @@ import Data.Void (Void) import Documentation.Haddock.Types import BasicTypes (Fixity(..), PromotionFlag(..)) +import Exception (ExceptionMonad(..), ghandle) import GHC import DynFlags (Language) import qualified GHC.LanguageExtensions as LangExt @@ -649,17 +650,28 @@ tell w = Writer ((), w) -- | Haddock's own exception type. -data HaddockException = HaddockException String deriving Typeable +data HaddockException + = HaddockException String + | WithContext [String] SomeException + deriving Typeable instance Show HaddockException where show (HaddockException str) = str - + show (WithContext ctxts se) = unlines $ ["While " ++ ctxt ++ ":\n" | ctxt <- reverse ctxts] ++ [show se] throwE :: String -> a instance Exception HaddockException throwE str = throw (HaddockException str) +withExceptionContext :: ExceptionMonad m => String -> m a -> m a +withExceptionContext ctxt = + ghandle (\ex -> + case ex of + HaddockException e -> throw $ WithContext [ctxt] (toException ex) + WithContext ctxts se -> throw $ WithContext (ctxt:ctxts) se + ) . + ghandle (throw . WithContext [ctxt]) -- In "Haddock.Interface.Create", we need to gather -- @Haddock.Types.ErrMsg@s a lot, like @ErrMsgM@ does, @@ -694,6 +706,12 @@ instance Monad ErrMsgGhc where instance MonadIO ErrMsgGhc where liftIO m = WriterGhc (fmap (\x -> (x, [])) (liftIO m)) +instance ExceptionMonad ErrMsgGhc where + gcatch act hand = WriterGhc $ + runWriterGhc act `gcatch` (runWriterGhc . hand) + gmask act = WriterGhc $ gmask $ \mask -> + runWriterGhc $ act (WriterGhc . mask . runWriterGhc) + ----------------------------------------------------------------------------- -- * Pass sensitive types ----------------------------------------------------------------------------- diff --git a/haddock-library/src/Documentation/Haddock/Parser.hs b/haddock-library/src/Documentation/Haddock/Parser.hs index bd01f354..a3bba38a 100644 --- a/haddock-library/src/Documentation/Haddock/Parser.hs +++ b/haddock-library/src/Documentation/Haddock/Parser.hs @@ -227,7 +227,7 @@ takeWhile1_ = mfilter (not . T.null) . takeWhile_ -- DocAName "Hello world" anchor :: Parser (DocH mod a) anchor = DocAName . T.unpack <$> - disallowNewline ("#" *> takeWhile1_ (/= '#') <* "#") + ("#" *> takeWhile1_ (\x -> x /= '#' && not (isSpace x)) <* "#") -- | Monospaced strings. -- diff --git a/haddock-library/src/Documentation/Haddock/Types.hs b/haddock-library/src/Documentation/Haddock/Types.hs index d8c7a9fa..12ccd28d 100644 --- a/haddock-library/src/Documentation/Haddock/Types.hs +++ b/haddock-library/src/Documentation/Haddock/Types.hs @@ -126,7 +126,7 @@ data DocH mod id | DocMathInline String | DocMathDisplay String | DocAName String - -- ^ A (HTML) anchor. + -- ^ A (HTML) anchor. It must not contain any spaces. | DocProperty String | DocExamples [Example] | DocHeader (Header (DocH mod id)) diff --git a/haddock-library/test/Documentation/Haddock/ParserSpec.hs b/haddock-library/test/Documentation/Haddock/ParserSpec.hs index 9bf9b6ea..f264dbba 100644 --- a/haddock-library/test/Documentation/Haddock/ParserSpec.hs +++ b/haddock-library/test/Documentation/Haddock/ParserSpec.hs @@ -289,8 +289,10 @@ spec = do it "parses a single word anchor" $ do "#foo#" `shouldParseTo` DocAName "foo" - it "parses a multi word anchor" $ do - "#foo bar#" `shouldParseTo` DocAName "foo bar" + -- Spaces are not allowed: + -- https://www.w3.org/TR/html51/dom.html#the-id-attribute + it "doesn't parse a multi word anchor" $ do + "#foo bar#" `shouldParseTo` "#foo bar#" it "parses a unicode anchor" $ do "#灼眼のシャナ#" `shouldParseTo` DocAName "灼眼のシャナ" @@ -305,6 +307,9 @@ spec = do it "does not accept empty anchors" $ do "##" `shouldParseTo` "##" + it "does not accept anchors containing spaces" $ do + "{-# LANGUAGE GADTs #-}" `shouldParseTo` "{-# LANGUAGE GADTs #-}" + context "when parsing emphasised text" $ do it "emphasises a word on its own" $ do "/foo/" `shouldParseTo` DocEmphasis "foo" -- cgit v1.2.3