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 Jun 3, 2023
1 parent f44986d commit a50eae5
Show file tree
Hide file tree
Showing 7 changed files with 208 additions and 6 deletions.
6 changes: 4 additions & 2 deletions support/nix/haskell-packages.nix
Original file line number Diff line number Diff line change
Expand Up @@ -54,8 +54,10 @@ in
skylighting-format-blaze-html = noJunk (self.callCabal2nix "skylighting-format-blaze-html" ((thunkSource ./dep/skylighting) + "/skylighting-format-blaze-html") {});
skylighting-format-context = noJunk (self.callCabal2nix "skylighting-format-context" ((thunkSource ./dep/skylighting) + "/skylighting-format-context") {});
skylighting-format-latex = noJunk (self.callCabal2nix "skylighting-format-latex" ((thunkSource ./dep/skylighting) + "/skylighting-format-latex") {});
skylighting-core = noJunk
(self.callCabal2nixWithOptions "skylighting-core" ((thunkSource ./dep/skylighting) + "/skylighting-core") "-fexecutable" {});
skylighting-core = noJunk (pkgs.haskell.lib.overrideCabal
(self.callCabal2nixWithOptions "skylighting-core" ((thunkSource ./dep/skylighting) + "/skylighting-core") "-fexecutable" {})
{ patches = [./skylighting-core.patch]; }
);
};
});
}
161 changes: 161 additions & 0 deletions support/nix/skylighting-core.patch
Original file line number Diff line number Diff line change
@@ -0,0 +1,161 @@
diff --git a/src/Skylighting/Regex.hs b/src/Skylighting/Regex.hs
index a6f6207..4140276 100644
--- a/src/Skylighting/Regex.hs
+++ b/src/Skylighting/Regex.hs
@@ -2,11 +2,14 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Skylighting.Regex (
Regex(..)
- , RE(..)
+ , RE
+ , pattern RE, reCaseSensitive, reString
+ , compileRE
, compileRegex
, matchRegex
, testRegex
@@ -14,25 +17,81 @@ module Skylighting.Regex (
) where

import Data.Aeson
-import Data.Binary (Binary)
+import Data.Binary (Binary(..))
import qualified Data.ByteString.Base64 as Base64
import qualified Data.ByteString.Char8 as BS
import Data.Data
import qualified Data.Text as Text
import qualified Data.Text.Encoding as TE
-import GHC.Generics (Generic)
#if !MIN_VERSION_base(4,13,0)
import Control.Monad.Fail (MonadFail)
#endif
import Regex.KDE

+import Text.Read hiding (get)
+
-- | A representation of a regular expression.
-data RE = RE{
- reString :: BS.ByteString
- , reCaseSensitive :: Bool
-} deriving (Show, Read, Ord, Eq, Data, Typeable, Generic)
+data RE = RE'{
+ _reString :: BS.ByteString
+ , _reCaseSensitive :: Bool
+ , reCompiled' :: Either String Regex
+} deriving Typeable
+
+-- We define a smart constructor which also holds the compiled regex, to avoid
+-- recompiling each time we tokenize.
+
+{-# COMPLETE RE #-}
+pattern RE :: BS.ByteString -> Bool -> RE
+pattern RE {reString, reCaseSensitive} <- RE' reString reCaseSensitive _ where
+ RE str caseSensitive = RE' str caseSensitive (compileRegex caseSensitive str)
+
+-- Unfortunately this means we need to derive all the instances ourselves.
+
+instance Show RE where
+ showsPrec d (RE str caseSensitive) = showParen (d > 10)
+ $ showString "RE {reString = "
+ . showsPrec 11 str
+ . showString ", reCaseSensitive = "
+ . showsPrec 11 caseSensitive
+ . showString "}"
+
+instance Read RE where
+ readPrec = parens . prec 10 $ do
+ Ident "RE" <- lexP
+ Punc "{" <- lexP
+ Ident "reString" <- lexP
+ Punc "=" <- lexP
+ str <- readPrec
+ Punc "," <- lexP
+ Ident "reCaseSensitive" <- lexP
+ Punc "=" <- lexP
+ caseSensitive <- readPrec
+ Punc "}" <- lexP
+ pure (RE str caseSensitive)

-instance Binary RE
+toComparisonKey :: RE -> (BS.ByteString, Bool)
+toComparisonKey (RE x y) = (x, y)
+
+instance Eq RE where
+ x == y = toComparisonKey x == toComparisonKey y
+
+instance Ord RE where
+ x `compare` y = toComparisonKey x `compare` toComparisonKey y
+
+conRE :: Constr
+conRE = mkConstr tyRE "RE" [] Prefix
+tyRE :: DataType
+tyRE = mkDataType "Skylighting.Regex.RE" [conRE]
+
+instance Data RE where
+ gfoldl k z (RE s c) = z RE `k` s `k` c
+ gunfold k z _ = k (k (z RE))
+ toConstr _ = conRE
+ dataTypeOf _ = tyRE
+
+instance Binary RE where
+ put (RE x y) = put x >> put y
+ get = RE <$> get <*> get

instance ToJSON RE where
toJSON re = object [ "reString" .= encodeToText (reString re)
@@ -49,3 +108,6 @@ encodeToText = TE.decodeUtf8 . Base64.encode

decodeFromText :: (Monad m, MonadFail m) => Text.Text -> m BS.ByteString
decodeFromText = either fail return . Base64.decode . TE.encodeUtf8
+
+compileRE :: RE -> Either String Regex
+compileRE = reCompiled'
\ No newline at end of file
diff --git a/src/Skylighting/Tokenizer.hs b/src/Skylighting/Tokenizer.hs
index 42c9b83..27119a4 100644
--- a/src/Skylighting/Tokenizer.hs
+++ b/src/Skylighting/Tokenizer.hs
@@ -56,7 +56,6 @@ data TokenizerState = TokenizerState{
, column :: Int
, lineContinuation :: Bool
, firstNonspaceColumn :: Maybe Int
- , compiledRegexes :: Map.Map RE Regex
}

-- | Configuration options for 'tokenize'.
@@ -163,7 +162,6 @@ tokenize config syntax inp =
, column = 0
, lineContinuation = False
, firstNonspaceColumn = Nothing
- , compiledRegexes = Map.empty
}

info :: String -> TokenizerM ()
@@ -552,18 +550,11 @@ regExpr dynamic re inp = do
-- return $! traceShowId $! (reStr, inp)
let reStr = reString re
when (BS.take 2 reStr == "\\b") $ wordBoundary inp
- compiledREs <- gets compiledRegexes
- regex <- case Map.lookup re compiledREs of
- Nothing -> do
- cre <- case compileRegex (reCaseSensitive re) reStr of
- Right r -> return r
- Left e -> throwError $
- "Error compiling regex " ++
- UTF8.toString reStr ++ ": " ++ e
- modify $ \st -> st{ compiledRegexes =
- Map.insert re cre (compiledRegexes st) }
- return cre
- Just cre -> return cre
+ regex <- case compileRE re of
+ Right r -> return r
+ Left e -> throwError $
+ "Error compiling regex " ++
+ UTF8.toString reStr ++ ": " ++ e
regex' <- if dynamic
then subDynamic regex
else return regex
1 change: 1 addition & 0 deletions support/shake/1lab-shake.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -54,6 +54,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 @@ -46,6 +46,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 @@ -103,8 +104,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 @@ -252,9 +256,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 @@ -268,6 +274,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 a50eae5

Please sign in to comment.