Skip to content

Commit

Permalink
RST reader: remove support for nested inlines.
Browse files Browse the repository at this point in the history
RST does not allow nested emphasis, links, or other inline
constructs.

Closes #4581, double parsing of links with URLs as
link text.  This supersedes the earlier fix for #4581
in 6419819.

Fixes #4561, a bug parsing with URLs inside emphasis.

Closes #4792.
  • Loading branch information
danse authored and jgm committed Jul 24, 2018
1 parent 50e8c3b commit be2d792
Show file tree
Hide file tree
Showing 3 changed files with 26 additions and 23 deletions.
32 changes: 15 additions & 17 deletions src/Text/Pandoc/Readers/RST.hs
Expand Up @@ -45,7 +45,6 @@ import Data.Maybe (fromMaybe, isJust)
import Data.Sequence (ViewR (..), viewr)
import Data.Text (Text)
import qualified Data.Text as T
import Text.Pandoc.Walk (walk)
import Text.Pandoc.Builder (Blocks, Inlines, fromList, setMeta, trimInlines)
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class (PandocMonad, fetchItem, readFileFromDirs)
Expand Down Expand Up @@ -1314,19 +1313,24 @@ table = gridTable False <|> simpleTable False <|>

inline :: PandocMonad m => RSTParser m Inlines
inline = choice [ note -- can start with whitespace, so try before ws
, whitespace
, link
, str
, endline
, strong
, emph
, code
, subst
, interpretedRole
, smart
, hyphens
, escapedChar
, symbol ] <?> "inline"
, inlineContent ] <?> "inline"

-- strings, spaces and other characters that can appear either by
-- themselves or within inline markup
inlineContent :: PandocMonad m => RSTParser m Inlines
inlineContent = choice [ whitespace
, str
, smart
, hyphens
, escapedChar
, symbol ] <?> "inline content"

parseInlineFromString :: PandocMonad m => String -> RSTParser m Inlines
parseInlineFromString = parseFromString' (trimInlines . mconcat <$> many inline)
Expand Down Expand Up @@ -1369,11 +1373,11 @@ atStart p = do

emph :: PandocMonad m => RSTParser m Inlines
emph = B.emph . trimInlines . mconcat <$>
enclosed (atStart $ char '*') (char '*') inline
enclosed (atStart $ char '*') (char '*') inlineContent

strong :: PandocMonad m => RSTParser m Inlines
strong = B.strong . trimInlines . mconcat <$>
enclosed (atStart $ string "**") (try $ string "**") inline
enclosed (atStart $ string "**") (try $ string "**") inlineContent

-- Note, this doesn't precisely implement the complex rule in
-- http://docutils.sourceforge.net/docs/ref/rst/restructuredtext.html#inline-markup-recognition-rules
Expand Down Expand Up @@ -1480,8 +1484,8 @@ explicitLink :: PandocMonad m => RSTParser m Inlines
explicitLink = try $ do
char '`'
notFollowedBy (char '`') -- `` marks start of inline code
label' <- removeLinks . trimInlines . mconcat <$>
manyTill (notFollowedBy (char '`') >> inline) (char '<')
label' <- trimInlines . mconcat <$>
manyTill (notFollowedBy (char '`') >> inlineContent) (char '<')
src <- trim <$> manyTill (noneOf ">\n") (char '>')
skipSpaces
string "`_"
Expand All @@ -1495,12 +1499,6 @@ explicitLink = try $ do
_ -> return ((src, ""), nullAttr)
return $ B.linkWith attr (escapeURI src') tit label''

removeLinks :: B.Inlines -> B.Inlines
removeLinks = B.fromList . walk (concatMap go) . B.toList
where go :: Inline -> [Inline]
go (Link _ lab _) = lab
go x = [x]

citationName :: PandocMonad m => RSTParser m String
citationName = do
raw <- citationMarker
Expand Down
11 changes: 11 additions & 0 deletions test/Tests/Readers/RST.hs
Expand Up @@ -188,4 +188,15 @@ tests = [ "line block with blank line" =:
] =?>
para ("foo" <> note (para "bar"))
]
, testGroup "inlines"
[ "links can contain an URI without being parsed twice (#4581)" =:
"`http://loc <http://loc>`__" =?>
para (link "http://loc" "" "http://loc")
, "inline markup cannot be nested" =:
"**a*b*c**" =?>
para (strong "a*b*c")
, "bare URI parsing disabled inside emphasis (#4561)" =:
"*http://location*" =?>
para (emph (text "http://location"))
]
]
6 changes: 0 additions & 6 deletions test/command/4581.md

This file was deleted.

0 comments on commit be2d792

Please sign in to comment.