dirty-haskell.org: Switch to Hakyll

It's not crazy — it's having fun with types.

I stopped using the software suite inherited from math.kleen.org and switched over to using hakyll instead, since I realised that the two were doing essentially the same job and keeping my mess in one haskell file (src/Site.hs) instead of spread over a large number of interlocking zsh and haskell scripts.

I expect nothing to be seriously broken (Only the filepaths of lists have changed), but some feed readers might have stopped working (hakyll´s deceptively named renderRss actually renders atom).

Implementation Details

I´m using this post to document some of the more involved things I had to do during migration in no particular order.

Lists → Tags

I´m using hakyll´s implementation of tags instead of the math.kleen.org concept of lists, now.

This required some tweaking.

In order to retain the All Posts list I introduced a function to add new tags to an already existing Tags structure and used it to add my desired pseudo-tag.

main = hakyllWith config $ do
  …
  tags <- buildTags "posts/*" tagTranslation' >>= addTag "All Posts" "posts/*"addTag :: MonadMetadata m => String -> Pattern -> Tags -> m Tags
addTag name pattern tags = do
  ids <- getMatches pattern
  return $ tags { tagsMap = tagsMap tags ++ [(name, ids)] }

Printing lists is an involved affair

I wanted to keep the layout of the site including the lists of posts on the index page.

Generating those lists turned out to be a hassle.

The Rule for index.md adds to the context of the templates used in it´s creation a list field which contains verbatim HTML as produced by renderTag for each tag. A trick I used to implement the desired behaviour of replacing old posts with “…” is to introduce a pseudo post-item which has a flag in it´s context to tell the corresponding template to only print “…”. Trimming the list of posts is straightforward.

renderTag :: String -- ^ Tag name
          -> Tags
          -> Compiler (Item String)
renderTag tag tags = do
  ellipsisItem <- makeItem ""
  let
    ids = fromMaybe [] $ lookup tag $ tagsMap tags
    postCtx = mconcat [ listField "posts" (ellipsisContext ellipsisItem) $
                          liftM (withEllipsis ellipsisItem) $ chronological =<< mapM load ids
                      , constField "title" tag
                      , constField "rss" ("tags/" ++ tagTranslation tag ++ ".rss")
                      , constField "url" ("tags/" ++ tagTranslation tag ++ ".html")
                      , defaultContext
                      ]
  makeItem ""
    >>= loadAndApplyTemplate "templates/post-list.html" postCtx
    >>= loadAndApplyTemplate "templates/tag.html" postCtx
  where
    ellipsisContext item = mconcat [ boolField "ellipsis" (== item)
                                   , defaultContext
                                   ]
    boolField name f = field name (\i -> if f i
                                         then pure (error $ unwords ["no string value for bool field:",name])
                                         else empty)
    withEllipsis ellipsisItem xs
      | length xs > max = [ellipsisItem] ++ takeEnd (max - 1) xs
      | otherwise = xs
    takeEnd i = reverse . take i . reverse
    max = 4

Everything needs a Rule

I was stumped for a while when my templates wouldn´t load.

This was easily rectified by realising, that even templates need (of course) a declaration of how to compile them:

main = hakyllWith config $ do
  match "templates/*" $ compile templateCompiler
  …

Duplicate Rules are duplicate

Hakyll tracks dependencies. Therefore it seems to keep a list of Identifiers it has encountered with priority given to the more early ones.

It was thus necessary to tweak the function that does Identifier/String conversion for tags contained within a Tags structure if I wanted to use (the very convenient) tagsRules twice.

So I did:

main = hakyllWith config $ do
  tags <- buildTags "posts/*" tagTranslation' …
  let
    tags' = tags { tagsMakeId = fromFilePath . (\b -> "rss" </> b <.> "rss") . takeBaseName . toFilePath . tagsMakeId tags}