A JavaScript-free Hakyll site

Compiling with KaTeX

November 20, 2018,
keywords: haskell, hakyll, katex, web, static sites

Wanted a Hakyll generated site which prerendered LaTeX\LaTeX so that no JavaScript runs on the client. Hacked this together over a few days and it somehow works!

Inline math looks like this: x+yx+y, and display math looks like the following. i=1npi+qi\prod_{i=1}^{n} p_i + q_i

The unfortunate part is that I still need some JavaScript on the server side. The blog posts are prerendered using KaTeX\KaTeX and relies on the katex binary which got added to my path when I did npm install katex -g.

The KaTeX\KaTeX compiler activates if there is a katex metadata field. The idea is to only enable KaTeX\KaTeX selectively when heavy LaTeX\LaTeX is needed and just use plain pandoc LaTeX\LaTeX otherwise. The KaTeX\KaTeX files are somewhat slow to compile since we spin up a new katex process for each LaTeX\LaTeX expression.

--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
import           Hakyll
import           Hakyll.Core.Compiler (unsafeCompiler)
import           KaTeX.KaTeXify       (kaTeXifyIO)

--------------------------------------------------------------------------------
main :: IO ()
main = hakyll $ do
    ...

    match "posts/*" $ do
        route $ setExtension "html"
        compile $ pandocMathCompiler
            >>= loadAndApplyTemplate "templates/post.html"    postCtx
            >>= loadAndApplyTemplate "templates/default.html" postCtx
            >>= relativizeUrls

    ...

--------------------------------------------------------------------------------
pandocMathCompiler :: Compiler (Item String)
pandocMathCompiler = do
  identifier <- getUnderlying
  s <- getMetadataField identifier "katex"
  case s of
    Just _ ->
      pandocCompilerWithTransformM
         defaultHakyllReaderOptions defaultHakyllWriterOptions
         (unsafeCompiler . kaTeXifyIO)
    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
kaTeXCmd DisplayMath = "katex --display-mode"
kaTeXCmd _           = "katex"

rawKaTeX :: MathType -> String -> IO String
rawKaTeX mt inner = readCreateProcess (shell $ kaTeXCmd 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
kaTeXify orig@(Math mt str) =
  do
    s <- fmap parseKaTeX $ rawKaTeX mt str
    case s of
      Just inl  -> return inl
      Nothing -> return orig
kaTeXify x = return x

--------------------------------------------------------------------------------
kaTeXifyIO :: Pandoc -> IO Pandoc
kaTeXifyIO = walkM kaTeXify