aboutsummaryrefslogtreecommitdiff
path: root/Text/Pandoc/Writers
diff options
context:
space:
mode:
Diffstat (limited to 'Text/Pandoc/Writers')
-rw-r--r--Text/Pandoc/Writers/ConTeXt.hs3
-rw-r--r--Text/Pandoc/Writers/Docbook.hs2
-rw-r--r--Text/Pandoc/Writers/HTML.hs24
-rw-r--r--Text/Pandoc/Writers/LaTeX.hs3
-rw-r--r--Text/Pandoc/Writers/Man.hs5
-rw-r--r--Text/Pandoc/Writers/Markdown.hs3
-rw-r--r--Text/Pandoc/Writers/MediaWiki.hs2
-rw-r--r--Text/Pandoc/Writers/OpenDocument.hs2
-rw-r--r--Text/Pandoc/Writers/RST.hs6
-rw-r--r--Text/Pandoc/Writers/RTF.hs2
-rw-r--r--Text/Pandoc/Writers/Texinfo.hs5
11 files changed, 36 insertions, 21 deletions
diff --git a/Text/Pandoc/Writers/ConTeXt.hs b/Text/Pandoc/Writers/ConTeXt.hs
index 62e205ee5..7f5af4191 100644
--- a/Text/Pandoc/Writers/ConTeXt.hs
+++ b/Text/Pandoc/Writers/ConTeXt.hs
@@ -272,7 +272,8 @@ inlineToConTeXt EmDash = return $ text "---"
inlineToConTeXt EnDash = return $ text "--"
inlineToConTeXt Ellipses = return $ text "\\ldots{}"
inlineToConTeXt (Str str) = return $ text $ stringToConTeXt str
-inlineToConTeXt (Math str) = return $ char '$' <> text str <> char '$'
+inlineToConTeXt (Math InlineMath str) = return $ char '$' <> text str <> char '$'
+inlineToConTeXt (Math DisplayMath str) = return $ text "\\startformula " <> text str <> text " \\stopformula"
inlineToConTeXt (TeX str) = return $ text str
inlineToConTeXt (HtmlInline _) = return empty
inlineToConTeXt (LineBreak) = return $ text "\\crlf\n"
diff --git a/Text/Pandoc/Writers/Docbook.hs b/Text/Pandoc/Writers/Docbook.hs
index 5b433c434..9ed4e808f 100644
--- a/Text/Pandoc/Writers/Docbook.hs
+++ b/Text/Pandoc/Writers/Docbook.hs
@@ -236,7 +236,7 @@ inlineToDocbook _ EmDash = text "&#8212;"
inlineToDocbook _ EnDash = text "&#8211;"
inlineToDocbook _ (Code str) =
inTagsSimple "literal" $ text (escapeStringForXML str)
-inlineToDocbook opts (Math str) = inlinesToDocbook opts $ readTeXMath str
+inlineToDocbook opts (Math _ str) = inlinesToDocbook opts $ readTeXMath str
inlineToDocbook _ (TeX _) = empty
inlineToDocbook _ (HtmlInline _) = empty
inlineToDocbook _ LineBreak = text $ "<literallayout></literallayout>"
diff --git a/Text/Pandoc/Writers/HTML.hs b/Text/Pandoc/Writers/HTML.hs
index e5ed4468e..4af644a91 100644
--- a/Text/Pandoc/Writers/HTML.hs
+++ b/Text/Pandoc/Writers/HTML.hs
@@ -30,7 +30,7 @@ Conversion of 'Pandoc' documents to HTML.
-}
module Text.Pandoc.Writers.HTML ( writeHtml , writeHtmlString ) where
import Text.Pandoc.Definition
-import Text.Pandoc.ASCIIMathML
+import Text.Pandoc.LaTeXMathML
import Text.Pandoc.CharacterReferences ( decodeCharacterReferences )
import Text.Pandoc.Shared
import Text.Pandoc.Readers.TeXMath
@@ -123,9 +123,9 @@ writeHtml opts (Pandoc (Meta tit authors date) blocks) =
'\n':(unlines $ S.toList cssLines)
math = if stMath newstate
then case writerHTMLMathMethod opts of
- ASCIIMathML Nothing ->
- primHtml asciiMathMLScript
- ASCIIMathML (Just url) ->
+ LaTeXMathML Nothing ->
+ primHtml latexMathMLScript
+ LaTeXMathML (Just url) ->
script !
[src url, thetype "text/javascript"] $
noHtml
@@ -268,7 +268,7 @@ inlineListToIdentifier' (x:xs) =
Apostrophe -> ""
Ellipses -> ""
LineBreak -> "-"
- Math _ -> ""
+ Math _ _ -> ""
TeX _ -> ""
HtmlInline _ -> ""
Link lst _ -> inlineListToIdentifier' lst
@@ -455,10 +455,13 @@ inlineToHtml opts inline =
primHtmlChar "rdquo")
in do contents <- inlineListToHtml opts lst
return $ leftQuote +++ contents +++ rightQuote
- (Math str) -> modify (\st -> st {stMath = True}) >>
+ (Math t str) ->
+ modify (\st -> st {stMath = True}) >>
(case writerHTMLMathMethod opts of
- ASCIIMathML _ ->
- return $ stringToHtml ("$" ++ str ++ "$")
+ LaTeXMathML _ ->
+ return $ if t == InlineMath
+ then primHtml ("$" ++ str ++ "$")
+ else primHtml ("$$" ++ str ++ "$$")
MimeTeX url ->
return $ image ! [src (url ++ "?" ++ str),
alt str, title str]
@@ -467,7 +470,10 @@ inlineToHtml opts inline =
PlainMath ->
inlineListToHtml opts (readTeXMath str) >>=
return . (thespan ! [theclass "math"]))
- (TeX _) -> return noHtml
+ (TeX str) -> case writerHTMLMathMethod opts of
+ LaTeXMathML _ -> do modify (\st -> st {stMath = True})
+ return $ primHtml str
+ _ -> return noHtml
(HtmlInline str) -> return $ primHtml str
(Link [Code str] (s,_)) | "mailto:" `isPrefixOf` s ->
return $ obfuscateLink opts str s
diff --git a/Text/Pandoc/Writers/LaTeX.hs b/Text/Pandoc/Writers/LaTeX.hs
index 89170dee1..a13c51b30 100644
--- a/Text/Pandoc/Writers/LaTeX.hs
+++ b/Text/Pandoc/Writers/LaTeX.hs
@@ -299,7 +299,8 @@ inlineToLaTeX EmDash = return $ text "---"
inlineToLaTeX EnDash = return $ text "--"
inlineToLaTeX Ellipses = return $ text "\\ldots{}"
inlineToLaTeX (Str str) = return $ text $ stringToLaTeX str
-inlineToLaTeX (Math str) = return $ char '$' <> text str <> char '$'
+inlineToLaTeX (Math InlineMath str) = return $ char '$' <> text str <> char '$'
+inlineToLaTeX (Math DisplayMath str) = return $ text "\\[" <> text str <> text "\\]"
inlineToLaTeX (TeX str) = return $ text str
inlineToLaTeX (HtmlInline _) = return empty
inlineToLaTeX (LineBreak) = return $ text "\\\\"
diff --git a/Text/Pandoc/Writers/Man.hs b/Text/Pandoc/Writers/Man.hs
index 9037c24af..0bd6b92ef 100644
--- a/Text/Pandoc/Writers/Man.hs
+++ b/Text/Pandoc/Writers/Man.hs
@@ -272,7 +272,10 @@ inlineToMan _ Ellipses = return $ text "\\&..."
inlineToMan _ (Code str) =
return $ text $ "\\f[B]" ++ escapeCode str ++ "\\f[]"
inlineToMan _ (Str str) = return $ text $ escapeString str
-inlineToMan opts (Math str) = inlineToMan opts (Code str)
+inlineToMan opts (Math InlineMath str) = inlineToMan opts (Code str)
+inlineToMan opts (Math DisplayMath str) = do
+ contents <- inlineToMan opts (Code str)
+ return $ text ".RS" $$ contents $$ text ".RE"
inlineToMan _ (TeX _) = return empty
inlineToMan _ (HtmlInline str) = return $ text $ escapeCode str
inlineToMan _ (LineBreak) = return $ text "\n.PD 0\n.P\n.PD\n"
diff --git a/Text/Pandoc/Writers/Markdown.hs b/Text/Pandoc/Writers/Markdown.hs
index 7c360bec2..d8ad8454f 100644
--- a/Text/Pandoc/Writers/Markdown.hs
+++ b/Text/Pandoc/Writers/Markdown.hs
@@ -337,7 +337,8 @@ inlineToMarkdown _ (Code str) =
spacer = if (longest == 0) then "" else " " in
return $ text (marker ++ spacer ++ str ++ spacer ++ marker)
inlineToMarkdown _ (Str str) = return $ text $ escapeString str
-inlineToMarkdown _ (Math str) = return $ char '$' <> text str <> char '$'
+inlineToMarkdown _ (Math InlineMath str) = return $ char '$' <> text str <> char '$'
+inlineToMarkdown _ (Math DisplayMath str) = return $ text "$$" <> text str <> text "$$"
inlineToMarkdown _ (TeX str) = return $ text str
inlineToMarkdown _ (HtmlInline str) = return $ text str
inlineToMarkdown _ (LineBreak) = return $ text " \n"
diff --git a/Text/Pandoc/Writers/MediaWiki.hs b/Text/Pandoc/Writers/MediaWiki.hs
index 97d9d00c6..7d43c6fc4 100644
--- a/Text/Pandoc/Writers/MediaWiki.hs
+++ b/Text/Pandoc/Writers/MediaWiki.hs
@@ -357,7 +357,7 @@ inlineToMediaWiki _ (Code str) =
inlineToMediaWiki _ (Str str) = return $ escapeString str
-inlineToMediaWiki _ (Math str) = return $ "<math>" ++ str ++ "</math>"
+inlineToMediaWiki _ (Math _ str) = return $ "<math>" ++ str ++ "</math>"
-- note: str should NOT be escaped
inlineToMediaWiki _ (TeX _) = return ""
diff --git a/Text/Pandoc/Writers/OpenDocument.hs b/Text/Pandoc/Writers/OpenDocument.hs
index 70aab92f1..875ab5fa8 100644
--- a/Text/Pandoc/Writers/OpenDocument.hs
+++ b/Text/Pandoc/Writers/OpenDocument.hs
@@ -379,7 +379,7 @@ inlineToOpenDocument o ils
| SmallCaps l <- ils = withTextStyle SmallC $ inlinesToOpenDocument o l
| Quoted t l <- ils = inQuotes t <$> inlinesToOpenDocument o l
| Code s <- ils = preformatted s
- | Math s <- ils = inlinesToOpenDocument o (readTeXMath s)
+ | Math _ s <- ils = inlinesToOpenDocument o (readTeXMath s)
| Cite _ l <- ils = inlinesToOpenDocument o l
| TeX s <- ils = preformatted s
| HtmlInline s <- ils = preformatted s
diff --git a/Text/Pandoc/Writers/RST.hs b/Text/Pandoc/Writers/RST.hs
index 9215f051d..de65bcf0e 100644
--- a/Text/Pandoc/Writers/RST.hs
+++ b/Text/Pandoc/Writers/RST.hs
@@ -291,14 +291,16 @@ inlineToRST Apostrophe = return $ char '\''
inlineToRST Ellipses = return $ text "..."
inlineToRST (Code str) = return $ text $ "``" ++ str ++ "``"
inlineToRST (Str str) = return $ text $ escapeString str
-inlineToRST (Math str) = do
+inlineToRST (Math t 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 ++ "$`"
+ return $ if t == InlineMath
+ then text $ ":math:`$" ++ str ++ "$`"
+ else text $ ":math:`$$" ++ str ++ "$$`"
inlineToRST (TeX _) = return empty
inlineToRST (HtmlInline _) = return empty
inlineToRST (LineBreak) = do
diff --git a/Text/Pandoc/Writers/RTF.hs b/Text/Pandoc/Writers/RTF.hs
index d0fbfb53a..e31a162a5 100644
--- a/Text/Pandoc/Writers/RTF.hs
+++ b/Text/Pandoc/Writers/RTF.hs
@@ -275,7 +275,7 @@ inlineToRTF EmDash = "\\u8212-"
inlineToRTF EnDash = "\\u8211-"
inlineToRTF (Code str) = "{\\f1 " ++ (codeStringToRTF str) ++ "}"
inlineToRTF (Str str) = stringToRTF str
-inlineToRTF (Math str) = inlineListToRTF $ readTeXMath str
+inlineToRTF (Math _ str) = inlineListToRTF $ readTeXMath str
inlineToRTF (Cite _ lst) = inlineListToRTF lst
inlineToRTF (TeX _) = ""
inlineToRTF (HtmlInline _) = ""
diff --git a/Text/Pandoc/Writers/Texinfo.hs b/Text/Pandoc/Writers/Texinfo.hs
index d0e134346..305a1a8d0 100644
--- a/Text/Pandoc/Writers/Texinfo.hs
+++ b/Text/Pandoc/Writers/Texinfo.hs
@@ -30,6 +30,7 @@ Conversion of 'Pandoc' format into Texinfo.
module Text.Pandoc.Writers.Texinfo ( writeTexinfo ) where
import Text.Pandoc.Definition
import Text.Pandoc.Shared
+import Text.Pandoc.Readers.TeXMath
import Text.Printf ( printf )
import Data.List ( isSuffixOf )
import Data.Char ( chr, ord )
@@ -364,7 +365,7 @@ inlineForNode EnDash = return $ text "--"
inlineForNode Apostrophe = return $ char '\''
inlineForNode Ellipses = return $ text "..."
inlineForNode LineBreak = return empty
-inlineForNode (Math _) = return empty
+inlineForNode (Math _ str) = inlineListForNode $ readTeXMath str
inlineForNode (TeX _) = return empty
inlineForNode (HtmlInline _) = return empty
inlineForNode (Link lst _) = inlineListForNode lst
@@ -437,7 +438,7 @@ inlineToTexinfo EmDash = return $ text "---"
inlineToTexinfo EnDash = return $ text "--"
inlineToTexinfo Ellipses = return $ text "@dots{}"
inlineToTexinfo (Str str) = return $ text (stringToTexinfo str)
-inlineToTexinfo (Math str) = return $ inCmd "math" $ text str
+inlineToTexinfo (Math _ str) = return $ inCmd "math" $ text str
inlineToTexinfo (TeX str) = return $ text "@tex" $$ text str $$ text "@end tex"
inlineToTexinfo (HtmlInline _) = return empty
inlineToTexinfo (LineBreak) = return $ text "@*"