summaryrefslogtreecommitdiff
path: root/wiki.hs
diff options
context:
space:
mode:
authorJJ2024-09-30 04:03:56 +0000
committerJJ2024-09-30 04:03:56 +0000
commit80a28355e979d03ab2dad308758436ff5e32b2ea (patch)
tree27efc568680a9d216e897d93b488704d59589173 /wiki.hs
parentcd0681c71f5e700358ad3e3feea7d495753d8429 (diff)
meow
Diffstat (limited to 'wiki.hs')
-rw-r--r--wiki.hs63
1 files changed, 63 insertions, 0 deletions
diff --git a/wiki.hs b/wiki.hs
new file mode 100644
index 0000000..cd6e664
--- /dev/null
+++ b/wiki.hs
@@ -0,0 +1,63 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+import Hakyll hiding (pandocCompiler)
+import Text.Pandoc.Options
+import Text.Pandoc.Highlighting
+
+-- Pass custom options to the Pandoc compiler
+pandocCompiler :: Compiler (Item String)
+pandocCompiler = pandocCompilerWith readerOptions writerOptions where
+ writerOptions = defaultHakyllWriterOptions {
+ writerExtensions = writerExtensions defaultHakyllWriterOptions
+ <> pandocExtensions,
+ writerHTMLMathMethod = MathML
+ }
+ readerOptions = defaultHakyllReaderOptions {
+ readerExtensions = readerExtensions defaultHakyllReaderOptions
+ <> pandocExtensions
+ <> extensionsFromList [Ext_lists_without_preceding_blankline]
+ }
+
+-- Applies the template specified in a post's metadata, if it exists
+applyMetadataTemplate :: Context String -> Item String -> Compiler (Item String)
+applyMetadataTemplate context item = do
+ field <- getMetadataField (itemIdentifier item) "layout"
+ case field of
+ Just path ->
+ let templatePath = "_templates/" ++ path ++ ".html" in
+ loadAndApplyTemplate (fromFilePath templatePath) context item
+ _ -> return item
+
+main :: IO ()
+main = hakyll $ do
+ -- Compile templates for future use
+ match "_templates/*" $ compile templateBodyCompiler
+
+ -- Detect whether HTML files are standalone or in need of a template
+ match ("**.html" .||. "**.htm") $ do
+ route idRoute
+ compile $ do
+ identifier <- getUnderlying
+ field <- getMetadataField identifier "layout"
+ case field of
+ Just _ -> pandocCompiler
+ Nothing -> getResourceBody
+ >>= applyMetadataTemplate defaultContext
+ >>= relativizeUrls
+
+ -- Match all other renderable files and apply their template, if it exists
+ match ("**.md" .||. "**.rst" .||. "**.org" .||. "**.adoc") $ do
+ route $ setExtension "html"
+ compile $ pandocCompiler
+ >>= applyMetadataTemplate defaultContext
+ >>= relativizeUrls
+
+ -- Additionally copy non-HTML files raw, without front matter
+ match ("**.md" .||. "**.rst" .||. "**.org" .||. "**.adoc") $ version "raw" $ do
+ route idRoute
+ compile getResourceBody
+
+ -- Copy all additional files verbatium
+ match "**" $ do
+ route idRoute
+ compile copyFileCompiler