summaryrefslogtreecommitdiff
path: root/data/example/site.hs
diff options
context:
space:
mode:
Diffstat (limited to 'data/example/site.hs')
-rw-r--r--data/example/site.hs50
1 files changed, 41 insertions, 9 deletions
diff --git a/data/example/site.hs b/data/example/site.hs
index ccf8ff8..5f064e8 100644
--- a/data/example/site.hs
+++ b/data/example/site.hs
@@ -1,8 +1,8 @@
--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
-import Hakyll
-import Data.List (sort)
-import Control.Applicative ((<$>))
+import Control.Applicative ((<$>))
+import Data.Monoid (mappend)
+import Hakyll
--------------------------------------------------------------------------------
@@ -16,7 +16,7 @@ main = hakyll $ do
route idRoute
compile compressCssCompiler
- match (fromList ["about.rst", "code.lhs"]) $ do
+ match (fromList ["about.rst", "contact.markdown"]) $ do
route $ setExtension "html"
compile $ pageCompiler
>>= requireApplyTemplate "templates/default.html" defaultContext
@@ -28,16 +28,48 @@ main = hakyll $ do
post <- pageCompiler
saveSnapshot "content" post
return post
- >>= requireApplyTemplate "templates/default.html" defaultContext
+ >>= requireApplyTemplate "templates/post.html" postCtx
+ >>= requireApplyTemplate "templates/default.html" postCtx
>>= relativizeUrls
+ match "archive.html" $ do
+ route idRoute
+ compile $ do
+ let archiveCtx =
+ field "posts" (\_ -> postList recentFirst) `mappend`
+ constField "title" "Archives" `mappend`
+ defaultContext
+
+ makeItem ""
+ >>= requireApplyTemplate "templates/archive.html" archiveCtx
+ >>= requireApplyTemplate "templates/default.html" archiveCtx
+ >>= relativizeUrls
+
+
match "index.html" $ do
route idRoute
compile $ do
- posts <- sort <$> getMatches "posts/*"
- post <- requireSnapshot (head posts) "content"
- return post
- >>= requireApplyTemplate "templates/default.html" defaultContext
+ let indexCtx = field "posts" $ \_ -> postList (take 3 . recentFirst)
+
+ getResourceBody
+ >>= applySelf indexCtx
+ >>= requireApplyTemplate "templates/default.html" postCtx
>>= relativizeUrls
match "templates/*" $ compile templateCompiler
+
+
+--------------------------------------------------------------------------------
+postCtx :: Context String
+postCtx =
+ dateField "date" "%B %e, %Y" `mappend`
+ defaultContext
+
+
+--------------------------------------------------------------------------------
+postList :: ([Item String] -> [Item String]) -> Compiler String
+postList preprocess = do
+ posts <- preprocess <$> requireAll "posts/*"
+ itemTpl <- requireBody "templates/post-item.html"
+ list <- applyTemplateList itemTpl postCtx posts
+ return list