-
Notifications
You must be signed in to change notification settings - Fork 2
/
site.hs
137 lines (107 loc) · 4.3 KB
/
site.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
import Data.Monoid (mappend, mconcat)
import Hakyll
import qualified Data.Set as S
import Text.Pandoc
import Hakyll.Core.Compiler
import qualified CssVars as CV
import CustomCompilers
import Collections
import qualified Data.Map as M
import Data.Maybe
--------------------------------------------------------------------------------
main :: IO ()
main = hakyll $ do
match "css/*" $ do
route idRoute
compile $ compressCssCompiler >>= applyAsTemplate CV.defaultCtx
match "images/*" $ do
route idRoute
compile copyFileCompiler
match "js/*" $ do
route idRoute
compile copyFileCompiler
match "js/elm/elm.js" $ do
route idRoute
compile copyFileCompiler
match "where.html" $ do
route idRoute
compile $ do
getResourceBody
>>= applyAsTemplate headContext
>>= loadAndApplyTemplate "templates/default.html" headContext
>>= relativizeUrls
match "font/*" $ do
route idRoute
compile copyFileCompiler
match "files/*" $ do
route idRoute
compile copyFileCompiler
match (fromList ["cv.pdf", "CNAME"]) $ do
route idRoute
compile copyFileCompiler
match (fromList ["about.md", "projects.md"]) $ do
route $ setExtension "html"
compile $ pandocCompiler
>>= loadAndApplyTemplate "templates/default.html" defaultContext
>>= relativizeUrls
colls <- buildCollections "drafts/*" (fromCapture "collections/*.html")
match "posts/*" $ do
route $ setExtension "html"
compile $ pandocMathCompiler
>>= loadAndApplyTemplate "templates/post.html" postCtx
>>= loadAndApplyTemplate "templates/default.html" postCtx
>>= relativizeUrls
match "drafts/*" $ do
route $ setExtension "html"
compile $ do
let ctx = collectionContext colls `mappend` postCtx
pandocMathCompiler
>>= loadAndApplyTemplate "templates/post.html" ctx
>>= loadAndApplyTemplate "templates/collectionInfo.html" ctx
>>= loadAndApplyTemplate "templates/draft.html" ctx
>>= loadAndApplyTemplate "templates/default.html" ctx
>>= relativizeUrls
create ["archive.html"] $ do
route idRoute
compile $ do
posts <- recentFirst =<< loadAll "posts/*"
let archiveCtx =
--listField "collections" collectionContext (map snd $ collMap colls) `mappend`
listField "posts" postCtx (return posts) `mappend`
constField "title" "Archives" `mappend`
defaultContext
makeItem ""
>>= loadAndApplyTemplate "templates/archive.html" archiveCtx
>>= loadAndApplyTemplate "templates/default.html" archiveCtx
>>= relativizeUrls
match "index.html" $ do
route idRoute
compile $ do
posts <- recentFirst =<< loadAll "posts/*"
let indexCtx =
listField "posts" postCtx (return posts) `mappend`
--constField "title" "Home" `mappend`
defaultContext
getResourceBody
>>= applyAsTemplate indexCtx
>>= loadAndApplyTemplate "templates/default.html" indexCtx
>>= relativizeUrls
match "templates/*" $ compile templateCompiler
--------------------------------------------------------------------------------
postCtx :: Context String
postCtx =
dateField "date" "%B %e, %Y" `mappend`
defaultContext
----
headContext = mconcat [ parseListMetadata "scripts"
, parseListMetadata "styles"
, defaultContext
]
parseListMetadata :: String -> Context a
parseListMetadata s = listField s defaultContext $ do
identifier <- getUnderlying
metadata <- getMetadata identifier
let metas = maybe [] (map trim . splitAll ",") $ M.lookup s metadata
return $ map (\x -> Item (fromFilePath x) x) metas