aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/RST.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers/RST.hs')
-rw-r--r--src/Text/Pandoc/Readers/RST.hs37
1 files changed, 34 insertions, 3 deletions
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 30d9aae44..35fe5d768 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -129,6 +129,7 @@ block = choice [ codeBlock
, imageBlock
, customCodeBlock
, mathBlock
+ , defaultRoleBlock
, unknownDirective
, header
, hrule
@@ -533,6 +534,24 @@ bulletList = many1 (listItem bulletListStart) >>=
return . BulletList . compactify
--
+-- default-role block
+--
+
+defaultRoleBlock :: GenParser Char ParserState Block
+defaultRoleBlock = try $ do
+ string ".. default-role::"
+ -- doesn't enforce any restrictions on the role name; embedded spaces shouldn't be allowed, for one
+ role <- manyTill anyChar newline >>= return . removeLeadingTrailingSpace
+ updateState $ \s -> s { stateRstDefaultRole =
+ if null role
+ then stateRstDefaultRole defaultParserState
+ else role
+ }
+ -- skip body of the directive if it exists
+ many $ blanklines <|> (spaceChar >> manyTill anyChar newline)
+ return Null
+
+--
-- unknown directive (e.g. comment)
--
@@ -805,13 +824,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])