summaryrefslogtreecommitdiff
path: root/provider/posts/blog/hakyll.md
diff options
context:
space:
mode:
Diffstat (limited to 'provider/posts/blog/hakyll.md')
-rw-r--r--provider/posts/blog/hakyll.md131
1 files changed, 131 insertions, 0 deletions
diff --git a/provider/posts/blog/hakyll.md b/provider/posts/blog/hakyll.md
new file mode 100644
index 0000000..be3bc1b
--- /dev/null
+++ b/provider/posts/blog/hakyll.md
@@ -0,0 +1,131 @@
1---
2title: Switch to Hakyll
3published: 2015-08-03
4tags: Blog Software
5---
6
7I stopped using the software suite inherited from
8[math.kleen.org](http://math.kleen.org) and switched over to using
9[hakyll](http://jaspervdj.be/hakyll/) instead, since I realised that the two
10were doing essentially the same job and keeping my mess in one haskell file
11(`src/Site.hs`, for those of you who are willing to checkout the
12[git repo](https://git.yggdrasil.li/gkleen/pub/dirty-haskell.org)) instead of spread over a
13large number of interlocking zsh and haskell scripts.
14
15I expect nothing to be seriously broken (Only the filepaths of lists have
16changed), but some feed readers might have stopped working (hakyll´s
17deceptively named `renderRss` actually renders atom).
18
19## Implementation Details
20
21I´m using this post to document some of the more involved things I had to do
22during migration in no particular order.
23
24### Lists → Tags
25
26I´m using hakyll´s implementation of
27[tags](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Web-Tags.html)
28instead of the [math.kleen.org](http://math.kleen.org) concept of lists, now.
29
30This required some tweaking.
31
32In order to retain the [All Posts](/tags/all-posts.html) list I introduced a
33function to add new tags to an already existing
34[Tags](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Web-Tags.html#t:Tags)
35structure and used it to add my desired pseudo-tag.
36
37~~~ {.haskell}
38main = hakyllWith config $ do
39
40 tags <- buildTags "posts/*" tagTranslation' >>= addTag "All Posts" "posts/*"
41
42
43addTag :: MonadMetadata m => String -> Pattern -> Tags -> m Tags
44addTag name pattern tags = do
45 ids <- getMatches pattern
46 return $ tags { tagsMap = tagsMap tags ++ [(name, ids)] }
47~~~
48
49### Printing lists is an involved affair
50
51I wanted to keep the layout of the site including the lists of posts on the
52[index page](/).
53
54Generating those lists turned out to be a hassle.
55
56The `Rule` for `index.md` adds to the context of the templates used in it´s
57creation a list field which contains verbatim HTML as produced by renderTag for
58each tag.
59A trick I used to implement the desired behaviour of replacing old posts with
60"…" is to introduce a pseudo post-item which has a flag in it´s context to tell
61the corresponding template to only print "…".
62Trimming the list of posts is straightforward.
63
64~~~ {.haskell}
65renderTag :: String -- ^ Tag name
66 -> Tags
67 -> Compiler (Item String)
68renderTag tag tags = do
69 ellipsisItem <- makeItem ""
70 let
71 ids = fromMaybe [] $ lookup tag $ tagsMap tags
72 postCtx = mconcat [ listField "posts" (ellipsisContext ellipsisItem) $
73 liftM (withEllipsis ellipsisItem) $ chronological =<< mapM load ids
74 , constField "title" tag
75 , constField "rss" ("tags/" ++ tagTranslation tag ++ ".rss")
76 , constField "url" ("tags/" ++ tagTranslation tag ++ ".html")
77 , defaultContext
78 ]
79 makeItem ""
80 >>= loadAndApplyTemplate "templates/post-list.html" postCtx
81 >>= loadAndApplyTemplate "templates/tag.html" postCtx
82 where
83 ellipsisContext item = mconcat [ boolField "ellipsis" (== item)
84 , defaultContext
85 ]
86 boolField name f = field name (\i -> if f i
87 then pure (error $ unwords ["no string value for bool field:",name])
88 else empty)
89 withEllipsis ellipsisItem xs
90 | length xs > max = [ellipsisItem] ++ takeEnd (max - 1) xs
91 | otherwise = xs
92 takeEnd i = reverse . take i . reverse
93 max = 4
94~~~
95
96### Everything needs a [Rule](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Core-Rules.html#t:Rules)
97
98I was stumped for a while when my templates wouldn´t
99[load](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Web-Template.html#v:loadAndApplyTemplate).
100
101This was easily rectified by realising, that even templates need (of course) a
102declaration of how to compile them:
103
104~~~ {.haskell}
105main = hakyllWith config $ do
106 match "templates/*" $ compile templateCompiler
107
108~~~
109
110### Duplicate Rules are duplicate
111
112Hakyll tracks dependencies.
113Therefore it seems to keep a list of
114[Identifier](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Core-Identifier.html#t:Identifier)s
115it has encountered with priority given to the more early ones.
116
117It was thus necessary to tweak the function that does `Identifier`/`String`
118conversion for tags contained within a
119[Tags](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Web-Tags.html#v:Tags)
120structure if I wanted to use (the very convenient)
121[tagsRules](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Web-Tags.html#v:tagsRules)
122twice.
123
124So I did:
125
126~~~ {.haskell}
127main = hakyllWith config $ do
128 tags <- buildTags "posts/*" tagTranslation' …
129 let
130 tags' = tags { tagsMakeId = fromFilePath . (\b -> "rss" </> b <.> "rss") . takeBaseName . toFilePath . tagsMakeId tags}
131~~~