summaryrefslogtreecommitdiff
path: root/hakyll-nix/defaultsite/site.hs
diff options
context:
space:
mode:
Diffstat (limited to 'hakyll-nix/defaultsite/site.hs')
-rw-r--r--hakyll-nix/defaultsite/site.hs66
1 files changed, 66 insertions, 0 deletions
diff --git a/hakyll-nix/defaultsite/site.hs b/hakyll-nix/defaultsite/site.hs
new file mode 100644
index 0000000..f370ed9
--- /dev/null
+++ b/hakyll-nix/defaultsite/site.hs
@@ -0,0 +1,66 @@
+--------------------------------------------------------------------------------
+{-# LANGUAGE OverloadedStrings #-}
+import Data.Monoid (mappend)
+import Hakyll
+
+
+--------------------------------------------------------------------------------
+main :: IO ()
+main = hakyll $ do
+ match "images/*" $ do
+ route idRoute
+ compile copyFileCompiler
+
+ match "css/*" $ do
+ route idRoute
+ compile compressCssCompiler
+
+ match (fromList ["about.rst", "contact.markdown"]) $ do
+ route $ setExtension "html"
+ compile $ pandocCompiler
+ >>= loadAndApplyTemplate "templates/default.html" defaultContext
+ >>= relativizeUrls
+
+ match "posts/*" $ do
+ route $ setExtension "html"
+ compile $ pandocCompiler
+ >>= loadAndApplyTemplate "templates/post.html" postCtx
+ >>= loadAndApplyTemplate "templates/default.html" postCtx
+ >>= relativizeUrls
+
+ create ["archive.html"] $ do
+ route idRoute
+ compile $ do
+ posts <- recentFirst =<< loadAll "posts/*"
+ let archiveCtx =
+ listField "posts" postCtx (return posts) `mappend`
+ constField "title" "Archives" `mappend`
+ defaultContext
+
+ makeItem ""
+ >>= loadAndApplyTemplate "templates/archive.html" archiveCtx
+ >>= loadAndApplyTemplate "templates/default.html" archiveCtx
+ >>= relativizeUrls
+
+
+ match "index.html" $ do
+ route idRoute
+ compile $ do
+ posts <- recentFirst =<< loadAll "posts/*"
+ let indexCtx =
+ listField "posts" postCtx (return posts) `mappend`
+ defaultContext
+
+ getResourceBody
+ >>= applyAsTemplate indexCtx
+ >>= loadAndApplyTemplate "templates/default.html" indexCtx
+ >>= relativizeUrls
+
+ match "templates/*" $ compile templateBodyCompiler
+
+
+--------------------------------------------------------------------------------
+postCtx :: Context String
+postCtx =
+ dateField "date" "%B %e, %Y" `mappend`
+ defaultContext