diff options
author | John MacFarlane <jgm@berkeley.edu> | 2013-11-01 14:27:22 -0700 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2013-11-01 14:28:24 -0700 |
commit | 0d95c15e8316eb28128bdd4c9c2f98e29f13f564 (patch) | |
tree | 4f63a3a9f11686c286c2ca3e3f1414add92e6ff5 | |
parent | ab0ffe6549261313410207a0b5beba9284135962 (diff) | |
download | pandoc-0d95c15e8316eb28128bdd4c9c2f98e29f13f564.tar.gz |
TexMath: Export readTeXMath', which attends to display/inline.
Deprecate readTeXMath, and use readTeXMath' in all the writers.
Require texmath >= 0.6.5.
-rw-r--r-- | pandoc.cabal | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/TeXMath.hs | 24 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docbook.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docx.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Man.hs | 5 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/OpenDocument.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/RTF.hs | 2 | ||||
-rw-r--r-- | tests/writer.docbook | 2 | ||||
-rw-r--r-- | tests/writer.html | 2 | ||||
-rw-r--r-- | tests/writer.man | 2 | ||||
-rw-r--r-- | tests/writer.opendocument | 2 | ||||
-rw-r--r-- | tests/writer.rtf | 2 |
14 files changed, 38 insertions, 23 deletions
diff --git a/pandoc.cabal b/pandoc.cabal index 6f51bc110..7e7081900 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -215,7 +215,7 @@ Library old-locale >= 1 && < 1.1, time >= 1.2 && < 1.5, HTTP >= 4000.0.5 && < 4000.3, - texmath >= 0.6.4 && < 0.7, + texmath >= 0.6.5 && < 0.7, xml >= 1.3.12 && < 1.4, random >= 1 && < 1.1, extensible-exceptions >= 0.1 && < 0.2, diff --git a/src/Text/Pandoc/Readers/TeXMath.hs b/src/Text/Pandoc/Readers/TeXMath.hs index 1f7088f72..6bd617f7e 100644 --- a/src/Text/Pandoc/Readers/TeXMath.hs +++ b/src/Text/Pandoc/Readers/TeXMath.hs @@ -27,16 +27,30 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Conversion of TeX math to a list of 'Pandoc' inline elements. -} -module Text.Pandoc.Readers.TeXMath ( readTeXMath ) where +module Text.Pandoc.Readers.TeXMath ( readTeXMath, readTeXMath' ) where import Text.Pandoc.Definition import Text.TeXMath -- | Converts a raw TeX math formula to a list of 'Pandoc' inlines. --- Defaults to raw formula between @$@ characters if entire formula +-- Defaults to raw formula between @$@ or @$$@ characters if entire formula -- can't be converted. +readTeXMath' :: MathType + -> String -- ^ String to parse (assumes @'\n'@ line endings) + -> [Inline] +readTeXMath' mt inp = case texMathToPandoc dt inp of + Left _ -> [Str (delim ++ inp ++ delim)] + Right res -> res + where (dt, delim) = case mt of + DisplayMath -> (DisplayBlock, "$$") + InlineMath -> (DisplayInline, "$") + +{-# DEPRECATED readTeXMath "Use readTeXMath' from Text.Pandoc.JSON instead" #-} +-- | Converts a raw TeX math formula to a list of 'Pandoc' inlines. +-- Defaults to raw formula between @$@ characters if entire formula +-- can't be converted. (This is provided for backwards compatibility; +-- it is better to use @readTeXMath'@, which properly distinguishes +-- between display and inline math.) readTeXMath :: String -- ^ String to parse (assumes @'\n'@ line endings) -> [Inline] -readTeXMath inp = case texMathToPandoc DisplayInline inp of - Left _ -> [Str ("$" ++ inp ++ "$")] - Right res -> res +readTeXMath = readTeXMath' InlineMath diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 7c03c07dc..dad83d7bb 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -281,8 +281,8 @@ inlineToDocbook opts (Math t str) $ fixNS $ removeAttr r Left _ -> inlinesToDocbook opts - $ readTeXMath str - | otherwise = inlinesToDocbook opts $ readTeXMath str + $ readTeXMath' t str + | otherwise = inlinesToDocbook opts $ readTeXMath' t str where (dt, tagtype) = case t of InlineMath -> (DisplayInline,"inlineequation") DisplayMath -> (DisplayBlock,"informalequation") diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index 1214e7f8b..0fdea0a7a 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -669,7 +669,7 @@ inlineToOpenXML opts (Math mathType str) = do else DisplayInline case texMathToOMML displayType str of Right r -> return [r] - Left _ -> inlinesToOpenXML opts (readTeXMath str) + Left _ -> inlinesToOpenXML opts (readTeXMath' mathType str) inlineToOpenXML opts (Cite _ lst) = inlinesToOpenXML opts lst inlineToOpenXML opts (Code attrs str) = withTextProp (rStyle "VerbatimChar") diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 8a71c3a2e..c1cca291b 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -685,14 +685,14 @@ inlineToHtml opts inline = Right r -> return $ preEscapedString $ ppcElement conf r Left _ -> inlineListToHtml opts - (readTeXMath str) >>= return . + (readTeXMath' t str) >>= return . (H.span ! A.class_ "math") MathJax _ -> return $ H.span ! A.class_ "math" $ toHtml $ case t of InlineMath -> "\\(" ++ str ++ "\\)" DisplayMath -> "\\[" ++ str ++ "\\]" PlainMath -> do - x <- inlineListToHtml opts (readTeXMath str) + x <- inlineListToHtml opts (readTeXMath' t str) let m = H.span ! A.class_ "math" $ x let brtag = if writerHtml5 opts then H5.br else H.br return $ case t of diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index 642a002d6..b31cc2b70 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -330,9 +330,10 @@ inlineToMan opts (Cite _ lst) = inlineToMan _ (Code _ str) = return $ text $ "\\f[C]" ++ escapeCode str ++ "\\f[]" inlineToMan _ (Str str) = return $ text $ escapeString str -inlineToMan opts (Math InlineMath str) = inlineListToMan opts $ readTeXMath str +inlineToMan opts (Math InlineMath str) = + inlineListToMan opts $ readTeXMath' InlineMath str inlineToMan opts (Math DisplayMath str) = do - contents <- inlineListToMan opts $ readTeXMath str + contents <- inlineListToMan opts $ readTeXMath' DisplayMath str return $ cr <> text ".RS" $$ contents $$ text ".RE" inlineToMan _ (RawInline f str) | f == Format "man" = return $ text str diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 33cb110b5..56be709d8 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -45,7 +45,7 @@ import Text.Pandoc.Pretty import Control.Monad.State import qualified Data.Set as Set import Text.Pandoc.Writers.HTML (writeHtmlString) -import Text.Pandoc.Readers.TeXMath (readTeXMath) +import Text.Pandoc.Readers.TeXMath (readTeXMath') import Text.HTML.TagSoup (renderTags, parseTags, isTagText, Tag(..)) import Network.URI (isURI) import Data.Default @@ -697,7 +697,7 @@ inlineToMarkdown opts (Math InlineMath str) return $ "\\(" <> text str <> "\\)" | isEnabled Ext_tex_math_double_backslash opts = return $ "\\\\(" <> text str <> "\\\\)" - | otherwise = inlineListToMarkdown opts $ readTeXMath str + | otherwise = inlineListToMarkdown opts $ readTeXMath' InlineMath str inlineToMarkdown opts (Math DisplayMath str) | isEnabled Ext_tex_math_dollars opts = return $ "$$" <> text str <> "$$" @@ -706,7 +706,7 @@ inlineToMarkdown opts (Math DisplayMath str) | isEnabled Ext_tex_math_double_backslash opts = return $ "\\\\[" <> text str <> "\\\\]" | otherwise = (\x -> cr <> x <> cr) `fmap` - inlineListToMarkdown opts (readTeXMath str) + inlineListToMarkdown opts (readTeXMath' DisplayMath str) inlineToMarkdown opts (RawInline f str) | f == "html" || f == "markdown" || (isEnabled Ext_raw_tex opts && (f == "latex" || f == "tex")) = diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index 206be7133..b38d250aa 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -374,7 +374,7 @@ inlineToOpenDocument o ils | SmallCaps l <- ils = withTextStyle SmallC $ inlinesToOpenDocument o l | Quoted t l <- ils = inQuotes t <$> inlinesToOpenDocument o l | Code _ s <- ils = withTextStyle Pre $ inTextStyle $ preformatted s - | Math _ s <- ils = inlinesToOpenDocument o (readTeXMath s) + | Math t s <- ils = inlinesToOpenDocument o (readTeXMath' t s) | Cite _ l <- ils = inlinesToOpenDocument o l | RawInline f s <- ils = if f == "opendocument" || f == "html" then withTextStyle Pre $ inTextStyle $ preformatted s diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index cb5fb3232..fb935fa6a 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -324,7 +324,7 @@ inlineToRTF (Quoted DoubleQuote lst) = "\\u8220\"" ++ (inlineListToRTF lst) ++ "\\u8221\"" inlineToRTF (Code _ str) = "{\\f1 " ++ (codeStringToRTF str) ++ "}" inlineToRTF (Str str) = stringToRTF str -inlineToRTF (Math _ str) = inlineListToRTF $ readTeXMath str +inlineToRTF (Math t str) = inlineListToRTF $ readTeXMath' t str inlineToRTF (Cite _ lst) = inlineListToRTF lst inlineToRTF (RawInline f str) | f == Format "rtf" = str diff --git a/tests/writer.docbook b/tests/writer.docbook index e427d8ffc..1d4da4842 100644 --- a/tests/writer.docbook +++ b/tests/writer.docbook @@ -1084,7 +1084,7 @@ These should not be escaped: \$ \\ \> \[ \{ <listitem> <para> Here’s some display math: - $\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$ + $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$ </para> </listitem> <listitem> diff --git a/tests/writer.html b/tests/writer.html index e8e619f44..e0d1a3b25 100644 --- a/tests/writer.html +++ b/tests/writer.html @@ -439,7 +439,7 @@ Blah <li><span class="math"><em>α</em> ∧ <em>ω</em></span></li> <li><span class="math">223</span></li> <li><span class="math"><em>p</em></span>-Tree</li> -<li>Here’s some display math: <br /><span class="math">$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span><br /></li> +<li>Here’s some display math: <br /><span class="math">$$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$</span><br /></li> <li>Here’s one that has a line break in it: <span class="math"><em>α</em> + <em>ω</em> × <em>x</em><sup>2</sup></span>.</li> </ul> <p>These shouldn’t be math:</p> diff --git a/tests/writer.man b/tests/writer.man index 54baaf791..aab588f9c 100644 --- a/tests/writer.man +++ b/tests/writer.man @@ -572,7 +572,7 @@ Ellipses\&...and\&...and\&.... .IP \[bu] 2 Here's some display math: .RS -$\\frac{d}{dx}f(x)=\\lim_{h\\to 0}\\frac{f(x+h)\-f(x)}{h}$ +$$\\frac{d}{dx}f(x)=\\lim_{h\\to 0}\\frac{f(x+h)\-f(x)}{h}$$ .RE .IP \[bu] 2 Here's one that has a line break in it: diff --git a/tests/writer.opendocument b/tests/writer.opendocument index d5eec1b60..b3888e34d 100644 --- a/tests/writer.opendocument +++ b/tests/writer.opendocument @@ -1418,7 +1418,7 @@ five.</text:p> </text:list-item> <text:list-item> <text:p text:style-name="P51">Here’s some display math: - $\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</text:p> + $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$</text:p> </text:list-item> <text:list-item> <text:p text:style-name="P51">Here’s one that has a line break in it: diff --git a/tests/writer.rtf b/tests/writer.rtf index 42c13d8c7..954d95cc4 100644 --- a/tests/writer.rtf +++ b/tests/writer.rtf @@ -269,7 +269,7 @@ quoted link {\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab {\i \u945?}\u8197?\u8743?\u8197?{\i \u969?}\par} {\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab 223\par} {\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab {\i p}-Tree\par} -{\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab Here\u8217's some display math: $\\frac\{d\}\{dx\}f(x)=\\lim_\{h\\to 0\}\\frac\{f(x+h)-f(x)\}\{h\}$\par} +{\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab Here\u8217's some display math: $$\\frac\{d\}\{dx\}f(x)=\\lim_\{h\\to 0\}\\frac\{f(x+h)-f(x)\}\{h\}$$\par} {\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab Here\u8217's one that has a line break in it: {\i \u945?}\u8197?+\u8197?{\i \u969?}\u8197?\u215?\u8197?{\i x}{\super 2}.\sa180\par} {\pard \ql \f0 \sa180 \li0 \fi0 These shouldn\u8217't be math:\par} {\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab To get the famous equation, write {\f1 $e = mc^2$}.\par} |