aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2011-12-30 23:46:43 -0800
committerJohn MacFarlane <fiddlosopher@gmail.com>2011-12-30 23:46:43 -0800
commitd8272d03561e4429c62f6a0dbb1a1b6d70899321 (patch)
treef35b91f286280dc5c7768bd1eff5e68603920c28 /src/Text/Pandoc/Readers
parent661d0646d041fe5093eb603c9f059d1d37da3783 (diff)
downloadpandoc-d8272d03561e4429c62f6a0dbb1a1b6d70899321.tar.gz
Support Sphinx style math in RST reader.
Inline: :math:`E=mc^2` Block: .. math: E = mc^2 .. math:: E = mc^2 a = b^2 (This latter will turn into a paragraph with two display math elements.) Closes #117.
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/RST.hs39
1 files changed, 35 insertions, 4 deletions
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index d8704d8c9..02154b5a3 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -128,6 +128,7 @@ block = choice [ codeBlock
, fieldList
, imageBlock
, customCodeBlock
+ , mathBlock
, unknownDirective
, header
, hrule
@@ -360,6 +361,32 @@ customCodeBlock = try $ do
result <- indentedBlock
return $ CodeBlock ("", ["sourceCode", language], []) $ stripTrailingNewlines result
+-- | The 'math' directive (from Sphinx) for display math.
+mathBlock :: GenParser Char st Block
+mathBlock = mathBlockMultiline <|> mathBlockOneLine
+
+mathBlockOneLine :: GenParser Char st Block
+mathBlockOneLine = try $ do
+ string ".. math:"
+ result <- manyTill anyChar newline
+ blanklines
+ return $ Para [Math DisplayMath $ removeLeadingTrailingSpace result]
+
+mathBlockMultiline :: GenParser Char st Block
+mathBlockMultiline = try $ do
+ string ".. math::"
+ blanklines
+ result <- indentedBlock
+ -- a single block can contain multiple equations, which need to go
+ -- in separate Pandoc math elements
+ let lns = map removeLeadingTrailingSpace $ lines result
+ -- drop :label, :nowrap, etc.
+ let startsWithColon (':':_) = True
+ startsWithColon _ = False
+ let lns' = dropWhile startsWithColon lns
+ let eqs = map unwords $ filter (not . null) $ splitBy null lns'
+ return $ Para $ map (Math DisplayMath) eqs
+
lhsCodeBlock :: GenParser Char ParserState Block
lhsCodeBlock = try $ do
failUnlessLHS
@@ -736,6 +763,7 @@ inline = choice [ whitespace
, image
, superscript
, subscript
+ , math
, note
, smartPunctuation inline
, hyphens
@@ -774,18 +802,21 @@ strong :: GenParser Char ParserState Inline
strong = enclosed (string "**") (try $ string "**") inline >>=
return . Strong . normalizeSpaces
-interpreted :: [Char] -> GenParser Char st [Inline]
+interpreted :: [Char] -> GenParser Char st [Char]
interpreted role = try $ do
optional $ try $ string "\\ "
result <- enclosed (string $ ":" ++ role ++ ":`") (char '`') anyChar
try (string "\\ ") <|> lookAhead (count 1 $ oneOf " \t\n") <|> (eof >> return "")
- return [Str result]
+ return result
superscript :: GenParser Char ParserState Inline
-superscript = interpreted "sup" >>= (return . Superscript)
+superscript = interpreted "sup" >>= \x -> return (Superscript [Str x])
subscript :: GenParser Char ParserState Inline
-subscript = interpreted "sub" >>= (return . Subscript)
+subscript = interpreted "sub" >>= \x -> return (Subscript [Str x])
+
+math :: GenParser Char ParserState Inline
+math = interpreted "math" >>= \x -> return (Math InlineMath x)
whitespace :: GenParser Char ParserState Inline
whitespace = many1 spaceChar >> return Space <?> "whitespace"