2015-01-03 22:23:27 +00:00
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
import Data.Monoid
|
|
|
|
import Control.Monad (forM_)
|
|
|
|
import Hakyll
|
|
|
|
import HakyllBibTex
|
|
|
|
import System.Process
|
|
|
|
import Text.Pandoc.Options
|
|
|
|
|
2015-01-05 06:20:06 +00:00
|
|
|
config :: Configuration
|
|
|
|
config = defaultConfiguration
|
2015-01-05 07:50:50 +00:00
|
|
|
{ deployCommand = "echo `pwd`; ./scripts/deploy.sh" }
|
2015-01-05 06:20:06 +00:00
|
|
|
|
2015-01-05 04:43:45 +00:00
|
|
|
--------------------------------------------------------------------------------
|
2016-02-19 04:48:24 +00:00
|
|
|
bibHeaders :: [(String, [String])]
|
|
|
|
bibHeaders = [ ("draft" , [ "-c", "$type='UNPUBLISHED'" ] ) ,
|
|
|
|
("confs" , [ "-c", "$type='INPROCEEDINGS'" ] ) ,
|
|
|
|
("journal", [ "-c", "$type='ARTICLE'" ] )
|
2015-01-05 04:43:45 +00:00
|
|
|
]
|
|
|
|
|
|
|
|
bibSources :: [String]
|
|
|
|
bibSources = [ "bibs/header.bib"
|
|
|
|
, "bibs/myrefs.bib"
|
|
|
|
]
|
|
|
|
|
|
|
|
contentSections :: [String]
|
|
|
|
contentSections = [ "contacts", "about", "news", "biblio" ]
|
|
|
|
--------------------------------------------------------------------------------
|
2015-01-03 22:23:27 +00:00
|
|
|
compass :: Compiler (Item String)
|
|
|
|
compass =
|
|
|
|
getResourceString >>=
|
|
|
|
withItemBody (unixFilter "sass" ["-s", "--scss", "--compass"])
|
|
|
|
|
|
|
|
b2bflags :: [String]
|
|
|
|
b2bflags = [ "--expand"
|
|
|
|
, "-c"
|
|
|
|
, "jh:'yes'"
|
|
|
|
, "-s"
|
|
|
|
, "$date"
|
|
|
|
, "-r"
|
|
|
|
]
|
|
|
|
|
|
|
|
|
|
|
|
bib2bib :: [String]
|
|
|
|
-> Compiler (Item String)
|
|
|
|
bib2bib flags = (unsafeCompiler $
|
|
|
|
readProcess "bib2bib" (bibSources ++ b2bflags ++ flags) "")
|
2015-01-05 04:43:45 +00:00
|
|
|
>>= makeItem
|
2015-01-03 22:23:27 +00:00
|
|
|
|
|
|
|
bib2bibParse :: Item String
|
|
|
|
-> Compiler [Item BibEntry]
|
|
|
|
bib2bibParse file =
|
|
|
|
let (BibFile bf) = parseBibFile (itemBody file) in
|
|
|
|
sequence $ fmap makeItem bf
|
|
|
|
|
|
|
|
|
|
|
|
--------------------------------------------------------------------------------
|
|
|
|
main :: IO ()
|
2015-01-05 06:20:06 +00:00
|
|
|
main = hakyllWith config $ do
|
2015-01-03 22:23:27 +00:00
|
|
|
match "files/**" $ do
|
|
|
|
route idRoute
|
|
|
|
compile copyFileCompiler
|
|
|
|
|
2015-01-05 04:43:45 +00:00
|
|
|
match "images/**" $ do
|
|
|
|
route idRoute
|
|
|
|
compile copyFileCompiler
|
|
|
|
|
2015-01-03 22:23:27 +00:00
|
|
|
match "css/*.scss" $ do
|
|
|
|
route $ setExtension "css"
|
|
|
|
compile $ compass
|
|
|
|
|
2016-02-19 04:48:24 +00:00
|
|
|
forM_ bibHeaders $ \(nick, flags) ->
|
2015-01-03 22:23:27 +00:00
|
|
|
create [fromCapture "bibs/*.html" nick] $ do
|
|
|
|
route idRoute
|
|
|
|
compile $
|
2016-10-13 16:27:10 +00:00
|
|
|
let biblioCtx = mconcat
|
2016-02-19 04:48:24 +00:00
|
|
|
[ field "bibitems" $ return . itemBody ] in do
|
2015-01-03 22:23:27 +00:00
|
|
|
bibTpl <- loadBody "templates/bibitemtpl.html"
|
|
|
|
(bib2bib flags)
|
|
|
|
>>= bib2bibParse
|
2016-10-13 16:27:10 +00:00
|
|
|
>>= applyTemplateList bibTpl bibEntryContext
|
2015-01-03 22:23:27 +00:00
|
|
|
>>= makeItem
|
2015-01-05 04:43:45 +00:00
|
|
|
>>= loadAndApplyTemplate "templates/biblisttpl.html" biblioCtx
|
2015-01-03 22:23:27 +00:00
|
|
|
>>= relativizeUrls
|
|
|
|
|
2015-01-05 04:43:45 +00:00
|
|
|
match "content/biblio.md" $ do
|
2015-01-03 22:23:27 +00:00
|
|
|
route $ setExtension "html"
|
|
|
|
compile $ do
|
2016-02-19 04:48:24 +00:00
|
|
|
let makeBibCtx (nick, _) =
|
2015-01-03 22:23:27 +00:00
|
|
|
field nick (\_ -> loadBody $ fromFilePath ("bibs/" ++ nick ++ ".html"))
|
2015-01-05 04:43:45 +00:00
|
|
|
secDiv = defaultHakyllWriterOptions { writerSectionDivs = True }
|
|
|
|
biblioCtx = mconcat $ map makeBibCtx bibHeaders in do
|
2015-01-03 22:23:27 +00:00
|
|
|
pandocCompilerWith defaultHakyllReaderOptions secDiv
|
2015-01-05 04:43:45 +00:00
|
|
|
>>= applyAsTemplate biblioCtx
|
2015-01-03 22:23:27 +00:00
|
|
|
>>= relativizeUrls
|
|
|
|
|
|
|
|
match "content/*.md" $ do
|
|
|
|
route $ setExtension "html"
|
|
|
|
compile $ do
|
2015-01-05 04:43:45 +00:00
|
|
|
let secDiv = defaultHakyllWriterOptions { writerSectionDivs = True }
|
|
|
|
pandocCompilerWith defaultHakyllReaderOptions secDiv
|
|
|
|
>>= relativizeUrls
|
2015-01-03 22:23:27 +00:00
|
|
|
|
|
|
|
match "index.html" $ do
|
|
|
|
route idRoute
|
|
|
|
compile $ do
|
2015-01-05 04:43:45 +00:00
|
|
|
let loadSec sec = field sec
|
|
|
|
(\_ -> loadBody (fromFilePath $ "content/" ++ sec ++ ".md"))
|
|
|
|
mainContext = mconcat $ fmap loadSec contentSections
|
|
|
|
indexContext =
|
|
|
|
field "footer" (\_ -> loadBody "content/footer.md")
|
|
|
|
`mappend`
|
|
|
|
defaultContext
|
2015-01-03 22:23:27 +00:00
|
|
|
getResourceBody
|
2015-01-05 04:43:45 +00:00
|
|
|
>>= applyAsTemplate mainContext
|
|
|
|
>>= loadAndApplyTemplate "templates/main.html" indexContext
|
|
|
|
>>= relativizeUrls
|
2015-01-03 22:23:27 +00:00
|
|
|
|
|
|
|
match "templates/*" $ compile templateCompiler
|