Merge pull request #2092 from lierdakil/issue1909

MD Reader: Smart apostrophe after inline math
This commit is contained in:
John MacFarlane 2015-04-17 18:55:35 -07:00
commit fb143be038
3 changed files with 11 additions and 2 deletions

View file

@ -161,7 +161,8 @@ module Text.Pandoc.Parsing ( anyLine,
setSourceColumn,
setSourceLine,
newPos,
addWarning
addWarning,
(<+?>)
)
where
@ -1245,3 +1246,7 @@ addWarning mbpos msg =
generalize :: (Monad m) => Parser s st a -> ParserT s st m a
generalize m = mkPT (\ s -> (return $ (return . runIdentity) <$> runIdentity (runParsecT m s)))
infixr 5 <+?>
(<+?>) :: (Monoid a, Monad m) => ParserT s st m a -> ParserT s st m a -> ParserT s st m a
a <+?> b = a >>= flip fmap (try b <|> return mempty) . (<>)

View file

@ -1487,7 +1487,8 @@ code = try $ do
math :: MarkdownParser Inlines
math = (B.displayMath <$> (mathDisplay >>= applyMacros'))
<|> (B.math <$> (mathInline >>= applyMacros'))
<|> ((B.math <$> (mathInline >>= applyMacros')) <+?>
((getOption readerSmart >>= guard) *> apostrophe <* notFollowedBy space))
-- Parses material enclosed in *s, **s, _s, or __s.
-- Designed to avoid backtracking.

View file

@ -208,6 +208,9 @@ tests = [ testGroup "inline code"
, test markdownSmart "apostrophe in French"
("À l'arrivée de la guerre, le thème de l'«impossibilité du socialisme»"
=?> para "À larrivée de la guerre, le thème de l«impossibilité du socialisme»")
, test markdownSmart "apostrophe after math" $ -- issue #1909
"The value of the $x$'s and the systems' condition." =?>
para (text "The value of the " <> math "x" <> text "\8217s and the systems\8217 condition.")
]
, testGroup "footnotes"
[ "indent followed by newline and flush-left text" =: