diff options
-rw-r--r-- | README | 24 | ||||
-rw-r--r-- | Text/Pandoc/Readers/TeXMath.hs | 218 | ||||
-rw-r--r-- | Text/Pandoc/Writers/Docbook.hs | 3 | ||||
-rw-r--r-- | Text/Pandoc/Writers/HTML.hs | 19 | ||||
-rw-r--r-- | Text/Pandoc/Writers/Man.hs | 5 | ||||
-rw-r--r-- | Text/Pandoc/Writers/RST.hs | 7 | ||||
-rw-r--r-- | Text/Pandoc/Writers/RTF.hs | 3 | ||||
-rw-r--r-- | pandoc.cabal | 1 | ||||
-rw-r--r-- | pandoc.cabal.ghc66 | 1 | ||||
-rw-r--r-- | tests/s5.basic.html | 28 | ||||
-rw-r--r-- | tests/s5.fragment.html | 28 | ||||
-rw-r--r-- | tests/s5.inserts.html | 28 | ||||
-rw-r--r-- | tests/writer.docbook | 14 | ||||
-rw-r--r-- | tests/writer.html | 58 | ||||
-rw-r--r-- | tests/writer.man | 14 | ||||
-rw-r--r-- | tests/writer.rtf | 14 |
16 files changed, 408 insertions, 57 deletions
@@ -846,12 +846,23 @@ closing $ must have a character immediately to its left. Thus, you need to enclose text in literal $ characters, backslash-escape them and they won't be treated as math delimiters. -TeX math will be printed in all output formats. In Markdown, LaTeX, and -ConTeXt output, it will appear between $ characters, so that it may be -treated as math. In HTML and S5 output, there are four possible ways -to display math: +TeX math will be printed in all output formats. In Markdown, +reStructuredText, LaTeX, and ConTeXt output, it will appear verbatim +between $ characters. -1. The default is to display TeX math verbatim. +In groff man output, it will be rendered verbatim without $'s. + +In RTF and Docbook output, it will be rendered, as far as possible, +using unicode characters, and will otherwise appear verbatim. Unknown +commands and symbols, and commands that cannot be dealt with this way +(like `\frac`), will be rendered verbatim. So the results may be a mix +of raw TeX code and properly rendered unicode math. + +In HTML and S5 output, the way math is rendered will depend on the +command-line options selected: + +1. The default is to render TeX math as far as possible using unicode + characters, as with RTF and Docbook output. 2. If the `--asciimathml` option is used, TeX math will be displayed between $ characters, as in LaTeX, and the [ASCIIMathML] script will @@ -877,9 +888,6 @@ to display math: gladtex -d myfile-images myfile.htex # produces myfile.html # and images in myfile-images -In other output formats, TeX math will appear verbatim, with no enclosing -$'s. - Inline TeX ---------- diff --git a/Text/Pandoc/Readers/TeXMath.hs b/Text/Pandoc/Readers/TeXMath.hs new file mode 100644 index 000000000..918bb0670 --- /dev/null +++ b/Text/Pandoc/Readers/TeXMath.hs @@ -0,0 +1,218 @@ +{- +Copyright (C) 2007 John MacFarlane <jgm@berkeley.edu> + +This program is free software; you can redistribute it and/or modify +it under the terms of the GNU General Public License as published by +the Free Software Foundation; either version 2 of the License, or +(at your option) any later version. + +This program is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +GNU General Public License for more details. + +You should have received a copy of the GNU General Public License +along with this program; if not, write to the Free Software +Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA +-} + +{- | + Module : Text.Pandoc.Readers.TeXMath + Copyright : Copyright (C) 2007 John MacFarlane + License : GNU GPL, version 2 or above + + Maintainer : John MacFarlane <jgm@berkeley.edu> + Stability : alpha + Portability : portable + +Conversion of TeX math to a list of 'Pandoc' inline elements. +-} +module Text.Pandoc.Readers.TeXMath ( + readTeXMath + ) where + +import Text.ParserCombinators.Parsec +import Text.Pandoc.UTF8 +import Text.Pandoc.Definition +import Text.Pandoc.Shared + +-- | Converts a string of raw TeX math to a list of 'Pandoc' inlines. +readTeXMath :: String -> [Inline] +readTeXMath inp = case parse teXMath "input" inp of + Left err -> error $ "\nError:\n" ++ show err + Right res -> res + +teXMath = manyTill mathPart eof >>= return . concat + +mathPart = whitespace <|> superscript <|> subscript <|> symbol <|> + argument <|> plain <|> misc + +whitespace = many1 space >> return [] + +symbol = try $ do + char '\\' + res <- many1 letter + case lookup res teXsymbols of + Just m -> return [Str m] + Nothing -> return [Str $ "\\" ++ res] + +argument = try $ do + char '{' + res <- many mathPart + char '}' + return $ if null res + then [Str " "] + else [Str "{"] ++ concat res ++ [Str "}"] + +plain = do + res <- many1 alphaNum + return $ [Emph [Str res]] + +misc = do + res <- noneOf "{}\\" + return [Str [res]] + +scriptArg = try $ do + (try (do{char '{'; r <- many mathPart; char '}'; return $ concat r})) + <|> symbol + <|> (do{c <- (letter <|> digit); return [Str [c]]}) + +superscript = try $ do + char '^' + arg <- scriptArg + return [Superscript arg] + +subscript = try $ do + char '_' + arg <- scriptArg + return [Subscript arg] + +withThinSpace str = "\x2009" ++ str ++ "\x2009" + +teXsymbols = + [("alpha","\x3B1") + ,("beta", "\x3B2") + ,("chi", "\x3C7") + ,("delta", "\x3B4") + ,("Delta", "\x394") + ,("epsilon", "\x3B5") + ,("varepsilon", "\x25B") + ,("eta", "\x3B7") + ,("gamma", "\x3B3") + ,("Gamma", "\x393") + ,("iota", "\x3B9") + ,("kappa", "\x3BA") + ,("lambda", "\x3BB") + ,("Lambda", "\x39B") + ,("mu", "\x3BC") + ,("nu", "\x3BD") + ,("omega", "\x3C9") + ,("Omega", "\x3A9") + ,("phi", "\x3C6") + ,("varphi", "\x3D5") + ,("Phi", "\x3A6") + ,("pi", "\x3C0") + ,("Pi", "\x3A0") + ,("psi", "\x3C8") + ,("Psi", "\x3A8") + ,("rho", "\x3C1") + ,("sigma", "\x3C3") + ,("Sigma", "\x3A3") + ,("tau", "\x3C4") + ,("theta", "\x3B8") + ,("vartheta", "\x3D1") + ,("Theta", "\x398") + ,("upsilon", "\x3C5") + ,("xi", "\x3BE") + ,("Xi", "\x39E") + ,("zeta", "\x3B6") + ,("ne", "\x2260") + ,("lt", withThinSpace "<") + ,("le", withThinSpace "\x2264") + ,("leq", withThinSpace "\x2264") + ,("ge", withThinSpace "\x2265") + ,("geq", withThinSpace "\x2265") + ,("prec", withThinSpace "\x227A") + ,("succ", withThinSpace "\x227B") + ,("preceq", withThinSpace "\x2AAF") + ,("succeq", withThinSpace "\x2AB0") + ,("in", withThinSpace "\x2208") + ,("notin", withThinSpace "\x2209") + ,("subset", withThinSpace "\x2282") + ,("supset", withThinSpace "\x2283") + ,("subseteq", withThinSpace "\x2286") + ,("supseteq", withThinSpace "\x2287") + ,("equiv", withThinSpace "\x2261") + ,("cong", withThinSpace "\x2245") + ,("approx", withThinSpace "\x2248") + ,("propto", withThinSpace "\x221D") + ,("cdot", withThinSpace "\x22C5") + ,("star", withThinSpace "\x22C6") + ,("backslash", "\\") + ,("times", withThinSpace "\x00D7") + ,("divide", withThinSpace "\x00F7") + ,("circ", withThinSpace "\x2218") + ,("oplus", withThinSpace "\x2295") + ,("otimes", withThinSpace "\x2297") + ,("odot", withThinSpace "\x2299") + ,("sum", "\x2211") + ,("prod", "\x220F") + ,("wedge", withThinSpace "\x2227") + ,("bigwedge", withThinSpace "\x22C0") + ,("vee", withThinSpace "\x2228") + ,("bigvee", withThinSpace "\x22C1") + ,("cap", withThinSpace "\x2229") + ,("bigcap", withThinSpace "\x22C2") + ,("cup", withThinSpace "\x222A") + ,("bigcup", withThinSpace "\x22C3") + ,("neg", "\x00AC") + ,("implies", withThinSpace "\x21D2") + ,("iff", withThinSpace "\x21D4") + ,("forall", "\x2200") + ,("exists", "\x2203") + ,("bot", "\x22A5") + ,("top", "\x22A4") + ,("vdash", "\x22A2") + ,("models", withThinSpace "\x22A8") + ,("uparrow", "\x2191") + ,("downarrow", "\x2193") + ,("rightarrow", withThinSpace "\x2192") + ,("to", withThinSpace "\x2192") + ,("rightarrowtail", "\x21A3") + ,("twoheadrightarrow", withThinSpace "\x21A0") + ,("twoheadrightarrowtail", withThinSpace "\x2916") + ,("mapsto", withThinSpace "\x21A6") + ,("leftarrow", withThinSpace "\x2190") + ,("leftrightarrow", withThinSpace "\x2194") + ,("Rightarrow", withThinSpace "\x21D2") + ,("Leftarrow", withThinSpace "\x21D0") + ,("Leftrightarrow", withThinSpace "\x21D4") + ,("partial", "\x2202") + ,("nabla", "\x2207") + ,("pm", "\x00B1") + ,("emptyset", "\x2205") + ,("infty", "\x221E") + ,("aleph", "\x2135") + ,("ldots", "...") + ,("therefore", "\x2234") + ,("angle", "\x2220") + ,("quad", "\x00A0\x00A0") + ,("cdots", "\x22EF") + ,("vdots", "\x22EE") + ,("ddots", "\x22F1") + ,("diamond", "\x22C4") + ,("Box", "\x25A1") + ,("lfloor", "\x230A") + ,("rfloor", "\x230B") + ,("lceiling", "\x2308") + ,("rceiling", "\x2309") + ,("langle", "\x2329") + ,("rangle", "\x232A") + ,("{", "{") + ,("}", "}") + ,("[", "[") + ,("]", "]") + ,("|", "|") + ,("||", "||") + ] + diff --git a/Text/Pandoc/Writers/Docbook.hs b/Text/Pandoc/Writers/Docbook.hs index 2cad0ca39..f0fde18a4 100644 --- a/Text/Pandoc/Writers/Docbook.hs +++ b/Text/Pandoc/Writers/Docbook.hs @@ -30,6 +30,7 @@ Conversion of 'Pandoc' documents to Docbook XML. module Text.Pandoc.Writers.Docbook ( writeDocbook) where import Text.Pandoc.Definition import Text.Pandoc.Shared +import Text.Pandoc.Readers.TeXMath import Data.List ( isPrefixOf, drop ) import Text.PrettyPrint.HughesPJ hiding ( Str ) @@ -274,7 +275,7 @@ inlineToDocbook opts EmDash = text "—" inlineToDocbook opts EnDash = text "–" inlineToDocbook opts (Code str) = inTagsSimple "literal" $ text (escapeStringForXML str) -inlineToDocbook opts (Math str) = inlineToDocbook opts (Code str) +inlineToDocbook opts (Math str) = inlinesToDocbook opts $ readTeXMath str inlineToDocbook opts (TeX str) = empty inlineToDocbook opts (HtmlInline str) = empty inlineToDocbook opts LineBreak = text $ "<literallayout></literallayout>" diff --git a/Text/Pandoc/Writers/HTML.hs b/Text/Pandoc/Writers/HTML.hs index 881e3c07c..70814eb15 100644 --- a/Text/Pandoc/Writers/HTML.hs +++ b/Text/Pandoc/Writers/HTML.hs @@ -32,6 +32,7 @@ import Text.Pandoc.Definition import Text.Pandoc.ASCIIMathML import Text.Pandoc.CharacterReferences ( decodeCharacterReferences ) import Text.Pandoc.Shared +import Text.Pandoc.Readers.TeXMath import Text.Regex ( mkRegex, matchRegex ) import Numeric ( showHex ) import Data.Char ( ord, toLower ) @@ -401,16 +402,16 @@ inlineToHtml opts inline = in do contents <- inlineListToHtml opts lst return $ leftQuote +++ contents +++ rightQuote (Math str) -> modify (\st -> st {stMath = True}) >> - (return $ case writerHTMLMathMethod opts of - ASCIIMathML _ -> - stringToHtml ("$" ++ str ++ "$") - MimeTeX url -> - image ! [src (url ++ "?" ++ str), + (case writerHTMLMathMethod opts of + ASCIIMathML _ -> + return $ stringToHtml ("$" ++ str ++ "$") + MimeTeX url -> + return $ image ! [src (url ++ "?" ++ str), alt str, title str] - GladTeX -> - tag "eq" << str - PlainMath -> - stringToHtml str) + GladTeX -> + return $ tag "eq" << str + PlainMath -> + inlineListToHtml opts (readTeXMath str)) (TeX str) -> return noHtml (HtmlInline str) -> return $ primHtml str (Link [Code str] (src,tit)) | "mailto:" `isPrefixOf` src -> diff --git a/Text/Pandoc/Writers/Man.hs b/Text/Pandoc/Writers/Man.hs index 899cd9f57..bd170f6ba 100644 --- a/Text/Pandoc/Writers/Man.hs +++ b/Text/Pandoc/Writers/Man.hs @@ -30,7 +30,8 @@ Conversion of 'Pandoc' documents to groff man page format. -} module Text.Pandoc.Writers.Man ( writeMan) where import Text.Pandoc.Definition -import Text.Pandoc.Shared +import Text.Pandoc.Shared +import Text.Pandoc.Readers.TeXMath import Text.Printf ( printf ) import Data.List ( isPrefixOf, drop, nub, intersperse ) import Text.PrettyPrint.HughesPJ hiding ( Str ) @@ -268,7 +269,7 @@ inlineToMan opts Ellipses = return $ text "\\&..." inlineToMan opts (Code str) = return $ text $ "\\f[B]" ++ escapeCode str ++ "\\f[]" inlineToMan opts (Str str) = return $ text $ escapeString str -inlineToMan opts (Math str) = return $ text $ escapeCode str +inlineToMan opts (Math str) = inlineToMan opts (Code str) inlineToMan opts (TeX str) = return empty inlineToMan opts (HtmlInline str) = return $ text $ escapeCode str inlineToMan opts (LineBreak) = return $ text "\n.PD 0\n.P\n.PD\n" diff --git a/Text/Pandoc/Writers/RST.hs b/Text/Pandoc/Writers/RST.hs index 4a7242d1f..7dd99f2ea 100644 --- a/Text/Pandoc/Writers/RST.hs +++ b/Text/Pandoc/Writers/RST.hs @@ -32,6 +32,7 @@ reStructuredText: <http://docutils.sourceforge.net/rst.html> module Text.Pandoc.Writers.RST ( writeRST) where import Text.Pandoc.Definition import Text.Pandoc.Shared +import Text.Pandoc.Readers.TeXMath import Text.Pandoc.Blocks import Data.List ( isPrefixOf, isSuffixOf, drop, intersperse ) import Text.PrettyPrint.HughesPJ hiding ( Str ) @@ -151,10 +152,6 @@ blockToRST :: WriterOptions -- ^ Options -> State WriterState Doc blockToRST opts Null = return empty blockToRST opts (Plain inlines) = wrappedRST opts inlines -blockToRST opts (Para [Math str]) = - let str' = if "\n" `isSuffixOf` str then str ++ "\n" else str ++ "\n\n" in - return $ hang (text "\n.. raw:: latex\n") 3 $ text "\\[" <> - (vcat $ map text (lines str')) <> text "\\]" blockToRST opts (Para inlines) = do contents <- wrappedRST opts inlines return $ contents <> text "\n" @@ -286,7 +283,7 @@ inlineToRST opts Apostrophe = return $ char '\'' inlineToRST opts Ellipses = return $ text "..." inlineToRST opts (Code str) = return $ text $ "``" ++ str ++ "``" inlineToRST opts (Str str) = return $ text $ escapeString str -inlineToRST opts (Math str) = return $ char '$' <> text str <> char '$' +inlineToRST opts (Math str) = return $ text $ "$" ++ str ++ "$" inlineToRST opts (TeX str) = return empty inlineToRST opts (HtmlInline str) = return empty inlineToRST opts (LineBreak) = return $ char ' ' -- RST doesn't have linebreaks diff --git a/Text/Pandoc/Writers/RTF.hs b/Text/Pandoc/Writers/RTF.hs index 9c5e6cbd3..64d73a30f 100644 --- a/Text/Pandoc/Writers/RTF.hs +++ b/Text/Pandoc/Writers/RTF.hs @@ -30,6 +30,7 @@ Conversion of 'Pandoc' documents to RTF (rich text format). module Text.Pandoc.Writers.RTF ( writeRTF ) where import Text.Pandoc.Definition import Text.Pandoc.Shared +import Text.Pandoc.Readers.TeXMath import Text.Regex ( matchRegexAll, mkRegex ) import Data.List ( isSuffixOf ) import Data.Char ( ord ) @@ -272,7 +273,7 @@ inlineToRTF EmDash = "\\u8212-" inlineToRTF EnDash = "\\u8211-" inlineToRTF (Code str) = "{\\f1 " ++ (codeStringToRTF str) ++ "} " inlineToRTF (Str str) = stringToRTF str -inlineToRTF (Math str) = latexToRTF str +inlineToRTF (Math str) = inlineListToRTF $ readTeXMath str inlineToRTF (TeX str) = "" inlineToRTF (HtmlInline str) = "" inlineToRTF (LineBreak) = "\\line " diff --git a/pandoc.cabal b/pandoc.cabal index d609b923e..f11086918 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -54,6 +54,7 @@ Library Text.Pandoc.Readers.LaTeX, Text.Pandoc.Readers.Markdown, Text.Pandoc.Readers.RST, + Text.Pandoc.Readers.TeXMath, Text.Pandoc.Writers.DefaultHeaders, Text.Pandoc.Writers.Docbook, Text.Pandoc.Writers.HTML, diff --git a/pandoc.cabal.ghc66 b/pandoc.cabal.ghc66 index ad26f0418..387f0ed13 100644 --- a/pandoc.cabal.ghc66 +++ b/pandoc.cabal.ghc66 @@ -44,6 +44,7 @@ Exposed-Modules: Text.Pandoc, Text.Pandoc.Readers.LaTeX, Text.Pandoc.Readers.Markdown, Text.Pandoc.Readers.RST, + Text.Pandoc.Readers.TeXMath, Text.Pandoc.Writers.DefaultHeaders, Text.Pandoc.Writers.Docbook, Text.Pandoc.Writers.HTML, diff --git a/tests/s5.basic.html b/tests/s5.basic.html index d5c670a0a..611818f7f 100644 --- a/tests/s5.basic.html +++ b/tests/s5.basic.html @@ -780,7 +780,33 @@ window.onresize = function(){setTimeout('fontScale()', 50);}</script> >Math</h1 ><ul ><li - >\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}</li + >\frac{<em + >d</em + >}{<em + >dx</em + >}<em + >f</em + >(<em + >x</em + >)=\lim<sub + ><em + >h</em + > → <em + >0</em + ></sub + >\frac{<em + >f</em + >(<em + >x</em + >+<em + >h</em + >)-<em + >f</em + >(<em + >x</em + >)}{<em + >h</em + >}</li ></ul ></div> </div> diff --git a/tests/s5.fragment.html b/tests/s5.fragment.html index b82aa290b..00166ea12 100644 --- a/tests/s5.fragment.html +++ b/tests/s5.fragment.html @@ -10,6 +10,32 @@ >Math</h1 ><ul ><li - >\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}</li + >\frac{<em + >d</em + >}{<em + >dx</em + >}<em + >f</em + >(<em + >x</em + >)=\lim<sub + ><em + >h</em + > → <em + >0</em + ></sub + >\frac{<em + >f</em + >(<em + >x</em + >+<em + >h</em + >)-<em + >f</em + >(<em + >x</em + >)}{<em + >h</em + >}</li ></ul > diff --git a/tests/s5.inserts.html b/tests/s5.inserts.html index 33cd4ffe1..9575c44f4 100644 --- a/tests/s5.inserts.html +++ b/tests/s5.inserts.html @@ -27,7 +27,33 @@ STUFF INSERTED >Math</h1 ><ul ><li - >\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}</li + >\frac{<em + >d</em + >}{<em + >dx</em + >}<em + >f</em + >(<em + >x</em + >)=\lim<sub + ><em + >h</em + > → <em + >0</em + ></sub + >\frac{<em + >f</em + >(<em + >x</em + >+<em + >h</em + >)-<em + >f</em + >(<em + >x</em + >)}{<em + >h</em + >}</li ></ul >STUFF INSERTED </body diff --git a/tests/writer.docbook b/tests/writer.docbook index fe44e437b..870898e50 100644 --- a/tests/writer.docbook +++ b/tests/writer.docbook @@ -891,38 +891,38 @@ These should not be escaped: \$ \\ \> \[ \{ </listitem> <listitem> <para> - <literal>2+2=4</literal> + <emphasis>2</emphasis>+<emphasis>2</emphasis>=<emphasis>4</emphasis> </para> </listitem> <listitem> <para> - <literal>x \in y</literal> + <emphasis>x</emphasis> ∈ <emphasis>y</emphasis> </para> </listitem> <listitem> <para> - <literal>\alpha \wedge \omega</literal> + α ∧ ω </para> </listitem> <listitem> <para> - <literal>223</literal> + <emphasis>223</emphasis> </para> </listitem> <listitem> <para> - <literal>p</literal>-Tree + <emphasis>p</emphasis>-Tree </para> </listitem> <listitem> <para> - <literal>\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}</literal> + \frac{<emphasis>d</emphasis>}{<emphasis>dx</emphasis>}<emphasis>f</emphasis>(<emphasis>x</emphasis>)=\lim<subscript><emphasis>h</emphasis> → <emphasis>0</emphasis></subscript>\frac{<emphasis>f</emphasis>(<emphasis>x</emphasis>+<emphasis>h</emphasis>)-<emphasis>f</emphasis>(<emphasis>x</emphasis>)}{<emphasis>h</emphasis>} </para> </listitem> <listitem> <para> Here's one that has a line break in it: - <literal>\alpha + \omega \times x^2</literal>. + α+ω × <emphasis>x</emphasis><superscript>2</superscript>. </para> </listitem> </itemizedlist> diff --git a/tests/writer.html b/tests/writer.html index 752d93690..b22dd36f8 100644 --- a/tests/writer.html +++ b/tests/writer.html @@ -762,19 +762,63 @@ Blah ><li ></li ><li - >2+2=4</li + ><em + >2</em + >+<em + >2</em + >=<em + >4</em + ></li ><li - >x \in y</li + ><em + >x</em + > ∈ <em + >y</em + ></li ><li - >\alpha \wedge \omega</li + >α ∧ ω</li ><li - >223</li + ><em + >223</em + ></li ><li - >p-Tree</li + ><em + >p</em + >-Tree</li ><li - >\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}</li + >\frac{<em + >d</em + >}{<em + >dx</em + >}<em + >f</em + >(<em + >x</em + >)=\lim<sub + ><em + >h</em + > → <em + >0</em + ></sub + >\frac{<em + >f</em + >(<em + >x</em + >+<em + >h</em + >)-<em + >f</em + >(<em + >x</em + >)}{<em + >h</em + >}</li ><li - >Here’s one that has a line break in it: \alpha + \omega \times x^2.</li + >Here’s one that has a line break in it: α+ω × <em + >x</em + ><sup + >2</sup + >.</li ></ul ><p >These shouldn’t be math:</p diff --git a/tests/writer.man b/tests/writer.man index 4a74f0800..13ae18927 100644 --- a/tests/writer.man +++ b/tests/writer.man @@ -576,20 +576,20 @@ Ellipses\&...and\&...and\&...\. .IP \[bu] 2 .IP \[bu] 2 .IP \[bu] 2 -2+2=4 +\f[B]2+2=4\f[] .IP \[bu] 2 -x\ \\in\ y +\f[B]x\ \\in\ y\f[] .IP \[bu] 2 -\\alpha\ \\wedge\ \\omega +\f[B]\\alpha\ \\wedge\ \\omega\f[] .IP \[bu] 2 -223 +\f[B]223\f[] .IP \[bu] 2 -p-Tree +\f[B]p\f[]-Tree .IP \[bu] 2 -\\frac{d}{dx}f(x)=\\lim_{h\\to\ 0}\\frac{f(x+h)-f(x)}{h} +\f[B]\\frac{d}{dx}f(x)=\\lim_{h\\to\ 0}\\frac{f(x+h)-f(x)}{h}\f[] .IP \[bu] 2 Here's one that has a line break in it: -\\alpha\ +\ \\omega\ \\times\ x^2\. +\f[B]\\alpha\ +\ \\omega\ \\times\ x^2\f[]\. .PP These shouldn't be math: .IP \[bu] 2 diff --git a/tests/writer.rtf b/tests/writer.rtf index c3f0fac3f..895902e8d 100644 --- a/tests/writer.rtf +++ b/tests/writer.rtf @@ -252,13 +252,13 @@ quoted link {\pard \ql \f0 \sa180 \li0 \fi0 \b \fs36 LaTeX\par} {\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab \par} {\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab \par} -{\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab {\cf1 2+2=4\cf0 } \par} -{\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab {\cf1 x \\in y\cf0 } \par} -{\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab {\cf1 \\alpha \\wedge \\omega\cf0 } \par} -{\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab {\cf1 223\cf0 } \par} -{\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab {\cf1 p\cf0 } -Tree\par} -{\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab {\cf1 \\frac\{d\}\{dx\}f(x)=\\lim_\{h\\to 0\}\\frac\{f(x+h)-f(x)\}\{h\}\cf0 } \par} -{\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab Here\u8217's one that has a line break in it: {\cf1 \\alpha + \\omega \\times x^2\cf0 } .\sa180\par} +{\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab {\i 2} +{\i 2} ={\i 4} \par} +{\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab {\i x} \u8201?\u8712?\u8201?{\i y} \par} +{\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab \u945?\u8201?\u8743?\u8201?\u969?\par} +{\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab {\i 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 \\frac\{{\i d} \}\{{\i dx} \}{\i f} ({\i x} )=\\lim{\sub {\i h} \u8201?\u8594?\u8201?{\i 0} } \\frac\{{\i f} ({\i x} +{\i h} )-{\i f} ({\i x} )\}\{{\i h} \}\par} +{\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab Here\u8217's one that has a line break in it: \u945?+\u969?\u8201?\u215?\u8201?{\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} {\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab $22,000 is a {\i lot} of money. So is $34,000. (It worked if \u8220"lot\u8221" is emphasized.)\par} |