Use an interpreted text role to render math in restructuredText.
See http://www.american.edu/econ/itex2mml/mathhack.rst for the strategy. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1168 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
parent
ec3f6b649f
commit
0921704d92
3 changed files with 34 additions and 14 deletions
4
README
4
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
|
reStructuredText, LaTeX, and ConTeXt output, it will appear verbatim
|
||||||
between $ characters.
|
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 groff man output, it will be rendered verbatim without $'s.
|
||||||
|
|
||||||
In RTF and Docbook output, it will be rendered, as far as possible,
|
In RTF and Docbook output, it will be rendered, as far as possible,
|
||||||
|
|
|
@ -44,7 +44,7 @@ data WriterState =
|
||||||
WriterState { stNotes :: [[Block]]
|
WriterState { stNotes :: [[Block]]
|
||||||
, stLinks :: KeyTable
|
, stLinks :: KeyTable
|
||||||
, stImages :: KeyTable
|
, stImages :: KeyTable
|
||||||
, stIncludes :: [Doc]
|
, stIncludes :: [String]
|
||||||
, stOptions :: WriterOptions
|
, stOptions :: WriterOptions
|
||||||
}
|
}
|
||||||
|
|
||||||
|
@ -69,12 +69,14 @@ pandocToRST (Pandoc meta blocks) = do
|
||||||
then metaBlock $+$ text (writerHeader opts)
|
then metaBlock $+$ text (writerHeader opts)
|
||||||
else empty
|
else empty
|
||||||
body <- blockListToRST blocks
|
body <- blockListToRST blocks
|
||||||
|
includes <- get >>= (return . concat . stIncludes)
|
||||||
|
let includes' = if null includes then empty else text includes
|
||||||
notes <- get >>= (notesToRST . reverse . stNotes)
|
notes <- get >>= (notesToRST . reverse . stNotes)
|
||||||
-- note that the notes may contain refs, so we do them first
|
-- note that the notes may contain refs, so we do them first
|
||||||
refs <- get >>= (keyTableToRST . reverse . stLinks)
|
refs <- get >>= (keyTableToRST . reverse . stLinks)
|
||||||
pics <- get >>= (pictTableToRST . reverse . stImages)
|
pics <- get >>= (pictTableToRST . reverse . stImages)
|
||||||
return $ head $+$ before' $+$ body $+$ notes $+$ text "" $+$ refs $+$
|
return $ head $+$ before' $+$ includes' $+$ body $+$ notes $+$ text "" $+$
|
||||||
pics $+$ after'
|
refs $+$ pics $+$ after'
|
||||||
|
|
||||||
-- | Return RST representation of reference key table.
|
-- | Return RST representation of reference key table.
|
||||||
keyTableToRST :: KeyTable -> State WriterState Doc
|
keyTableToRST :: KeyTable -> State WriterState Doc
|
||||||
|
@ -117,8 +119,11 @@ pictToRST (label, (src, _)) = do
|
||||||
|
|
||||||
-- | Take list of inline elements and return wrapped doc.
|
-- | Take list of inline elements and return wrapped doc.
|
||||||
wrappedRST :: WriterOptions -> [Inline] -> State WriterState Doc
|
wrappedRST :: WriterOptions -> [Inline] -> State WriterState Doc
|
||||||
wrappedRST opts inlines = mapM (wrapIfNeeded opts inlineListToRST)
|
wrappedRST opts inlines = do
|
||||||
(splitBy LineBreak inlines) >>= return . vcat
|
lineBreakDoc <- inlineToRST LineBreak
|
||||||
|
chunks <- mapM (wrapIfNeeded opts inlineListToRST)
|
||||||
|
(splitBy LineBreak inlines)
|
||||||
|
return $ vcat $ intersperse lineBreakDoc chunks
|
||||||
|
|
||||||
-- | Escape special characters for RST.
|
-- | Escape special characters for RST.
|
||||||
escapeString :: String -> String
|
escapeString :: String -> String
|
||||||
|
@ -293,10 +298,18 @@ inlineToRST Apostrophe = return $ char '\''
|
||||||
inlineToRST Ellipses = return $ text "..."
|
inlineToRST Ellipses = return $ text "..."
|
||||||
inlineToRST (Code str) = return $ text $ "``" ++ str ++ "``"
|
inlineToRST (Code str) = return $ text $ "``" ++ str ++ "``"
|
||||||
inlineToRST (Str str) = return $ text $ escapeString 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 (TeX str) = return empty
|
||||||
inlineToRST (HtmlInline 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 Space = return $ char ' '
|
||||||
inlineToRST (Link [Code str] (src, tit)) | src == str ||
|
inlineToRST (Link [Code str] (src, tit)) | src == str ||
|
||||||
src == "mailto:" ++ str = do
|
src == "mailto:" ++ str = do
|
||||||
|
|
|
@ -6,6 +6,9 @@ Pandoc Test Suite
|
||||||
:Author: Anonymous
|
:Author: Anonymous
|
||||||
:Date: July 17, 2006
|
:Date: July 17, 2006
|
||||||
|
|
||||||
|
.. role:: math(raw)
|
||||||
|
:format: html latex
|
||||||
|
|
||||||
This is a set of tests for pandoc. Most of them are adapted from
|
This is a set of tests for pandoc. Most of them are adapted from
|
||||||
John Gruber's markdown test suite.
|
John Gruber's markdown test suite.
|
||||||
|
|
||||||
|
@ -620,14 +623,14 @@ LaTeX
|
||||||
|
|
||||||
-
|
-
|
||||||
-
|
-
|
||||||
- $2+2=4$
|
- :math:`$2+2=4$`
|
||||||
- $x \in y$
|
- :math:`$x \in y$`
|
||||||
- $\alpha \wedge \omega$
|
- :math:`$\alpha \wedge \omega$`
|
||||||
- $223$
|
- :math:`$223$`
|
||||||
- $p$-Tree
|
- :math:`$p$`-Tree
|
||||||
- $\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$
|
- :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:
|
- 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:
|
These shouldn't be math:
|
||||||
|
|
||||||
|
|
Loading…
Reference in a new issue