hakyll/examples/tagblog/hakyll.hs

61 lines
2.3 KiB
Haskell
Raw Normal View History

module Main where
import Text.Hakyll (hakyll)
import Text.Hakyll.Render
import Text.Hakyll.Tags (readTagMap, renderTagCloud, renderTagLinks)
import Text.Hakyll.File (getRecursiveContents, directory, removeSpaces)
2010-01-29 14:16:08 +00:00
import Text.Hakyll.Renderables (createPagePath, createCustomPage, createListingWith, createListing)
import Text.Hakyll.Context (ContextManipulation, renderDate)
import Data.List (sort)
import Data.Map (toList)
import Control.Monad (mapM_, liftM)
import Data.Either (Either(..))
main = hakyll $ do
-- Static directory.
directory css "css"
-- Find all post paths.
postPaths <- liftM (reverse . sort) $ getRecursiveContents "posts"
let renderablePosts = map createPagePath postPaths
-- Read tag map.
tagMap <- readTagMap "postTags" renderablePosts
-- Render all posts list.
renderPostList "posts.html" "All posts" renderablePosts
-- Render post list per tag
2010-01-31 10:19:57 +00:00
mapM_ (\(tag, posts) -> renderPostList (tagToUrl tag) ("Posts tagged " ++ tag) posts)
(toList tagMap)
-- Render index, including recent posts.
2010-01-31 10:19:57 +00:00
let tagCloud = renderTagCloud tagMap tagToUrl 100 200
2010-01-29 12:58:29 +00:00
index = createListingWith postManipulation "index.html"
"templates/postitem.html"
(take 3 renderablePosts)
[ ("title", "Home")
, ("tagcloud", tagCloud)
]
renderChain ["index.html", "templates/default.html"] index
-- Render all posts.
mapM_ (renderChainWith postManipulation
["templates/post.html"
,"templates/default.html"
]) renderablePosts
-- Render rss feed
2010-01-29 14:16:08 +00:00
let rss = createListing "rss.xml" "templates/rssitem.xml" (take 3 renderablePosts) []
renderChain ["templates/rss.xml"] rss
where postManipulation :: ContextManipulation
postManipulation = renderDate "date" "%B %e, %Y" "Date unknown"
2010-01-31 10:19:57 +00:00
. renderTagLinks tagToUrl
2010-01-31 10:19:57 +00:00
tagToUrl tag = "$root/tags/" ++ removeSpaces tag ++ ".html"
renderPostList url title posts = do
let list = createListingWith postManipulation url "templates/postitem.html" posts [("title", title)]
renderChain ["posts.html", "templates/default.html"] list