-
Notifications
You must be signed in to change notification settings - Fork 0
/
generator.hs
146 lines (126 loc) · 3.32 KB
/
generator.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
138
139
140
141
142
143
144
145
146
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Hakyll
import Text.Pandoc (
WriterOptions
, writerTemplate
, writerTopLevelDivision
, writerTableOfContents
, writerNumberSections
, writerHTMLMathMethod
, HTMLMathMethod(MathJax)
, compileTemplate
, runPure
, runWithDefaultPartials
)
import Control.Monad (forM_)
import Data.Monoid (mappend)
import qualified Data.Map as M
import Data.Maybe (isJust, fromMaybe)
import System.Process (callCommand)
-----------------
-- Configuration
-----------------
cfg :: Configuration
cfg = defaultConfiguration
{ deployCommand = "rsync -avzdP _site/ digitalocean:/var/www" }
------------
-- Contexts
------------
postCtx :: Context String
postCtx =
dateField "date" "%B %e, %Y"
`mappend` defaultContext
archiveCtx posts =
listField "posts" postCtx (return posts)
`mappend` constField "title" "Posts"
`mappend` defaultContext
------------
-- Options
------------
tocTemplate =
either error id $ either (error . show) id $
runPure $ runWithDefaultPartials $
compileTemplate "" "<h2>Table of Contents</h2>$toc$\n$body$"
withTOC :: WriterOptions
withTOC = defaultHakyllWriterOptions{
writerNumberSections = True,
writerTableOfContents = True,
writerTemplate = Just tocTemplate,
writerHTMLMathMethod = MathJax ""
}
withoutTOC :: WriterOptions
withoutTOC = defaultHakyllWriterOptions{
writerHTMLMathMethod = MathJax ""
}
-------------
-- Compilers
-------------
compiler :: Compiler (Item String)
compiler = do
csl <- load "apa.csl"
biblio <- load "refs.bib"
ident <- getUnderlying
toc <- getMetadataField ident "toc"
let writerOptions' = case toc of
Just _ -> withTOC
Nothing -> withoutTOC
getResourceBody
>>= readPandocBiblio defaultHakyllReaderOptions csl biblio
>>= return . writePandocWith writerOptions'
------------
-- Rules
------------
templates :: Rules ()
templates = match "templates/*" $ compile templateCompiler
posts :: Rules ()
posts = match (
"**.md"
.&&. complement "README.md"
.&&. complement "**index.md"
.&&. complement "Curriculum-Vitae/**"
) $ do
route $ setExtension "html"
compile $ compiler
>>= loadAndApplyTemplate "templates/post.html" defaultContext
>>= relativizeUrls
archive :: Rules ()
archive = create ["posts.html"] $ do
route $ setExtension "html"
compile $ do
posts <- recentFirst =<< loadAll "posts/*"
makeItem ""
>>= loadAndApplyTemplate "templates/list.html" (archiveCtx posts)
>>= loadAndApplyTemplate "templates/index.html" (archiveCtx posts)
>>= relativizeUrls
indices :: Rules ()
indices = match "**index.md" $ do
route $ setExtension "html"
compile $ compiler
>>= loadAndApplyTemplate "templates/index.html" defaultContext
>>= relativizeUrls
static :: Rules ()
static = forM_ [
"fonts/*",
"assets/**",
"css/*",
"js/*",
"teaching/**.tex",
"teaching/**.jpg",
"teaching/**.pdf",
"robots.txt"
] $ \x -> match x $ do
route idRoute
compile $ copyFileCompiler
------------
-- Main
------------
main :: IO ()
main = hakyllWith cfg $ do
match "apa.csl" $ compile cslCompiler
match "refs.bib" $ compile biblioCompiler
static
indices
posts
templates
archive