aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--README4
-rw-r--r--Text/Pandoc/Writers/RST.hs27
-rw-r--r--tests/writer.rst17
3 files changed, 34 insertions, 14 deletions
diff --git a/README b/README
index 0f17b3b5e..0817ad2df 100644
--- a/README
+++ b/README
@@ -852,6 +852,10 @@ TeX math will be printed in all output formats. In Markdown,
reStructuredText, LaTeX, and ConTeXt output, it will appear verbatim
between $ characters.
+In reStructuredText output, it will be rendered using an interpreted
+text role `:math:`, as described
+[here](http://www.american.edu/econ/itex2mml/mathhack.rst).
+
In groff man output, it will be rendered verbatim without $'s.
In RTF and Docbook output, it will be rendered, as far as possible,
diff --git a/Text/Pandoc/Writers/RST.hs b/Text/Pandoc/Writers/RST.hs
index 08ff9b928..e7708d9a8 100644
--- a/Text/Pandoc/Writers/RST.hs
+++ b/Text/Pandoc/Writers/RST.hs
@@ -44,7 +44,7 @@ data WriterState =
WriterState { stNotes :: [[Block]]
, stLinks :: KeyTable
, stImages :: KeyTable
- , stIncludes :: [Doc]
+ , stIncludes :: [String]
, stOptions :: WriterOptions
}
@@ -69,12 +69,14 @@ pandocToRST (Pandoc meta blocks) = do
then metaBlock $+$ text (writerHeader opts)
else empty
body <- blockListToRST blocks
+ includes <- get >>= (return . concat . stIncludes)
+ let includes' = if null includes then empty else text includes
notes <- get >>= (notesToRST . reverse . stNotes)
-- note that the notes may contain refs, so we do them first
refs <- get >>= (keyTableToRST . reverse . stLinks)
pics <- get >>= (pictTableToRST . reverse . stImages)
- return $ head $+$ before' $+$ body $+$ notes $+$ text "" $+$ refs $+$
- pics $+$ after'
+ return $ head $+$ before' $+$ includes' $+$ body $+$ notes $+$ text "" $+$
+ refs $+$ pics $+$ after'
-- | Return RST representation of reference key table.
keyTableToRST :: KeyTable -> State WriterState Doc
@@ -117,8 +119,11 @@ pictToRST (label, (src, _)) = do
-- | Take list of inline elements and return wrapped doc.
wrappedRST :: WriterOptions -> [Inline] -> State WriterState Doc
-wrappedRST opts inlines = mapM (wrapIfNeeded opts inlineListToRST)
- (splitBy LineBreak inlines) >>= return . vcat
+wrappedRST opts inlines = do
+ lineBreakDoc <- inlineToRST LineBreak
+ chunks <- mapM (wrapIfNeeded opts inlineListToRST)
+ (splitBy LineBreak inlines)
+ return $ vcat $ intersperse lineBreakDoc chunks
-- | Escape special characters for RST.
escapeString :: String -> String
@@ -293,10 +298,18 @@ inlineToRST Apostrophe = return $ char '\''
inlineToRST Ellipses = return $ text "..."
inlineToRST (Code str) = return $ text $ "``" ++ str ++ "``"
inlineToRST (Str str) = return $ text $ escapeString str
-inlineToRST (Math str) = return $ text $ "$" ++ str ++ "$"
+inlineToRST (Math str) = do
+ includes <- get >>= (return . stIncludes)
+ let rawMathRole = ".. role:: math(raw)\n\
+ \ :format: html latex\n"
+ if not (rawMathRole `elem` includes)
+ then modify $ \st -> st { stIncludes = rawMathRole : includes }
+ else return ()
+ return $ text $ ":math:`$" ++ str ++ "$`"
inlineToRST (TeX str) = return empty
inlineToRST (HtmlInline str) = return empty
-inlineToRST (LineBreak) = return $ char ' ' -- RST doesn't have linebreaks
+inlineToRST (LineBreak) = do
+ return $ empty -- there's no line break in RST
inlineToRST Space = return $ char ' '
inlineToRST (Link [Code str] (src, tit)) | src == str ||
src == "mailto:" ++ str = do
diff --git a/tests/writer.rst b/tests/writer.rst
index 2b44bd257..d5c4d2617 100644
--- a/tests/writer.rst
+++ b/tests/writer.rst
@@ -6,6 +6,9 @@ Pandoc Test Suite
:Author: Anonymous
:Date: July 17, 2006
+.. role:: math(raw)
+ :format: html latex
+
This is a set of tests for pandoc. Most of them are adapted from
John Gruber's markdown test suite.
@@ -620,14 +623,14 @@ LaTeX
-
-
-- $2+2=4$
-- $x \in y$
-- $\alpha \wedge \omega$
-- $223$
-- $p$-Tree
-- $\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$
+- :math:`$2+2=4$`
+- :math:`$x \in y$`
+- :math:`$\alpha \wedge \omega$`
+- :math:`$223$`
+- :math:`$p$`-Tree
+- :math:`$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$`
- Here's one that has a line break in it:
- $\alpha + \omega \times x^2$.
+ :math:`$\alpha + \omega \times x^2$`.
These shouldn't be math: