summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorGregor Kleen <gkleen@yggdrasil.li>2015-08-03 18:31:42 +0200
committerGregor Kleen <gkleen@yggdrasil.li>2015-08-03 18:31:42 +0200
commit9b857aea3cb21c0b63aba24d3379649580b9601b (patch)
treeafbb689065ad07c340751a3652dc0a5999f08809
parent928b92515f2ab21bc7bb74fe65cdaaf40e81e57c (diff)
downloaddirty-haskell.org-9b857aea3cb21c0b63aba24d3379649580b9601b.tar
dirty-haskell.org-9b857aea3cb21c0b63aba24d3379649580b9601b.tar.gz
dirty-haskell.org-9b857aea3cb21c0b63aba24d3379649580b9601b.tar.bz2
dirty-haskell.org-9b857aea3cb21c0b63aba24d3379649580b9601b.tar.xz
dirty-haskell.org-9b857aea3cb21c0b63aba24d3379649580b9601b.zip
Migration post
-rw-r--r--provider/posts/hakyll.md130
1 files changed, 130 insertions, 0 deletions
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 @@
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](git://git.yggdrasil.li/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) $ liftM (withEllipsis ellipsisItem) $ chronological =<< mapM load ids
73 , constField "title" tag
74 , constField "rss" ("tags/" ++ tagTranslation tag ++ ".rss")
75 , constField "url" ("tags/" ++ tagTranslation tag ++ ".html")
76 , defaultContext
77 ]
78 makeItem ""
79 >>= loadAndApplyTemplate "templates/post-list.html" postCtx
80 >>= loadAndApplyTemplate "templates/tag.html" postCtx
81 where
82 ellipsisContext item = mconcat [ boolField "ellipsis" (== item)
83 , defaultContext
84 ]
85 boolField name f = field name (\i -> if f i
86 then pure (error $ unwords ["no string value for bool field:",name])
87 else empty)
88 withEllipsis ellipsisItem xs
89 | length xs > max = [ellipsisItem] ++ takeEnd (max - 1) xs
90 | otherwise = xs
91 takeEnd i = reverse . take i . reverse
92 max = 4
93~~~
94
95### Everything needs a [Rule](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Core-Rules.html#t:Rules)
96
97I was stumped for a while when my templates wouldn´t
98[load](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Web-Template.html#v:loadAndApplyTemplate).
99
100This was easily rectified by realising, that even templates need (of course) a
101declaration of how to compile them:
102
103~~~ {.haskell}
104main = hakyllWith config $ do
105 match "templates/*" $ compile templateCompiler
106
107~~~
108
109### Duplicate Rules are duplicate
110
111Hakyll tracks dependencies.
112Therefore it seems to keep a list of
113[Identifier](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Core-Identifier.html#t:Identifier)s
114it has encountered with priority given to the more early ones.
115
116I thus had to tweak the function that does `Identifier`/`String` conversion for
117tags contained within a
118[Tags](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Web-Tags.html#v:Tags)
119structure if I wanted to use (the very convenient)
120[tagsRules](http://hackage.haskell.org/package/hakyll-4.7.2.2/docs/Hakyll-Web-Tags.html#v:tagsRules)
121twice.
122
123So I did:
124
125~~~ {.haskell}
126main = hakyllWith config $ do
127 tags <- buildTags "posts/*" tagTranslation' …
128 let
129 tags' = tags { tagsMakeId = fromFilePath . (\b -> "rss" </> b <.> "rss") . takeBaseName . toFilePath . tagsMakeId tags}
130~~~