I have modified your site.hs
to create a rudimentary tags list page which I believe has the structure required: a list of tags, each of which contains a list of posts with that tag.
Here's a summary of each of the things that I had to do to get it to work:
{-# LANGUAGE ViewPatterns #-}
Not strictly necessary, but a nice language extension which I use once. I thought I'd use/mention it since you mentioned that you're a beginner to Haskell, and it's nice to know about.
tags <- buildTags "posts/*" (fromCapture "tags/*.html")
There are two changes needed to this line, compared to the buildTags
in your initial site.hs
. One is that it should probably moved out of the individual match
clauses into the top level Rules
monad, so that we can create individual tag pages if required. The other is that the capture was similarly changed from "tags.html#"
to "tags/*.html"
. This is important because Hakyll wants every Item
to have a unique Identifier
, and not every tags page is the same.
Having the individual tag pages with unique identifiers may not be strictly necessary, but simplifies the rest of the setup since a lot of the Hakyll machinery assumes they exist. In particular, the Tags:
line in the individual post descriptions was not previously being rendered correctly either.
For the same reason, it's a good idea to actually make these individual tag pages routable: without this stanza in the top-level Rules
monad, the tags on each post won't render correctly with the default tagsField
that you use, since they can't figure out how to link to an individual tag page:
tagsRules tags $ \tag pat -> do
route idRoute
compile $ do
posts <- recentFirst =<< loadAll pat
let postCtx = postCtxWithTags tags
postsField = listField "posts" postCtx (pure posts)
titleField = constField "title" ("Posts tagged \""++tag++"\"")
indexCtx = postsField <> titleField <> defaultContext
makeItem "" >>= applyTemplate postListTemplate indexCtx
>>= applyTemplate defaultTemplate defaultContext
>>= relativizeUrls
>>= cleanIndexUrls
Alright, that's the preliminaries. Now onto the main attraction:
defaultCtxWithTags tags = listField "tags" tagsCtx getAllTags `mappend`
defaultContext
Alright, the important thing added here is some tags
field. It will contain one item for each thing returned by getAllTags
, and the fields on each item will be given by tagsCtx
.
where getAllTags :: Compiler [Item (String, [Identifier])]
getAllTags = pure . map mkItem $ tagsMap tags
where mkItem :: (String, [Identifier]) -> Item (String, [Identifier])
mkItem x@(t, _) = Item (tagsMakeId tags t) x
What's getAllTags
doing? Well, it starts with tagsMap tags
, just like your example. But Hakyll wants the result to be an Item
, so we have to wrap it up using mkItem
. What's in an Item
other than the body? Just an Identifier
, and the Tags
object happens to contain a field that tells us how to get this! So mkItem
just uses tagsMakeId
to get an identifier and wraps up the given body with that identifier.
What about tagsCtx?
tagsCtx :: Context (String, [Identifier])
tagsCtx = listFieldWith "posts" postsCtx getPosts `mappend`
metadataField `mappend`
urlField "url" `mappend`
pathField "path" `mappend`
titleField "title" `mappend`
missingField
Everything starting with metadataField
is just the usual stuff we expect to get from defaultContext
; we can't use defaultContext
here since it wants to add a bodyField
, but the body of this Item
isn't a string (but instead a much more useful for us Haskell structure representing a tag). The interesting bit of this is line which adds the posts
field, which should look a bit familiar. The big difference is that it uses listFieldWith
instead of listField
, which basically means that getPosts
gets an extra argument, which is the body of the Item
that this field is on. In this case, that's the tag record from tagsMap
.
where getPosts :: Item (String, [Identifier])
-> Compiler [Item String]
getPosts (itemBody -> (_, is)) = mapM load is
getPosts
mostly just uses the load
function to get ahold of the Item
for each post given its Identifier
---it's a lot like the loadAll
you do to get all the posts on the index page, but it just gives you one post. The weird-looking pattern-match on the left is ViewPatterns
in action: it's basically saying that for this pattern to match, the pattern on the right of the ->
(i.e. (_, is)
) should match the result of applying the function on the left (i.e. itemBody
) to the argument.
postsCtx :: Context String
postsCtx = postCtxWithTags tags
postsCtx
is very simple: just the same postCtxWithTags
used everywhere else we render a post.
That's everything necessary to get a Context
with everything that you want; all that's left is to actually make a template to render it!
tagListTemplateRaw :: Html
tagListTemplateRaw =
ul $ do
"$for(tags)$"
li ! A.class_ "" $ do
a ! href "$url$" $ "$title$"
ul $ do
"$for(posts)$"
li ! A.class_ "" $ do
a ! href "$url$" $ "$title$"
"$endfor$"
"$endfor$"
This is just a very simple template that renders nested lists; you could of course do various things to make it fancier/nicer-looking.
I have made a PR to your repo so that you can see these changes in context here.
Tags
are. You will need to use one of the functions that take aTags
argument and produce aCompiler
or betterContext
, that you can use instead of (or together with) thedefaultContext
. – Decasyllabictags
that I generated, and make a context from it that contains a list of all tags, and all their associated posts? – Frosteddata
type. You can usetagsMap tags
to get a list of tuples, each with a tag name and a list of page identifiers having that tag. Then read theTemplate
andContext
documentation for how to build alistField
from that, which you should be able to use to render a list of tag names. – DecasyllabicgetMetadata
will do that (when called in aCompiler
monad or the top-levelRule
monad). But first try to get the list of tag names working, and post an update to your question if you did. – DecasyllabiclistField
fromtagsMap tags
. – Frosted