-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathsite.hs
executable file
·137 lines (113 loc) · 4.39 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 Control.Monad (liftM)
import Data.Monoid (mappend)
import Data.Maybe
import Hakyll
import Hakyll.Core.Compiler
import Text.Pandoc.Options
import System.FilePath
import System.Directory (createDirectoryIfMissing)
import System.FilePath.Posix (takeDirectory)
-- Helper functions
createAndWriteFile :: FilePath -> String -> IO ()
createAndWriteFile path content = do
createDirectoryIfMissing True $ takeDirectory path
writeFile path content
-- | My own configuration for the website
config :: Configuration
config = defaultConfiguration
{ destinationDirectory = "docs"
, previewPort = 5000 }
-- --------------------------------------
postCtx :: Context String
postCtx = dateField "published" "%B %e, %Y"
<> defaultContext
posts :: Context String
posts = listField "posts" postCtx $
do posts <- recentFirst =<< loadAll "main/posts/en/*"
return posts
archiveCtx :: Context String
archiveCtx = posts
<> defaultContext
-- --------------------------------------
{- Include MathJax in the pandoc options so it is possible
to render pretty math equations. -}
pandocWOptions :: WriterOptions
pandocWOptions = defaultHakyllWriterOptions
{ writerHTMLMathMethod = MathJax "" }
{- My personal website compiler with my preferences. -}
grassBiblioCompiler :: Compiler (Item String)
grassBiblioCompiler = do
csl <- load "bib/tpls.csl"
bib <- load "bib/global.bib"
getResourceBody
>>= readPandocBiblio defaultHakyllReaderOptions csl bib
>>= pure . (writePandocWith pandocWOptions)
grassCompiler :: Compiler (Item String)
grassCompiler = pandocBiblioCompiler "bib/acm.csl" "bib/global.bib"
{- Used to process the main contents of the site. -}
baseFolderAndHtml :: Routes
baseFolderAndHtml =
customRoute $ takeFileName . (`replaceExtension` "html") . toFilePath
folderAndHtml :: FilePath -> Routes
folderAndHtml path =
customRoute $
(++) path . takeFileName . (`replaceExtension` "html") . toFilePath
switchMainFolderFor :: FilePath -> Routes
switchMainFolderFor path =
customRoute $ (++) path . takeFileName . toFilePath
removeMainFolder :: Routes
removeMainFolder = gsubRoute "main/" (const "")
-- If there is a draft field and it has a value other than false, then
-- the site generator will not publish it/consider it
filterDrafts :: Metadata -> Bool
filterDrafts meta = maybe True (=="false") $ lookupString "draft" meta
------------------------------------------------------------------------
buildSite :: IO ()
buildSite = hakyllWith config $ do
match "bib/global.bib" $ compile biblioCompiler
match "bib/acm.csl" $ compile cslCompiler
match "templates/*" $ compile templateBodyCompiler
match "css/*" $ do
route idRoute
compile compressCssCompiler
match ("main/images/**.png" .||. "main/images/**.svg") $ do
route $ removeMainFolder
compile copyFileCompiler
{- moving pdfs and extra info into a docs folder-}
match "main/extra/*" $ do
route $ switchMainFolderFor "docs/"
compile copyFileCompiler
match "main/js/*" $ do
route $ removeMainFolder
compile copyFileCompiler
match "main/*" $ do
route baseFolderAndHtml
compile $ grassCompiler
>>= loadAndApplyTemplate "templates/default.html" defaultContext
>>= relativizeUrls
match "main/Alf0nso/index.org" $ do
route $ folderAndHtml "Alf0nso/"
compile $ grassCompiler
>>= loadAndApplyTemplate "templates/default.html" defaultContext
>>= relativizeUrls
match "main/posts/archive.org" $ do
route baseFolderAndHtml
compile $ grassCompiler
>>= loadAndApplyTemplate "templates/archive.html" archiveCtx
>>= loadAndApplyTemplate "templates/default.html" archiveCtx
>>= relativizeUrls
matchMetadata "main/posts/en/*" filterDrafts $ do
route baseFolderAndHtml
compile $ grassCompiler
>>= loadAndApplyTemplate "templates/post.html" postCtx
>>= loadAndApplyTemplate "templates/default.html" postCtx
>>= relativizeUrls
matchMetadata "main/posts/pt/*" filterDrafts $ do
route baseFolderAndHtml
compile $ grassCompiler
>>= loadAndApplyTemplate "templates/post.html" postCtx
>>= loadAndApplyTemplate "templates/default.html" postCtx
>>= relativizeUrls
main :: IO ()
main = buildSite