summaryrefslogtreecommitdiff
path: root/examples/simpleblog/hakyll.hs
diff options
context:
space:
mode:
Diffstat (limited to 'examples/simpleblog/hakyll.hs')
-rw-r--r--examples/simpleblog/hakyll.hs90
1 files changed, 57 insertions, 33 deletions
diff --git a/examples/simpleblog/hakyll.hs b/examples/simpleblog/hakyll.hs
index 38472d5..db4230f 100644
--- a/examples/simpleblog/hakyll.hs
+++ b/examples/simpleblog/hakyll.hs
@@ -1,35 +1,59 @@
+{-# LANGUAGE OverloadedStrings #-}
module Main where
-import Text.Hakyll (hakyll)
-import Text.Hakyll.Render
-import Text.Hakyll.Context
-import Text.Hakyll.File (getRecursiveContents, directory)
-import Text.Hakyll.CreateContext (createPage, createCustomPage, createListing)
-import Data.List (sort)
-import Control.Monad (forM_, liftM)
-import Control.Monad.Reader (liftIO)
-import Data.Either (Either(..))
-
-main = hakyll "http://example.com" $ do
- -- Static directory.
- directory css "css"
-
- -- Find all post paths.
- postPaths <- liftM (reverse . sort) $ getRecursiveContents "posts"
- let postPages = map createPage postPaths
-
- -- Render index, including recent posts.
- let index = createListing "index.html" ["templates/postitem.html"]
- (take 3 postPages) [("title", Left "Home")]
- renderChain ["index.html", "templates/default.html"] index
-
- -- Render all posts list.
- let posts = createListing "posts.html" ["templates/postitem.html"]
- postPages [("title", Left "All posts")]
- renderChain ["posts.html", "templates/default.html"] posts
-
- -- Render all posts.
- liftIO $ putStrLn "Generating posts..."
- forM_ postPages $ renderChain [ "templates/post.html"
- , "templates/default.html"
- ]
+import Prelude hiding (id)
+import Control.Category (id)
+import Control.Arrow ((>>>), (***), arr)
+import Data.Monoid (mempty, mconcat)
+
+import Hakyll
+
+main :: IO ()
+main = hakyll $ do
+ -- Compress CSS
+ route "css/*" idRoute
+ compile "css/*" compressCssCompiler
+
+ -- Render posts
+ route "posts/*" $ setExtension ".html"
+ compile "posts/*" $
+ pageCompiler
+ >>> applyTemplateCompiler "templates/post.html"
+ >>> applyTemplateCompiler "templates/default.html"
+ >>> relativizeUrlsCompiler
+
+ -- Render posts list
+ route "posts.html" $ idRoute
+ create "posts.html" $
+ constA mempty
+ >>> arr (setField "title" "All posts")
+ >>> requireAllA "posts/*" addPostList
+ >>> applyTemplateCompiler "templates/posts.html"
+ >>> applyTemplateCompiler "templates/default.html"
+ >>> relativizeUrlsCompiler
+
+ -- Index
+ route "index.html" idRoute
+ create "index.html" $
+ constA mempty
+ >>> arr (setField "title" "Home")
+ >>> requireAllA "posts/*" (id *** arr (take 3 . reverse . sortByBaseName) >>> addPostList)
+ >>> applyTemplateCompiler "templates/index.html"
+ >>> applyTemplateCompiler "templates/default.html"
+ >>> relativizeUrlsCompiler
+
+ -- Read templates
+ compile "templates/*" templateCompiler
+
+ -- End
+ return ()
+
+-- | Auxiliary compiler: generate a post list from a list of given posts, and
+-- add it to the current page under @$posts@
+--
+addPostList :: Compiler (Page String, [Page String]) (Page String)
+addPostList = setFieldA "posts" $
+ arr (reverse . sortByBaseName)
+ >>> require "templates/postitem.html" (\p t -> map (applyTemplate t) p)
+ >>> arr mconcat
+ >>> arr pageBody