aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--doc/markup.rst77
-rw-r--r--haddock-api/src/Haddock/Backends/Xhtml.hs1
-rw-r--r--haddock-api/src/Haddock/Interface.hs2
-rw-r--r--haddock-api/src/Haddock/Interface/Create.hs27
-rw-r--r--haddock-api/src/Haddock/Interface/Rename.hs16
-rw-r--r--haddock-api/src/Haddock/Options.hs10
-rw-r--r--haddock-api/src/Haddock/Types.hs22
-rw-r--r--haddock-library/src/Documentation/Haddock/Parser.hs2
-rw-r--r--haddock-library/src/Documentation/Haddock/Types.hs2
-rw-r--r--haddock-library/test/Documentation/Haddock/ParserSpec.hs9
10 files changed, 111 insertions, 57 deletions
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 <https://www.mathjax.org>`__.
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"