Use texmath's parser in TexMath module.
* This replaces a lot of custom parser code, and expands the tex -> unicode conversion. * The behavior has also changed: if the whole formula can't be converted, the whole formula is left in raw TeX. Previously, pandoc converted parts of the formula to unicode and left other parts in raw TeX. * Added (but not yet exported) readTeXMath', which returns a Maybe. * Updated tests
This commit is contained in:
parent
b3669e139c
commit
c243e5b67b
8 changed files with 80 additions and 333 deletions
|
@ -28,208 +28,64 @@ 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
|
||||
readTeXMath
|
||||
) where
|
||||
|
||||
import Text.ParserCombinators.Parsec
|
||||
import Text.Pandoc.Definition
|
||||
import Text.TeXMath.Parser
|
||||
|
||||
-- | Converts a string of raw TeX math to a list of 'Pandoc' inlines.
|
||||
-- | 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.
|
||||
readTeXMath :: String -- ^ String to parse (assumes @'\n'@ line endings)
|
||||
-> [Inline]
|
||||
readTeXMath inp = case parse teXMath ("formula: " ++ inp) inp of
|
||||
Left _ -> [Str inp] -- if unparseable, just include original
|
||||
Right res -> res
|
||||
readTeXMath inp = case readTeXMath' inp of
|
||||
Nothing -> [Str ("$" ++ inp ++ "$")]
|
||||
Just res -> res
|
||||
|
||||
teXMath :: GenParser Char st [Inline]
|
||||
teXMath = manyTill mathPart eof >>= return . concat
|
||||
-- | Like 'readTeXMath', but without the default.
|
||||
readTeXMath' :: String -- ^ String to parse (assumes @'\n'@ line endings)
|
||||
-> Maybe [Inline]
|
||||
readTeXMath' inp = case parse formula "formula" inp of
|
||||
Left _ -> Just [Str inp]
|
||||
Right exps -> expsToInlines exps
|
||||
|
||||
mathPart :: GenParser Char st [Inline]
|
||||
mathPart = whitespace <|> superscript <|> subscript <|> symbol <|>
|
||||
argument <|> digits <|> letters <|> misc
|
||||
expsToInlines :: [Exp] -> Maybe [Inline]
|
||||
expsToInlines xs = do
|
||||
res <- mapM expToInlines xs
|
||||
return (concat res)
|
||||
|
||||
whitespace :: GenParser Char st [Inline]
|
||||
whitespace = many1 space >> return []
|
||||
|
||||
symbol :: GenParser Char st [Inline]
|
||||
symbol = try $ do
|
||||
char '\\'
|
||||
res <- many1 letter
|
||||
case lookup res teXsymbols of
|
||||
Just m -> return [Str m]
|
||||
Nothing -> return [Str $ "\\" ++ res]
|
||||
|
||||
argument :: GenParser Char st [Inline]
|
||||
argument = try $ do
|
||||
char '{'
|
||||
res <- many mathPart
|
||||
char '}'
|
||||
return $ if null res
|
||||
then [Str " "]
|
||||
else [Str "{"] ++ concat res ++ [Str "}"]
|
||||
|
||||
digits :: GenParser Char st [Inline]
|
||||
digits = do
|
||||
res <- many1 digit
|
||||
return [Str res]
|
||||
|
||||
letters :: GenParser Char st [Inline]
|
||||
letters = do
|
||||
res <- many1 letter
|
||||
return [Emph [Str res]]
|
||||
|
||||
misc :: GenParser Char st [Inline]
|
||||
misc = do
|
||||
res <- noneOf "}"
|
||||
return [Str [res]]
|
||||
|
||||
scriptArg :: GenParser Char st [Inline]
|
||||
scriptArg = try $ do
|
||||
(try (do{char '{'; r <- many mathPart; char '}'; return $ concat r}))
|
||||
<|> symbol
|
||||
<|> (do{c <- (letter <|> digit); return [Str [c]]})
|
||||
|
||||
superscript :: GenParser Char st [Inline]
|
||||
superscript = try $ do
|
||||
char '^'
|
||||
arg <- scriptArg
|
||||
return [Superscript arg]
|
||||
|
||||
subscript :: GenParser Char st [Inline]
|
||||
subscript = try $ do
|
||||
char '_'
|
||||
arg <- scriptArg
|
||||
return [Subscript arg]
|
||||
|
||||
withThinSpace :: String -> String
|
||||
withThinSpace str = "\x2009" ++ str ++ "\x2009"
|
||||
|
||||
teXsymbols :: [(String, String)]
|
||||
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")
|
||||
,("int", "\8747")
|
||||
,("{", "{")
|
||||
,("}", "}")
|
||||
,("[", "[")
|
||||
,("]", "]")
|
||||
,("|", "|")
|
||||
,("||", "||")
|
||||
]
|
||||
expToInlines :: Exp -> Maybe [Inline]
|
||||
expToInlines (ENumber s) = Just [Str s]
|
||||
expToInlines (EIdentifier s) = Just [Emph [Str s]]
|
||||
expToInlines (EMathOperator s) = Just [Str s]
|
||||
expToInlines (ESymbol t s) = Just $ addSpace t (Str s)
|
||||
where addSpace Op x = [x, thinspace]
|
||||
addSpace Bin x = [medspace, x, medspace]
|
||||
addSpace Rel x = [widespace, x, widespace]
|
||||
addSpace Pun x = [x, thinspace]
|
||||
addSpace _ x = [x]
|
||||
thinspace = Str "\x2006"
|
||||
medspace = Str "\x2005"
|
||||
widespace = Str "\x2004"
|
||||
expToInlines (EStretchy x) = expToInlines x
|
||||
expToInlines (EGrouped xs) = expsToInlines xs
|
||||
expToInlines (ESpace _) = Just [Str " "] -- variable widths not supported
|
||||
expToInlines (EBinary _ _ _) = Nothing
|
||||
expToInlines (ESub x y) = do
|
||||
x' <- expToInlines x
|
||||
y' <- expToInlines y
|
||||
return $ x' ++ [Subscript y']
|
||||
expToInlines (ESuper x y) = do
|
||||
x' <- expToInlines x
|
||||
y' <- expToInlines y
|
||||
return $ x' ++ [Superscript y']
|
||||
expToInlines (ESubsup x y z) = do
|
||||
x' <- expToInlines x
|
||||
y' <- expToInlines y
|
||||
z' <- expToInlines z
|
||||
return $ x' ++ [Subscript y'] ++ [Superscript z']
|
||||
expToInlines (EText _ x) = Just [Emph [Str x]]
|
||||
expToInlines _ = Nothing
|
||||
|
||||
|
|
|
@ -309,31 +309,7 @@
|
|||
><ul
|
||||
><li
|
||||
><span class="math"
|
||||
>\frac{<em
|
||||
>d</em
|
||||
>}{<em
|
||||
>dx</em
|
||||
>}<em
|
||||
>f</em
|
||||
>(<em
|
||||
>x</em
|
||||
>)=\lim<sub
|
||||
><em
|
||||
>h</em
|
||||
> → 0</sub
|
||||
>\frac{<em
|
||||
>f</em
|
||||
>(<em
|
||||
>x</em
|
||||
>+<em
|
||||
>h</em
|
||||
>)-<em
|
||||
>f</em
|
||||
>(<em
|
||||
>x</em
|
||||
>)}{<em
|
||||
>h</em
|
||||
>}</span
|
||||
>$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span
|
||||
></li
|
||||
></ul
|
||||
></div>
|
||||
|
|
|
@ -14,31 +14,7 @@
|
|||
><ul
|
||||
><li
|
||||
><span class="math"
|
||||
>\frac{<em
|
||||
>d</em
|
||||
>}{<em
|
||||
>dx</em
|
||||
>}<em
|
||||
>f</em
|
||||
>(<em
|
||||
>x</em
|
||||
>)=\lim<sub
|
||||
><em
|
||||
>h</em
|
||||
> → 0</sub
|
||||
>\frac{<em
|
||||
>f</em
|
||||
>(<em
|
||||
>x</em
|
||||
>+<em
|
||||
>h</em
|
||||
>)-<em
|
||||
>f</em
|
||||
>(<em
|
||||
>x</em
|
||||
>)}{<em
|
||||
>h</em
|
||||
>}</span
|
||||
>$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span
|
||||
></li
|
||||
></ul
|
||||
></div
|
||||
|
|
|
@ -29,31 +29,7 @@ STUFF INSERTED
|
|||
><ul
|
||||
><li
|
||||
><span class="math"
|
||||
>\frac{<em
|
||||
>d</em
|
||||
>}{<em
|
||||
>dx</em
|
||||
>}<em
|
||||
>f</em
|
||||
>(<em
|
||||
>x</em
|
||||
>)=\lim<sub
|
||||
><em
|
||||
>h</em
|
||||
> → 0</sub
|
||||
>\frac{<em
|
||||
>f</em
|
||||
>(<em
|
||||
>x</em
|
||||
>+<em
|
||||
>h</em
|
||||
>)-<em
|
||||
>f</em
|
||||
>(<em
|
||||
>x</em
|
||||
>)}{<em
|
||||
>h</em
|
||||
>}</span
|
||||
>$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span
|
||||
></li
|
||||
></ul
|
||||
></div
|
||||
|
|
|
@ -1077,17 +1077,17 @@ Blah
|
|||
</listitem>
|
||||
<listitem>
|
||||
<para>
|
||||
2+2=4
|
||||
2 + 2 = 4
|
||||
</para>
|
||||
</listitem>
|
||||
<listitem>
|
||||
<para>
|
||||
<emphasis>x</emphasis> ∈ <emphasis>y</emphasis>
|
||||
<emphasis>x</emphasis> ∈ <emphasis>y</emphasis>
|
||||
</para>
|
||||
</listitem>
|
||||
<listitem>
|
||||
<para>
|
||||
α ∧ ω
|
||||
α ∧ ω
|
||||
</para>
|
||||
</listitem>
|
||||
<listitem>
|
||||
|
@ -1103,13 +1103,13 @@ Blah
|
|||
<listitem>
|
||||
<para>
|
||||
Here's some display math:
|
||||
\frac{<emphasis>d</emphasis>}{<emphasis>dx</emphasis>}<emphasis>f</emphasis>(<emphasis>x</emphasis>)=\lim<subscript><emphasis>h</emphasis> → 0</subscript>\frac{<emphasis>f</emphasis>(<emphasis>x</emphasis>+<emphasis>h</emphasis>)-<emphasis>f</emphasis>(<emphasis>x</emphasis>)}{<emphasis>h</emphasis>}
|
||||
$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$
|
||||
</para>
|
||||
</listitem>
|
||||
<listitem>
|
||||
<para>
|
||||
Here's one that has a line break in it:
|
||||
α+ω × <emphasis>x</emphasis><superscript>2</superscript>.
|
||||
α + ω × <emphasis>x</emphasis><superscript>2</superscript>.
|
||||
</para>
|
||||
</listitem>
|
||||
</itemizedlist>
|
||||
|
|
|
@ -830,19 +830,19 @@ Blah
|
|||
></li
|
||||
><li
|
||||
><span class="math"
|
||||
>2+2=4</span
|
||||
>2 + 2 = 4</span
|
||||
></li
|
||||
><li
|
||||
><span class="math"
|
||||
><em
|
||||
>x</em
|
||||
> ∈ <em
|
||||
> ∈ <em
|
||||
>y</em
|
||||
></span
|
||||
></li
|
||||
><li
|
||||
><span class="math"
|
||||
>α ∧ ω</span
|
||||
>α ∧ ω</span
|
||||
></li
|
||||
><li
|
||||
><span class="math"
|
||||
|
@ -856,35 +856,11 @@ Blah
|
|||
>-Tree</li
|
||||
><li
|
||||
>Here’s some display math: <span class="math"
|
||||
>\frac{<em
|
||||
>d</em
|
||||
>}{<em
|
||||
>dx</em
|
||||
>}<em
|
||||
>f</em
|
||||
>(<em
|
||||
>x</em
|
||||
>)=\lim<sub
|
||||
><em
|
||||
>h</em
|
||||
> → 0</sub
|
||||
>\frac{<em
|
||||
>f</em
|
||||
>(<em
|
||||
>x</em
|
||||
>+<em
|
||||
>h</em
|
||||
>)-<em
|
||||
>f</em
|
||||
>(<em
|
||||
>x</em
|
||||
>)}{<em
|
||||
>h</em
|
||||
>}</span
|
||||
>$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span
|
||||
></li
|
||||
><li
|
||||
>Here’s one that has a line break in it: <span class="math"
|
||||
>α+ω × <em
|
||||
>α + ω × <em
|
||||
>x</em
|
||||
><sup
|
||||
>2</sup
|
||||
|
|
|
@ -689,30 +689,17 @@
|
|||
<style:style style:name="T59" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T60" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T61" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T62" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T62" style:family="text"><style:text-properties style:text-position="super 58%" /></style:style>
|
||||
<style:style style:name="T63" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T64" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T65" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" style:text-position="sub 58%" /></style:style>
|
||||
<style:style style:name="T66" style:family="text"><style:text-properties style:text-position="sub 58%" /></style:style>
|
||||
<style:style style:name="T67" style:family="text"><style:text-properties style:text-position="sub 58%" /></style:style>
|
||||
<style:style style:name="T65" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T66" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T67" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T68" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T69" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T70" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T71" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T72" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T73" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T74" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T75" style:family="text"><style:text-properties style:text-position="super 58%" /></style:style>
|
||||
<style:style style:name="T76" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T77" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T78" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T79" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T80" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T81" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T82" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T83" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T84" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="T85" style:family="text"><style:text-properties fo:font-style="italic" style:font-style-asian="italic" style:font-style-complex="italic" /></style:style>
|
||||
<style:style style:name="P1" style:family="paragraph" style:parent-style-name="Quotations">
|
||||
<style:paragraph-properties fo:margin-left="0.5in" fo:margin-right="0in" fo:text-indent="0in" style:auto-text-indent="false" />
|
||||
</style:style>
|
||||
|
@ -1317,13 +1304,13 @@
|
|||
<text:p text:style-name="P51"><text:span text:style-name="Teletype">\cite[22-23]{smith.1899}</text:span></text:p>
|
||||
</text:list-item>
|
||||
<text:list-item>
|
||||
<text:p text:style-name="P51">2+2=4</text:p>
|
||||
<text:p text:style-name="P51">2 + 2 = 4</text:p>
|
||||
</text:list-item>
|
||||
<text:list-item>
|
||||
<text:p text:style-name="P51"><text:span text:style-name="T58">x</text:span> ∈ <text:span text:style-name="T59">y</text:span></text:p>
|
||||
<text:p text:style-name="P51"><text:span text:style-name="T58">x</text:span> ∈ <text:span text:style-name="T59">y</text:span></text:p>
|
||||
</text:list-item>
|
||||
<text:list-item>
|
||||
<text:p text:style-name="P51">α ∧ ω</text:p>
|
||||
<text:p text:style-name="P51">α ∧ ω</text:p>
|
||||
</text:list-item>
|
||||
<text:list-item>
|
||||
<text:p text:style-name="P51">223</text:p>
|
||||
|
@ -1332,10 +1319,10 @@
|
|||
<text:p text:style-name="P51"><text:span text:style-name="T60">p</text:span>-Tree</text:p>
|
||||
</text:list-item>
|
||||
<text:list-item>
|
||||
<text:p text:style-name="P51">Here’s some display math: \frac{<text:span text:style-name="T61">d</text:span>}{<text:span text:style-name="T62">dx</text:span>}<text:span text:style-name="T63">f</text:span>(<text:span text:style-name="T64">x</text:span>)=\lim<text:span text:style-name="T65">h</text:span><text:span text:style-name="T66"> → </text:span><text:span text:style-name="T67">0</text:span>\frac{<text:span text:style-name="T68">f</text:span>(<text:span text:style-name="T69">x</text:span>+<text:span text:style-name="T70">h</text:span>)-<text:span text:style-name="T71">f</text:span>(<text:span text:style-name="T72">x</text:span>)}{<text:span text:style-name="T73">h</text:span>}</text:p>
|
||||
<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>
|
||||
</text:list-item>
|
||||
<text:list-item>
|
||||
<text:p text:style-name="P51">Here’s one that has a line break in it: α+ω × <text:span text:style-name="T74">x</text:span><text:span text:style-name="T75">2</text:span>.</text:p>
|
||||
<text:p text:style-name="P51">Here’s one that has a line break in it: α + ω × <text:span text:style-name="T61">x</text:span><text:span text:style-name="T62">2</text:span>.</text:p>
|
||||
</text:list-item>
|
||||
</text:list>
|
||||
<text:p text:style-name="Text_20_body">These shouldn’t be math:</text:p>
|
||||
|
@ -1344,13 +1331,13 @@
|
|||
<text:p text:style-name="P52">To get the famous equation, write <text:span text:style-name="Teletype">$e = mc^2$</text:span>.</text:p>
|
||||
</text:list-item>
|
||||
<text:list-item>
|
||||
<text:p text:style-name="P52">$22,000 is a <text:span text:style-name="T76">lot</text:span> of money. So is $34,000. (It worked if “lot” is emphasized.)</text:p>
|
||||
<text:p text:style-name="P52">$22,000 is a <text:span text:style-name="T63">lot</text:span> of money. So is $34,000. (It worked if “lot” is emphasized.)</text:p>
|
||||
</text:list-item>
|
||||
<text:list-item>
|
||||
<text:p text:style-name="P52">Shoes ($20) and socks ($5).</text:p>
|
||||
</text:list-item>
|
||||
<text:list-item>
|
||||
<text:p text:style-name="P52">Escaped <text:span text:style-name="Teletype">$</text:span>: $73 <text:span text:style-name="T77">this</text:span><text:span text:style-name="T78"> </text:span><text:span text:style-name="T79">should</text:span><text:span text:style-name="T80"> </text:span><text:span text:style-name="T81">be</text:span><text:span text:style-name="T82"> </text:span><text:span text:style-name="T83">emphasized</text:span> 23$.</text:p>
|
||||
<text:p text:style-name="P52">Escaped <text:span text:style-name="Teletype">$</text:span>: $73 <text:span text:style-name="T64">this</text:span><text:span text:style-name="T65"> </text:span><text:span text:style-name="T66">should</text:span><text:span text:style-name="T67"> </text:span><text:span text:style-name="T68">be</text:span><text:span text:style-name="T69"> </text:span><text:span text:style-name="T70">emphasized</text:span> 23$.</text:p>
|
||||
</text:list-item>
|
||||
</text:list>
|
||||
<text:p text:style-name="Text_20_body">Here’s a LaTeX table:</text:p>
|
||||
|
@ -1454,7 +1441,7 @@ Cat <text:s text:c="3" />& 1 <text:s text:c="5" />\\ \hline
|
|||
<text:p text:style-name="Text_20_body">Here is a movie <draw:frame><draw:image xlink:href="movie.jpg" xlink:type="simple" xlink:show="embed" xlink:actuate="onLoad" /></draw:frame> icon.</text:p>
|
||||
<text:p text:style-name="Horizontal_20_Line" />
|
||||
<text:h text:style-name="Heading_20_1" text:outline-level="1">Footnotes</text:h>
|
||||
<text:p text:style-name="Text_20_body">Here is a footnote reference,<text:note text:id="ftn0" text:note-class="footnote"><text:note-citation>1</text:note-citation><text:note-body><text:p text:style-name="Footnote">Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.</text:p></text:note-body></text:note> and another.<text:note text:id="ftn1" text:note-class="footnote"><text:note-citation>2</text:note-citation><text:note-body><text:p text:style-name="Footnote">Here’s the long note. This one contains multiple blocks.</text:p><text:p text:style-name="Footnote">Subsequent blocks are indented to show that they belong to the footnote (as with list items).</text:p><text:p text:style-name="P58"><text:s text:c="2" />{ <code> }</text:p><text:p text:style-name="Footnote">If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.</text:p></text:note-body></text:note> This should <text:span text:style-name="T84">not</text:span> be a footnote reference, because it contains a space.[^my note] Here is an inline note.<text:note text:id="ftn2" text:note-class="footnote"><text:note-citation>3</text:note-citation><text:note-body><text:p text:style-name="Footnote">This is <text:span text:style-name="T85">easier</text:span> to type. Inline notes may contain <text:a xlink:type="simple" xlink:href="http://google.com" office:name=""><text:span text:style-name="Definition">links</text:span></text:a> and <text:span text:style-name="Teletype">]</text:span> verbatim characters, as well as [bracketed text].</text:p></text:note-body></text:note></text:p>
|
||||
<text:p text:style-name="Text_20_body">Here is a footnote reference,<text:note text:id="ftn0" text:note-class="footnote"><text:note-citation>1</text:note-citation><text:note-body><text:p text:style-name="Footnote">Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.</text:p></text:note-body></text:note> and another.<text:note text:id="ftn1" text:note-class="footnote"><text:note-citation>2</text:note-citation><text:note-body><text:p text:style-name="Footnote">Here’s the long note. This one contains multiple blocks.</text:p><text:p text:style-name="Footnote">Subsequent blocks are indented to show that they belong to the footnote (as with list items).</text:p><text:p text:style-name="P58"><text:s text:c="2" />{ <code> }</text:p><text:p text:style-name="Footnote">If you want, you can indent every line, but you can also be lazy and just indent the first line of each block.</text:p></text:note-body></text:note> This should <text:span text:style-name="T71">not</text:span> be a footnote reference, because it contains a space.[^my note] Here is an inline note.<text:note text:id="ftn2" text:note-class="footnote"><text:note-citation>3</text:note-citation><text:note-body><text:p text:style-name="Footnote">This is <text:span text:style-name="T72">easier</text:span> to type. Inline notes may contain <text:a xlink:type="simple" xlink:href="http://google.com" office:name=""><text:span text:style-name="Definition">links</text:span></text:a> and <text:span text:style-name="Teletype">]</text:span> verbatim characters, as well as [bracketed text].</text:p></text:note-body></text:note></text:p>
|
||||
<text:p text:style-name="P59">Notes can go in quotes.<text:note text:id="ftn3" text:note-class="footnote"><text:note-citation>4</text:note-citation><text:note-body><text:p text:style-name="Footnote">In quote.</text:p></text:note-body></text:note></text:p>
|
||||
<text:list text:style-name="L30">
|
||||
<text:list-item>
|
||||
|
|
|
@ -264,13 +264,13 @@ quoted link
|
|||
{\pard \qc \f0 \sa180 \li0 \fi0 \emdash\emdash\emdash\emdash\emdash\par}
|
||||
{\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 2+2=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 2\u8197?+\u8197?2\u8196?=\u8196?4\par}
|
||||
{\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab {\i x}\u8196?\u8712?\u8196?{\i y}\par}
|
||||
{\pard \ql \f0 \sa0 \li360 \fi-360 \bullet \tx360\tab \u945?\u8197?\u8743?\u8197?\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\{{\i d}\}\{{\i dx}\}{\i f}({\i x})=\\lim{\sub {\i h}\u8201?\u8594?\u8201?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 \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: \u945?\u8197?+\u8197?\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}
|
||||
{\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}
|
||||
|
|
Loading…
Reference in a new issue