HTML writer: Add "inline" or "display" class to math spans.

This allows inline and display math to be styled differently.

Closes #1914.
This commit is contained in:
John MacFarlane 2015-02-01 11:08:27 -08:00
parent 5073758bb8
commit 6a0d4da382
5 changed files with 70 additions and 67 deletions

View file

@ -1,4 +1,4 @@
{-# LANGUAGE OverloadedStrings, CPP, ViewPatterns #-}
{-# LANGUAGE OverloadedStrings, CPP, ViewPatterns, ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-deprecations #-}
{-
Copyright (C) 2006-2014 John MacFarlane <jgm@berkeley.edu>
@ -704,62 +704,65 @@ inlineToHtml opts inline =
H.q `fmap` inlineListToHtml opts lst
else (\x -> leftQuote >> x >> rightQuote)
`fmap` inlineListToHtml opts lst
(Math t str) -> modify (\st -> st {stMath = True}) >>
(case writerHTMLMathMethod opts of
LaTeXMathML _ ->
-- putting LaTeXMathML in container with class "LaTeX" prevents
-- non-math elements on the page from being treated as math by
-- the javascript
return $ H.span ! A.class_ "LaTeX" $
case t of
InlineMath -> toHtml ("$" ++ str ++ "$")
DisplayMath -> toHtml ("$$" ++ str ++ "$$")
JsMath _ -> do
let m = preEscapedString str
return $ case t of
InlineMath -> H.span ! A.class_ "math" $ m
DisplayMath -> H.div ! A.class_ "math" $ m
WebTeX url -> do
let imtag = if writerHtml5 opts then H5.img else H.img
let m = imtag ! A.style "vertical-align:middle"
! A.src (toValue $ url ++ urlEncode str)
! A.alt (toValue str)
! A.title (toValue str)
let brtag = if writerHtml5 opts then H5.br else H.br
return $ case t of
InlineMath -> m
DisplayMath -> brtag >> m >> brtag
GladTeX ->
return $ case t of
InlineMath -> preEscapedString $ "<EQ ENV=\"math\">" ++ str ++ "</EQ>"
DisplayMath -> preEscapedString $ "<EQ ENV=\"displaymath\">" ++ str ++ "</EQ>"
MathML _ -> do
let dt = if t == InlineMath
then DisplayInline
else DisplayBlock
let conf = useShortEmptyTags (const False)
defaultConfigPP
case writeMathML dt <$> readTeX str of
Right r -> return $ preEscapedString $
ppcElement conf (annotateMML r str)
Left _ -> inlineListToHtml opts
(texMathToInlines t str) >>=
return . (H.span ! A.class_ "math")
MathJax _ -> return $ H.span ! A.class_ "math" $ toHtml $
case t of
InlineMath -> "\\(" ++ str ++ "\\)"
DisplayMath -> "\\[" ++ str ++ "\\]"
KaTeX _ _ -> return $ H.span ! A.class_ "math" $
toHtml (case t of
InlineMath -> str
DisplayMath -> "\\displaystyle " ++ str)
PlainMath -> do
x <- inlineListToHtml opts (texMathToInlines 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
InlineMath -> m
DisplayMath -> brtag >> m >> brtag )
(Math t str) -> do
modify (\st -> st {stMath = True})
let mathClass = toValue $ ("math " :: String) ++
if t == InlineMath then "inline" else "display"
case writerHTMLMathMethod opts of
LaTeXMathML _ ->
-- putting LaTeXMathML in container with class "LaTeX" prevents
-- non-math elements on the page from being treated as math by
-- the javascript
return $ H.span ! A.class_ "LaTeX" $
case t of
InlineMath -> toHtml ("$" ++ str ++ "$")
DisplayMath -> toHtml ("$$" ++ str ++ "$$")
JsMath _ -> do
let m = preEscapedString str
return $ case t of
InlineMath -> H.span ! A.class_ mathClass $ m
DisplayMath -> H.div ! A.class_ mathClass $ m
WebTeX url -> do
let imtag = if writerHtml5 opts then H5.img else H.img
let m = imtag ! A.style "vertical-align:middle"
! A.src (toValue $ url ++ urlEncode str)
! A.alt (toValue str)
! A.title (toValue str)
let brtag = if writerHtml5 opts then H5.br else H.br
return $ case t of
InlineMath -> m
DisplayMath -> brtag >> m >> brtag
GladTeX ->
return $ case t of
InlineMath -> preEscapedString $ "<EQ ENV=\"math\">" ++ str ++ "</EQ>"
DisplayMath -> preEscapedString $ "<EQ ENV=\"displaymath\">" ++ str ++ "</EQ>"
MathML _ -> do
let dt = if t == InlineMath
then DisplayInline
else DisplayBlock
let conf = useShortEmptyTags (const False)
defaultConfigPP
case writeMathML dt <$> readTeX str of
Right r -> return $ preEscapedString $
ppcElement conf (annotateMML r str)
Left _ -> inlineListToHtml opts
(texMathToInlines t str) >>=
return . (H.span ! A.class_ mathClass)
MathJax _ -> return $ H.span ! A.class_ mathClass $ toHtml $
case t of
InlineMath -> "\\(" ++ str ++ "\\)"
DisplayMath -> "\\[" ++ str ++ "\\]"
KaTeX _ _ -> return $ H.span ! A.class_ mathClass $
toHtml (case t of
InlineMath -> str
DisplayMath -> "\\displaystyle " ++ str)
PlainMath -> do
x <- inlineListToHtml opts (texMathToInlines t str)
let m = H.span ! A.class_ mathClass $ x
let brtag = if writerHtml5 opts then H5.br else H.br
return $ case t of
InlineMath -> m
DisplayMath -> brtag >> m >> brtag
(RawInline f str)
| f == Format "latex" ->
case writerHTMLMathMethod opts of

View file

@ -46,7 +46,7 @@
<div id="math" class="slide section level1">
<h1>Math</h1>
<ul>
<li><span class="math">$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span></li>
<li><span class="math inline">$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span></li>
</ul>
</div>
</div>

View file

@ -5,5 +5,5 @@
</ul>
<h1 id="math">Math</h1>
<ul>
<li><span class="math">$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span></li>
<li><span class="math inline">$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span></li>
</ul>

View file

@ -27,7 +27,7 @@ STUFF INSERTED
</ul>
<h1 id="math">Math</h1>
<ul>
<li><span class="math">$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span></li>
<li><span class="math inline">$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$</span></li>
</ul>
STUFF INSERTED
</body>

View file

@ -419,13 +419,13 @@ Blah
<h1 id="latex">LaTeX</h1>
<ul>
<li></li>
<li><span class="math">2+2=4</span></li>
<li><span class="math"><em>x</em> ∈ <em>y</em></span></li>
<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>Heres 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>Heres one that has a line break in it: <span class="math"><em>α</em>+<em>ω</em>×<em>x</em><sup>2</sup></span>.</li>
<li><span class="math inline">2+2=4</span></li>
<li><span class="math inline"><em>x</em> ∈ <em>y</em></span></li>
<li><span class="math inline"><em>α</em> ∧ <em>ω</em></span></li>
<li><span class="math inline">223</span></li>
<li><span class="math inline"><em>p</em></span>-Tree</li>
<li>Heres some display math: <br /><span class="math display">$$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$</span><br /></li>
<li>Heres one that has a line break in it: <span class="math inline"><em>α</em>+<em>ω</em>×<em>x</em><sup>2</sup></span>.</li>
</ul>
<p>These shouldnt be math:</p>
<ul>