--mathml and MathML in HTMLMathMethod longer take an argument.

The argument was for a bridge javascript that used to be necessary
in 2004.  We have removed the script already.
This commit is contained in:
John MacFarlane 2017-01-30 11:31:50 +01:00
parent 42257b9be9
commit 7018003811
7 changed files with 15 additions and 26 deletions

View file

@ -945,13 +945,10 @@ Math rendering in HTML
several pages, it is much better to link to a copy of the script,
so it can be cached.
`--mathml`[`=`*URL*]
`--mathml`
: Convert TeX math to [MathML] (in `docbook4`, `docbook5`,
`html4` and `html5`). In standalone HTML output, a small
JavaScript (or a link to such a script if a *URL* is
supplied) will be inserted that allows the MathML to be
viewed on some browsers.
`html4` and `html5`).
`--jsmath`[`=`*URL*]

View file

@ -256,9 +256,6 @@ convertWithOpts opts args = do
LaTeXMathML Nothing -> do
s <- readDataFileUTF8 datadir "LaTeXMathML.js"
return $ ("mathml-script", s) : variables
MathML Nothing -> do
s <- readDataFileUTF8 datadir "MathMLinHTML.js"
return $ ("mathml-script", s) : variables
_ -> return variables
variables'' <- if format == "dzslides"
@ -1110,10 +1107,9 @@ options =
"" -- "Use LaTeXMathML script in html output"
, Option "" ["mathml"]
(OptArg
(\arg opt ->
return opt { optHTMLMathMethod = MathML arg })
"URL")
(NoArg
(\opt ->
return opt { optHTMLMathMethod = MathML }))
"" -- "Use mathml for HTML math"
, Option "" ["mimetex"]

View file

@ -89,7 +89,7 @@ data HTMLMathMethod = PlainMath
| JsMath (Maybe String) -- url of jsMath load script
| GladTeX
| WebTeX String -- url of TeX->image script.
| MathML (Maybe String) -- url of MathMLinHTML.js
| MathML
| MathJax String -- url of MathJax.js
| KaTeX String String -- url of stylesheet and katex.js
deriving (Show, Read, Eq, Data, Typeable, Generic)

View file

@ -117,8 +117,8 @@ writeDocbook opts (Pandoc meta blocks) = do
main <- (render' . vcat) <$> (mapM (elementToDocbook opts' startLvl) elements)
let context = defField "body" main
$ defField "mathml" (case writerHTMLMathMethod opts of
MathML _ -> True
_ -> False)
MathML -> True
_ -> False)
$ metadata
return $ case writerTemplate opts of
Nothing -> main
@ -421,8 +421,8 @@ inlineToDocbook opts (Note contents) =
inTagsIndented "footnote" <$> blocksToDocbook opts contents
isMathML :: HTMLMathMethod -> Bool
isMathML (MathML _) = True
isMathML _ = False
isMathML MathML = True
isMathML _ = False
idAndRole :: Attr -> [(String, String)]
idAndRole (id',cls,_) = ident ++ role

View file

@ -382,7 +382,7 @@ pandocToEPUB version opts doc@(Pandoc meta _) = do
, writerVariables = vars
, writerHTMLMathMethod =
if epub3
then MathML Nothing
then MathML
else writerHTMLMathMethod opts
, writerWrapText = WrapAuto }
metadata <- getEPUBMetadata opts' meta

View file

@ -230,10 +230,6 @@ pandocToHtml opts (Pandoc meta blocks) = do
H.script ! A.src (toValue url)
! A.type_ "text/javascript"
$ mempty
MathML (Just url) ->
H.script ! A.src (toValue url)
! A.type_ "text/javascript"
$ mempty
MathJax url ->
H.script ! A.src (toValue url)
! A.type_ "text/javascript"
@ -903,7 +899,7 @@ inlineToHtml opts inline = do
return $ case t of
InlineMath -> preEscapedString $ "<EQ ENV=\"math\">" ++ str ++ "</EQ>"
DisplayMath -> preEscapedString $ "<EQ ENV=\"displaymath\">" ++ str ++ "</EQ>"
MathML _ -> do
MathML -> do
let conf = useShortEmptyTags (const False)
defaultConfigPP
res <- lift $ convertMath writeMathML t str
@ -1061,6 +1057,6 @@ isMathEnvironment s = "\\begin{" `isPrefixOf` s &&
allowsMathEnvironments :: HTMLMathMethod -> Bool
allowsMathEnvironments (MathJax _) = True
allowsMathEnvironments (MathML _) = True
allowsMathEnvironments (MathML) = True
allowsMathEnvironments (WebTeX _) = True
allowsMathEnvironments _ = False

View file

@ -76,8 +76,8 @@ writeTEI opts (Pandoc meta blocks) = return $
main = render' $ vcat (map (elementToTEI opts startLvl) elements)
context = defField "body" main
$ defField "mathml" (case writerHTMLMathMethod opts of
MathML _ -> True
_ -> False)
MathML -> True
_ -> False)
$ metadata
in case writerTemplate opts of
Nothing -> main