summaryrefslogtreecommitdiffstats
path: root/site.hs
diff options
context:
space:
mode:
authorLibravatar cel 🌸 <cel@blos.sm>2024-07-11 02:38:39 +0100
committerLibravatar cel 🌸 <cel@blos.sm>2024-07-11 02:38:39 +0100
commit3a1d7848cb3ceb122b573737b4fba8106792ab5d (patch)
tree6fb0101f38ecd8d3e4fcae79dc96a01d24468951 /site.hs
downloadinfoculture.pub-3a1d7848cb3ceb122b573737b4fba8106792ab5d.tar.gz
infoculture.pub-3a1d7848cb3ceb122b573737b4fba8106792ab5d.tar.bz2
infoculture.pub-3a1d7848cb3ceb122b573737b4fba8106792ab5d.zip
initial commit
Diffstat (limited to 'site.hs')
-rw-r--r--site.hs161
1 files changed, 161 insertions, 0 deletions
diff --git a/site.hs b/site.hs
new file mode 100644
index 0000000..b8ad4b3
--- /dev/null
+++ b/site.hs
@@ -0,0 +1,161 @@
+--------------------------------------------------------------------------------
+{-# LANGUAGE OverloadedStrings #-}
+import Data.Monoid (mappend)
+import System.FilePath ((</>), (<.>), splitExtension, splitFileName, takeDirectory)
+import Hakyll
+
+
+--------------------------------------------------------------------------------
+main :: IO ()
+main = hakyll $ do
+ match "assets/*" $ do
+ route idRoute
+ compile copyFileCompiler
+
+ match "fonts/*" $ do
+ route idRoute
+ compile copyFileCompiler
+
+ match "files/*" $ do
+ route idRoute
+ compile copyFileCompiler
+
+
+ match "style.css" $ do
+ route idRoute
+ compile compressCssCompiler
+
+ match (fromList ["about.md", "contact.md"]) $ do
+ route $ setExtension "html" `composeRoutes` appendIndex
+ compile $ pandocCompiler
+ >>= loadAndApplyTemplate "templates/base.html" defaultContext
+ >>= relativizeUrls
+
+ -- build up tags
+ tags <- buildTags "posts/*" (fromCapture "tags/*.html")
+ tagsRules tags $ \tag pattern -> do
+ let title = "posts tagged \"" ++ tag ++ "\""
+ route appendIndex
+ compile $ do
+ posts <- recentFirst =<< loadAll pattern
+ let ctx = constField "title" title
+ `mappend` listField "posts" (postCtxWithTags tags) (return posts)
+ `mappend` defaultContext
+
+ makeItem ""
+ >>= loadAndApplyTemplate "templates/tag.html" ctx
+ >>= loadAndApplyTemplate "templates/base.html" ctx
+ >>= relativizeUrls
+
+ match "posts/*" $ do
+ route $ setExtension "html" `composeRoutes`
+ dateFolders `composeRoutes`
+ appendIndex
+ compile $ pandocCompiler
+ >>= saveSnapshot "article-text"
+ >>= loadAndApplyTemplate "templates/post.html" (postCtxWithTags tags)
+ >>= saveSnapshot "content"
+ >>= loadAndApplyTemplate "templates/base.html" (postCtxWithTags tags)
+ >>= relativizeUrls
+
+ match "posts/*" $ version "raw" $ do
+ route idRoute
+ compile getResourceBody
+
+ create ["archives.html"] $ do
+ route appendIndex
+ compile $ do
+ posts <- recentFirst =<< loadAll ("posts/*" .&&. hasNoVersion)
+ let archiveCtx =
+ listField "posts" postCtx (return posts) `mappend`
+ constField "title" "archives" `mappend`
+ defaultContext
+
+ makeItem ""
+ >>= loadAndApplyTemplate "templates/archives.html" archiveCtx
+ >>= loadAndApplyTemplate "templates/base.html" archiveCtx
+ >>= relativizeUrls
+
+
+ match "index.html" $ do
+ route idRoute
+ compile $ do
+ posts <- recentFirst =<< loadAllSnapshots ("posts/*" .&&. hasNoVersion) "article-text"
+ let indexCtx =
+ listField "posts" postCtx (return posts) `mappend`
+ defaultContext
+
+ getResourceBody
+ >>= applyAsTemplate indexCtx
+ >>= loadAndApplyTemplate "templates/base.html" indexCtx
+ >>= relativizeUrls
+
+ match "templates/*" $ compile templateBodyCompiler
+
+ create ["feed.xml"] $ do
+ route idRoute
+ compile $ do
+ let feedCtx = postCtx `mappend` bodyField "description"
+ posts <- fmap (take 10) . recentFirst =<<
+ loadAllSnapshots ("posts/*" .&&. hasNoVersion) "content"
+ renderAtom feedConfig feedCtx posts
+
+ create ["sitemap.xml"] $ do
+ route idRoute
+ compile $ do
+ -- load and sort the posts
+ posts <- recentFirst =<< loadAll "posts/*"
+
+ -- load individual pages from a list (globs DO NOT work here)
+ singlePages <- loadAll (fromList ["about.md", "contact.md", "archives.html", "feed.xml"])
+
+ -- mappend the posts and singlePages together
+ let pages = posts <> singlePages
+
+ -- create the `pages` field with the postCtx
+ -- and return the `pages` value for it
+ sitemapCtx =
+ constField "root" root <>
+ listField "pages" postCtx (return pages)
+
+ -- make the item and apply our sitemap template
+ makeItem ""
+ >>= loadAndApplyTemplate "templates/sitemap.xml" sitemapCtx
+
+
+--------------------------------------------------------------------------------
+postCtx :: Context String
+postCtx =
+ constField "root" root `mappend`
+ dateField "date" "%Y-%m-%d" `mappend`
+ dropIndexHtml "url" `mappend`
+ defaultContext
+
+postCtxWithTags :: Tags -> Context String
+postCtxWithTags tags = tagsField "tags" tags `mappend` postCtx
+
+appendIndex :: Routes
+appendIndex = customRoute $
+ (\(p, e) -> p </> "index" <.> e) . splitExtension . toFilePath
+
+dropIndexHtml :: String -> Context a
+dropIndexHtml key = mapContext transform (urlField key) where
+ transform url = case splitFileName url of
+ (p, "index.html") -> takeDirectory p
+ _ -> url
+
+dateFolders :: Routes
+dateFolders =
+ gsubRoute "/[0-9]{4}-[0-9]{2}-[0-9]{2}-" $ replaceAll "-" (const "/")
+
+root :: String
+root = "https://infoculture.pub"
+
+feedConfig :: FeedConfiguration
+feedConfig = FeedConfiguration
+ { feedTitle = "info{culture}"
+ , feedDescription = "cultivating informatics"
+ , feedAuthorName = "cel ❀"
+ , feedAuthorEmail = "cel@infoculture.pub"
+ , feedRoot = "https://infoculture.pub"
+ }