From 9b857aea3cb21c0b63aba24d3379649580b9601b Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Mon, 3 Aug 2015 18:31:42 +0200 Subject: Migration post --- provider/posts/hakyll.md | 130 +++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 130 insertions(+) create mode 100644 provider/posts/hakyll.md diff --git a/provider/posts/hakyll.md b/provider/posts/hakyll.md new file mode 100644 index 0000000..77e1736 --- /dev/null +++ b/provider/posts/hakyll.md @@ -0,0 +1,130 @@ +--- +title: Switch to Hakyll +published: 2015-08-03 +tags: Blog Software +--- + +I stopped using the software suite inherited from +[math.kleen.org](http://math.kleen.org) and switched over to using +[hakyll](http://jaspervdj.be/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`, for those of you who are willing to checkout the +[git repo](git://git.yggdrasil.li/dirty-haskell.org)) 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](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Web-Tags.html) +instead of the [math.kleen.org](http://math.kleen.org) concept of lists, now. + +This required some tweaking. + +In order to retain the [All Posts](/tags/all-posts.html) list I introduced a +function to add new tags to an already existing +[Tags](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Web-Tags.html#t:Tags) +structure and used it to add my desired pseudo-tag. + +~~~ {.haskell} +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. + +~~~ {.haskell} +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](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Core-Rules.html#t:Rules) + +I was stumped for a while when my templates wouldn´t +[load](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Web-Template.html#v:loadAndApplyTemplate). + +This was easily rectified by realising, that even templates need (of course) a +declaration of how to compile them: + +~~~ {.haskell} +main = hakyllWith config $ do + match "templates/*" $ compile templateCompiler + … +~~~ + +### Duplicate Rules are duplicate + +Hakyll tracks dependencies. +Therefore it seems to keep a list of +[Identifier](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Core-Identifier.html#t:Identifier)s +it has encountered with priority given to the more early ones. + +I thus had to tweak the function that does `Identifier`/`String` conversion for +tags contained within a +[Tags](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Web-Tags.html#v:Tags) +structure if I wanted to use (the very convenient) +[tagsRules](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Web-Tags.html#v:tagsRules) +twice. + +So I did: + +~~~ {.haskell} +main = hakyllWith config $ do + tags <- buildTags "posts/*" tagTranslation' … + let + tags' = tags { tagsMakeId = fromFilePath . (\b -> "rss" b <.> "rss") . takeBaseName . toFilePath . tagsMakeId tags} +~~~ -- cgit v1.2.3