Skip to content

Commit

Permalink
Add cachebusters to CSS and JS
Browse files Browse the repository at this point in the history
  • Loading branch information
SquidDev committed Sep 12, 2023
1 parent 71cb456 commit e5cb686
Show file tree
Hide file tree
Showing 5 changed files with 43 additions and 4 deletions.
1 change: 1 addition & 0 deletions support/shake/1lab-shake.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -78,6 +78,7 @@ executable shake
, Shake.AgdaCompile
, Shake.AgdaRefs
, Shake.Diagram
, Shake.Digest
, Shake.Git
, Shake.KaTeX
, Shake.LinkGraph
Expand Down
2 changes: 2 additions & 0 deletions support/shake/app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,7 @@ import Shake.LinkGraph
import Shake.Markdown
import Shake.Modules
import Shake.Diagram
import Shake.Digest
import Shake.KaTeX
import Shake.Git
import Shake.Utils
Expand All @@ -50,6 +51,7 @@ rules :: Rules ()
rules = do
agdaRules
agdaRefs <- getAgdaRefs
digestRules
gitRules
katexRules
moduleRules
Expand Down
28 changes: 28 additions & 0 deletions support/shake/app/Shake/Digest.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,28 @@
{-# LANGUAGE BlockArguments, GeneralizedNewtypeDeriving, TypeFamilies #-}

-- | Take the
module Shake.Digest (digestRules, getFileDigest) where

import qualified Data.ByteString.Lazy as LazyBS
import Data.Digest.Pure.SHA
import Data.Typeable

import Development.Shake.Classes (Hashable, Binary, NFData)
import Development.Shake

newtype FileDigest = FileDigest FilePath
deriving (Show, Typeable, Eq, Hashable, Binary, NFData)

type instance RuleResult FileDigest = String

-- | Shake rules required for compiling KaTeX equations.
digestRules :: Rules ()
digestRules = versioned 1 do
_ <- addOracle \(FileDigest f) -> do
need [f]
take 8 . showDigest . sha256 <$> liftIO (LazyBS.readFile f)
pure ()

-- | Get parsed preamble
getFileDigest :: FilePath -> Action String
getFileDigest = askOracle . FileDigest
12 changes: 10 additions & 2 deletions support/shake/app/Shake/Markdown.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,7 @@ import Shake.LinkReferences
import Shake.SearchData
import Shake.AgdaRefs
import Shake.Options
import Shake.Digest
import Shake.KaTeX
import Shake.Git

Expand Down Expand Up @@ -149,8 +150,11 @@ buildMarkdown refs modname input output = do
(markdown, MarkdownState references dependencies) <- runWriterT (walkM patchBlock markdown)
need dependencies

cssDigest <- getFileDigest "_build/html/css/default.css"
jsDigest <- getFileDigest "_build/html/main.js"

text <- liftIO $ either (fail . show) pure =<<
runIO (renderMarkdown authors references modname markdown)
runIO (renderMarkdown authors references cssDigest jsDigest modname markdown)

tags <- mapM (parseAgdaLink modname refs) . foldEquations False $ parseTags text
traverse_ (checkMarkup input) tags
Expand Down Expand Up @@ -284,9 +288,11 @@ patchBlock h = pure h
renderMarkdown :: PandocMonad m
=> [Text] -- ^ List of authors
-> [Val Text] -- ^ List of references
-> String -- ^ Digest of the CSS file
-> String -- ^ Digest of the JS file
-> String -- ^ Name of the current module
-> Pandoc -> m Text
renderMarkdown authors references modname markdown = do
renderMarkdown authors references cssDigest jsDigest modname markdown = do
template <- getTemplate templateName >>= runWithPartials . compileTemplate templateName
>>= either (throwError . PandocTemplateError . Text.pack) pure

Expand All @@ -300,6 +306,8 @@ renderMarkdown authors references modname markdown = do
[ ("is-index", toVal (modname == "index"))
, ("authors", toVal authors')
, ("reference", toVal references)
, ("cssDigest", toVal $ Text.pack cssDigest)
, ("jsDigest", toVal $ Text.pack jsDigest)
]

options = def { writerTemplate = Just template
Expand Down
4 changes: 2 additions & 2 deletions support/web/template.html
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@

<title>$pagetitle$ - 1Lab</title>

<link rel="stylesheet" href="/css/default.css" />
<link rel="stylesheet" href="/css/default.css?v=$cssDigest$" />
<link rel="stylesheet" href="/css/katex.min.css" />

<meta name="twitter:card" content="summary" />
Expand All @@ -29,7 +29,7 @@
<meta name="description" content="A formalised, explorable online resource for Homotopy Type Theory." />
$endif$

<script defer src="/main.js"></script>
<script defer src="/main.js?v=$jsDigest$"></script>

<noscript>
<style>
Expand Down

0 comments on commit e5cb686

Please sign in to comment.