my blog lives here now
You can not select more than 25 topics Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.

530 lines
18 KiB

6 years ago
2 years ago
2 years ago
6 years ago
2 years ago
6 years ago
2 years ago
6 years ago
2 years ago
6 years ago
2 years ago
6 years ago
2 years ago
6 years ago
2 years ago
2 years ago
6 years ago
2 years ago
6 years ago
2 years ago
6 years ago
2 years ago
2 years ago
2 years ago
2 years ago
2 years ago
2 years ago
2 years ago
2 years ago
2 years ago
6 years ago
2 years ago
6 years ago
2 years ago
6 years ago
2 years ago
2 years ago
2 years ago
6 years ago
2 years ago
6 years ago
2 years ago
6 years ago
2 years ago
6 years ago
2 years ago
2 years ago
2 years ago
6 years ago
2 years ago
6 years ago
2 years ago
6 years ago
2 years ago
2 years ago
6 years ago
2 years ago
6 years ago
2 years ago
6 years ago
2 years ago
6 years ago
2 years ago
2 years ago
2 years ago
2 years ago
6 years ago
2 years ago
6 years ago
2 years ago
  1. {-# LANGUAGE BangPatterns #-}
  2. {-# LANGUAGE MultiWayIf #-}
  3. {-# LANGUAGE OverloadedStrings #-}
  4. {-# LANGUAGE BlockArguments #-}
  5. {-# LANGUAGE LambdaCase #-}
  6. import Control.DeepSeq (rnf)
  7. import Control.Concurrent
  8. import Control.Exception
  9. import Control.Monad
  10. import qualified Data.ByteString.Lazy.Char8 as BS
  11. import Data.ByteString.Lazy.Char8 (pack, unpack)
  12. import qualified Data.HashMap.Strict as HMap
  13. import qualified Data.Text.Encoding as T
  14. import qualified Data.Map.Strict as Map
  15. import qualified Data.Text as T
  16. import Data.Functor
  17. import Data.Monoid
  18. import Data.Binary
  19. import Data.Maybe
  20. import Data.Aeson
  21. import Data.List
  22. import Data.Char
  23. import Hakyll.Core.Compiler.Internal
  24. import Hakyll.Core.Compiler
  25. import Hakyll.Web.Sass
  26. import Hakyll
  27. import qualified Network.URI.Encode as URI (encode)
  28. import qualified Skylighting as Sky
  29. import System.Directory
  30. import System.Environment
  31. import System.Process
  32. import System.Exit
  33. import System.IO
  34. import Text.Pandoc.Walk (query, walkM, walk)
  35. import Text.Pandoc.Highlighting
  36. import Text.Pandoc.Definition
  37. import Text.Pandoc.Options
  38. import Text.Sass.Functions
  39. import Data.Text (Text)
  40. import Data.IORef
  41. import Data.Hashable (Hashable (hashWithSalt))
  42. import GHC.Stack
  43. import Text.Read (readMaybe)
  44. import GHC.Show (showCommaSpace)
  45. readerOpts :: ReaderOptions
  46. readerOpts = def { readerExtensions = pandocExtensions
  47. , readerIndentedCodeClasses = ["amulet"] }
  48. writerOptions :: Compiler WriterOptions
  49. writerOptions = do
  50. syntaxMap <- loadAllSnapshots "syntax/*.xml" "syntax"
  51. <&> foldr (Sky.addSyntaxDefinition . itemBody) Sky.defaultSyntaxMap
  52. pure $ defaultHakyllWriterOptions
  53. { writerExtensions = extensionsFromList
  54. [ Ext_tex_math_dollars
  55. , Ext_tex_math_double_backslash
  56. , Ext_latex_macros
  57. ] <> writerExtensions defaultHakyllWriterOptions
  58. , writerSyntaxMap = syntaxMap
  59. , writerHighlightStyle = Just kate
  60. }
  61. rssfeed :: FeedConfiguration
  62. rssfeed
  63. = FeedConfiguration { feedTitle = "Abigail's Blag: Latest articles"
  64. , feedDescription = ""
  65. , feedAuthorName = "Abigail Magalhães"
  66. , feedAuthorEmail = "[email protected]"
  67. , feedRoot = "https://abby.how"
  68. }
  69. conf :: Configuration
  70. conf = def { destinationDirectory = ".site"
  71. , storeDirectory = ".store"
  72. , tmpDirectory = ".store/tmp"
  73. , deployCommand = "./sync" }
  74. katexFilter :: IORef KatexCache -> Pandoc -> Compiler Pandoc
  75. katexFilter cacheVar (Pandoc meta doc) =
  76. do
  77. initCache <- unsafeCompiler (readIORef cacheVar)
  78. id <- compilerUnderlying <$> compilerAsk
  79. t <- getMetadata id
  80. invalidateCache id (abbrevs t) cacheVar
  81. doc <- Pandoc meta <$> walkM (go (show id) (abbrevs t)) doc
  82. unsafeCompiler $ flushCache cacheVar
  83. pure doc
  84. where
  85. abbrevs :: HMap.HashMap Text Value -> [String]
  86. abbrevs x =
  87. case HMap.lookup "abbreviations" x of
  88. Just (Object map) -> concat $ mapMaybe oneAbbrev (HMap.toList map)
  89. _ -> []
  90. oneAbbrev (x, String t) = Just ["-m", '\\':T.unpack x ++ ':':T.unpack t]
  91. oneAbbrev _ = Nothing
  92. go :: String -> [String] -> Inline -> Compiler Inline
  93. go id abbrevs (Math kind math) = unsafeCompiler $ do
  94. cache <- readIORef cacheVar
  95. case HMap.lookup (id, kind, math) (spanMap cache) of
  96. Just x -> pure (RawInline "html" x)
  97. Nothing -> do
  98. let args = flip (:) abbrevs $ case kind of { DisplayMath -> "-td"; InlineMath -> "-t" }
  99. (contents, _) <- readProcessBS "node_modules/.bin/katex" args . BS.fromStrict . T.encodeUtf8 $ math
  100. let text = T.init . T.init . T.decodeUtf8 . BS.toStrict $ contents
  101. atomicModifyIORef' cacheVar (\m -> (bumpCacheEntry cache id abbrevs kind text math, ()))
  102. pure $ RawInline "html" text
  103. go id _ x = pure x
  104. bumpCacheEntry (KatexCache spans depends abbrevVars) id abbrevs kind text math =
  105. let
  106. str = T.unpack text
  107. usedAbbrevs = map (\x -> (T.pack (takeWhile (/= ':') (tail x)), T.pack (tail (dropWhile (/= ':') (tail x)))))
  108. $ filter (\x -> (takeWhile (/= ':') (tail x)) `isInfixOf` str)
  109. $ filter (not . isPrefixOf "-") abbrevs
  110. addDeps [] x = x
  111. addDeps ((k, _):xs) vl = HMap.alter (\v -> Just (maybe [(id, kind, math)] ((id, kind, math):) v)) (id, k) $ addDeps xs vl
  112. recordVars [] x = x
  113. recordVars ((k, v):xs) x = HMap.insert (id, k) v (recordVars xs x)
  114. in
  115. case usedAbbrevs of
  116. [] -> KatexCache (HMap.insert (id, kind, math) text spans) depends abbrevVars
  117. xs -> KatexCache (HMap.insert (id, kind, math) text spans) (addDeps xs depends) (recordVars xs abbrevVars)
  118. abbreviationFilter :: Pandoc -> Compiler Pandoc
  119. abbreviationFilter (Pandoc meta doc) =
  120. do
  121. id <- compilerUnderlying <$> compilerAsk
  122. t <- getMetadata id
  123. case HMap.lookup "abbreviations" t of
  124. Just (Object map) -> do
  125. pure (Pandoc meta (walk (replace map) doc))
  126. _ -> pure (Pandoc meta doc)
  127. where
  128. replace map x =
  129. case x of
  130. Str t | Just (e, r) <- entity t -> fromMaybe (Str t) (toInline r =<< HMap.lookup e map)
  131. x -> x
  132. toInline r (String t) = Just (Str (t <> r))
  133. toInline _ _ = Nothing
  134. entity x
  135. | T.isPrefixOf "&" x && T.length x >= 3 =
  136. let
  137. (name, rest') = T.span (/= ';') (T.tail x)
  138. rest = T.tail rest'
  139. in pure (name, rest)
  140. | otherwise = Nothing
  141. addLanguageTag :: Pandoc -> Pandoc
  142. addLanguageTag (Pandoc meta blocks) = Pandoc meta (map go blocks) where
  143. go :: Block -> Block
  144. go block@(CodeBlock (identifier, classes@(language:classes'), kv) text) =
  145. Div
  146. ( mempty
  147. , "code-container":if haskv then "custom-tag":classes' else classes'
  148. , []
  149. )
  150. $ [block] ++ maybe [Div (mempty, ["code-tag"], []) [Plain [Span (mempty, [], []) [Str tag]]]]
  151. where
  152. language' = case T.uncons language of
  153. Nothing -> mempty
  154. Just (c, cs) -> T.cons (toUpper c) cs
  155. tag = fromMaybe language' (lookup "tag" kv)
  156. haskv = fromMaybe False (True <$ lookup "tag" kv)
  157. maybe
  158. | "notag" `elem` classes' = const []
  159. | otherwise = id
  160. go block@(CodeBlock (identifier, [], kv) text) =
  161. Div (mempty, ["code-container"], [])
  162. [block, Div (mempty, ["empty-code-tag"], []) []]
  163. go x = x
  164. saveSynopsys :: Pandoc -> Compiler Pandoc
  165. saveSynopsys (Pandoc meta doc) =
  166. do
  167. id <- getUnderlying
  168. n <- fromMaybe (1 :: Int) . readMaybe . fromMaybe "" . lookupString "synopsys" <$> getMetadata id
  169. case dropWhile (not . isParagraph) doc of
  170. p:ps -> do
  171. saveSnapshot "synopsys" =<< makeItem (map removeFootnotes (take n (p:ps)))
  172. pure ()
  173. [] -> pure ()
  174. pure $ Pandoc meta doc
  175. where
  176. isParagraph Para{} = True
  177. isParagraph _ = False
  178. removeFootnotes (Para xs) = Para $ filter (\case { Note _ -> False; _ -> True }) xs
  179. removeFootnotes x = x
  180. saveWordCount :: Pandoc -> Compiler Pandoc
  181. saveWordCount (Pandoc meta doc) =
  182. do
  183. saveSnapshot "wc" =<< makeItem wordCount
  184. pure $ Pandoc meta doc
  185. where
  186. wordCount = show (getSum (query inlineLen doc))
  187. inlineLen (Str s) = Sum (length (T.words s))
  188. inlineLen _ = mempty
  189. saveTableOfContents :: Pandoc -> Compiler Pandoc
  190. saveTableOfContents (Pandoc meta input) =
  191. do
  192. saveSnapshot "table-of-contents" =<< makeItem toc
  193. pure $ Pandoc meta (fixHeaders 0 doc)
  194. where
  195. headers = filter (\case { Header _ _ _ -> True; _ -> False }) doc
  196. doc = fixHeaders 0 input
  197. fixHeaders n (Header l (_, ms, mt) x:bs) =
  198. Header l (anchor, ms, mt) (Link (anchor, ms, mt) [] (T.singleton '#' <> anchor, mempty):x):fixHeaders (n + 1) bs where
  199. anchor = T.pack ("h" ++ show n)
  200. fixHeaders k (x:bs) = x:fixHeaders k bs
  201. fixHeaders _ [] = []
  202. into :: [Block] -> [[Block]]
  203. into (Header l m@(anchor, _, _) x:ms) =
  204. let
  205. contained (Header l' _ _) = l' > l
  206. contained _ = undefined
  207. (ours, rest) = span contained ms
  208. in [Para [Link (mempty, mempty, mempty) (tail x) (T.singleton '#' <> anchor, mempty)], list (into ours)]:into rest
  209. into [] = []
  210. into _ = undefined
  211. list = BulletList
  212. toc :: Block
  213. toc = list (into headers)
  214. sassImporter :: SassImporter
  215. sassImporter = SassImporter 0 go where
  216. go "normalize" _ = do
  217. c <- readFile "node_modules/normalize.css/normalize.css"
  218. pure [ SassImport { importPath = Nothing
  219. , importAbsolutePath = Nothing
  220. , importSource = Just c
  221. , importSourceMap = Nothing
  222. } ]
  223. go _ _ = pure []
  224. setup :: IO (IORef KatexCache)
  225. setup = do
  226. setEnv "AMC_LIBRARY_PATH" "/usr/lib/amuletml/lib/"
  227. loadCache
  228. compiler :: IORef KatexCache -> Compiler (Item String)
  229. compiler katexCache = do
  230. wops <- writerOptions
  231. pandocCompilerWithTransformM readerOpts wops $
  232. katexFilter katexCache
  233. >=> abbreviationFilter
  234. >=> saveSynopsys
  235. >=> saveWordCount
  236. >=> saveTableOfContents
  237. >=> pure . addLanguageTag
  238. main :: IO ()
  239. main = setup >>= \katexCache -> hakyllWith conf $ do
  240. match "static/*" do
  241. route idRoute
  242. compile copyFileCompiler
  243. match "static/**/*" $ do
  244. route idRoute
  245. compile copyFileCompiler
  246. match "css/**/*" $ do
  247. route idRoute
  248. compile copyFileCompiler
  249. match "css/*.css" $ do
  250. route idRoute
  251. compile copyFileCompiler
  252. match "css/*.scss" $ do
  253. route $ setExtension "css"
  254. compile $ sassCompilerWith def { sassOutputStyle = SassStyleCompressed
  255. , sassImporters = Just [ sassImporter ]
  256. }
  257. match "diagrams/**/*.tex" $ do
  258. route $ setExtension "svg"
  259. compile $ getResourceBody
  260. >>= loadAndApplyTemplate "templates/tikz.tex" (bodyField "body")
  261. >>= withItemBody (return . pack
  262. >=> unixFilterLBS "rubber-pipe" ["--pdf"]
  263. >=> unixFilterLBS "pdftocairo" ["-svg", "-", "-"]
  264. >=> return . unpack)
  265. match "pages/posts/*" do
  266. route $ metadataRoute pathFromTitle
  267. compile $ do
  268. wops <- writerOptions
  269. id <- getUnderlying
  270. r <- compiler katexCache
  271. >>= loadAndApplyTemplate "templates/post.html" postCtx
  272. >>= saveSnapshot "content"
  273. >>= loadAndApplyTemplate "templates/default.html" postCtx
  274. >>= relativizeUrls
  275. loadSnapshot id "synopsys"
  276. >>= saveSnapshot "synopsys"
  277. . writePandocWith wops
  278. . fmap (Pandoc mempty)
  279. pure r
  280. match "pages/posts/*.lhs" $ version "raw" $ do
  281. route idRoute
  282. compile copyFileCompiler
  283. create ["archive.html"] $ do
  284. route idRoute
  285. compile $ do
  286. posts <- recentFirst =<< onlyPublic =<< loadAll ("pages/posts/*" .&&. hasNoVersion)
  287. let archiveCtx =
  288. listField "posts" postCtx (return posts) <>
  289. constField "title" "Archives" <>
  290. defaultContext
  291. makeItem ""
  292. >>= loadAndApplyTemplate "templates/archive.html" archiveCtx
  293. >>= loadAndApplyTemplate "templates/default.html" archiveCtx
  294. >>= relativizeUrls
  295. match "pages/*.html" $ do
  296. route $ gsubRoute "pages/" (const "")
  297. compile $ do
  298. posts <- fmap (take 5) . recentFirst =<< onlyPublic =<< loadAll ("pages/posts/*" .&&. hasNoVersion)
  299. let indexCtx =
  300. listField "posts" postCtx (return posts) <>
  301. constField "title" "Home" <>
  302. defaultContext
  303. getResourceBody
  304. >>= applyAsTemplate indexCtx
  305. >>= loadAndApplyTemplate "templates/default.html" indexCtx
  306. >>= relativizeUrls
  307. match "pages/*.md" $ do
  308. route $ setExtension "html" <> gsubRoute "pages/" (const "")
  309. compile $ compiler katexCache
  310. >>= loadAndApplyTemplate "templates/page.html" defaultContext
  311. >>= loadAndApplyTemplate "templates/default.html" defaultContext
  312. >>= relativizeUrls
  313. match "syntax/*.xml" $ compile $ do
  314. path <- toFilePath <$> getUnderlying
  315. contents <- itemBody <$> getResourceBody
  316. debugCompiler ("Loaded syntax definition from " ++ show path)
  317. res <- unsafeCompiler (Sky.parseSyntaxDefinitionFromString path contents)
  318. _ <- saveSnapshot "syntax" =<< case res of
  319. Left e -> fail e
  320. Right x -> makeItem x
  321. makeItem contents
  322. match "templates/*" $ compile templateBodyCompiler
  323. create ["feed.xml"] $ do
  324. route idRoute
  325. compile $ do
  326. let feedCtx = postCtx <> bodyField "description"
  327. posts <- fmap (take 10) . recentFirst =<< onlyPublic =<< loadAllSnapshots ("pages/posts/*" .&&. hasNoVersion) "synopsys"
  328. renderRss rssfeed feedCtx posts
  329. onlyPublic :: [Item String] -> Compiler [Item String]
  330. onlyPublic = filterM isPublic where
  331. isPublic item = do
  332. t <- getMetadata (itemIdentifier item)
  333. case HMap.lookup "public" t of
  334. Just (Bool False) -> pure False
  335. _ -> pure True
  336. postCtx :: Context String
  337. postCtx =
  338. dateField "date" "%B %e, %Y"
  339. <> snapshotField "synopsys" "synopsys"
  340. <> snapshotField "words" "wc"
  341. <> snapshotField' render "toc" "table-of-contents"
  342. <> defaultContext
  343. where
  344. snapshotField = snapshotField' pure
  345. snapshotField' f key snap = field key $ \x -> do
  346. let id = itemIdentifier x
  347. fmap itemBody . f =<< loadSnapshot id snap
  348. render x = do
  349. wops <- writerOptions
  350. pure . writePandocWith wops . fmap (Pandoc mempty . pure) $ x
  351. readProcessBS :: FilePath -> [String] -> BS.ByteString -> IO (BS.ByteString, String)
  352. readProcessBS path args input =
  353. let process = (proc path args)
  354. { std_in = CreatePipe
  355. , std_out = CreatePipe
  356. , std_err = CreatePipe
  357. }
  358. in withCreateProcess process $ \stdin stdout stderr ph ->
  359. case (stdin, stdout, stderr) of
  360. (Nothing, _, _) -> fail "Failed to get a stdin handle."
  361. (_, Nothing, _) -> fail "Failed to get a stdout handle."
  362. (_, _, Nothing) -> fail "Failed to get a stderr handle."
  363. (Just stdin, Just stdout, Just stderr) -> do
  364. out <- BS.hGetContents stdout
  365. err <- hGetContents stderr
  366. withForkWait (evaluate $ rnf out) $ \waitOut ->
  367. withForkWait (evaluate $ rnf err) $ \waitErr -> do
  368. -- Write input and close.
  369. BS.hPutStr stdin input
  370. hClose stdin
  371. -- wait on the output
  372. waitOut
  373. waitErr
  374. hClose stdout
  375. hClose stderr
  376. -- wait on the process
  377. ex <- waitForProcess ph
  378. case ex of
  379. ExitSuccess -> pure (out, err)
  380. ExitFailure ex -> fail (err ++ "Exited with " ++ show ex)
  381. where
  382. withForkWait :: IO () -> (IO () -> IO a) -> IO a
  383. withForkWait async body = do
  384. waitVar <- newEmptyMVar :: IO (MVar (Either SomeException ()))
  385. mask $ \restore -> do
  386. tid <- forkIO $ try (restore async) >>= putMVar waitVar
  387. let wait = takeMVar waitVar >>= either throwIO return
  388. restore (body wait) `onException` killThread tid
  389. pathFromTitle :: Metadata -> Routes
  390. pathFromTitle meta =
  391. let
  392. declaredCategory =
  393. case lookupString "category" meta of
  394. Just s -> ((s ++ "/") ++)
  395. Nothing -> ("posts/" <>)
  396. !titleString =
  397. case lookupString "title" meta of
  398. Just s -> s
  399. Nothing -> error "post has no title?"
  400. title = filter (/= "") . map (filter isAlphaNum . map toLower) . words $ titleString
  401. (category, title') =
  402. if | "or" `elem` title -> (declaredCategory, takeWhile (/= "or") title)
  403. | ["a", "quickie"] `isPrefixOf` title -> (("quick/" ++), drop 2 title)
  404. | otherwise -> (declaredCategory, title)
  405. in
  406. case lookupString "path" meta of
  407. Just p -> constRoute (category (p <> ".html"))
  408. Nothing -> constRoute (category (intercalate "-" title' <> ".html"))
  409. foldMapM :: (Monad w, Monoid m, Foldable f) => (a -> w m) -> f a -> w m
  410. foldMapM k = foldr (\x y -> do { m <- k x; (m <>) <$> y }) (pure mempty)
  411. loadCache :: HasCallStack => IO (IORef KatexCache)
  412. loadCache = do
  413. t <- doesFileExist ".katex_cache"
  414. let fixup (a, b, c) = KatexCache (HMap.fromList a) (HMap.fromList b) (HMap.fromList c)
  415. map <- if t
  416. then (fixup <$> decodeFile ".katex_cache") `catch` \e ->
  417. const (print e *> pure (KatexCache mempty mempty mempty)) (e :: SomeException)
  418. else pure (KatexCache mempty mempty mempty)
  419. var <- newIORef map
  420. pure var
  421. flushCache :: IORef KatexCache -> IO ()
  422. flushCache var = do
  423. KatexCache x y z <- readIORef var
  424. Data.Binary.encodeFile ".katex_cache" (HMap.toList x, HMap.toList y, HMap.toList z)
  425. invalidateCache :: Identifier -> [String] -> IORef KatexCache -> Compiler KatexCache
  426. invalidateCache id abbrevs cacheVar = unsafeCompiler $ atomicModifyIORef' cacheVar (\x -> (go x, go x)) where
  427. currentValues = map (\x -> (T.pack (takeWhile (/= ':') (tail x)), T.pack (tail (dropWhile (/= ':') (tail x)))))
  428. $ filter (not . isPrefixOf "-") abbrevs
  429. ident = show id
  430. go (KatexCache spanMap abbrKeys abbrText) =
  431. let
  432. go (abbr, val) (spanMap, abbrKeys, abbrText) =
  433. case HMap.lookup (ident, abbr) abbrText of
  434. Just vl | vl /= val ->
  435. let l = HMap.lookupDefault [] (ident, abbr) abbrKeys
  436. in (foldr HMap.delete spanMap l, abbrKeys, abbrText)
  437. _ -> (spanMap, abbrKeys, abbrText)
  438. (a, b, c) = foldr go (spanMap, abbrKeys, abbrText) currentValues
  439. in KatexCache a b c
  440. data KatexCache
  441. = KatexCache { spanMap :: HMap.HashMap (String, MathType, Text) Text
  442. , abbreviationKeys :: HMap.HashMap (String, Text) [(String, MathType, Text)]
  443. , abbreviationText :: HMap.HashMap (String, Text) Text
  444. }
  445. instance Hashable MathType where
  446. hashWithSalt s DisplayMath = hashWithSalt s (0 :: Int)
  447. hashWithSalt s InlineMath = hashWithSalt s (1 :: Int)