From dd47029cb29c80b1ab4db520c9c2ce4dca37f833 Mon Sep 17 00:00:00 2001
From: Alec Theriault
Date: Thu, 19 Jul 2018 11:42:26 -0700
Subject: Support value/type namespaces on identifier links
Identifier links can be prefixed with a 'v' or 't' to indicate the value or
type namespace of the desired identifier. For example:
-- | Some link to a value: v'Data.Functor.Identity'
--
-- Some link to a type: t'Data.Functor.Identity'
The default is still the type (with a warning about the ambiguity)
---
.../src/Documentation/Haddock/Parser.hs | 22 ++++++++++++++--------
haddock-library/src/Documentation/Haddock/Types.hs | 10 ++++++++++
2 files changed, 24 insertions(+), 8 deletions(-)
(limited to 'haddock-library/src')
diff --git a/haddock-library/src/Documentation/Haddock/Parser.hs b/haddock-library/src/Documentation/Haddock/Parser.hs
index 82d65a0a..e9b1c496 100644
--- a/haddock-library/src/Documentation/Haddock/Parser.hs
+++ b/haddock-library/src/Documentation/Haddock/Parser.hs
@@ -28,6 +28,7 @@ import Control.Applicative
import Control.Arrow (first)
import Control.Monad
import Data.Char (chr, isUpper, isAlpha, isAlphaNum, isSpace)
+import Data.Foldable (asum)
import Data.List (intercalate, unfoldr, elemIndex)
import Data.Maybe (fromMaybe, mapMaybe)
import Data.Monoid
@@ -75,24 +76,24 @@ isSymbolChar c = not (isPuncChar c) && case generalCategory c of
#endif
-- | Identifier string surrounded with opening and closing quotes/backticks.
-type Identifier = (Char, String, Char)
+data Identifier = Identifier !Namespace !Char String !Char
-- | Drops the quotes/backticks around all identifiers, as if they
-- were valid but still 'String's.
toRegular :: DocH mod Identifier -> DocH mod String
-toRegular = fmap (\(_, x, _) -> x)
+toRegular = fmap (\(Identifier _ _ x _) -> x)
-- | Maps over 'DocIdentifier's over 'String' with potentially failing
-- conversion using user-supplied function. If the conversion fails,
-- the identifier is deemed to not be valid and is treated as a
-- regular string.
-overIdentifier :: (String -> Maybe a)
+overIdentifier :: (Namespace -> String -> Maybe a)
-> DocH mod Identifier
-> DocH mod a
overIdentifier f d = g d
where
- g (DocIdentifier (o, x, e)) = case f x of
- Nothing -> DocString $ o : x ++ [e]
+ g (DocIdentifier (Identifier ns o x e)) = case f ns x of
+ Nothing -> DocString $ renderNs ns ++ [o] ++ x ++ [e]
Just x' -> DocIdentifier x'
g DocEmpty = DocEmpty
g (DocAppend x x') = DocAppend (g x) (g x')
@@ -314,7 +315,8 @@ markdownImage :: Parser (DocH mod Identifier)
markdownImage = DocPic . fromHyperlink <$> ("!" *> linkParser)
where
fromHyperlink (Hyperlink u l) = Picture u (fmap (markup stringMarkup) l)
- stringMarkup = plainMarkup (const "") (\(l,c,r) -> [l] <> c <> [r])
+ stringMarkup = plainMarkup (const "") renderIdent
+ renderIdent (Identifier ns l c r) = renderNs ns <> [l] <> c <> [r]
-- | Paragraph parser, called by 'parseParas'.
paragraph :: Parser (DocH mod Identifier)
@@ -857,9 +859,13 @@ parseValid = p some
-- 'String' from the string it deems valid.
identifier :: Parser (DocH mod Identifier)
identifier = do
+ ns <- asum [ Value <$ Parsec.char 'v'
+ , Type <$ Parsec.char 't'
+ , pure None
+ ]
o <- idDelim
vid <- parseValid
e <- idDelim
- return $ DocIdentifier (o, vid, e)
+ return $ DocIdentifier (Identifier ns o vid e)
where
- idDelim = Parsec.satisfy (\c -> c == '\'' || c == '`')
+ idDelim = Parsec.oneOf "'`"
diff --git a/haddock-library/src/Documentation/Haddock/Types.hs b/haddock-library/src/Documentation/Haddock/Types.hs
index f8f7d353..ba2f873c 100644
--- a/haddock-library/src/Documentation/Haddock/Types.hs
+++ b/haddock-library/src/Documentation/Haddock/Types.hs
@@ -203,6 +203,16 @@ instance Bitraversable DocH where
bitraverse f g (DocTable (Table header body)) = (\h b -> DocTable (Table h b)) <$> traverse (traverse (bitraverse f g)) header <*> traverse (traverse (bitraverse f g)) body
#endif
+-- | The namespace qualification for an identifier.
+data Namespace = Value | Type | None deriving (Eq, Ord, Enum, Show)
+
+-- | Render the a namespace into the same format it was initially parsed.
+renderNs :: Namespace -> String
+renderNs Value = "v"
+renderNs Type = "t"
+renderNs None = ""
+
+
-- | 'DocMarkupH' is a set of instructions for marking up documentation.
-- In fact, it's really just a mapping from 'Doc' to some other
-- type [a], where [a] is usually the type of the output (HTML, say).
--
cgit v1.2.3
From a5199600c39d25d7b71dcb2328000c1c49ad95a2 Mon Sep 17 00:00:00 2001
From: Alec Theriault
Date: Wed, 6 Feb 2019 01:01:41 -0800
Subject: Better identifier parsing
* '(<|>)' and '`elem`' now get parsed and rendered properly as links
* 'DbModule'/'DbUnitId' now properly get split apart into two links
* tuple names now get parsed properly
* some more small niceties...
The identifier parsing code is more precise and more efficient (although to be
fair: it is also longer and in its own module). On the rendering side, we need
to pipe through information about backticks/parens/neither all the way through
from renaming to the backends.
In terms of impact: a total of 35 modules in the entirety of the bootlib + ghc
lib docs change. The only "regression" is things like '\0'. These should be
changed to @\\0@ (the path by which this previously worked seems accidental).
---
doc/markup.rst | 9 +-
haddock-api/src/Haddock.hs | 2 +-
haddock-api/src/Haddock/Backends/Hoogle.hs | 2 +-
haddock-api/src/Haddock/Backends/LaTeX.hs | 19 +-
.../src/Haddock/Backends/Xhtml/DocMarkup.hs | 16 +-
haddock-api/src/Haddock/Backends/Xhtml/Names.hs | 28 +-
haddock-api/src/Haddock/Interface/Json.hs | 5 +-
haddock-api/src/Haddock/Interface/LexParseRn.hs | 58 +++--
haddock-api/src/Haddock/Interface/Rename.hs | 4 +-
haddock-api/src/Haddock/InterfaceFile.hs | 27 +-
haddock-api/src/Haddock/Parser.hs | 19 +-
haddock-api/src/Haddock/Types.hs | 28 +-
haddock-library/haddock-library.cabal | 2 +
.../src/Documentation/Haddock/Parser.hs | 63 +----
.../src/Documentation/Haddock/Parser/Identifier.hs | 186 ++++++++++++++
.../src/Documentation/Haddock/Parser/Monad.hs | 13 +-
.../test/Documentation/Haddock/ParserSpec.hs | 9 +-
haddock.cabal | 1 +
html-test/ref/Identifiers.html | 286 +++++++++++++++++++++
html-test/ref/Test.html | 2 +-
html-test/src/Identifiers.hs | 35 +++
21 files changed, 679 insertions(+), 135 deletions(-)
create mode 100644 haddock-library/src/Documentation/Haddock/Parser/Identifier.hs
create mode 100644 html-test/ref/Identifiers.html
create mode 100644 html-test/src/Identifiers.hs
(limited to 'haddock-library/src')
diff --git a/doc/markup.rst b/doc/markup.rst
index 48a6f4ad..56238855 100644
--- a/doc/markup.rst
+++ b/doc/markup.rst
@@ -932,14 +932,9 @@ necessary to escape the single quote when used as an apostrophe: ::
Nothing special is needed to hyperlink identifiers which contain
apostrophes themselves: to hyperlink ``foo'`` one would simply type
-``'foo''``. Hyperlinking operators works in exactly the same way.
+``'foo''``. Hyperlinking operators works in exactly the same way. ::
-Note that it is not possible to directly hyperlink an identifier in infix
-form or an operator in prefix form. The next best thing to do is to wrap
-the whole identifier in monospaced text and put the parentheses/backticks
-outside of the identifier, but inside the link: ::
-
- -- | A prefix operator @('++')@ and an infix identifier @\``elem`\`@.
+ -- | A prefix operator @'(++)'@ and an infix identifier @'`elem`'@.
Emphasis, Bold and Monospaced Text
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
diff --git a/haddock-api/src/Haddock.hs b/haddock-api/src/Haddock.hs
index 1378c173..3e0332b5 100644
--- a/haddock-api/src/Haddock.hs
+++ b/haddock-api/src/Haddock.hs
@@ -663,7 +663,7 @@ getPrologue dflags flags =
h <- openFile filename ReadMode
hSetEncoding h utf8
str <- hGetContents h -- semi-closes the handle
- return . Just $! second rdrName $ parseParas dflags Nothing str
+ return . Just $! second (fmap rdrName) $ parseParas dflags Nothing str
_ -> throwE "multiple -p/--prologue options"
diff --git a/haddock-api/src/Haddock/Backends/Hoogle.hs b/haddock-api/src/Haddock/Backends/Hoogle.hs
index 9e3186e5..f581c01a 100644
--- a/haddock-api/src/Haddock/Backends/Hoogle.hs
+++ b/haddock-api/src/Haddock/Backends/Hoogle.hs
@@ -334,7 +334,7 @@ markupTag dflags = Markup {
markupString = str,
markupAppend = (++),
markupIdentifier = box (TagInline "a") . str . out dflags,
- markupIdentifierUnchecked = box (TagInline "a") . str . out dflags . snd,
+ markupIdentifierUnchecked = box (TagInline "a") . str . showWrapped (out dflags . snd),
markupModule = box (TagInline "a") . str,
markupWarning = box (TagInline "i"),
markupEmphasis = box (TagInline "i"),
diff --git a/haddock-api/src/Haddock/Backends/LaTeX.hs b/haddock-api/src/Haddock/Backends/LaTeX.hs
index d0752506..85769b13 100644
--- a/haddock-api/src/Haddock/Backends/LaTeX.hs
+++ b/haddock-api/src/Haddock/Backends/LaTeX.hs
@@ -1106,8 +1106,8 @@ ppSymName name
| otherwise = ppName name
-ppVerbOccName :: OccName -> LaTeX
-ppVerbOccName = text . latexFilter . occNameString
+ppVerbOccName :: Wrap OccName -> LaTeX
+ppVerbOccName = text . latexFilter . showWrapped occNameString
ppIPName :: HsIPName -> LaTeX
ppIPName = text . ('?':) . unpackFS . hsIPNameFS
@@ -1115,13 +1115,12 @@ ppIPName = text . ('?':) . unpackFS . hsIPNameFS
ppOccName :: OccName -> LaTeX
ppOccName = text . occNameString
+ppVerbDocName :: Wrap DocName -> LaTeX
+ppVerbDocName = text . latexFilter . showWrapped (occNameString . nameOccName . getName)
-ppVerbDocName :: DocName -> LaTeX
-ppVerbDocName = ppVerbOccName . nameOccName . getName
-
-ppVerbRdrName :: RdrName -> LaTeX
-ppVerbRdrName = ppVerbOccName . rdrNameOcc
+ppVerbRdrName :: Wrap RdrName -> LaTeX
+ppVerbRdrName = text . latexFilter . showWrapped (occNameString . rdrNameOcc)
ppDocName :: DocName -> LaTeX
@@ -1182,7 +1181,7 @@ parLatexMarkup ppId = Markup {
markupString = \s v -> text (fixString v s),
markupAppend = \l r v -> l v <> r v,
markupIdentifier = markupId ppId,
- markupIdentifierUnchecked = markupId (ppVerbOccName . snd),
+ markupIdentifierUnchecked = markupId (ppVerbOccName . fmap snd),
markupModule = \m _ -> let (mdl,_ref) = break (=='#') m in tt (text mdl),
markupWarning = \p v -> emph (p v),
markupEmphasis = \p v -> emph (p v),
@@ -1239,11 +1238,11 @@ parLatexMarkup ppId = Markup {
where theid = ppId_ id
-latexMarkup :: DocMarkup DocName (StringContext -> LaTeX)
+latexMarkup :: DocMarkup (Wrap DocName) (StringContext -> LaTeX)
latexMarkup = parLatexMarkup ppVerbDocName
-rdrLatexMarkup :: DocMarkup RdrName (StringContext -> LaTeX)
+rdrLatexMarkup :: DocMarkup (Wrap RdrName) (StringContext -> LaTeX)
rdrLatexMarkup = parLatexMarkup ppVerbRdrName
diff --git a/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs b/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
index 09aabc0c..1901cf05 100644
--- a/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
+++ b/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
@@ -171,12 +171,12 @@ flatten x = [x]
-- extract/append the underlying 'Doc' and convert it to 'Html'. For
-- 'CollapsingHeader', we attach extra info to the generated 'Html'
-- that allows us to expand/collapse the content.
-hackMarkup :: DocMarkup id Html -> Maybe Package -> Hack (ModuleName, OccName) id -> Html
+hackMarkup :: DocMarkup id Html -> Maybe Package -> Hack (Wrap (ModuleName, OccName)) id -> Html
hackMarkup fmt' currPkg h' =
let (html, ms) = hackMarkup' fmt' h'
in html +++ renderMeta fmt' currPkg (metaConcat ms)
where
- hackMarkup' :: DocMarkup id Html -> Hack (ModuleName, OccName) id
+ hackMarkup' :: DocMarkup id Html -> Hack (Wrap (ModuleName, OccName)) id
-> (Html, [Meta])
hackMarkup' fmt h = case h of
UntouchedDoc d -> (markup fmt $ _doc d, [_meta d])
@@ -206,7 +206,7 @@ renderMeta _ _ _ = noHtml
-- | Goes through 'hackMarkup' to generate the 'Html' rather than
-- skipping straight to 'markup': this allows us to employ XHtml
-- specific hacks to the tree first.
-markupHacked :: DocMarkup id Html
+markupHacked :: DocMarkup (Wrap id) Html
-> Maybe Package -- this package
-> Maybe String
-> MDoc id
@@ -220,7 +220,7 @@ docToHtml :: Maybe String -- ^ Name of the thing this doc is for. See
-> Maybe Package -- ^ Current package
-> Qualification -> MDoc DocName -> Html
docToHtml n pkg qual = markupHacked fmt pkg n . cleanup
- where fmt = parHtmlMarkup qual True (ppDocName qual Raw)
+ where fmt = parHtmlMarkup qual True (ppWrappedDocName qual Raw)
-- | Same as 'docToHtml' but it doesn't insert the 'anchor' element
-- in links. This is used to generate the Contents box elements.
@@ -228,16 +228,16 @@ docToHtmlNoAnchors :: Maybe String -- ^ See 'toHack'
-> Maybe Package -- ^ Current package
-> Qualification -> MDoc DocName -> Html
docToHtmlNoAnchors n pkg qual = markupHacked fmt pkg n . cleanup
- where fmt = parHtmlMarkup qual False (ppDocName qual Raw)
+ where fmt = parHtmlMarkup qual False (ppWrappedDocName qual Raw)
origDocToHtml :: Maybe Package -> Qualification -> MDoc Name -> Html
origDocToHtml pkg qual = markupHacked fmt pkg Nothing . cleanup
- where fmt = parHtmlMarkup qual True (const $ ppName Raw)
+ where fmt = parHtmlMarkup qual True (const (ppWrappedName Raw))
rdrDocToHtml :: Maybe Package -> Qualification -> MDoc RdrName -> Html
rdrDocToHtml pkg qual = markupHacked fmt pkg Nothing . cleanup
- where fmt = parHtmlMarkup qual True (const ppRdrName)
+ where fmt = parHtmlMarkup qual True (const (ppRdrName . unwrap))
docElement :: (Html -> Html) -> Html -> Html
@@ -273,7 +273,7 @@ cleanup = overDoc (markup fmtUnParagraphLists)
unParagraph (DocParagraph d) = d
unParagraph doc = doc
- fmtUnParagraphLists :: DocMarkup a (Doc a)
+ fmtUnParagraphLists :: DocMarkup (Wrap a) (Doc a)
fmtUnParagraphLists = idMarkup {
markupUnorderedList = DocUnorderedList . map unParagraph,
markupOrderedList = DocOrderedList . map unParagraph
diff --git a/haddock-api/src/Haddock/Backends/Xhtml/Names.hs b/haddock-api/src/Haddock/Backends/Xhtml/Names.hs
index 574045e0..6a047747 100644
--- a/haddock-api/src/Haddock/Backends/Xhtml/Names.hs
+++ b/haddock-api/src/Haddock/Backends/Xhtml/Names.hs
@@ -13,7 +13,8 @@
module Haddock.Backends.Xhtml.Names (
ppName, ppDocName, ppLDocName, ppRdrName, ppUncheckedLink,
ppBinder, ppBinderInfix, ppBinder',
- ppModule, ppModuleRef, ppIPName, linkId, Notation(..)
+ ppModule, ppModuleRef, ppIPName, linkId, Notation(..),
+ ppWrappedDocName, ppWrappedName,
) where
@@ -24,7 +25,7 @@ import Haddock.Utils
import Text.XHtml hiding ( name, p, quote )
import qualified Data.Map as M
-import qualified Data.List as List
+import Data.List ( stripPrefix )
import GHC hiding (LexicalFixity(..))
import Name
@@ -49,9 +50,11 @@ ppIPName :: HsIPName -> Html
ppIPName = toHtml . ('?':) . unpackFS . hsIPNameFS
-ppUncheckedLink :: Qualification -> (ModuleName, OccName) -> Html
-ppUncheckedLink _ (mdl, occ) = linkIdOcc' mdl (Just occ) << ppOccName occ -- TODO: apply ppQualifyName
-
+ppUncheckedLink :: Qualification -> Wrap (ModuleName, OccName) -> Html
+ppUncheckedLink _ x = linkIdOcc' mdl (Just occ) << occHtml
+ where
+ (mdl, occ) = unwrap x
+ occHtml = toHtml (showWrapped (occNameString . snd) x) -- TODO: apply ppQualifyName
-- The Bool indicates if it is to be rendered in infix notation
ppLDocName :: Qualification -> Notation -> Located DocName -> Html
@@ -68,6 +71,19 @@ ppDocName qual notation insertAnchors docName =
ppQualifyName qual notation name (nameModule name)
| otherwise -> ppName notation name
+
+ppWrappedDocName :: Qualification -> Notation -> Bool -> Wrap DocName -> Html
+ppWrappedDocName qual notation insertAnchors docName = case docName of
+ Unadorned n -> ppDocName qual notation insertAnchors n
+ Parenthesized n -> ppDocName qual Prefix insertAnchors n
+ Backticked n -> ppDocName qual Infix insertAnchors n
+
+ppWrappedName :: Notation -> Wrap Name -> Html
+ppWrappedName notation docName = case docName of
+ Unadorned n -> ppName notation n
+ Parenthesized n -> ppName Prefix n
+ Backticked n -> ppName Infix n
+
-- | Render a name depending on the selected qualification mode
ppQualifyName :: Qualification -> Notation -> Name -> Module -> Html
ppQualifyName qual notation name mdl =
@@ -79,7 +95,7 @@ ppQualifyName qual notation name mdl =
then ppName notation name
else ppFullQualName notation mdl name
RelativeQual localmdl ->
- case List.stripPrefix (moduleString localmdl) (moduleString mdl) of
+ case stripPrefix (moduleString localmdl) (moduleString mdl) of
-- local, A.x -> x
Just [] -> ppName notation name
-- sub-module, A.B.x -> B.x
diff --git a/haddock-api/src/Haddock/Interface/Json.hs b/haddock-api/src/Haddock/Interface/Json.hs
index 636d3e19..a9834fa0 100644
--- a/haddock-api/src/Haddock/Interface/Json.hs
+++ b/haddock-api/src/Haddock/Interface/Json.hs
@@ -62,7 +62,10 @@ jsonMDoc MetaDoc{..} =
]
jsonDoc :: Doc Name -> JsonDoc
-jsonDoc doc = jsonString (show (bimap (moduleNameString . fst) nameStableString doc))
+jsonDoc doc = jsonString (show (bimap showModName showName doc))
+ where
+ showModName = showWrapped (moduleNameString . fst)
+ showName = showWrapped nameStableString
jsonModule :: Module -> JsonDoc
jsonModule = JSString . moduleStableString
diff --git a/haddock-api/src/Haddock/Interface/LexParseRn.hs b/haddock-api/src/Haddock/Interface/LexParseRn.hs
index 66083cf5..faf23728 100644
--- a/haddock-api/src/Haddock/Interface/LexParseRn.hs
+++ b/haddock-api/src/Haddock/Interface/LexParseRn.hs
@@ -22,6 +22,7 @@ module Haddock.Interface.LexParseRn
import Avail
import Control.Arrow
import Control.Monad
+import Data.Functor (($>))
import Data.List
import Data.Ord
import Documentation.Haddock.Doc (metaDocConcat)
@@ -95,8 +96,9 @@ rename dflags gre = rn
rn d = case d of
DocAppend a b -> DocAppend <$> rn a <*> rn b
DocParagraph doc -> DocParagraph <$> rn doc
- DocIdentifier (NsRdrName ns x) -> do
- let occ = rdrNameOcc x
+ DocIdentifier i -> do
+ let NsRdrName ns x = unwrap i
+ occ = rdrNameOcc x
isValueName = isDataOcc occ || isVarOcc occ
let valueNsChoices | isValueName = [x]
@@ -119,7 +121,7 @@ rename dflags gre = rn
case choices of
-- The only way this can happen is if a value namespace was
-- specified on something that cannot be a value.
- [] -> invalidValue dflags x
+ [] -> invalidValue dflags i
-- There was nothing in the environment so we need to
-- pick some default from what's available to us. We
@@ -129,14 +131,14 @@ rename dflags gre = rn
-- type constructor names (such as in #253). So now we
-- only get type constructor links if they are actually
-- in scope.
- a:_ -> outOfScope dflags ns a
+ a:_ -> outOfScope dflags ns (i $> a)
-- There is only one name in the environment that matches so
-- use it.
- [a] -> pure (DocIdentifier (gre_name a))
+ [a] -> pure (DocIdentifier (i $> gre_name a))
-- There are multiple names available.
- gres -> ambiguous dflags x gres
+ gres -> ambiguous dflags i gres
DocWarning doc -> DocWarning <$> rn doc
DocEmphasis doc -> DocEmphasis <$> rn doc
@@ -168,13 +170,13 @@ rename dflags gre = rn
-- users shouldn't rely on this doing the right thing. See tickets
-- #253 and #375 on the confusion this causes depending on which
-- default we pick in 'rename'.
-outOfScope :: DynFlags -> Namespace -> RdrName -> ErrMsgM (Doc a)
+outOfScope :: DynFlags -> Namespace -> Wrap RdrName -> ErrMsgM (Doc a)
outOfScope dflags ns x =
- case x of
- Unqual occ -> warnAndMonospace occ
- Qual mdl occ -> pure (DocIdentifierUnchecked (mdl, occ))
- Orig _ occ -> warnAndMonospace occ
- Exact name -> warnAndMonospace name -- Shouldn't happen since x is out of scope
+ case unwrap x of
+ Unqual occ -> warnAndMonospace (x $> occ)
+ Qual mdl occ -> pure (DocIdentifierUnchecked (x $> (mdl, occ)))
+ Orig _ occ -> warnAndMonospace (x $> occ)
+ Exact name -> warnAndMonospace (x $> name) -- Shouldn't happen since x is out of scope
where
prefix = case ns of
Value -> "the value "
@@ -182,11 +184,11 @@ outOfScope dflags ns x =
None -> ""
warnAndMonospace a = do
- tell ["Warning: " ++ prefix ++ "'" ++ showPpr dflags a ++ "' is out of scope.\n" ++
- " If you qualify the identifier, haddock can try to link it\n" ++
- " it anyway."]
- pure (monospaced a)
- monospaced a = DocMonospaced (DocString (showPpr dflags a))
+ let a' = showWrapped (showPpr dflags) a
+ tell ["Warning: " ++ prefix ++ "'" ++ a' ++ "' is out of scope.\n" ++
+ " If you qualify the identifier, haddock can try to link it anyway."]
+ pure (monospaced a')
+ monospaced = DocMonospaced . DocString
-- | Handle ambiguous identifiers.
--
@@ -194,36 +196,42 @@ outOfScope dflags ns x =
--
-- Emits a warning if the 'GlobalRdrElts's don't belong to the same type or class.
ambiguous :: DynFlags
- -> RdrName
+ -> Wrap NsRdrName
-> [GlobalRdrElt] -- ^ More than one @gre@s sharing the same `RdrName` above.
-> ErrMsgM (Doc Name)
ambiguous dflags x gres = do
let noChildren = map availName (gresToAvailInfo gres)
dflt = maximumBy (comparing (isLocalName &&& isTyConName)) noChildren
- msg = "Warning: " ++ x_str ++ " is ambiguous. It is defined\n" ++
+ msg = "Warning: " ++ showNsRdrName dflags x ++ " is ambiguous. It is defined\n" ++
concatMap (\n -> " * " ++ defnLoc n ++ "\n") (map gre_name gres) ++
" You may be able to disambiguate the identifier by qualifying it or\n" ++
" by specifying the type/value namespace explicitly.\n" ++
- " Defaulting to " ++ x_str ++ " defined " ++ defnLoc dflt
+ " Defaulting to the one defined " ++ defnLoc dflt
-- TODO: Once we have a syntax for namespace qualification (#667) we may also
-- want to emit a warning when an identifier is a data constructor for a type
-- of the same name, but not the only constructor.
-- For example, for @data D = C | D@, someone may want to reference the @D@
-- constructor.
when (length noChildren > 1) $ tell [msg]
- pure (DocIdentifier dflt)
+ pure (DocIdentifier (x $> dflt))
where
isLocalName (nameSrcLoc -> RealSrcLoc {}) = True
isLocalName _ = False
- x_str = '\'' : showPpr dflags x ++ "'"
defnLoc = showSDoc dflags . pprNameDefnLoc
-- | Handle value-namespaced names that cannot be for values.
--
-- Emits a warning that the value-namespace is invalid on a non-value identifier.
-invalidValue :: DynFlags -> RdrName -> ErrMsgM (Doc a)
+invalidValue :: DynFlags -> Wrap NsRdrName -> ErrMsgM (Doc a)
invalidValue dflags x = do
- tell ["Warning: '" ++ showPpr dflags x ++ "' cannot be value, yet it is\n" ++
+ tell ["Warning: " ++ showNsRdrName dflags x ++ " cannot be value, yet it is\n" ++
" namespaced as such. Did you mean to specify a type namespace\n" ++
" instead?"]
- pure (DocMonospaced (DocString (showPpr dflags x)))
+ pure (DocMonospaced (DocString (showNsRdrName dflags x)))
+
+-- | Printable representation of a wrapped and namespaced name
+showNsRdrName :: DynFlags -> Wrap NsRdrName -> String
+showNsRdrName dflags = (\p i -> p ++ "'" ++ i ++ "'") <$> prefix <*> ident
+ where
+ ident = showWrapped (showPpr dflags . rdrName)
+ prefix = renderNs . namespace . unwrap
diff --git a/haddock-api/src/Haddock/Interface/Rename.hs b/haddock-api/src/Haddock/Interface/Rename.hs
index 57e6d699..88238f04 100644
--- a/haddock-api/src/Haddock/Interface/Rename.hs
+++ b/haddock-api/src/Haddock/Interface/Rename.hs
@@ -173,8 +173,8 @@ renameLDocHsSyn :: LHsDocString -> RnM LHsDocString
renameLDocHsSyn = return
-renameDoc :: Traversable t => t Name -> RnM (t DocName)
-renameDoc = traverse rename
+renameDoc :: Traversable t => t (Wrap Name) -> RnM (t (Wrap DocName))
+renameDoc = traverse (traverse rename)
renameFnArgsDoc :: FnArgsDoc Name -> RnM (FnArgsDoc DocName)
renameFnArgsDoc = mapM renameDoc
diff --git a/haddock-api/src/Haddock/InterfaceFile.hs b/haddock-api/src/Haddock/InterfaceFile.hs
index e1d8dbe1..7645b1bb 100644
--- a/haddock-api/src/Haddock/InterfaceFile.hs
+++ b/haddock-api/src/Haddock/InterfaceFile.hs
@@ -83,7 +83,7 @@ binaryInterfaceMagic = 0xD0Cface
--
binaryInterfaceVersion :: Word16
#if (__GLASGOW_HASKELL__ >= 807) && (__GLASGOW_HASKELL__ < 809)
-binaryInterfaceVersion = 34
+binaryInterfaceVersion = 35
binaryInterfaceVersionCompatibility :: [Word16]
binaryInterfaceVersionCompatibility = [binaryInterfaceVersion]
@@ -701,3 +701,28 @@ instance Binary DocName where
name <- get bh
return (Undocumented name)
_ -> error "get DocName: Bad h"
+
+instance Binary n => Binary (Wrap n) where
+ put_ bh (Unadorned n) = do
+ putByte bh 0
+ put_ bh n
+ put_ bh (Parenthesized n) = do
+ putByte bh 1
+ put_ bh n
+ put_ bh (Backticked n) = do
+ putByte bh 2
+ put_ bh n
+
+ get bh = do
+ h <- getByte bh
+ case h of
+ 0 -> do
+ name <- get bh
+ return (Unadorned name)
+ 1 -> do
+ name <- get bh
+ return (Parenthesized name)
+ 2 -> do
+ name <- get bh
+ return (Backticked name)
+ _ -> error "get Wrap: Bad h"
diff --git a/haddock-api/src/Haddock/Parser.hs b/haddock-api/src/Haddock/Parser.hs
index 8b7dda7c..6d5dc103 100644
--- a/haddock-api/src/Haddock/Parser.hs
+++ b/haddock-api/src/Haddock/Parser.hs
@@ -15,27 +15,32 @@ module Haddock.Parser ( parseParas
import qualified Documentation.Haddock.Parser as P
import Documentation.Haddock.Types
-import Haddock.Types (NsRdrName(..))
+import Haddock.Types
import DynFlags ( DynFlags )
import FastString ( fsLit )
import Lexer ( mkPState, unP, ParseResult(POk) )
import Parser ( parseIdentifier )
-import RdrName ( RdrName )
import SrcLoc ( mkRealSrcLoc, GenLocated(..) )
import StringBuffer ( stringToStringBuffer )
-parseParas :: DynFlags -> Maybe Package -> String -> MetaDoc mod NsRdrName
+
+parseParas :: DynFlags -> Maybe Package -> String -> MetaDoc mod (Wrap NsRdrName)
parseParas d p = overDoc (P.overIdentifier (parseIdent d)) . P.parseParas p
-parseString :: DynFlags -> String -> DocH mod NsRdrName
+parseString :: DynFlags -> String -> DocH mod (Wrap NsRdrName)
parseString d = P.overIdentifier (parseIdent d) . P.parseString
-parseIdent :: DynFlags -> Namespace -> String -> Maybe NsRdrName
+parseIdent :: DynFlags -> Namespace -> String -> Maybe (Wrap NsRdrName)
parseIdent dflags ns str0 =
- let buffer = stringToStringBuffer str0
+ let buffer = stringToStringBuffer str1
realSrcLc = mkRealSrcLoc (fsLit "") 0 0
pstate = mkPState dflags buffer realSrcLc
+ (wrap,str1) = case str0 of
+ '(' : s@(c : _) | c /= ',', c /= ')' -- rule out tuple names
+ -> (Parenthesized, init s)
+ '`' : s@(_ : _) -> (Backticked, init s)
+ _ -> (Unadorned, str0)
in case unP parseIdentifier pstate of
- POk _ (L _ name) -> Just (NsRdrName ns name)
+ POk _ (L _ name) -> Just (wrap (NsRdrName ns name))
_ -> Nothing
diff --git a/haddock-api/src/Haddock/Types.hs b/haddock-api/src/Haddock/Types.hs
index e8da4120..cd4ac1a1 100644
--- a/haddock-api/src/Haddock/Types.hs
+++ b/haddock-api/src/Haddock/Types.hs
@@ -42,7 +42,7 @@ import GHC
import DynFlags (Language)
import qualified GHC.LanguageExtensions as LangExt
import OccName
-import Outputable
+import Outputable hiding ((<>))
-----------------------------------------------------------------------------
-- * Convenient synonyms
@@ -334,6 +334,26 @@ instance SetName DocName where
setName name' (Documented _ mdl) = Documented name' mdl
setName name' (Undocumented _) = Undocumented name'
+-- | Adds extra "wrapper" information to a name.
+--
+-- This is to work around the fact that most name types in GHC ('Name', 'RdrName',
+-- 'OccName', ...) don't include backticks or parens.
+data Wrap n
+ = Unadorned { unwrap :: n } -- ^ don't do anything to the name
+ | Parenthesized { unwrap :: n } -- ^ add parentheses around the name
+ | Backticked { unwrap :: n } -- ^ add backticks around the name
+ deriving (Show, Functor, Foldable, Traversable)
+
+-- | Useful for debugging
+instance Outputable n => Outputable (Wrap n) where
+ ppr (Unadorned n) = ppr n
+ ppr (Parenthesized n) = hcat [ char '(', ppr n, char ')' ]
+ ppr (Backticked n) = hcat [ char '`', ppr n, char '`' ]
+
+showWrapped :: (a -> String) -> Wrap a -> String
+showWrapped f (Unadorned n) = f n
+showWrapped f (Parenthesized n) = "(" ++ f n ++ ")"
+showWrapped f (Backticked n) = "`" ++ f n ++ "`"
-----------------------------------------------------------------------------
@@ -429,10 +449,10 @@ instance NamedThing name => NamedThing (InstOrigin name) where
type LDoc id = Located (Doc id)
-type Doc id = DocH (ModuleName, OccName) id
-type MDoc id = MetaDoc (ModuleName, OccName) id
+type Doc id = DocH (Wrap (ModuleName, OccName)) (Wrap id)
+type MDoc id = MetaDoc (Wrap (ModuleName, OccName)) (Wrap id)
-type DocMarkup id a = DocMarkupH (ModuleName, OccName) id a
+type DocMarkup id a = DocMarkupH (Wrap (ModuleName, OccName)) id a
instance (NFData a, NFData mod)
=> NFData (DocH mod a) where
diff --git a/haddock-library/haddock-library.cabal b/haddock-library/haddock-library.cabal
index b24db5d4..5475d61b 100644
--- a/haddock-library/haddock-library.cabal
+++ b/haddock-library/haddock-library.cabal
@@ -49,6 +49,7 @@ library
other-modules:
Documentation.Haddock.Parser.Util
Documentation.Haddock.Parser.Monad
+ Documentation.Haddock.Parser.Identifier
test-suite spec
import: lib-defaults
@@ -70,6 +71,7 @@ test-suite spec
Documentation.Haddock.Parser.UtilSpec
Documentation.Haddock.ParserSpec
Documentation.Haddock.Types
+ Documentation.Haddock.Parser.Identifier
build-depends:
, base-compat ^>= 0.9.3 || ^>= 0.10.0
diff --git a/haddock-library/src/Documentation/Haddock/Parser.hs b/haddock-library/src/Documentation/Haddock/Parser.hs
index e9b1c496..36c8bb5b 100644
--- a/haddock-library/src/Documentation/Haddock/Parser.hs
+++ b/haddock-library/src/Documentation/Haddock/Parser.hs
@@ -27,8 +27,7 @@ module Documentation.Haddock.Parser (
import Control.Applicative
import Control.Arrow (first)
import Control.Monad
-import Data.Char (chr, isUpper, isAlpha, isAlphaNum, isSpace)
-import Data.Foldable (asum)
+import Data.Char (chr, isUpper, isAlpha, isSpace)
import Data.List (intercalate, unfoldr, elemIndex)
import Data.Maybe (fromMaybe, mapMaybe)
import Data.Monoid
@@ -37,6 +36,7 @@ import Documentation.Haddock.Doc
import Documentation.Haddock.Markup ( markup, plainMarkup )
import Documentation.Haddock.Parser.Monad
import Documentation.Haddock.Parser.Util
+import Documentation.Haddock.Parser.Identifier
import Documentation.Haddock.Types
import Prelude hiding (takeWhile)
import qualified Prelude as P
@@ -47,37 +47,10 @@ import Text.Parsec (try)
import qualified Data.Text as T
import Data.Text (Text)
-#if MIN_VERSION_base(4,9,0)
-import Text.Read.Lex (isSymbolChar)
-#else
-import Data.Char (GeneralCategory (..),
- generalCategory)
-#endif
-- $setup
-- >>> :set -XOverloadedStrings
-#if !MIN_VERSION_base(4,9,0)
--- inlined from base-4.10.0.0
-isSymbolChar :: Char -> Bool
-isSymbolChar c = not (isPuncChar c) && case generalCategory c of
- MathSymbol -> True
- CurrencySymbol -> True
- ModifierSymbol -> True
- OtherSymbol -> True
- DashPunctuation -> True
- OtherPunctuation -> c `notElem` ("'\"" :: String)
- ConnectorPunctuation -> c /= '_'
- _ -> False
- where
- -- | The @special@ character class as defined in the Haskell Report.
- isPuncChar :: Char -> Bool
- isPuncChar = (`elem` (",;()[]{}`" :: String))
-#endif
-
--- | Identifier string surrounded with opening and closing quotes/backticks.
-data Identifier = Identifier !Namespace !Char String !Char
-
-- | Drops the quotes/backticks around all identifiers, as if they
-- were valid but still 'String's.
toRegular :: DocH mod Identifier -> DocH mod String
@@ -838,34 +811,6 @@ autoUrl = mkLink <$> url
mkHyperlink lnk = Hyperlink (T.unpack lnk) Nothing
-
--- | Parses strings between identifier delimiters. Consumes all input that it
--- deems to be valid in an identifier. Note that it simply blindly consumes
--- characters and does no actual validation itself.
-parseValid :: Parser String
-parseValid = p some
- where
- idChar = Parsec.satisfy (\c -> isAlphaNum c || isSymbolChar c || c == '_')
-
- p p' = do
- vs <- p' idChar
- c <- peekChar'
- case c of
- '`' -> return vs
- '\'' -> choice' [ (\x -> vs ++ "'" ++ x) <$> ("'" *> p many), return vs ]
- _ -> fail "outofvalid"
-
--- | Parses identifiers with help of 'parseValid'. Asks GHC for
--- 'String' from the string it deems valid.
+-- | Parses identifiers with help of 'parseValid'.
identifier :: Parser (DocH mod Identifier)
-identifier = do
- ns <- asum [ Value <$ Parsec.char 'v'
- , Type <$ Parsec.char 't'
- , pure None
- ]
- o <- idDelim
- vid <- parseValid
- e <- idDelim
- return $ DocIdentifier (Identifier ns o vid e)
- where
- idDelim = Parsec.oneOf "'`"
+identifier = DocIdentifier <$> parseValid
diff --git a/haddock-library/src/Documentation/Haddock/Parser/Identifier.hs b/haddock-library/src/Documentation/Haddock/Parser/Identifier.hs
new file mode 100644
index 00000000..7bc98b62
--- /dev/null
+++ b/haddock-library/src/Documentation/Haddock/Parser/Identifier.hs
@@ -0,0 +1,186 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE ViewPatterns #-}
+-- |
+-- Module : Documentation.Haddock.Parser.Identifier
+-- Copyright : (c) Alec Theriault 2019,
+-- License : BSD-like
+--
+-- Maintainer : haddock@projects.haskell.org
+-- Stability : experimental
+-- Portability : portable
+--
+-- Functionality for parsing identifiers and operators
+
+module Documentation.Haddock.Parser.Identifier (
+ Identifier(..),
+ parseValid,
+) where
+
+import Documentation.Haddock.Types ( Namespace(..) )
+import Documentation.Haddock.Parser.Monad
+import qualified Text.Parsec as Parsec
+import Text.Parsec.Pos ( updatePosChar )
+import Text.Parsec ( State(..)
+ , getParserState, setParserState )
+
+import Data.Text (Text)
+import qualified Data.Text as T
+
+import Data.Char (isAlpha, isAlphaNum)
+import Control.Monad (guard)
+import Data.Functor (($>))
+#if MIN_VERSION_base(4,9,0)
+import Text.Read.Lex (isSymbolChar)
+#else
+import Data.Char (GeneralCategory (..),
+ generalCategory)
+#endif
+
+import Data.Maybe
+
+-- | Identifier string surrounded with namespace, opening, and closing quotes/backticks.
+data Identifier = Identifier !Namespace !Char String !Char
+ deriving (Show, Eq)
+
+parseValid :: Parser Identifier
+parseValid = do
+ s@State{ stateInput = inp, statePos = pos } <- getParserState
+
+ case takeIdentifier inp of
+ Nothing -> Parsec.parserFail "parseValid: Failed to match a valid identifier"
+ Just (ns, op, ident, cl, inp') ->
+ let posOp = updatePosChar pos op
+ posIdent = T.foldl updatePosChar posOp ident
+ posCl = updatePosChar posIdent cl
+ s' = s{ stateInput = inp', statePos = posCl }
+ in setParserState s' $> Identifier ns op (T.unpack ident) cl
+
+
+#if !MIN_VERSION_base(4,9,0)
+-- inlined from base-4.10.0.0
+isSymbolChar :: Char -> Bool
+isSymbolChar c = not (isPuncChar c) && case generalCategory c of
+ MathSymbol -> True
+ CurrencySymbol -> True
+ ModifierSymbol -> True
+ OtherSymbol -> True
+ DashPunctuation -> True
+ OtherPunctuation -> c `notElem` "'\""
+ ConnectorPunctuation -> c /= '_'
+ _ -> False
+ where
+ -- | The @special@ character class as defined in the Haskell Report.
+ isPuncChar :: Char -> Bool
+ isPuncChar = (`elem` (",;()[]{}`" :: String))
+#endif
+
+-- | Try to parse a delimited identifier off the front of the given input.
+--
+-- This tries to match as many valid Haskell identifiers/operators as possible,
+-- to the point of sometimes accepting invalid things (ex: keywords). Some
+-- considerations:
+--
+-- - operators and identifiers can have module qualifications
+-- - operators can be wrapped in parens (for prefix)
+-- - identifiers can be wrapped in backticks (for infix)
+-- - delimiters are backticks or regular ticks
+-- - since regular ticks are also valid in identifiers, we opt for the
+-- longest successful parse
+--
+-- This function should make /O(1)/ allocations
+takeIdentifier :: Text -> Maybe (Namespace, Char, Text, Char, Text)
+takeIdentifier input = listToMaybe $ do
+
+ -- Optional namespace
+ let (ns, input') = case T.uncons input of
+ Just ('v', i) -> (Value, i)
+ Just ('t', i) -> (Type, i)
+ _ -> (None, input)
+
+ -- Opening tick
+ (op, input'') <- maybeToList (T.uncons input')
+ guard (op == '\'' || op == '`')
+
+ -- Identifier/operator
+ (ident, input''') <- wrapped input''
+
+ -- Closing tick
+ (cl, input'''') <- maybeToList (T.uncons input''')
+ guard (cl == '\'' || cl == '`')
+
+ pure (ns, op, ident, cl, input'''')
+
+ where
+
+ -- | Parse out a wrapped, possibly qualified, operator or identifier
+ wrapped t = do
+ (c, t' ) <- maybeToList (T.uncons t)
+ -- Tuples
+ case c of
+ '(' | Just (c', _) <- T.uncons t'
+ , c' == ',' || c' == ')'
+ -> do let (commas, t'') = T.span (== ',') t'
+ (')', t''') <- maybeToList (T.uncons t'')
+ pure (T.take (T.length commas + 2) t, t''')
+
+ -- Parenthesized
+ '(' -> do (n, t'' ) <- general False 0 [] t'
+ (')', t''') <- maybeToList (T.uncons t'')
+ pure (T.take (n + 2) t, t''')
+
+ -- Backticked
+ '`' -> do (n, t'' ) <- general False 0 [] t'
+ ('`', t''') <- maybeToList (T.uncons t'')
+ pure (T.take (n + 2) t, t''')
+
+ -- Unadorned
+ _ -> do (n, t'' ) <- general False 0 [] t
+ pure (T.take n t, t'')
+
+ -- | Parse out a possibly qualified operator or identifier
+ general :: Bool -- ^ refuse inputs starting with operators
+ -> Int -- ^ total characters \"consumed\" so far
+ -> [(Int, Text)] -- ^ accumulated results
+ -> Text -- ^ current input
+ -> [(Int, Text)] -- ^ total characters parsed & what remains
+ general !identOnly !i acc t
+ -- Starts with an identifier (either just an identifier, or a module qual)
+ | Just (n, rest) <- identLike t
+ = if T.null rest
+ then acc
+ else case T.head rest of
+ '`' -> (n + i, rest) : acc
+ ')' -> (n + i, rest) : acc
+ '.' -> general False (n + i + 1) acc (T.tail rest)
+ '\'' -> let (m, rest') = quotes rest
+ in general True (n + m + 1 + i) ((n + m + i, rest') : acc) (T.tail rest')
+ _ -> acc
+
+ -- An operator
+ | Just (n, rest) <- optr t
+ , not identOnly
+ = (n + i, rest) : acc
+
+ -- Anything else
+ | otherwise
+ = acc
+
+ -- | Parse an identifier off the front of the input
+ identLike t
+ | T.null t = Nothing
+ | isAlpha (T.head t) || '_' == T.head t
+ = let !(idt, rest) = T.span (\c -> isAlphaNum c || c == '_') t
+ !(octos, rest') = T.span (== '#') rest
+ in Just (T.length idt + T.length octos, rest')
+ | otherwise = Nothing
+
+ -- | Parse all but the last quote off the front of the input
+ -- PRECONDITION: T.head t == '\''
+ quotes :: Text -> (Int, Text)
+ quotes t = let !n = T.length (T.takeWhile (== '\'') t) - 1
+ in (n, T.drop n t)
+
+ -- | Parse an operator off the front of the input
+ optr t = let !(op, rest) = T.span isSymbolChar t
+ in if T.null op then Nothing else Just (T.length op, rest)
diff --git a/haddock-library/src/Documentation/Haddock/Parser/Monad.hs b/haddock-library/src/Documentation/Haddock/Parser/Monad.hs
index 8f5bd217..fa46f536 100644
--- a/haddock-library/src/Documentation/Haddock/Parser/Monad.hs
+++ b/haddock-library/src/Documentation/Haddock/Parser/Monad.hs
@@ -4,6 +4,18 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE TypeSynonymInstances #-}
+-- |
+-- Module : Documentation.Haddock.Parser.Monad
+-- Copyright : (c) Alec Theriault 2018-2019,
+-- License : BSD-like
+--
+-- Maintainer : haddock@projects.haskell.org
+-- Stability : experimental
+-- Portability : portable
+--
+-- Defines the Parsec monad over which all parsing is done and also provides
+-- more efficient versions of the usual parsec combinator functions (but
+-- specialized to 'Text').
module Documentation.Haddock.Parser.Monad where
@@ -96,7 +108,6 @@ takeWhile f = do
s' = s{ stateInput = inp', statePos = pos' }
setParserState s' $> t
-
-- | Like 'takeWhile', but fails if no characters matched.
--
-- Equivalent to @fmap T.pack . Parsec.many1@, but more efficient.
diff --git a/haddock-library/test/Documentation/Haddock/ParserSpec.hs b/haddock-library/test/Documentation/Haddock/ParserSpec.hs
index e186a5cf..bc40a0a2 100644
--- a/haddock-library/test/Documentation/Haddock/ParserSpec.hs
+++ b/haddock-library/test/Documentation/Haddock/ParserSpec.hs
@@ -112,7 +112,7 @@ spec = do
"``" `shouldParseTo` "``"
it "can parse an identifier in infix notation enclosed within backticks" $ do
- "``infix``" `shouldParseTo` "`" <> DocIdentifier "infix" <> "`"
+ "``infix``" `shouldParseTo` DocIdentifier "`infix`"
it "can parse identifiers containing a single quote" $ do
"'don't'" `shouldParseTo` DocIdentifier "don't"
@@ -138,6 +138,13 @@ spec = do
it "can parse type-namespaced identifiers" $ do
"t'foo'" `shouldParseTo` DocIdentifier "foo"
+ it "can parse parenthesized operators and backticked identifiers" $ do
+ "'(<|>)'" `shouldParseTo` DocIdentifier "(<|>)"
+ "'`elem`'" `shouldParseTo` DocIdentifier "`elem`"
+
+ it "can properly figure out the end of identifiers" $ do
+ "'DbModule'/'DbUnitId'" `shouldParseTo` DocIdentifier "DbModule" <> "/" <> DocIdentifier "DbUnitId"
+
context "when parsing operators" $ do
it "can parse an operator enclosed within single quotes" $ do
"'.='" `shouldParseTo` DocIdentifier ".="
diff --git a/haddock.cabal b/haddock.cabal
index 2b8ee6ff..91a5ea3d 100644
--- a/haddock.cabal
+++ b/haddock.cabal
@@ -89,6 +89,7 @@ executable haddock
other-modules:
Documentation.Haddock.Parser
Documentation.Haddock.Parser.Monad
+ Documentation.Haddock.Parser.Identifier
Documentation.Haddock.Types
Documentation.Haddock.Doc
Documentation.Haddock.Parser.Util
diff --git a/html-test/ref/Identifiers.html b/html-test/ref/Identifiers.html
new file mode 100644
index 00000000..1a0a18a5
--- /dev/null
+++ b/html-test/ref/Identifiers.html
@@ -0,0 +1,286 @@
+Identifiers
diff --git a/html-test/ref/Test.html b/html-test/ref/Test.html
index b76622e7..aefc4d14 100644
--- a/html-test/ref/Test.html
+++ b/html-test/ref/Test.html
@@ -2364,7 +2364,7 @@ is at the beginning of the line).f'
- but f' doesn't get link'd 'f\''
Date: Sun, 26 May 2019 15:19:27 -0400
Subject: Release haddock-2.23, haddock-library-1.8.0
Tentatively adjust bounds and changelogs for the release to be bundled
with GHC 8.8.1.
---
CHANGES.md | 4 +++-
haddock-api/haddock-api.cabal | 6 +++---
haddock-library/haddock-library.cabal | 2 +-
.../src/Documentation/Haddock/Parser/Identifier.hs | 10 +++++-----
haddock-test/haddock-test.cabal | 2 +-
haddock.cabal | 11 +++++------
6 files changed, 18 insertions(+), 17 deletions(-)
(limited to 'haddock-library/src')
diff --git a/CHANGES.md b/CHANGES.md
index a6d96fed..88656da4 100644
--- a/CHANGES.md
+++ b/CHANGES.md
@@ -1,4 +1,4 @@
-## Changes in TBA
+## Changes in 2.23.0
* "Linuwial" is the new default theme (#721, #782, #949)
@@ -29,6 +29,8 @@
* Many fixes to the LaTeX backend, mostly focused on not crashing
as well as generating LaTeX source that compiles
+ * More flexible parsing of the module header
+
## Changes in version 2.22.0
* Make `--package-version` optional for `--hoogle` (#899)
diff --git a/haddock-api/haddock-api.cabal b/haddock-api/haddock-api.cabal
index c427e752..9a120f5d 100644
--- a/haddock-api/haddock-api.cabal
+++ b/haddock-api/haddock-api.cabal
@@ -1,6 +1,6 @@
cabal-version: 2.0
name: haddock-api
-version: 2.22.0
+version: 2.23.0
synopsis: A documentation-generation tool for Haskell libraries
description: Haddock is a documentation-generation tool for Haskell
libraries
@@ -42,7 +42,7 @@ library
default-language: Haskell2010
-- this package typically supports only single major versions
- build-depends: base ^>= 4.12.0
+ build-depends: base ^>= 4.13.0
, ghc ^>= 8.8
, ghc-paths ^>= 0.1.0.9
, haddock-library ^>= 1.8.0
@@ -65,7 +65,7 @@ library
ghc-options: -funbox-strict-fields -Wall -fwarn-tabs -O2
ghc-options: -Wall
if impl(ghc >= 8.0)
- ghc-options: -Wcompat -Wnoncanonical-monad-instances -Wnoncanonical-monadfail-instances
+ ghc-options: -Wcompat -Wnoncanonical-monad-instances
exposed-modules:
Documentation.Haddock
diff --git a/haddock-library/haddock-library.cabal b/haddock-library/haddock-library.cabal
index 5c744082..99773475 100644
--- a/haddock-library/haddock-library.cabal
+++ b/haddock-library/haddock-library.cabal
@@ -33,7 +33,7 @@ common lib-defaults
ghc-options: -funbox-strict-fields -Wall -fwarn-tabs
if impl(ghc >= 8.0)
- ghc-options: -Wcompat -Wnoncanonical-monad-instances -Wnoncanonical-monadfail-instances
+ ghc-options: -Wcompat -Wnoncanonical-monad-instances
library
import: lib-defaults
diff --git a/haddock-library/src/Documentation/Haddock/Parser/Identifier.hs b/haddock-library/src/Documentation/Haddock/Parser/Identifier.hs
index 7bc98b62..a83e5abf 100644
--- a/haddock-library/src/Documentation/Haddock/Parser/Identifier.hs
+++ b/haddock-library/src/Documentation/Haddock/Parser/Identifier.hs
@@ -109,7 +109,7 @@ takeIdentifier input = listToMaybe $ do
(cl, input'''') <- maybeToList (T.uncons input''')
guard (cl == '\'' || cl == '`')
- pure (ns, op, ident, cl, input'''')
+ return (ns, op, ident, cl, input'''')
where
@@ -122,21 +122,21 @@ takeIdentifier input = listToMaybe $ do
, c' == ',' || c' == ')'
-> do let (commas, t'') = T.span (== ',') t'
(')', t''') <- maybeToList (T.uncons t'')
- pure (T.take (T.length commas + 2) t, t''')
+ return (T.take (T.length commas + 2) t, t''')
-- Parenthesized
'(' -> do (n, t'' ) <- general False 0 [] t'
(')', t''') <- maybeToList (T.uncons t'')
- pure (T.take (n + 2) t, t''')
+ return (T.take (n + 2) t, t''')
-- Backticked
'`' -> do (n, t'' ) <- general False 0 [] t'
('`', t''') <- maybeToList (T.uncons t'')
- pure (T.take (n + 2) t, t''')
+ return (T.take (n + 2) t, t''')
-- Unadorned
_ -> do (n, t'' ) <- general False 0 [] t
- pure (T.take n t, t'')
+ return (T.take n t, t'')
-- | Parse out a possibly qualified operator or identifier
general :: Bool -- ^ refuse inputs starting with operators
diff --git a/haddock-test/haddock-test.cabal b/haddock-test/haddock-test.cabal
index 23b5953c..ed174e4f 100644
--- a/haddock-test/haddock-test.cabal
+++ b/haddock-test/haddock-test.cabal
@@ -16,7 +16,7 @@ library
default-language: Haskell2010
ghc-options: -Wall
hs-source-dirs: src
- build-depends: base >= 4.3 && < 4.13, bytestring, directory, process, filepath, Cabal, xml, xhtml
+ build-depends: base >= 4.3 && < 4.14, bytestring, directory, process, filepath, Cabal, xml, xhtml
exposed-modules:
Test.Haddock
diff --git a/haddock.cabal b/haddock.cabal
index 078955fb..563955b9 100644
--- a/haddock.cabal
+++ b/haddock.cabal
@@ -1,6 +1,6 @@
cabal-version: 2.0
name: haddock
-version: 2.22.0
+version: 2.23.0
synopsis: A documentation-generation tool for Haskell libraries
description:
This is Haddock, a tool for automatically generating documentation
@@ -23,7 +23,7 @@ description:
without any documentation annotations, Haddock can generate useful documentation
from your source code.
.
- <>
+ <>
license: BSD3
license-file: LICENSE
author: Simon Marlow, David Waern
@@ -33,7 +33,7 @@ bug-reports: https://github.com/haskell/haddock/issues
copyright: (c) Simon Marlow, David Waern
category: Documentation
build-type: Simple
-tested-with: GHC==8.6.*
+tested-with: GHC==8.8.*
extra-source-files:
CHANGES.md
@@ -64,8 +64,7 @@ executable haddock
-- haddock typically only supports a single GHC major version
build-depends:
- -- FIXME: drop 4.12.0.0 once GHC HEAD updates to 4.13.0.0
- base ^>= 4.12.0.0 || ^>= 4.13.0.0
+ base ^>= 4.13.0.0
if flag(in-ghc-tree)
hs-source-dirs: haddock-api/src, haddock-library/src
@@ -141,7 +140,7 @@ executable haddock
else
-- in order for haddock's advertised version number to have proper meaning,
-- we pin down to a single haddock-api version.
- build-depends: haddock-api == 2.22.0
+ build-depends: haddock-api == 2.23.0
test-suite html-test
type: exitcode-stdio-1.0
--
cgit v1.2.3
From ee05ff1ecde866e31f72e3fa4f773dca98944dc3 Mon Sep 17 00:00:00 2001
From: Herbert Valerio Riedel
Date: Sun, 8 Dec 2019 11:47:58 +0100
Subject: Document error-prone conditional definition of instances
This can easily trip up people if one isn't aware of it. Usually it's
better to avoid this kind of conditionality especially for typeclasses
for which there's an compat-package as conditional instances like
these tend to fragment the ecosystem into those packages that go the
extra mile to provide backward compat via those compat-packages and
those that fail to do so.
---
haddock-library/src/Documentation/Haddock/Types.hs | 6 ++++++
1 file changed, 6 insertions(+)
(limited to 'haddock-library/src')
diff --git a/haddock-library/src/Documentation/Haddock/Types.hs b/haddock-library/src/Documentation/Haddock/Types.hs
index ba2f873c..4cf61fee 100644
--- a/haddock-library/src/Documentation/Haddock/Types.hs
+++ b/haddock-library/src/Documentation/Haddock/Types.hs
@@ -44,14 +44,17 @@ data MetaDoc mod id =
} deriving (Eq, Show, Functor, Foldable, Traversable)
#if MIN_VERSION_base(4,8,0)
+-- | __NOTE__: Only defined for @base >= 4.8.0@
instance Bifunctor MetaDoc where
bimap f g (MetaDoc m d) = MetaDoc m (bimap f g d)
#endif
#if MIN_VERSION_base(4,10,0)
+-- | __NOTE__: Only defined for @base >= 4.10.0@
instance Bifoldable MetaDoc where
bifoldr f g z d = bifoldr f g z (_doc d)
+-- | __NOTE__: Only defined for @base >= 4.10.0@
instance Bitraversable MetaDoc where
bitraverse f g (MetaDoc m d) = MetaDoc m <$> bitraverse f g d
#endif
@@ -131,6 +134,7 @@ data DocH mod id
deriving (Eq, Show, Functor, Foldable, Traversable)
#if MIN_VERSION_base(4,8,0)
+-- | __NOTE__: Only defined for @base >= 4.8.0@
instance Bifunctor DocH where
bimap _ _ DocEmpty = DocEmpty
bimap f g (DocAppend docA docB) = DocAppend (bimap f g docA) (bimap f g docB)
@@ -159,6 +163,7 @@ instance Bifunctor DocH where
#endif
#if MIN_VERSION_base(4,10,0)
+-- | __NOTE__: Only defined for @base >= 4.10.0@
instance Bifoldable DocH where
bifoldr f g z (DocAppend docA docB) = bifoldr f g (bifoldr f g z docA) docB
bifoldr f g z (DocParagraph doc) = bifoldr f g z doc
@@ -176,6 +181,7 @@ instance Bifoldable DocH where
bifoldr f g z (DocTable (Table header body)) = foldr (\r acc -> foldr (flip (bifoldr f g)) acc r) (foldr (\r acc -> foldr (flip (bifoldr f g)) acc r) z body) header
bifoldr _ _ z _ = z
+-- | __NOTE__: Only defined for @base >= 4.10.0@
instance Bitraversable DocH where
bitraverse _ _ DocEmpty = pure DocEmpty
bitraverse f g (DocAppend docA docB) = DocAppend <$> bitraverse f g docA <*> bitraverse f g docB
--
cgit v1.2.3
From be8b02c4e3cffe7d45b3dad0a0f071d35a274d65 Mon Sep 17 00:00:00 2001
From: Herbert Valerio Riedel
Date: Sun, 8 Dec 2019 11:53:39 +0100
Subject: Fix build-failure regression for base < 4.7
The `$>` operator definition is available only since base-4.7 which
unfortunately wasn't caught before release to Hackage (but has been
fixed up by a metadata-revision)
This commit introduces a `CompatPrelude` module which allows to reduce
the amount of CPP by ousting it to a central location, i.e. the new
`CompatPrelude` module. This pattern also tends to reduce the tricks
needed to silence unused import warnings.
Addresses #1119
---
haddock-library/CHANGES.md | 4 ++
haddock-library/haddock-library.cabal | 3 +-
haddock-library/src/CompatPrelude.hs | 52 ++++++++++++++++++++++
.../src/Documentation/Haddock/Parser.hs | 1 -
.../src/Documentation/Haddock/Parser/Identifier.hs | 28 +-----------
.../src/Documentation/Haddock/Parser/Monad.hs | 3 +-
6 files changed, 61 insertions(+), 30 deletions(-)
create mode 100644 haddock-library/src/CompatPrelude.hs
(limited to 'haddock-library/src')
diff --git a/haddock-library/CHANGES.md b/haddock-library/CHANGES.md
index 265579ca..d112db45 100644
--- a/haddock-library/CHANGES.md
+++ b/haddock-library/CHANGES.md
@@ -1,3 +1,7 @@
+## Changes in version 1.8.0.1
+
+ * Fix build-time regression for `base < 4.7` (#1119)
+
## Changes in version 1.8.0
* Support inline markup in markdown-style links (#875)
diff --git a/haddock-library/haddock-library.cabal b/haddock-library/haddock-library.cabal
index fe6aeede..7f91fd19 100644
--- a/haddock-library/haddock-library.cabal
+++ b/haddock-library/haddock-library.cabal
@@ -1,6 +1,6 @@
cabal-version: 2.2
name: haddock-library
-version: 1.8.0
+version: 1.8.0.1
synopsis: Library exposing some functionality of Haddock.
description: Haddock is a documentation-generation tool for Haskell
@@ -49,6 +49,7 @@ library
Documentation.Haddock.Types
other-modules:
+ CompatPrelude
Documentation.Haddock.Parser.Util
Documentation.Haddock.Parser.Monad
Documentation.Haddock.Parser.Identifier
diff --git a/haddock-library/src/CompatPrelude.hs b/haddock-library/src/CompatPrelude.hs
new file mode 100644
index 00000000..60fa94d9
--- /dev/null
+++ b/haddock-library/src/CompatPrelude.hs
@@ -0,0 +1,52 @@
+{-# LANGUAGE CPP #-}
+
+#if !MIN_VERSION_base(4,5,0)
+# error This module doesn't provide compat-shims for versions prior to base-4.5
+#endif
+
+-- | Bridge impedance mismatch of different @base@ versions back till @base-4.5@ (GHC 7.4.2)
+module CompatPrelude
+ ( ($>)
+ , isSymbolChar
+ ) where
+
+#if MIN_VERSION_base(4,7,0)
+import Data.Functor ( ($>) )
+#else
+import Data.Functor ( (<$) )
+#endif
+
+#if MIN_VERSION_base(4,9,0)
+import Text.Read.Lex (isSymbolChar)
+#else
+import Data.Char (GeneralCategory(..), generalCategory)
+#endif
+
+
+#if !MIN_VERSION_base(4,7,0)
+infixl 4 $>
+
+-- | Flipped version of '<$'.
+--
+-- @since 4.7.0.0
+($>) :: Functor f => f a -> b -> f b
+($>) = flip (<$)
+#endif
+
+#if !MIN_VERSION_base(4,9,0)
+-- inlined from base-4.10.0.0
+isSymbolChar :: Char -> Bool
+isSymbolChar c = not (isPuncChar c) && case generalCategory c of
+ MathSymbol -> True
+ CurrencySymbol -> True
+ ModifierSymbol -> True
+ OtherSymbol -> True
+ DashPunctuation -> True
+ OtherPunctuation -> c `notElem` "'\""
+ ConnectorPunctuation -> c /= '_'
+ _ -> False
+ where
+ -- | The @special@ character class as defined in the Haskell Report.
+ isPuncChar :: Char -> Bool
+ isPuncChar = (`elem` (",;()[]{}`" :: String))
+#endif
diff --git a/haddock-library/src/Documentation/Haddock/Parser.hs b/haddock-library/src/Documentation/Haddock/Parser.hs
index 36c8bb5b..028422a7 100644
--- a/haddock-library/src/Documentation/Haddock/Parser.hs
+++ b/haddock-library/src/Documentation/Haddock/Parser.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
-- |
diff --git a/haddock-library/src/Documentation/Haddock/Parser/Identifier.hs b/haddock-library/src/Documentation/Haddock/Parser/Identifier.hs
index a83e5abf..b8afb951 100644
--- a/haddock-library/src/Documentation/Haddock/Parser/Identifier.hs
+++ b/haddock-library/src/Documentation/Haddock/Parser/Identifier.hs
@@ -1,4 +1,3 @@
-{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE ViewPatterns #-}
-- |
@@ -29,15 +28,8 @@ import qualified Data.Text as T
import Data.Char (isAlpha, isAlphaNum)
import Control.Monad (guard)
-import Data.Functor (($>))
-#if MIN_VERSION_base(4,9,0)
-import Text.Read.Lex (isSymbolChar)
-#else
-import Data.Char (GeneralCategory (..),
- generalCategory)
-#endif
-
import Data.Maybe
+import CompatPrelude
-- | Identifier string surrounded with namespace, opening, and closing quotes/backticks.
data Identifier = Identifier !Namespace !Char String !Char
@@ -57,24 +49,6 @@ parseValid = do
in setParserState s' $> Identifier ns op (T.unpack ident) cl
-#if !MIN_VERSION_base(4,9,0)
--- inlined from base-4.10.0.0
-isSymbolChar :: Char -> Bool
-isSymbolChar c = not (isPuncChar c) && case generalCategory c of
- MathSymbol -> True
- CurrencySymbol -> True
- ModifierSymbol -> True
- OtherSymbol -> True
- DashPunctuation -> True
- OtherPunctuation -> c `notElem` "'\""
- ConnectorPunctuation -> c /= '_'
- _ -> False
- where
- -- | The @special@ character class as defined in the Haskell Report.
- isPuncChar :: Char -> Bool
- isPuncChar = (`elem` (",;()[]{}`" :: String))
-#endif
-
-- | Try to parse a delimited identifier off the front of the given input.
--
-- This tries to match as many valid Haskell identifiers/operators as possible,
diff --git a/haddock-library/src/Documentation/Haddock/Parser/Monad.hs b/haddock-library/src/Documentation/Haddock/Parser/Monad.hs
index fa46f536..7c73a168 100644
--- a/haddock-library/src/Documentation/Haddock/Parser/Monad.hs
+++ b/haddock-library/src/Documentation/Haddock/Parser/Monad.hs
@@ -29,7 +29,6 @@ import qualified Data.Text as T
import Data.Text ( Text )
import Control.Monad ( mfilter )
-import Data.Functor ( ($>) )
import Data.String ( IsString(..) )
import Data.Bits ( Bits(..) )
import Data.Char ( ord )
@@ -37,7 +36,9 @@ import Data.List ( foldl' )
import Control.Applicative as App
import Documentation.Haddock.Types ( Version )
+
import Prelude hiding (takeWhile)
+import CompatPrelude
-- | The only bit of information we really care about truding along with us
-- through parsing is the version attached to a @\@since@ annotation - if
--
cgit v1.2.3
From dec888641006eb685a642ec489b198c61a5736dc Mon Sep 17 00:00:00 2001
From: Alina Banerjee
Date: Thu, 1 Aug 2019 16:01:39 -0500
Subject: Update parsing to strip whitespace from table cells (#1074)
* Update parsing to strip leading & trailing whitespace from table cells
* Update fixture data to disallow whitespaces at both ends in table cells
* Add test case for whitespaces stripped from both ends of table cells
* Update table reference test data for html tests
---
.../examples/table-cell-strip-whitespaces.input | 5 ++
.../examples/table-cell-strip-whitespaces.parsed | 29 +++++++
.../fixtures/examples/table-simple.parsed | 28 ++-----
haddock-library/fixtures/examples/table1.parsed | 45 ++++------
haddock-library/fixtures/examples/table2.parsed | 20 ++---
haddock-library/fixtures/examples/table3.parsed | 22 ++---
haddock-library/fixtures/examples/table4.parsed | 10 +--
haddock-library/fixtures/examples/table5.parsed | 27 +++---
.../src/Documentation/Haddock/Parser.hs | 14 ++--
html-test/ref/Table.html | 96 +++++++++++-----------
10 files changed, 150 insertions(+), 146 deletions(-)
create mode 100644 haddock-library/fixtures/examples/table-cell-strip-whitespaces.input
create mode 100644 haddock-library/fixtures/examples/table-cell-strip-whitespaces.parsed
(limited to 'haddock-library/src')
diff --git a/haddock-library/fixtures/examples/table-cell-strip-whitespaces.input b/haddock-library/fixtures/examples/table-cell-strip-whitespaces.input
new file mode 100644
index 00000000..f5e3756d
--- /dev/null
+++ b/haddock-library/fixtures/examples/table-cell-strip-whitespaces.input
@@ -0,0 +1,5 @@
++------+--------------+-------------------------------------------------+
+| C1 | C2 | C3 |
++======+==============+=================================================+
+| row | 'test' | 'test table cell with .. whitepspace ' |
++------+--------------+-------------------------------------------------+
diff --git a/haddock-library/fixtures/examples/table-cell-strip-whitespaces.parsed b/haddock-library/fixtures/examples/table-cell-strip-whitespaces.parsed
new file mode 100644
index 00000000..19002369
--- /dev/null
+++ b/haddock-library/fixtures/examples/table-cell-strip-whitespaces.parsed
@@ -0,0 +1,29 @@
+DocTable
+ Table
+ {tableBodyRows = [TableRow
+ [TableCell
+ {tableCellColspan = 1,
+ tableCellContents = DocString "row",
+ tableCellRowspan = 1},
+ TableCell
+ {tableCellColspan = 1,
+ tableCellContents = DocIdentifier "test",
+ tableCellRowspan = 1},
+ TableCell
+ {tableCellColspan = 1,
+ tableCellContents = DocString
+ "'test table cell with .. whitepspace '",
+ tableCellRowspan = 1}]],
+ tableHeaderRows = [TableRow
+ [TableCell
+ {tableCellColspan = 1,
+ tableCellContents = DocString "C1",
+ tableCellRowspan = 1},
+ TableCell
+ {tableCellColspan = 1,
+ tableCellContents = DocString "C2",
+ tableCellRowspan = 1},
+ TableCell
+ {tableCellColspan = 1,
+ tableCellContents = DocString "C3",
+ tableCellRowspan = 1}]]}
diff --git a/haddock-library/fixtures/examples/table-simple.parsed b/haddock-library/fixtures/examples/table-simple.parsed
index b5e62453..d027c75d 100644
--- a/haddock-library/fixtures/examples/table-simple.parsed
+++ b/haddock-library/fixtures/examples/table-simple.parsed
@@ -3,50 +3,40 @@ DocTable
{tableBodyRows = [TableRow
[TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " 200 ",
+ tableCellContents = DocString "200",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocAppend
- (DocString " ")
- (DocAppend
- (DocMonospaced (DocString "OK"))
- (DocString " ")),
+ tableCellContents = DocMonospaced (DocString "OK"),
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString
- " operation successful ",
+ tableCellContents = DocString "operation successful",
tableCellRowspan = 1}],
TableRow
[TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " 204 ",
+ tableCellContents = DocString "204",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocAppend
- (DocString " ")
- (DocAppend
- (DocMonospaced (DocString "No Content"))
- (DocString " ")),
+ tableCellContents = DocMonospaced (DocString "No Content"),
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
tableCellContents = DocString
- " operation successful, no body returned ",
+ "operation successful, no body returned",
tableCellRowspan = 1}]],
tableHeaderRows = [TableRow
[TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " code ",
+ tableCellContents = DocString "code",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " message ",
+ tableCellContents = DocString "message",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString
- " description ",
+ tableCellContents = DocString "description",
tableCellRowspan = 1}]]}
diff --git a/haddock-library/fixtures/examples/table1.parsed b/haddock-library/fixtures/examples/table1.parsed
index 2fa58fd8..8b8908f4 100644
--- a/haddock-library/fixtures/examples/table1.parsed
+++ b/haddock-library/fixtures/examples/table1.parsed
@@ -3,79 +3,66 @@ DocTable
{tableBodyRows = [TableRow
[TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " body row 1, column 1 ",
+ tableCellContents = DocString "body row 1, column 1",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " column 2 ",
+ tableCellContents = DocString "column 2",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " column 3 ",
+ tableCellContents = DocString "column 3",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " column 4 ",
+ tableCellContents = DocString "column 4",
tableCellRowspan = 1}],
TableRow
[TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " body row 2 ",
+ tableCellContents = DocString "body row 2",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 3,
- tableCellContents = DocString " Cells may span columns. ",
+ tableCellContents = DocString "Cells may span columns.",
tableCellRowspan = 1}],
TableRow
[TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " body row 3 ",
+ tableCellContents = DocString "body row 3",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
tableCellContents = DocString
- (concat
- [" Cells may \n",
- " span rows. \n",
- " "]),
+ (concat ["Cells may\n", "span rows.\n"]),
tableCellRowspan = 2},
TableCell
{tableCellColspan = 2,
- tableCellContents = DocAppend
- (DocString " ")
- (DocAppend
- (DocMathDisplay
- (concat
- [" \n",
- " f(n) = \\sum_{i=1} \n",
- " "]))
- (DocString " ")),
+ tableCellContents = DocMathDisplay
+ (concat ["\n", "f(n) = \\sum_{i=1}\n"]),
tableCellRowspan = 2}],
TableRow
[TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " body row 4 ",
+ tableCellContents = DocString "body row 4",
tableCellRowspan = 1}]],
tableHeaderRows = [TableRow
[TableCell
{tableCellColspan = 1,
tableCellContents = DocString
(concat
- [" Header row, column 1 \n",
- " (header rows optional) "]),
+ ["Header row, column 1\n",
+ "(header rows optional)"]),
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString
- (concat [" Header 2 \n", " "]),
+ tableCellContents = DocString "Header 2\n",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString
- (concat [" Header 3 \n", " "]),
+ tableCellContents = DocString "Header 3\n",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString
- (concat [" Header 4 \n", " "]),
+ tableCellContents = DocString "Header 4\n",
tableCellRowspan = 1}]]}
diff --git a/haddock-library/fixtures/examples/table2.parsed b/haddock-library/fixtures/examples/table2.parsed
index e3dbf0b4..44cc813b 100644
--- a/haddock-library/fixtures/examples/table2.parsed
+++ b/haddock-library/fixtures/examples/table2.parsed
@@ -3,44 +3,44 @@ DocTable
{tableBodyRows = [TableRow
[TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " row 1, col 1 ",
+ tableCellContents = DocString "row 1, col 1",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " column 2 ",
+ tableCellContents = DocString "column 2",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " column 3 ",
+ tableCellContents = DocString "column 3",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " column 4 ",
+ tableCellContents = DocString "column 4",
tableCellRowspan = 1}],
TableRow
[TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " row 2 ",
+ tableCellContents = DocString "row 2",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 3,
- tableCellContents = DocString " ",
+ tableCellContents = DocEmpty,
tableCellRowspan = 1}],
TableRow
[TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " row 3 ",
+ tableCellContents = DocString "row 3",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " ",
+ tableCellContents = DocEmpty,
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " ",
+ tableCellContents = DocEmpty,
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " ",
+ tableCellContents = DocEmpty,
tableCellRowspan = 1}]],
tableHeaderRows = []}
diff --git a/haddock-library/fixtures/examples/table3.parsed b/haddock-library/fixtures/examples/table3.parsed
index cabff9cb..c978b50f 100644
--- a/haddock-library/fixtures/examples/table3.parsed
+++ b/haddock-library/fixtures/examples/table3.parsed
@@ -3,48 +3,48 @@ DocTable
{tableBodyRows = [TableRow
[TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " row 1, col 1 ",
+ tableCellContents = DocString "row 1, col 1",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " column 2 ",
+ tableCellContents = DocString "column 2",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " column 3 ",
+ tableCellContents = DocString "column 3",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " column 4 ",
+ tableCellContents = DocString "column 4",
tableCellRowspan = 1}],
TableRow
[TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " row 2 ",
+ tableCellContents = DocString "row 2",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 2,
- tableCellContents = DocString " Use the command ``ls ",
+ tableCellContents = DocString "Use the command ``ls",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " more``. ",
+ tableCellContents = DocString "more``.",
tableCellRowspan = 1}],
TableRow
[TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " row 3 ",
+ tableCellContents = DocString "row 3",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " ",
+ tableCellContents = DocEmpty,
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " ",
+ tableCellContents = DocEmpty,
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " ",
+ tableCellContents = DocEmpty,
tableCellRowspan = 1}]],
tableHeaderRows = []}
diff --git a/haddock-library/fixtures/examples/table4.parsed b/haddock-library/fixtures/examples/table4.parsed
index cfdd6f0f..c4dabb0d 100644
--- a/haddock-library/fixtures/examples/table4.parsed
+++ b/haddock-library/fixtures/examples/table4.parsed
@@ -8,10 +8,10 @@ DocAppend
{tableCellColspan = 1,
tableCellContents = DocString
(concat
- [" outer \n",
- " \n",
- "-------+ \n",
- " inner | "]),
+ ["outer\n",
+ "\n",
+ "-------+\n",
+ "inner |"]),
tableCellRowspan = 1}]],
tableHeaderRows = []})
(DocAppend
@@ -21,6 +21,6 @@ DocAppend
{tableBodyRows = [TableRow
[TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " inner ",
+ tableCellContents = DocString "inner",
tableCellRowspan = 1}]],
tableHeaderRows = []})))
diff --git a/haddock-library/fixtures/examples/table5.parsed b/haddock-library/fixtures/examples/table5.parsed
index 9a547ad3..f9a387bb 100644
--- a/haddock-library/fixtures/examples/table5.parsed
+++ b/haddock-library/fixtures/examples/table5.parsed
@@ -4,50 +4,43 @@ DocTable
[TableCell
{tableCellColspan = 1,
tableCellContents = DocString
- (concat
- [" row 2 \n",
- " \n",
- " \n",
- " row 3 "]),
+ (concat ["row 2\n", "\n", "\n", "row 3"]),
tableCellRowspan = 2},
TableCell
{tableCellColspan = 3,
tableCellContents = DocAppend
- (DocString " Use the command ")
+ (DocString "Use the command ")
(DocAppend
(DocMonospaced (DocString "ls | more"))
- (DocString
- (concat
- [". \n",
- " "]))),
+ (DocString ".\n")),
tableCellRowspan = 1}],
TableRow
[TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " ",
+ tableCellContents = DocEmpty,
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " ",
+ tableCellContents = DocEmpty,
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " ",
+ tableCellContents = DocEmpty,
tableCellRowspan = 1}]],
tableHeaderRows = [TableRow
[TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " row 1, col 1 ",
+ tableCellContents = DocString "row 1, col 1",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " column 2 ",
+ tableCellContents = DocString "column 2",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " column 3 ",
+ tableCellContents = DocString "column 3",
tableCellRowspan = 1},
TableCell
{tableCellColspan = 1,
- tableCellContents = DocString " column 4 ",
+ tableCellContents = DocString "column 4",
tableCellRowspan = 1}]]}
diff --git a/haddock-library/src/Documentation/Haddock/Parser.hs b/haddock-library/src/Documentation/Haddock/Parser.hs
index 028422a7..17240792 100644
--- a/haddock-library/src/Documentation/Haddock/Parser.hs
+++ b/haddock-library/src/Documentation/Haddock/Parser.hs
@@ -267,7 +267,7 @@ picture = DocPic . makeLabeled Picture
-- >>> parseString "\\(\\int_{-\\infty}^{\\infty} e^{-x^2/2} = \\sqrt{2\\pi}\\)"
-- DocMathInline "\\int_{-\\infty}^{\\infty} e^{-x^2/2} = \\sqrt{2\\pi}"
mathInline :: Parser (DocH mod a)
-mathInline = DocMathInline . T.unpack
+mathInline = DocMathInline . T.unpack
<$> disallowNewline ("\\(" *> takeUntil "\\)")
-- | Display math parser, surrounded by \\[ and \\].
@@ -492,7 +492,7 @@ tableStepFour rs hdrIndex cells = case hdrIndex of
-- extract cell contents given boundaries
extract :: Int -> Int -> Int -> Int -> Text
extract x y x2 y2 = T.intercalate "\n"
- [ T.take (x2 - x + 1) $ T.drop x $ rs !! y'
+ [ T.stripEnd $ T.stripStart $ T.take (x2 - x + 1) $ T.drop x $ rs !! y'
| y' <- [y .. y2]
]
@@ -579,7 +579,7 @@ definitionList indent = DocDefList <$> p
Right i -> (label, contents) : i
-- | Drops all trailing newlines.
-dropNLs :: Text -> Text
+dropNLs :: Text -> Text
dropNLs = T.dropWhileEnd (== '\n')
-- | Main worker for 'innerList' and 'definitionList'.
@@ -653,7 +653,7 @@ takeNonEmptyLine = do
--
-- More precisely: skips all whitespace-only lines and returns indentation
-- (horizontal space, might be empty) of that non-empty line.
-takeIndent :: Parser Text
+takeIndent :: Parser Text
takeIndent = do
indent <- takeHorizontalSpace
choice' [ "\n" *> takeIndent
@@ -711,14 +711,14 @@ examples = DocExamples <$> (many (try (skipHorizontalSpace *> "\n")) *> go)
substituteBlankLine "" = ""
substituteBlankLine xs = xs
-nonEmptyLine :: Parser Text
+nonEmptyLine :: Parser Text
nonEmptyLine = try (mfilter (T.any (not . isSpace)) takeLine)
takeLine :: Parser Text
takeLine = try (takeWhile (/= '\n') <* endOfLine)
endOfLine :: Parser ()
-endOfLine = void "\n" <|> Parsec.eof
+endOfLine = void "\n" <|> Parsec.eof
-- | Property parser.
--
@@ -800,7 +800,7 @@ autoUrl :: Parser (DocH mod a)
autoUrl = mkLink <$> url
where
url = mappend <$> choice' [ "http://", "https://", "ftp://"] <*> takeWhile1 (not . isSpace)
-
+
mkLink :: Text -> DocH mod a
mkLink s = case T.unsnoc s of
Just (xs,x) | x `elem` (",.!?" :: String) -> DocHyperlink (mkHyperlink xs) `docAppend` DocString [x]
diff --git a/html-test/ref/Table.html b/html-test/ref/Table.html
index 8a299018..26b0254d 100644
--- a/html-test/ref/Table.html
+++ b/html-test/ref/Table.html
@@ -87,33 +87,33 @@
>
Date: Fri, 27 Mar 2020 20:16:51 -0400
Subject: Fix crash in `haddock-library` on unicode space
Our quickcheck tests for `haddock-library` stumbled across an edge case
input that was causing Haddock to crash: it was a unicode space
character.
The root cause of the crash is that we were implicitly assuming that
if a space character was not " \t\f\v\r", it would have to be "\n".
We fix this by instead defining horizontal space as: any space character
that is not '\n'.
Fixes #1142
---
haddock-library/src/Documentation/Haddock/Parser/Util.hs | 14 +++++++-------
haddock-library/test/Documentation/Haddock/ParserSpec.hs | 8 +++++++-
2 files changed, 14 insertions(+), 8 deletions(-)
(limited to 'haddock-library/src')
diff --git a/haddock-library/src/Documentation/Haddock/Parser/Util.hs b/haddock-library/src/Documentation/Haddock/Parser/Util.hs
index 98570c22..eef744d8 100644
--- a/haddock-library/src/Documentation/Haddock/Parser/Util.hs
+++ b/haddock-library/src/Documentation/Haddock/Parser/Util.hs
@@ -31,16 +31,16 @@ import Prelude hiding (takeWhile)
import Data.Char (isSpace)
-- | Characters that count as horizontal space
-horizontalSpace :: [Char]
-horizontalSpace = " \t\f\v\r"
+horizontalSpace :: Char -> Bool
+horizontalSpace c = isSpace c && c /= '\n'
-- | Skip and ignore leading horizontal space
skipHorizontalSpace :: Parser ()
-skipHorizontalSpace = Parsec.skipMany (Parsec.oneOf horizontalSpace)
+skipHorizontalSpace = Parsec.skipMany (Parsec.satisfy horizontalSpace)
-- | Take leading horizontal space
-takeHorizontalSpace :: Parser Text
-takeHorizontalSpace = takeWhile (`elem` horizontalSpace)
+takeHorizontalSpace :: Parser Text
+takeHorizontalSpace = takeWhile horizontalSpace
makeLabeled :: (String -> Maybe String -> a) -> Text -> a
makeLabeled f input = case T.break isSpace $ removeEscapes $ T.strip input of
@@ -60,10 +60,10 @@ removeEscapes = T.unfoldr go
-- | Consume characters from the input up to and including the given pattern.
-- Return everything consumed except for the end pattern itself.
-takeUntil :: Text -> Parser Text
+takeUntil :: Text -> Parser Text
takeUntil end_ = T.dropEnd (T.length end_) <$> requireEnd (scan p (False, end)) >>= gotSome
where
- end = T.unpack end_
+ end = T.unpack end_
p :: (Bool, String) -> Char -> Maybe (Bool, String)
p acc c = case acc of
diff --git a/haddock-library/test/Documentation/Haddock/ParserSpec.hs b/haddock-library/test/Documentation/Haddock/ParserSpec.hs
index bc40a0a2..8b59b560 100644
--- a/haddock-library/test/Documentation/Haddock/ParserSpec.hs
+++ b/haddock-library/test/Documentation/Haddock/ParserSpec.hs
@@ -3,6 +3,7 @@
module Documentation.Haddock.ParserSpec (main, spec) where
+import Data.Char (isSpace)
import Data.String
import qualified Documentation.Haddock.Parser as Parse
import Documentation.Haddock.Types
@@ -442,6 +443,10 @@ spec = do
property $ \xs ->
(length . show . parseParas) xs `shouldSatisfy` (> 0)
+ -- See
+ it "doesn't crash on unicode whitespace" $ do
+ "\8197" `shouldParseTo` DocEmpty
+
context "when parsing @since" $ do
it "adds specified version to the result" $ do
parseParas "@since 0.5.0" `shouldBe`
@@ -470,7 +475,8 @@ spec = do
context "when parsing text paragraphs" $ do
- let filterSpecial = filter (`notElem` (".(=#-[*`\v\f\n\t\r\\\"'_/@<> " :: String))
+ let isSpecial c = isSpace c || c `elem` (".(=#-[*`\\\"'_/@<>" :: String)
+ filterSpecial = filter (not . isSpecial)
it "parses an empty paragraph" $ do
"" `shouldParseTo` DocEmpty
--
cgit v1.2.3
From d8bedeb98a84db0d51c49d41c632d9d4846d1bbe Mon Sep 17 00:00:00 2001
From: Alec Theriault
Date: Sat, 28 Mar 2020 13:17:35 -0400
Subject: `haddock-library` document header level
Document the fact the header level is going to always be between 1 and 6
inclusive. Along the way, I also optimized the parsing code a bit.
---
haddock-library/src/Documentation/Haddock/Parser.hs | 8 ++++----
haddock-library/src/Documentation/Haddock/Types.hs | 2 +-
2 files changed, 5 insertions(+), 5 deletions(-)
(limited to 'haddock-library/src')
diff --git a/haddock-library/src/Documentation/Haddock/Parser.hs b/haddock-library/src/Documentation/Haddock/Parser.hs
index 17240792..149ff93d 100644
--- a/haddock-library/src/Documentation/Haddock/Parser.hs
+++ b/haddock-library/src/Documentation/Haddock/Parser.hs
@@ -512,11 +512,11 @@ since = ("@since " *> version <* skipHorizontalSpace <* endOfLine) >>= setSince
header :: Parser (DocH mod Identifier)
header = do
let psers = map (string . flip T.replicate "=") [6, 5 .. 1]
- pser = choice' psers
- delim <- T.unpack <$> pser
- line <- skipHorizontalSpace *> nonEmptyLine >>= return . parseText
+ pser = Parsec.choice psers
+ depth <- T.length <$> pser
+ line <- parseText <$> (skipHorizontalSpace *> nonEmptyLine)
rest <- try paragraph <|> return DocEmpty
- return $ DocHeader (Header (length delim) line) `docAppend` rest
+ return $ DocHeader (Header depth line) `docAppend` rest
textParagraph :: Parser (DocH mod Identifier)
textParagraph = parseText . T.intercalate "\n" <$> some nonEmptyLine
diff --git a/haddock-library/src/Documentation/Haddock/Types.hs b/haddock-library/src/Documentation/Haddock/Types.hs
index 4cf61fee..d8c7a9fa 100644
--- a/haddock-library/src/Documentation/Haddock/Types.hs
+++ b/haddock-library/src/Documentation/Haddock/Types.hs
@@ -79,7 +79,7 @@ data Picture = Picture
} deriving (Eq, Show)
data Header id = Header
- { headerLevel :: Int
+ { headerLevel :: Int -- ^ between 1 and 6 inclusive
, headerTitle :: id
} deriving (Eq, Show, Functor, Foldable, Traversable)
--
cgit v1.2.3
From 1bedd20b94359728c25f64f7643a0ca0fb0f9fa2 Mon Sep 17 00:00:00 2001
From: Xia Li-yao
Date: Tue, 8 Dec 2020 10:42:17 -0500
Subject: Allow more characters in anchor following module reference (#1220)
---
haddock-library/src/Documentation/Haddock/Parser.hs | 10 ++++++++--
haddock-library/test/Documentation/Haddock/ParserSpec.hs | 3 +++
2 files changed, 11 insertions(+), 2 deletions(-)
(limited to 'haddock-library/src')
diff --git a/haddock-library/src/Documentation/Haddock/Parser.hs b/haddock-library/src/Documentation/Haddock/Parser.hs
index 149ff93d..bd01f354 100644
--- a/haddock-library/src/Documentation/Haddock/Parser.hs
+++ b/haddock-library/src/Documentation/Haddock/Parser.hs
@@ -242,12 +242,18 @@ monospace = DocMonospaced . parseParagraph
-- Note that we allow '#' and '\' to support anchors (old style anchors are of
-- the form "SomeModule\#anchor").
moduleName :: Parser (DocH mod a)
-moduleName = DocModule <$> ("\"" *> modid <* "\"")
+moduleName = DocModule <$> ("\"" *> (modid `maybeFollowedBy` anchor_) <* "\"")
where
modid = intercalate "." <$> conid `Parsec.sepBy1` "."
+ anchor_ = (++)
+ <$> (Parsec.string "#" <|> Parsec.string "\\#")
+ <*> many (Parsec.satisfy (\c -> c /= '"' && not (isSpace c)))
+
+ maybeFollowedBy pre suf = (\x -> maybe x (x ++)) <$> pre <*> optional suf
+
conid = (:)
<$> Parsec.satisfy (\c -> isAlpha c && isUpper c)
- <*> many (conChar <|> Parsec.oneOf "\\#")
+ <*> many conChar
conChar = Parsec.alphaNum <|> Parsec.char '_'
diff --git a/haddock-library/test/Documentation/Haddock/ParserSpec.hs b/haddock-library/test/Documentation/Haddock/ParserSpec.hs
index 8b59b560..9bf9b6ea 100644
--- a/haddock-library/test/Documentation/Haddock/ParserSpec.hs
+++ b/haddock-library/test/Documentation/Haddock/ParserSpec.hs
@@ -431,6 +431,9 @@ spec = do
it "accepts anchor reference syntax as DocModule" $ do
"\"Foo#bar\"" `shouldParseTo` DocModule "Foo#bar"
+ it "accepts anchor with hyphen as DocModule" $ do
+ "\"Foo#bar-baz\"" `shouldParseTo` DocModule "Foo\\#bar-baz"
+
it "accepts old anchor reference syntax as DocModule" $ do
"\"Foo\\#bar\"" `shouldParseTo` DocModule "Foo\\#bar"
--
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-library/src')
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