Add parsing support for the rST default-role directive.

This commit is contained in:
Greg Maslov 2012-03-24 21:30:10 -04:00
parent 3c4e1ff063
commit 618dc294f9
4 changed files with 59 additions and 6 deletions

View file

@ -652,7 +652,8 @@ data ParserState = ParserState
stateExamples :: M.Map String Int, -- ^ Map from example labels to numbers
stateHasChapters :: Bool, -- ^ True if \chapter encountered
stateApplyMacros :: Bool, -- ^ Apply LaTeX macros?
stateMacros :: [Macro] -- ^ List of macros defined so far
stateMacros :: [Macro], -- ^ List of macros defined so far
stateRstDefaultRole :: String -- ^ Current rST default interpreted text role
}
deriving Show
@ -682,7 +683,8 @@ defaultParserState =
stateExamples = M.empty,
stateHasChapters = False,
stateApplyMacros = True,
stateMacros = []}
stateMacros = [],
stateRstDefaultRole = "title-reference"}
data HeaderType
= SingleHeader Char -- ^ Single line of characters underneath

View file

@ -129,6 +129,7 @@ block = choice [ codeBlock
, imageBlock
, customCodeBlock
, mathBlock
, defaultRoleBlock
, unknownDirective
, header
, hrule
@ -532,6 +533,21 @@ bulletList :: GenParser Char ParserState Block
bulletList = many1 (listItem bulletListStart) >>=
return . BulletList . compactify
--
-- default-role block
--
defaultRoleBlock :: GenParser Char ParserState Block
defaultRoleBlock = try $ do
string ".. default-role:: "
role <- manyTill anyChar newline >>= return . removeLeadingTrailingSpace
updateState $ \s -> s { stateRstDefaultRole =
if null role
then stateRstDefaultRole defaultParserState
else role
}
return Null
--
-- unknown directive (e.g. comment)
--
@ -805,13 +821,25 @@ strong :: GenParser Char ParserState Inline
strong = enclosed (string "**") (try $ string "**") inline >>=
return . Strong . normalizeSpaces
interpreted :: [Char] -> GenParser Char st [Char]
-- Parses inline interpreted text which is required to have the given role.
-- This decision is based on the role marker (if present),
-- and the current default interpreted text role.
interpreted :: [Char] -> GenParser Char ParserState [Char]
interpreted role = try $ do
state <- getState
if role == stateRstDefaultRole state
then try markedInterpretedText <|> unmarkedInterpretedText
else markedInterpretedText
where
markedInterpretedText = try (roleMarker >> unmarkedInterpretedText)
<|> (unmarkedInterpretedText >>= (\txt -> roleMarker >> return txt))
roleMarker = string $ ":" ++ role ++ ":"
-- Note, this doesn't precisely implement the complex rule in
-- http://docutils.sourceforge.net/docs/ref/rst/restructuredtext.html#inline-markup-recognition-rules
-- but it should be good enough for most purposes
result <- enclosed (string $ ":" ++ role ++ ":`") (char '`') anyChar
return result
unmarkedInterpretedText = do
result <- enclosed (char '`') (char '`') anyChar
return result
superscript :: GenParser Char ParserState Inline
superscript = interpreted "sup" >>= \x -> return (Superscript [Str x])

View file

@ -312,4 +312,9 @@ Pandoc (Meta {docTitle = [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":
,Para [Math DisplayMath "E = mc^2"]
,Para [Math DisplayMath "E = mc^2",Math DisplayMath "\\alpha = \\beta"]
,Para [Math DisplayMath "E &= mc^2\\\\\nF &= \\pi E",Math DisplayMath "F &= \\gamma \\alpha^2"]
,Para [Str "All",Space,Str "done",Str "."]]
,Para [Str "All",Space,Str "done",Str "."]
,Header 1 [Str "Default",Str "-",Str "Role"]
,Para [Str "Try",Space,Str "changing",Space,Str "the",Space,Str "default",Space,Str "role",Space,Str "to",Space,Str "a",Space,Str "few",Space,Str "different",Space,Str "things",Str "."]
,Para [Str "Inline",Space,Str "math",Str ":",Space,Math InlineMath "E=mc^2",Space,Str "or",Space,Math InlineMath "E=mc^2",Space,Str "or",Space,Math InlineMath "E=mc^2",Str ".",Space,Str "Other",Space,Str "roles",Str ":",Space,Superscript [Str "super"],Str ",",Space,Subscript [Str "sub"],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",Str "-",Str "role",Space,Str "to",Space,Str "the",Space,Str "default",Space,Str "default",Str "."]]

View file

@ -565,3 +565,21 @@ display math:
All done.
Default-Role
============
Try changing the default role to a few different things.
.. default-role:: math
Inline math: `E=mc^2` or :math:`E=mc^2` or `E=mc^2`:math:.
Other roles: :sup:`super`, `sub`:sub:.
.. default-role:: sup
Some `of` these :sup:`words` are in `superscript`:sup:.
Reset default-role to the default default.
.. default-role::