aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/App.hs26
-rw-r--r--src/Text/Pandoc/Options.hs2
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs34
-rw-r--r--src/Text/Pandoc/Writers/Math.hs2
4 files changed, 21 insertions, 43 deletions
diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs
index 57a91581b..a18cc2961 100644
--- a/src/Text/Pandoc/App.hs
+++ b/src/Text/Pandoc/App.hs
@@ -183,13 +183,6 @@ convertWithOpts opts = do
Nothing -> return Nothing
Just fp -> Just <$> UTF8.readFile fp
- let mathMethod =
- case (optKaTeXJS opts, optKaTeXStylesheet opts) of
- (Nothing, _) -> optHTMLMathMethod opts
- (Just js, ss) -> KaTeX js (fromMaybe
- (defaultKaTeXURL ++ "katex.min.css") ss)
-
-
-- --bibliography implies -F pandoc-citeproc for backwards compatibility:
let needsCiteproc = isJust (lookup "bibliography" (optMetadata opts)) &&
optCiteMethod opts `notElem` [Natbib, Biblatex] &&
@@ -368,7 +361,7 @@ convertWithOpts opts = do
maybe return (addStringAsVariable "epub-cover-image")
(optEpubCoverImage opts)
>>=
- (\vars -> case mathMethod of
+ (\vars -> case optHTMLMathMethod opts of
LaTeXMathML Nothing -> do
s <- UTF8.toString <$> readDataFile "LaTeXMathML.js"
return $ ("mathml-script", s) : vars
@@ -428,7 +421,7 @@ convertWithOpts opts = do
, writerVariables = variables
, writerTabStop = optTabStop opts
, writerTableOfContents = optTableOfContents opts
- , writerHTMLMathMethod = mathMethod
+ , writerHTMLMathMethod = optHTMLMathMethod opts
, writerIncremental = optIncremental opts
, writerCiteMethod = optCiteMethod opts
, writerNumberSections = optNumberSections opts
@@ -642,8 +635,6 @@ data Opt = Opt
, optExtractMedia :: Maybe FilePath -- ^ Path to extract embedded media
, optTrackChanges :: TrackChanges -- ^ Accept or reject MS Word track-changes.
, optFileScope :: Bool -- ^ Parse input files before combining
- , optKaTeXStylesheet :: Maybe String -- ^ Path to stylesheet for KaTeX
- , optKaTeXJS :: Maybe String -- ^ Path to js file for KaTeX
, optTitlePrefix :: Maybe String -- ^ Prefix for title
, optCss :: [FilePath] -- ^ CSS files to link to
, optIncludeBeforeBody :: [FilePath] -- ^ Files to include before
@@ -719,8 +710,6 @@ defaultOpts = Opt
, optExtractMedia = Nothing
, optTrackChanges = AcceptChanges
, optFileScope = False
- , optKaTeXStylesheet = Nothing
- , optKaTeXJS = Nothing
, optTitlePrefix = Nothing
, optCss = []
, optIncludeBeforeBody = []
@@ -1455,18 +1444,11 @@ options =
(OptArg
(\arg opt ->
return opt
- { optKaTeXJS =
- arg <|> Just (defaultKaTeXURL ++ "katex.min.js")})
+ { optHTMLMathMethod = KaTeX $
+ fromMaybe defaultKaTeXURL arg })
"URL")
"" -- Use KaTeX for HTML Math
- , Option "" ["katex-stylesheet"]
- (ReqArg
- (\arg opt ->
- return opt { optKaTeXStylesheet = Just arg })
- "URL")
- "" -- Set the KaTeX Stylesheet location
-
, Option "" ["gladtex"]
(NoArg
(\opt -> return opt { optHTMLMathMethod = GladTeX }))
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index f936658f4..99c7afba7 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -107,7 +107,7 @@ data HTMLMathMethod = PlainMath
| WebTeX String -- url of TeX->image script.
| MathML
| MathJax String -- url of MathJax.js
- | KaTeX String String -- url of stylesheet and katex.js
+ | KaTeX String -- url of KaTeX files
deriving (Show, Read, Eq, Data, Typeable, Generic)
instance ToJSON HTMLMathMethod where
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 1641b991c..41b50bf70 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -268,10 +268,17 @@ pandocToHtml opts (Pandoc meta blocks) = do
H.script ! A.src (toValue url)
! A.type_ "text/javascript"
$ mempty
- KaTeX js css ->
- (H.script ! A.src (toValue js) $ mempty) <>
- (H.link ! A.rel "stylesheet" ! A.href (toValue css)) <>
- (H.script ! A.type_ "text/javascript" $ toHtml renderKaTeX)
+ KaTeX url ->
+ (H.script !
+ A.src (toValue $ url ++ "katex.min.js") $ mempty) <>
+ (H.script !
+ A.src (toValue $ url ++ "contrib/auto-render.min.js")
+ $ mempty) <>
+ (H.script $
+ "document.addEventListener(\"DOMContentLoaded\", function() {\n renderMathInElement(document.body);\n});") <>
+ (H.link ! A.rel "stylesheet" !
+ A.href (toValue $ url ++ "katex.min.css"))
+
_ -> case lookup "mathml-script" (writerVariables opts) of
Just s | not (stHtml5 st) ->
H.script ! A.type_ "text/javascript"
@@ -1009,10 +1016,10 @@ inlineToHtml opts inline = do
case t of
InlineMath -> "\\(" ++ str ++ "\\)"
DisplayMath -> "\\[" ++ str ++ "\\]"
- KaTeX _ _ -> return $ H.span ! A.class_ mathClass $
- toHtml (case t of
- InlineMath -> str
- DisplayMath -> "\\displaystyle " ++ str)
+ KaTeX _ -> return $ H.span ! A.class_ mathClass $ toHtml $
+ case t of
+ InlineMath -> "\\(" ++ str ++ "\\)"
+ DisplayMath -> "\\[" ++ str ++ "\\]"
PlainMath -> do
x <- lift (texMathToInlines t str) >>= inlineListToHtml opts
let m = H.span ! A.class_ mathClass $ x
@@ -1133,17 +1140,6 @@ blockListToNote opts ref blocks =
_ -> noteItem
return $ nl opts >> noteItem'
--- Javascript snippet to render all KaTeX elements
-renderKaTeX :: String
-renderKaTeX = unlines [
- "window.onload = function(){var mathElements = document.getElementsByClassName(\"math\");"
- , "for (var i=0; i < mathElements.length; i++)"
- , "{"
- , " var texText = mathElements[i].firstChild"
- , " katex.render(texText.data, mathElements[i])"
- , "}}"
- ]
-
isMathEnvironment :: String -> Bool
isMathEnvironment s = "\\begin{" `isPrefixOf` s &&
envName `elem` mathmlenvs
diff --git a/src/Text/Pandoc/Writers/Math.hs b/src/Text/Pandoc/Writers/Math.hs
index 58252d60f..1677cb5b6 100644
--- a/src/Text/Pandoc/Writers/Math.hs
+++ b/src/Text/Pandoc/Writers/Math.hs
@@ -53,4 +53,4 @@ defaultMathJaxURL :: String
defaultMathJaxURL = "https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.0/"
defaultKaTeXURL :: String
-defaultKaTeXURL = "https://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.6.0/"
+defaultKaTeXURL = "https://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.8.3/"