haskellstatic-sitehakyll

How to have a second list for a second directory of posts in Hakyll html?


I have a section in an index page that lists posts from the posts/* directory. What I would like is to have another section that lists posts from a bibs/* directory.

So, it would look something like:

                    <section id="one" class="wrapper style2 spotlights">
                        <section>
                            <div class="content">
                                <div class="inner">
                                    <h2>Blog posts</h2>
                                    $body$
                                    <p><a href="./posts.html">See all.</a></p>
                                </div>
                            </div>
                        </section>
                    </section>
                    <!-- Two -->
                    <section id="two" class="wrapper style1 fade-up">
                        <div class="inner">
                            <h2>Bibliographies</h2>
                            $body2$
                            <p><a href="./bibs.html">See all bibs.</a></p>
                        </div>
                    </section>

Currently, I get the error

[ERROR] Hakyll.Web.Template.applyTemplate: Failed to apply template templates/index.html to item index.html:
    In expr '$body2$',
    Tried field title,
    Tried field date,
    Tried field body,
    No 'body2' field in metadata of item index.html,
    Tried field url,
    Tried field path,
    Tried field title,
    Missing field 'body2' in context

The code I am using for my regular posts is below - how can I replicate the same list, but for a different directory? (I have cut the irrelevant code to save length, if you want to see the projects source, you can here, with the relevant files being site.hs and templates/index.html.) Thank you for your time, and please let me know if I can clarify anything or give additional information.

defaultCtx :: Context String
defaultCtx = dateField "date" "%B %e, %Y" <> defaultContext

basicCtx :: String -> Context String
basicCtx title = constField "title" title <> defaultCtx

homeCtx :: Context String
homeCtx = basicCtx "Home"

allPostsCtx :: Context String
allPostsCtx = basicCtx "All posts"

feedCtx :: Context String
feedCtx = bodyField "description" <> defaultCtx

tagsCtx :: Tags -> Context String
tagsCtx tags = tagsField "prettytags" tags <> defaultCtx

postsCtx :: String -> String -> Context String
postsCtx title list = constField "body" list <> basicCtx title

externalizeUrls :: String -> Item String -> Compiler (Item String)
externalizeUrls root item = return $ withUrls ext <$> item
  where
    ext x = if isExternal x then x else root ++ x

unExternalizeUrls :: String -> Item String -> Compiler (Item String)
unExternalizeUrls root item = return $ withUrls unExt <$> item
  where
    unExt x = fromMaybe x $ stripPrefix root x

postList :: Tags -> Pattern -> ([Item String] -> Compiler [Item String]) -> Compiler String
postList tags pattern preprocess' = do
    postItemTpl <- loadBody "templates/postitem.html"
    posts <- preprocess' =<< loadAll pattern
    applyTemplateList postItemTpl (tagsCtx tags) posts

main :: IO ()
main = hakyllWith configuration $ do
    -- Build tags
    tags <- buildTags "posts/*" $ fromCapture "tags/*.html"
    let tagsCtx' = tagsCtx tags

    match "posts/*" $ do
        route   $ setExtension ".html"
        compile $ pandocCompiler
            >>= loadAndApplyTemplate "templates/post.html"     tagsCtx'
            >>= (externalizeUrls     $ feedRoot feedConfiguration)
            >>= saveSnapshot         "content"
            >>= (unExternalizeUrls   $ feedRoot feedConfiguration)
            >>= loadAndApplyTemplate "templates/default.html"  tagsCtx'
            >>= relativizeUrls

    create ["posts.html"] $ do
        route idRoute
        compile $ do
            list <- postList tags "posts/*" recentFirst
            makeItem list
                >>= loadAndApplyTemplate "templates/posts.html"   allPostsCtx
                >>= loadAndApplyTemplate "templates/default.html" allPostsCtx
                >>= relativizeUrls

    create ["index.html"] $ do
        route idRoute
        compile $ do
            list <- postList tags "posts/*" (fmap (take 10) . recentFirst)
            makeItem list
                >>= loadAndApplyTemplate "templates/index.html"   homeCtx
                >>= loadAndApplyTemplate "templates/default.html" homeCtx
                >>= relativizeUrls

    tagsRules tags $ \tag pattern -> do
        route idRoute
        compile $ do
            list <- postList tags pattern recentFirst

            let title       = "Posts tagged '" ++ tag ++ "'"
            let defaultCtx' = basicCtx title
            let postsCtx'   = postsCtx title list

            makeItem ""
                >>= loadAndApplyTemplate "templates/posts.html"   postsCtx'
                >>= loadAndApplyTemplate "templates/default.html" defaultCtx'
                >>= relativizeUrls

Solution

  • You can use the field and <> combinators to extend a Context (homeCtx in this case) with the contents of the lists under some tags. Here, I've renamed the tags body and body2 to posts and bibs because body is a tag with a special meaning in Hakyll. Remember to also rename the tags in templates/index.html.

        -- Index
        create ["index.html"] $ do
            route idRoute
            compile $ do
                let mkposts = postList tags "posts/*" (fmap (take 10) . recentFirst)
                    mkbibs = bibList tags "bibs/*" (fmap (take 10) . recentFirst)
                    homeCtx' = field "posts" (const mkposts)  -- Populate the context with those fields
                            <> field "bibs" (const mkbibs)    --
                            <> homeCtx
                makeItem ""  -- This doesn't matter since the next template does not contain "body" (after renaming it to "posts")
                    >>= loadAndApplyTemplate "templates/index.html"   homeCtx'  -- This template mentions "posts" and "bibs", which will be looked up in homeCtx'
                    >>= loadAndApplyTemplate "templates/default.html" homeCtx'
                    >>= relativizeUrls