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.

472 lines
16 KiB

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