Wanted a Hakyll generated site which prerendered so that no JavaScript runs on the client. Hacked this together over a few days and it somehow works!
Inline math looks like this: , and display math looks like the following.
The unfortunate part is that I still need some JavaScript on the server side.
The blog posts are prerendered using and relies on
the katex
binary which got added to my path when I did npm install katex -g
.
The compiler activates if there is a katex
metadata field. The idea
is to only enable selectively when heavy is needed and just
use plain pandoc otherwise. The files are somewhat slow to
compile since we spin up a new katex
process for each expression.
--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
import Hakyll
import Hakyll.Core.Compiler (unsafeCompiler)
import KaTeX.KaTeXify (kaTeXifyIO)
--------------------------------------------------------------------------------
main :: IO ()
= hakyll $ do
main ...
"posts/*" $ do
match $ setExtension "html"
route $ pandocMathCompiler
compile >>= loadAndApplyTemplate "templates/post.html" postCtx
>>= loadAndApplyTemplate "templates/default.html" postCtx
>>= relativizeUrls
...
--------------------------------------------------------------------------------
pandocMathCompiler :: Compiler (Item String)
= do
pandocMathCompiler <- getUnderlying
identifier <- getMetadataField identifier "katex"
s case s of
Just _ ->
pandocCompilerWithTransformM
defaultHakyllReaderOptions defaultHakyllWriterOptions. kaTeXifyIO)
(unsafeCompiler Nothing -> pandocCompiler
Most of the magic happens in the KaTeX.KaTeXify
module. The file ended up
being somewhat small since Pandoc suppies most of the functions needed out of
the box. In particular, Pandoc provides the walkM
function which walks a
Pandoc parse tree bottom up.
module KaTeX.KaTeXify (kaTeXifyIO) where
import System.Process (readCreateProcess, shell)
import Text.Pandoc.Definition (MathType(..), Inline(..), Pandoc, Format(..))
import Text.Pandoc.Readers.HTML (readHtml)
import Text.Pandoc.Options (def)
import Text.Pandoc.Walk (walkM)
import Text.Pandoc.Class (PandocPure, runPure)
import Data.String.Conversions (convertString)
--------------------------------------------------------------------------------
kaTeXCmd :: MathType -> String
DisplayMath = "katex --display-mode"
kaTeXCmd = "katex"
kaTeXCmd _
rawKaTeX :: MathType -> String -> IO String
= readCreateProcess (shell $ kaTeXCmd mt) inner
rawKaTeX mt inner
parseKaTeX :: String -> Maybe Inline
=
parseKaTeX str -- Ensure str is parsable HTML
case runPure $ readHtml def (convertString str) of
Right _ -> Just (RawInline (Format "html") str)
otherwise -> Nothing
kaTeXify :: Inline -> IO Inline
@(Math mt str) =
kaTeXify origdo
<- fmap parseKaTeX $ rawKaTeX mt str
s case s of
Just inl -> return inl
Nothing -> return orig
= return x
kaTeXify x
--------------------------------------------------------------------------------
kaTeXifyIO :: Pandoc -> IO Pandoc
= walkM kaTeXify kaTeXifyIO