Removed deprecated ancient HTML math methods.
Removed `--latexmathml`, `--gladtex`, `--mimetex`, `--jsmath`, `-m`, `--asciimathml` options. Removed `JsMath`, `LaTeXMathML`, and `GladTeX` constructors from `Text.Pandoc.Options.HTMLMathMethod` [API change]. Removed unneeded data file LaTeXMathML.js and updated tests. Bumped version to 2.2.
This commit is contained in:
parent
28f7d8ab4d
commit
16f36eee43
8 changed files with 4 additions and 518 deletions
46
MANUAL.txt
46
MANUAL.txt
|
@ -1206,54 +1206,8 @@ of the following options.
|
|||
not specified, a link to the KaTeX CDN will be inserted. Note that this
|
||||
option does not imply `--katex`.
|
||||
|
||||
`-m` [*URL*], `--latexmathml`[`=`*URL*]
|
||||
|
||||
: *Deprecated.*
|
||||
Use the [LaTeXMathML] script to display embedded TeX math in HTML output.
|
||||
TeX math will be displayed between `$` or `$$` characters and put in
|
||||
`<span>` tags with class `LaTeX`. The LaTeXMathML JavaScript will then
|
||||
change it to MathML. Note that currently only Firefox and Safari
|
||||
(and select e-book readers) natively support MathML.
|
||||
To insert a link the `LaTeXMathML.js` script, provide a *URL*.
|
||||
|
||||
`--jsmath`[`=`*URL*]
|
||||
|
||||
: *Deprecated.*
|
||||
Use [jsMath] (the predecessor of MathJax) to display embedded TeX
|
||||
math in HTML output. TeX math will be put inside `<span>` tags
|
||||
(for inline math) or `<div>` tags (for display math) with class
|
||||
`math` and rendered by the jsMath script. The *URL* should point to
|
||||
the script (e.g. `jsMath/easy/load.js`); if provided, it will be linked
|
||||
to in the header of standalone HTML documents. If a *URL* is not provided,
|
||||
no link to the jsMath load script will be inserted; it is then
|
||||
up to the author to provide such a link in the HTML template.
|
||||
|
||||
`--gladtex`
|
||||
|
||||
: *Deprecated.*
|
||||
Enclose TeX math in `<eq>` tags in HTML output. The resulting HTML
|
||||
can then be processed by [gladTeX] to produce images of the typeset
|
||||
formulas and an HTML file with links to these images.
|
||||
So, the procedure is:
|
||||
|
||||
pandoc -s --gladtex input.md -o myfile.htex
|
||||
gladtex -d myfile-images myfile.htex
|
||||
# produces myfile.html and images in myfile-images
|
||||
|
||||
`--mimetex`[`=`*URL*]
|
||||
|
||||
: *Deprecated.*
|
||||
Render TeX math using the [mimeTeX] CGI script, which generates an
|
||||
image for each TeX formula. This should work in all browsers. If
|
||||
*URL* is not specified, it is assumed that the script is at
|
||||
`/cgi-bin/mimetex.cgi`.
|
||||
|
||||
[MathML]: http://www.w3.org/Math/
|
||||
[LaTeXMathML]: http://math.etsu.edu/LaTeXMathML/
|
||||
[jsMath]: http://www.math.union.edu/~dpvc/jsmath/
|
||||
[MathJax]: https://www.mathjax.org
|
||||
[gladTeX]: http://ans.hsh.no/home/mgg/gladtex/
|
||||
[mimeTeX]: http://www.forkosh.com/mimetex.html
|
||||
[KaTeX]: https://github.com/Khan/KaTeX
|
||||
|
||||
Options for wrapper scripts
|
||||
|
|
File diff suppressed because one or more lines are too long
|
@ -1,5 +1,5 @@
|
|||
name: pandoc
|
||||
version: 2.1.4
|
||||
version: 2.2
|
||||
cabal-version: >= 1.10
|
||||
build-type: Custom
|
||||
license: GPL-2
|
||||
|
@ -148,8 +148,6 @@ data-files:
|
|||
data/pptx/[Content_Types].xml
|
||||
-- stylesheet for EPUB writer
|
||||
data/epub.css
|
||||
-- data for LaTeXMathML writer
|
||||
data/LaTeXMathML.js
|
||||
-- data for dzslides writer
|
||||
data/dzslides/template.html
|
||||
-- default abbreviations file
|
||||
|
|
|
@ -357,12 +357,6 @@ convertWithOpts opts = do
|
|||
maybe return (addStringAsVariable "epub-cover-image")
|
||||
(optEpubCoverImage opts)
|
||||
>>=
|
||||
(\vars -> case optHTMLMathMethod opts of
|
||||
LaTeXMathML Nothing -> do
|
||||
s <- UTF8.toString <$> readDataFile "LaTeXMathML.js"
|
||||
return $ ("mathml-script", s) : vars
|
||||
_ -> return vars)
|
||||
>>=
|
||||
(\vars -> if format == "dzslides"
|
||||
then do
|
||||
dztempl <- UTF8.toString <$> readDataFile
|
||||
|
@ -1401,40 +1395,6 @@ options =
|
|||
"URL")
|
||||
"" -- Use KaTeX for HTML Math
|
||||
|
||||
, Option "m" ["latexmathml", "asciimathml"]
|
||||
(OptArg
|
||||
(\arg opt -> do
|
||||
deprecatedOption "--latexmathml, --asciimathml, -m" ""
|
||||
return opt { optHTMLMathMethod = LaTeXMathML arg })
|
||||
"URL")
|
||||
"" -- "Use LaTeXMathML script in html output"
|
||||
|
||||
, Option "" ["mimetex"]
|
||||
(OptArg
|
||||
(\arg opt -> do
|
||||
deprecatedOption "--mimetex" ""
|
||||
let url' = case arg of
|
||||
Just u -> u ++ "?"
|
||||
Nothing -> "/cgi-bin/mimetex.cgi?"
|
||||
return opt { optHTMLMathMethod = WebTeX url' })
|
||||
"URL")
|
||||
"" -- "Use mimetex for HTML math"
|
||||
|
||||
, Option "" ["jsmath"]
|
||||
(OptArg
|
||||
(\arg opt -> do
|
||||
deprecatedOption "--jsmath" ""
|
||||
return opt { optHTMLMathMethod = JsMath arg})
|
||||
"URL")
|
||||
"" -- "Use jsMath for HTML math"
|
||||
|
||||
, Option "" ["gladtex"]
|
||||
(NoArg
|
||||
(\opt -> do
|
||||
deprecatedOption "--gladtex" ""
|
||||
return opt { optHTMLMathMethod = GladTeX }))
|
||||
"" -- "Use gladtex for HTML math"
|
||||
|
||||
, Option "" ["abbreviations"]
|
||||
(ReqArg
|
||||
(\arg opt -> return opt { optAbbreviations = Just arg })
|
||||
|
|
|
@ -106,9 +106,6 @@ defaultAbbrevs = Set.fromList
|
|||
data EPUBVersion = EPUB2 | EPUB3 deriving (Eq, Show, Read, Data, Typeable, Generic)
|
||||
|
||||
data HTMLMathMethod = PlainMath
|
||||
| LaTeXMathML (Maybe String) -- url of LaTeXMathML.js
|
||||
| JsMath (Maybe String) -- url of jsMath load script
|
||||
| GladTeX
|
||||
| WebTeX String -- url of TeX->image script.
|
||||
| MathML
|
||||
| MathJax String -- url of MathJax.js
|
||||
|
|
|
@ -260,10 +260,6 @@ pandocToHtml opts (Pandoc meta blocks) = do
|
|||
notes <- footnoteSection opts (reverse (stNotes st))
|
||||
let thebody = blocks' >> notes
|
||||
let math = case writerHTMLMathMethod opts of
|
||||
LaTeXMathML (Just url) ->
|
||||
H.script ! A.src (toValue url)
|
||||
! A.type_ "text/javascript"
|
||||
$ mempty
|
||||
MathJax url
|
||||
| slideVariant /= RevealJsSlides ->
|
||||
-- mathjax is handled via a special plugin in revealjs
|
||||
|
@ -274,10 +270,6 @@ pandocToHtml opts (Pandoc meta blocks) = do
|
|||
preEscapedString
|
||||
"MathJax.Hub.Queue([\"Typeset\",MathJax.Hub]);"
|
||||
_ -> mempty
|
||||
JsMath (Just url) ->
|
||||
H.script ! A.src (toValue url)
|
||||
! A.type_ "text/javascript"
|
||||
$ mempty
|
||||
KaTeX url -> do
|
||||
H.script !
|
||||
A.src (toValue $ url ++ "katex.min.js") $ mempty
|
||||
|
@ -1024,19 +1016,6 @@ inlineToHtml opts inline = do
|
|||
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 html5 then H5.img else H.img
|
||||
let m = imtag ! A.style "vertical-align:middle"
|
||||
|
@ -1047,10 +1026,6 @@ inlineToHtml opts inline = do
|
|||
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 conf = useShortEmptyTags (const False)
|
||||
defaultConfigPP
|
||||
|
|
|
@ -59,7 +59,7 @@ tests = [ testGroup "markdown"
|
|||
]
|
||||
, testGroup "s5"
|
||||
[ s5WriterTest "basic" ["-s"] "s5"
|
||||
, s5WriterTest "fancy" ["-s","-m","-i"] "s5"
|
||||
, s5WriterTest "fancy" ["-s","--mathjax","-i"] "s5"
|
||||
, s5WriterTest "fragment" [] "html4"
|
||||
, s5WriterTest "inserts" ["-s", "-H", "insert",
|
||||
"-B", "insert", "-A", "insert", "-c", "main.css"] "html4"
|
||||
|
|
File diff suppressed because one or more lines are too long
Loading…
Add table
Reference in a new issue