Updated categoryblog example to Hakyll-2.x.

This commit is contained in:
Jasper Van der Jeugt 2010-03-30 17:36:56 +02:00
parent 6fd37349cf
commit 82931dd666
4 changed files with 37 additions and 40 deletions

View file

@ -1,64 +1,75 @@
module Main where module Main where
import Control.Arrow ((>>>), arr)
import Text.Hakyll (hakyll) import Text.Hakyll (hakyll)
import Text.Hakyll.Render import Text.Hakyll.Render
import Text.Hakyll.Tags (TagMap, readCategoryMap) import Text.Hakyll.Tags (readCategoryMap, withTagMap)
import Text.Hakyll.Feed (FeedConfiguration (..), renderRss)
import Text.Hakyll.File (getRecursiveContents, directory, removeSpaces, sortByBaseName) import Text.Hakyll.File (getRecursiveContents, directory, removeSpaces, sortByBaseName)
import Text.Hakyll.Renderables (createPagePath, createCustomPage, createListingWith, createListing) import Text.Hakyll.CreateContext (createPage, createCustomPage, createListing)
import Text.Hakyll.Context (ContextManipulation, renderDate) import Text.Hakyll.ContextManipulations (renderDate, copyValue, changeValue)
import Text.Hakyll.Util (link) import Text.Hakyll.Util (link)
import Data.Map (toList) import Data.Map (toList)
import Control.Monad (mapM_, liftM, (<=<)) import Control.Monad (mapM_, liftM, (<=<))
import Data.Either (Either(..)) import Data.Either (Either(..))
main = hakyll $ do main = hakyll "http://example.com" $ do
-- Static directory. -- Static directory.
directory css "css" directory css "css"
-- Find all post paths. -- Find all post paths.
postPaths <- liftM (reverse . sortByBaseName) $ getRecursiveContents "posts" postPaths <- liftM (reverse . sortByBaseName) $ getRecursiveContents "posts"
let renderablePosts = map createPagePath postPaths let renderablePosts = map ((>>> postManipulation) . createPage) postPaths
-- Read category map. -- Read category map.
categoryMap <- readCategoryMap "categoryMap" renderablePosts let categoryMap = readCategoryMap "categoryMap" postPaths
-- Render all posts list. -- Render all posts list.
renderPostList "posts.html" "All posts" renderablePosts renderPostList "posts.html" "All posts" renderablePosts
-- Render post list per category -- Render post list per category
mapM_ (\(category, posts) -> renderPostList (categoryToUrl category) ("Posts about " ++ category) posts) let renderListForCategory category posts =
(toList categoryMap) renderPostList (categoryToUrl category) ("Posts about " ++ category)
(map (>>> postManipulation) posts)
withTagMap categoryMap renderListForCategory
-- Render index, including recent posts. -- Render index, including recent posts.
let index = createListingWith postManipulation "index.html" let index = createListing "index.html"
"templates/postitem.html" ["templates/postitem.html"]
(take 3 renderablePosts) (take 3 renderablePosts)
[ ("title", "Home") [ ("title", Left "Home")
, ("categories", categoryList categoryMap) , ("categories", Right $ categoryMap >>> categoryList)
] ]
renderChain ["index.html", "templates/default.html"] index renderChain ["index.html", "templates/default.html"] index
-- Render all posts. -- Render all posts.
mapM_ (renderChainWith postManipulation mapM_ (renderChain ["templates/post.html"
["templates/post.html" ,"templates/default.html"
,"templates/default.html" ]) renderablePosts
]) renderablePosts
-- Render rss feed -- Render rss feed
let rss = createListing "rss.xml" "templates/rssitem.xml" (take 3 renderablePosts) [] renderRss myFeedConfiguration $
renderChain ["templates/rss.xml"] rss map (>>> copyValue "body" "description") (take 3 renderablePosts)
where postManipulation :: ContextManipulation where postManipulation = renderDate "date" "%B %e, %Y" "Date unknown"
postManipulation = renderDate "date" "%B %e, %Y" "Date unknown" >>> renderCategoryLink
renderCategoryLink = changeValue "category" (\c -> link c $ categoryToUrl c)
categoryToUrl category = "$root/categories/" ++ removeSpaces category ++ ".html" categoryToUrl category = "$root/categories/" ++ removeSpaces category ++ ".html"
categoryList :: TagMap -> String categoryList = arr $ uncurry categoryListItem <=< toList
categoryList = uncurry categoryListItem <=< toList
categoryListItem category posts = "<li>" ++ link category (categoryToUrl category) categoryListItem category posts = "<li>" ++ link category (categoryToUrl category)
++ " - " ++ show (length posts) ++ " items.</li>" ++ " - " ++ show (length posts) ++ " items.</li>"
renderPostList url title posts = do renderPostList url title posts = do
let list = createListingWith postManipulation url "templates/postitem.html" posts [("title", title)] let list = createListing url ["templates/postitem.html"] posts [("title", Left title)]
renderChain ["posts.html", "templates/default.html"] list renderChain ["posts.html", "templates/default.html"] list
myFeedConfiguration = FeedConfiguration
{ feedUrl = "rss.xml"
, feedTitle = "SimpleBlog RSS feed."
, feedDescription = "A simple demo of an RSS feed created with Hakyll."
, feedAuthorName = "Jasper Van der Jeugt"
}

View file

@ -1,5 +1,5 @@
<h1>$title</h1> <h1>$title</h1>
by <em>$author</em> on <strong>$date</strong> by <em>$author</em> on <strong>$date</strong>
<div>Tagged as: $tags.</div> <div>Posted in: $category.</div>
$body $body

View file

@ -1,9 +0,0 @@
<?xml version="1.0" ?>
<rss version="2.0">
<channel>
<title>The SimpleBlog</title>
<link>http://example.com</link>
<description>Simple blog in hakyll</description>
$items
</channel>
</rss>

View file

@ -1,5 +0,0 @@
<item>
<title>$title</title>
<link>http://example.com/$url</link>
<description>$title by $author</description>
</item>