parent
575c76e36b
commit
515a120d04
3 changed files with 52 additions and 3 deletions
35
pandoc.hs
35
pandoc.hs
|
@ -58,7 +58,7 @@ import qualified Control.Exception as E
|
|||
import Control.Exception.Extensible ( throwIO )
|
||||
import qualified Text.Pandoc.UTF8 as UTF8
|
||||
import Control.Monad (when, unless, (>=>))
|
||||
import Data.Maybe (isJust)
|
||||
import Data.Maybe (isJust, fromMaybe)
|
||||
import Data.Foldable (foldrM)
|
||||
import Network.URI (parseURI, isURI, URI(..))
|
||||
import qualified Data.ByteString.Lazy as B
|
||||
|
@ -68,7 +68,7 @@ import qualified Data.Map as M
|
|||
import Data.Yaml (decode)
|
||||
import qualified Data.Yaml as Yaml
|
||||
import qualified Data.Text as T
|
||||
import Control.Applicative ((<$>))
|
||||
import Control.Applicative ((<$>), (<|>))
|
||||
import Text.Pandoc.Readers.Txt2Tags (getT2TMeta)
|
||||
import Data.Monoid
|
||||
|
||||
|
@ -205,6 +205,8 @@ data Opt = Opt
|
|||
, optExtractMedia :: Maybe FilePath -- ^ Path to extract embedded media
|
||||
, optTrace :: Bool -- ^ Print debug information
|
||||
, optTrackChanges :: TrackChanges -- ^ Accept or reject MS Word track-changes.
|
||||
, optKaTeXStylesheet :: Maybe String -- ^ Path to stylesheet for KaTeX
|
||||
, optKaTeXJS :: Maybe String -- ^ Path to js file for KaTeX
|
||||
}
|
||||
|
||||
-- | Defaults for command-line options.
|
||||
|
@ -263,6 +265,8 @@ defaultOpts = Opt
|
|||
, optExtractMedia = Nothing
|
||||
, optTrace = False
|
||||
, optTrackChanges = AcceptChanges
|
||||
, optKaTeXStylesheet = Nothing
|
||||
, optKaTeXJS = Nothing
|
||||
}
|
||||
|
||||
-- | A list of functions, each transforming the options data structure
|
||||
|
@ -818,6 +822,21 @@ options =
|
|||
return opt { optHTMLMathMethod = MathJax url'})
|
||||
"URL")
|
||||
"" -- "Use MathJax for HTML math"
|
||||
, Option "" ["katex"]
|
||||
(OptArg
|
||||
(\arg opt ->
|
||||
return opt
|
||||
{ optKaTeXJS =
|
||||
arg <|> Just "http://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.1.0/katex.min.js"})
|
||||
"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
|
||||
|
@ -860,6 +879,7 @@ options =
|
|||
|
||||
]
|
||||
|
||||
|
||||
addMetadata :: String -> MetaValue -> M.Map String MetaValue
|
||||
-> M.Map String MetaValue
|
||||
addMetadata k v m = case M.lookup k m of
|
||||
|
@ -1027,7 +1047,7 @@ main = do
|
|||
, optHighlight = highlight
|
||||
, optHighlightStyle = highlightStyle
|
||||
, optChapters = chapters
|
||||
, optHTMLMathMethod = mathMethod
|
||||
, optHTMLMathMethod = mathMethod'
|
||||
, optReferenceODT = referenceODT
|
||||
, optReferenceDocx = referenceDocx
|
||||
, optEpubStylesheet = epubStylesheet
|
||||
|
@ -1056,6 +1076,8 @@ main = do
|
|||
, optExtractMedia = mbExtractMedia
|
||||
, optTrace = trace
|
||||
, optTrackChanges = trackChanges
|
||||
, optKaTeXStylesheet = katexStylesheet
|
||||
, optKaTeXJS = katexJS
|
||||
} = opts
|
||||
|
||||
when dumpArgs $
|
||||
|
@ -1063,6 +1085,13 @@ main = do
|
|||
mapM_ (\arg -> UTF8.hPutStrLn stdout arg) args
|
||||
exitWith ExitSuccess
|
||||
|
||||
let csscdn = "http://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.1.0/katex.min.css"
|
||||
let mathMethod =
|
||||
case (katexJS, katexStylesheet) of
|
||||
(Nothing, _) -> mathMethod'
|
||||
(Just js, ss) -> KaTeX js (fromMaybe csscdn ss)
|
||||
|
||||
|
||||
-- --bibliography implies -F pandoc-citeproc for backwards compatibility:
|
||||
let needsCiteproc = isJust (M.lookup "bibliography" metadata) &&
|
||||
optCiteMethod opts `notElem` [Natbib, Biblatex] &&
|
||||
|
|
|
@ -251,6 +251,7 @@ data HTMLMathMethod = PlainMath
|
|||
| WebTeX String -- url of TeX->image script.
|
||||
| MathML (Maybe String) -- url of MathMLinHTML.js
|
||||
| MathJax String -- url of MathJax.js
|
||||
| KaTeX String String -- url of stylesheet and katex.js
|
||||
deriving (Show, Read, Eq)
|
||||
|
||||
data CiteMethod = Citeproc -- use citeproc to render them
|
||||
|
|
|
@ -157,6 +157,10 @@ 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)
|
||||
_ -> case lookup "mathml-script" (writerVariables opts) of
|
||||
Just s | not (writerHtml5 opts) ->
|
||||
H.script ! A.type_ "text/javascript"
|
||||
|
@ -728,6 +732,10 @@ inlineToHtml opts inline =
|
|||
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
|
||||
|
@ -829,3 +837,14 @@ blockListToNote opts ref blocks =
|
|||
Just EPUB3 -> noteItem ! customAttribute "epub:type" "footnote"
|
||||
_ -> 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])"
|
||||
, "}}"
|
||||
]
|
||||
|
|
Loading…
Reference in a new issue