RST reader: Consolidate super/subscript, math into interpretedRole.

This commit is contained in:
John MacFarlane 2012-09-30 20:28:50 -07:00
parent 9366d8681d
commit e8260c27e1
2 changed files with 27 additions and 36 deletions

View file

@ -854,9 +854,6 @@ inline = choice [ whitespace
, emph , emph
, code , code
, subst , subst
, superscript
, subscript
, math
, interpretedRole , interpretedRole
, note , note
, smart , smart
@ -907,42 +904,36 @@ strong :: RSTParser Inlines
strong = B.strong . trimInlines . mconcat <$> strong = B.strong . trimInlines . mconcat <$>
enclosed (atStart $ string "**") (try $ string "**") inline enclosed (atStart $ string "**") (try $ string "**") inline
-- Parses inline interpreted text which is required to have the given role. -- Note, this doesn't precisely implement the complex rule in
-- This decision is based on the role marker (if present), -- http://docutils.sourceforge.net/docs/ref/rst/restructuredtext.html#inline-markup-recognition-rules
-- and the current default interpreted text role. -- but it should be good enough for most purposes
interpreted :: [Char] -> RSTParser [Char] interpretedRole :: RSTParser Inlines
interpreted role = try $ do interpretedRole = try $ do
state <- getState (role, contents) <- roleBefore <|> roleAfter
if role == stateRstDefaultRole state case role of
then try markedInterpretedText <|> unmarkedInterpretedText "sup" -> return $ B.superscript $ B.str contents
else markedInterpretedText "sub" -> return $ B.subscript $ B.str contents
where "math" -> return $ B.math contents
markedInterpretedText = try (roleMarker *> unmarkedInterpretedText) _ -> return $ B.str contents --unknown
<|> (unmarkedInterpretedText <* roleMarker)
roleMarker = string $ ":" ++ role ++ ":" roleMarker :: RSTParser String
-- Note, this doesn't precisely implement the complex rule in roleMarker = char ':' *> many1Till (letter <|> char '-') (char ':')
-- http://docutils.sourceforge.net/docs/ref/rst/restructuredtext.html#inline-markup-recognition-rules
-- but it should be good enough for most purposes roleBefore :: RSTParser (String,String)
roleBefore = try $ do
role <- roleMarker
contents <- unmarkedInterpretedText
return (role,contents)
roleAfter :: RSTParser (String,String)
roleAfter = try $ do
contents <- unmarkedInterpretedText
role <- roleMarker <|> (stateRstDefaultRole <$> getState)
return (role,contents)
unmarkedInterpretedText :: RSTParser [Char] unmarkedInterpretedText :: RSTParser [Char]
unmarkedInterpretedText = enclosed (atStart $ char '`') (char '`') anyChar unmarkedInterpretedText = enclosed (atStart $ char '`') (char '`') anyChar
-- For unknown interpreted roles, we just ignore the role.
interpretedRole :: RSTParser Inlines
interpretedRole = try $ B.str <$>
( (roleMarker *> unmarkedInterpretedText)
<|> (unmarkedInterpretedText <* roleMarker) )
where roleMarker = char ':' *> many1Till (letter <|> char '-') (char ':')
superscript :: RSTParser Inlines
superscript = B.superscript . B.str <$> interpreted "sup"
subscript :: RSTParser Inlines
subscript = B.subscript . B.str <$> interpreted "sub"
math :: RSTParser Inlines
math = B.math <$> interpreted "math"
whitespace :: RSTParser Inlines whitespace :: RSTParser Inlines
whitespace = B.space <$ skipMany1 spaceChar <?> "whitespace" whitespace = B.space <$ skipMany1 spaceChar <?> "whitespace"

View file

@ -321,6 +321,6 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":
,Para [Math DisplayMath "\\alpha = beta",Math DisplayMath "E = mc^2"] ,Para [Math DisplayMath "\\alpha = beta",Math DisplayMath "E = mc^2"]
,Para [Str "Some",Space,Superscript [Str "of"],Space,Str "these",Space,Superscript [Str "words"],Space,Str "are",Space,Str "in",Space,Superscript [Str "superscript"],Str "."] ,Para [Str "Some",Space,Superscript [Str "of"],Space,Str "these",Space,Superscript [Str "words"],Space,Str "are",Space,Str "in",Space,Superscript [Str "superscript"],Str "."]
,Para [Str "Reset",Space,Str "default-role",Space,Str "to",Space,Str "the",Space,Str "default",Space,Str "default."] ,Para [Str "Reset",Space,Str "default-role",Space,Str "to",Space,Str "the",Space,Str "default",Space,Str "default."]
,Para [Str "And",Space,Str "now",Space,Str "`some-invalid-string-3231231`",Space,Str "is",Space,Str "nonsense."] ,Para [Str "And",Space,Str "now",Space,Str "some-invalid-string-3231231",Space,Str "is",Space,Str "nonsense."]
,Header 2 [Str "Literal",Space,Str "symbols"] ,Header 2 [Str "Literal",Space,Str "symbols"]
,Para [Str "2*2",Space,Str "=",Space,Str "4*1"]] ,Para [Str "2*2",Space,Str "=",Space,Str "4*1"]]