Skip to content
This repository was archived by the owner on Aug 3, 2024. It is now read-only.

Backward compat: Add support for labeled module references #1319

Merged
merged 1 commit into from
Feb 7, 2021
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
5 changes: 5 additions & 0 deletions doc/markup.rst
Original file line number Diff line number Diff line change
Expand Up @@ -982,6 +982,11 @@ is valid before turning it into a link but unlike with identifiers,
whether the module is in scope isn't checked and will always be turned
into a link.

It is also possible to specify alternate text for the generated link
using syntax analogous to that used for URLs: ::

-- | This is a reference to [the main module]("Module.Main").

Itemized and Enumerated Lists
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

Expand Down
2 changes: 1 addition & 1 deletion haddock-api/src/Haddock/Backends/Hoogle.hs
Original file line number Diff line number Diff line change
Expand Up @@ -325,7 +325,7 @@ markupTag dflags = Markup {
markupAppend = (++),
markupIdentifier = box (TagInline "a") . str . out dflags,
markupIdentifierUnchecked = box (TagInline "a") . str . showWrapped (out dflags . snd),
markupModule = box (TagInline "a") . str,
markupModule = \(ModLink m label) -> box (TagInline "a") (fromMaybe (str m) label),
markupWarning = box (TagInline "i"),
markupEmphasis = box (TagInline "i"),
markupBold = box (TagInline "b"),
Expand Down
7 changes: 6 additions & 1 deletion haddock-api/src/Haddock/Backends/LaTeX.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1210,7 +1210,12 @@ latexMarkup = Markup
, markupAppend = \l r v -> l v . r v
, markupIdentifier = \i v -> inlineElem (markupId v (fmap occName i))
, markupIdentifierUnchecked = \i v -> inlineElem (markupId v (fmap snd i))
, markupModule = \m _ -> inlineElem (let (mdl,_ref) = break (=='#') m in (tt (text mdl)))
, markupModule =
\(ModLink m mLabel) v ->
case mLabel of
Just lbl -> inlineElem . tt $ lbl v empty
Nothing -> inlineElem (let (mdl,_ref) = break (=='#') m
in (tt (text mdl)))
, markupWarning = \p v -> p v
, markupEmphasis = \p v -> inlineElem (emph (p v empty))
, markupBold = \p v -> inlineElem (bold (p v empty))
Expand Down
15 changes: 8 additions & 7 deletions haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -44,13 +44,14 @@ parHtmlMarkup qual insertAnchors ppId = Markup {
markupAppend = (+++),
markupIdentifier = thecode . ppId insertAnchors,
markupIdentifierUnchecked = thecode . ppUncheckedLink qual,
markupModule = \m -> let (mdl,ref) = break (=='#') m
-- Accomodate for old style
-- foo\#bar anchors
mdl' = case reverse mdl of
'\\':_ -> init mdl
_ -> mdl
in ppModuleRef (mkModuleName mdl') ref,
markupModule = \(ModLink m lbl) ->
let (mdl,ref) = break (=='#') m
-- Accomodate for old style
-- foo\#bar anchors
mdl' = case reverse mdl of
'\\':_ -> init mdl
_ -> mdl
in ppModuleRef lbl (mkModuleName mdl') ref,
markupWarning = thediv ! [theclass "warning"],
markupEmphasis = emphasize,
markupBold = strong,
Expand Down
9 changes: 6 additions & 3 deletions haddock-api/src/Haddock/Backends/Xhtml/Names.hs
Original file line number Diff line number Diff line change
Expand Up @@ -186,9 +186,12 @@ ppModule mdl = anchor ! [href (moduleUrl mdl)]
<< toHtml (moduleString mdl)


ppModuleRef :: ModuleName -> String -> Html
ppModuleRef mdl ref = anchor ! [href (moduleHtmlFile' mdl ++ ref)]
<< toHtml (moduleNameString mdl)
ppModuleRef :: Maybe Html -> ModuleName -> String -> Html
ppModuleRef Nothing mdl ref = anchor ! [href (moduleHtmlFile' mdl ++ ref)]
<< toHtml (moduleNameString mdl)
ppModuleRef (Just lbl) mdl ref = anchor ! [href (moduleHtmlFile' mdl ++ ref)]
<< lbl

-- NB: The ref parameter already includes the '#'.
-- This function is only called from markupModule expanding a
-- DocModule, which doesn't seem to be ever be used.
4 changes: 2 additions & 2 deletions haddock-api/src/Haddock/Interface/Json.hs
Original file line number Diff line number Diff line change
Expand Up @@ -98,9 +98,9 @@ jsonDoc (DocIdentifierUnchecked modName) = jsonObject
, ("modName", jsonString (showModName modName))
]

jsonDoc (DocModule s) = jsonObject
jsonDoc (DocModule (ModLink m _l)) = jsonObject
[ ("tag", jsonString "DocModule")
, ("string", jsonString s)
, ("string", jsonString m)
]

jsonDoc (DocWarning x) = jsonObject
Expand Down
2 changes: 1 addition & 1 deletion haddock-api/src/Haddock/Interface/LexParseRn.hs
Original file line number Diff line number Diff line change
Expand Up @@ -148,7 +148,7 @@ rename dflags gre = rn
DocDefList list -> DocDefList <$> traverse (\(a, b) -> (,) <$> rn a <*> rn b) list
DocCodeBlock doc -> DocCodeBlock <$> rn doc
DocIdentifierUnchecked x -> pure (DocIdentifierUnchecked x)
DocModule str -> pure (DocModule str)
DocModule (ModLink m l) -> DocModule . ModLink m <$> traverse rn l
DocHyperlink (Hyperlink u l) -> DocHyperlink . Hyperlink u <$> traverse rn l
DocPic str -> pure (DocPic str)
DocMathInline str -> pure (DocMathInline str)
Expand Down
41 changes: 35 additions & 6 deletions haddock-api/src/Haddock/InterfaceFile.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,6 +46,8 @@ import GHC.Types.Unique.FM
import GHC.Types.Unique.Supply
import GHC.Types.Unique

import Documentation.Haddock.Parser (parseModLink)


data InterfaceFile = InterfaceFile {
ifLinkEnv :: LinkEnv,
Expand All @@ -69,6 +71,18 @@ ifUnitId if_ =
binaryInterfaceMagic :: Word32
binaryInterfaceMagic = 0xD0Cface

-- Note [The DocModule story]
--
-- Breaking changes to the DocH type result in Haddock being unable to read
-- existing interfaces. This is especially painful for interfaces shipped
-- with GHC distributions since there is no easy way to regenerate them!
--
-- PR #1315 introduced a breaking change to the DocModule constructor. To
-- maintain backward compatibility we
--
-- Parse the old DocModule constructor format (tag 5) and parse the contained
-- string into a proper ModLink structure. When writing interfaces we exclusively
-- use the new DocModule format (tag 24)

-- IMPORTANT: Since datatypes in the GHC API might change between major
-- versions, and because we store GHC datatypes in our interface files, we need
Expand All @@ -84,10 +98,10 @@ binaryInterfaceMagic = 0xD0Cface
--
binaryInterfaceVersion :: Word16
#if MIN_VERSION_ghc(9,0,0) && !MIN_VERSION_ghc(9,1,0)
binaryInterfaceVersion = 37
binaryInterfaceVersion = 38

binaryInterfaceVersionCompatibility :: [Word16]
binaryInterfaceVersionCompatibility = [binaryInterfaceVersion]
binaryInterfaceVersionCompatibility = [37, binaryInterfaceVersion]
#else
#error Unsupported GHC version
#endif
Expand Down Expand Up @@ -444,6 +458,15 @@ instance Binary a => Binary (Hyperlink a) where
label <- get bh
return (Hyperlink url label)

instance Binary a => Binary (ModLink a) where
put_ bh (ModLink m label) = do
put_ bh m
put_ bh label
get bh = do
m <- get bh
label <- get bh
return (ModLink m label)

instance Binary Picture where
put_ bh (Picture uri title) = do
put_ bh uri
Expand Down Expand Up @@ -522,9 +545,6 @@ instance (Binary mod, Binary id) => Binary (DocH mod id) where
put_ bh (DocIdentifier ae) = do
putByte bh 4
put_ bh ae
put_ bh (DocModule af) = do
putByte bh 5
put_ bh af
put_ bh (DocEmphasis ag) = do
putByte bh 6
put_ bh ag
Expand Down Expand Up @@ -579,6 +599,10 @@ instance (Binary mod, Binary id) => Binary (DocH mod id) where
put_ bh (DocTable x) = do
putByte bh 23
put_ bh x
-- See note [The DocModule story]
put_ bh (DocModule af) = do
putByte bh 24
put_ bh af

get bh = do
h <- getByte bh
Expand All @@ -598,9 +622,10 @@ instance (Binary mod, Binary id) => Binary (DocH mod id) where
4 -> do
ae <- get bh
return (DocIdentifier ae)
-- See note [The DocModule story]
5 -> do
af <- get bh
return (DocModule af)
return (parseModLink af)
6 -> do
ag <- get bh
return (DocEmphasis ag)
Expand Down Expand Up @@ -655,6 +680,10 @@ instance (Binary mod, Binary id) => Binary (DocH mod id) where
23 -> do
x <- get bh
return (DocTable x)
-- See note [The DocModule story]
24 -> do
af <- get bh
return (DocModule af)
_ -> error "invalid binary data found in the interface file"


Expand Down
3 changes: 3 additions & 0 deletions haddock-api/src/Haddock/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -501,6 +501,9 @@ instance NFData id => NFData (Header id) where
instance NFData id => NFData (Hyperlink id) where
rnf (Hyperlink a b) = a `deepseq` b `deepseq` ()

instance NFData id => NFData (ModLink id) where
rnf (ModLink a b) = a `deepseq` b `deepseq` ()

instance NFData Picture where
rnf (Picture a b) = a `deepseq` b `deepseq` ()

Expand Down
3 changes: 3 additions & 0 deletions haddock-library/fixtures/Fixtures.hs
Original file line number Diff line number Diff line change
Expand Up @@ -149,6 +149,9 @@ instance ToExpr id => ToExpr (Header id)
deriving instance Generic (Hyperlink id)
instance ToExpr id => ToExpr (Hyperlink id)

deriving instance Generic (ModLink id)
instance ToExpr id => ToExpr (ModLink id)

deriving instance Generic Picture
instance ToExpr Picture

Expand Down
4 changes: 2 additions & 2 deletions haddock-library/src/Documentation/Haddock/Markup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ markup m (DocString s) = markupString m s
markup m (DocParagraph d) = markupParagraph m (markup m d)
markup m (DocIdentifier x) = markupIdentifier m x
markup m (DocIdentifierUnchecked x) = markupIdentifierUnchecked m x
markup m (DocModule mod0) = markupModule m mod0
markup m (DocModule (ModLink mo l)) = markupModule m (ModLink mo (fmap (markup m) l))
markup m (DocWarning d) = markupWarning m (markup m d)
markup m (DocEmphasis d) = markupEmphasis m (markup m d)
markup m (DocBold d) = markupBold m (markup m d)
Expand Down Expand Up @@ -78,7 +78,7 @@ plainMarkup plainMod plainIdent = Markup {
markupAppend = (++),
markupIdentifier = plainIdent,
markupIdentifierUnchecked = plainMod,
markupModule = id,
markupModule = \(ModLink m lbl) -> fromMaybe m lbl,
markupWarning = id,
markupEmphasis = id,
markupBold = id,
Expand Down
54 changes: 41 additions & 13 deletions haddock-library/src/Documentation/Haddock/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@
module Documentation.Haddock.Parser (
parseString,
parseParas,
parseModLink,
overIdentifier,
toRegular,
Identifier
Expand Down Expand Up @@ -72,7 +73,7 @@ overIdentifier f d = g d
g (DocString x) = DocString x
g (DocParagraph x) = DocParagraph $ g x
g (DocIdentifierUnchecked x) = DocIdentifierUnchecked x
g (DocModule x) = DocModule x
g (DocModule (ModLink m x)) = DocModule (ModLink m (fmap g x))
g (DocWarning x) = DocWarning $ g x
g (DocEmphasis x) = DocEmphasis $ g x
g (DocMonospaced x) = DocMonospaced $ g x
Expand Down Expand Up @@ -136,6 +137,9 @@ parseString = parseText . T.pack
parseText :: Text -> DocH mod Identifier
parseText = parseParagraph . T.dropWhile isSpace . T.filter (/= '\r')

parseModLink :: String -> DocH mod id
parseModLink s = snd $ parse moduleName (T.pack s)

parseParagraph :: Text -> DocH mod Identifier
parseParagraph = snd . parse p
where
Expand All @@ -148,6 +152,7 @@ parseParagraph = snd . parse p
, mathDisplay
, mathInline
, markdownImage
, markdownLink
, hyperlink
, bold
, emphasis
Expand Down Expand Up @@ -242,21 +247,43 @@ 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 `maybeFollowedBy` anchor_) <* "\"")
moduleName = DocModule . flip ModLink Nothing <$> ("\"" *> moduleNameString <* "\"")

-- | A module name, optionally with an anchor
--
moduleNameString :: Parser String
moduleNameString = 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 :: Parser String
conid = (:)
<$> Parsec.satisfy (\c -> isAlpha c && isUpper c)
<*> many conChar

conChar = Parsec.alphaNum <|> Parsec.char '_'

-- | A labeled link to an indentifier, module or url using markdown
-- syntax.
markdownLink :: Parser (DocH mod Identifier)
markdownLink = do
lbl <- markdownLinkText
choice' [ markdownModuleName lbl, markdownURL lbl ]
where
markdownModuleName lbl = do
mn <- "(" *> skipHorizontalSpace *>
"\"" *> moduleNameString <* "\""
<* skipHorizontalSpace <* ")"
pure $ DocModule (ModLink mn (Just lbl))

markdownURL lbl = do
target <- markdownLinkTarget
pure $ DocHyperlink $ Hyperlink target (Just lbl)

-- | Picture parser, surrounded by \<\< and \>\>. It's possible to specify
-- a title for the picture.
--
Expand Down Expand Up @@ -290,9 +317,11 @@ mathDisplay = DocMathDisplay . T.unpack
-- >>> parseString "![some /emphasis/ in a description](www.site.com)"
-- DocPic (Picture "www.site.com" (Just "some emphasis in a description"))
markdownImage :: Parser (DocH mod Identifier)
markdownImage = DocPic . fromHyperlink <$> ("!" *> linkParser)
markdownImage = do
text <- markup stringMarkup <$> ("!" *> markdownLinkText)
url <- markdownLinkTarget
pure $ DocPic (Picture url (Just text))
where
fromHyperlink (Hyperlink u l) = Picture u (fmap (markup stringMarkup) l)
stringMarkup = plainMarkup (const "") renderIdent
renderIdent (Identifier ns l c r) = renderNs ns <> [l] <> c <> [r]

Expand Down Expand Up @@ -772,22 +801,21 @@ codeblock =
| otherwise = Just $ c == '\n'

hyperlink :: Parser (DocH mod Identifier)
hyperlink = choice' [ angleBracketLink, markdownLink, autoUrl ]
hyperlink = choice' [ angleBracketLink, autoUrl ]

angleBracketLink :: Parser (DocH mod a)
angleBracketLink =
DocHyperlink . makeLabeled (\s -> Hyperlink s . fmap DocString)
<$> disallowNewline ("<" *> takeUntil ">")

markdownLink :: Parser (DocH mod Identifier)
markdownLink = DocHyperlink <$> linkParser
-- | The text for a markdown link, enclosed in square brackets.
markdownLinkText :: Parser (DocH mod Identifier)
markdownLinkText = parseParagraph . T.strip <$> ("[" *> takeUntil "]")

linkParser :: Parser (Hyperlink (DocH mod Identifier))
linkParser = flip Hyperlink <$> label <*> (whitespace *> url)
-- | The target for a markdown link, enclosed in parenthesis.
markdownLinkTarget :: Parser String
markdownLinkTarget = whitespace *> url
where
label :: Parser (Maybe (DocH mod Identifier))
label = Just . parseParagraph . T.strip <$> ("[" *> takeUntil "]")

whitespace :: Parser ()
whitespace = skipHorizontalSpace <* optional ("\n" *> skipHorizontalSpace)

Expand Down
Loading