justin-site/site.hs

117 lines
4.1 KiB
Haskell

--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
import Data.Monoid
import Control.Monad (forM_)
import Hakyll
import HakyllBibTex
import System.Process
import Text.Pandoc.Options
compass :: Compiler (Item String)
compass =
getResourceString >>=
withItemBody (unixFilter "sass" ["-s", "--scss", "--compass"])
b2bflags :: [String]
b2bflags = [ "--expand"
, "-c"
, "jh:'yes'"
, "-s"
, "$date"
, "-r"
]
bibHeaders :: [(String, String, [String])]
bibHeaders = [ ("confs", "Conference Publications",
["-c", "$type='INPROCEEDINGS'" ] )
, ("draft", "Drafts" ,
[ "-c", "$type='UNPUBLISHED'" ] )
]
bibSources :: [String]
bibSources = [ "bibs/header.bib"
, "bibs/myrefs.bib"
]
bib2bib :: [String]
-> Compiler (Item String)
bib2bib flags = (unsafeCompiler $
readProcess "bib2bib" (bibSources ++ b2bflags ++ flags) "")
>>= makeItem
bib2bibParse :: Item String
-> Compiler [Item BibEntry]
bib2bibParse file =
let (BibFile bf) = parseBibFile (itemBody file) in
sequence $ fmap makeItem bf
--------------------------------------------------------------------------------
main :: IO ()
main = hakyll $ do
match "files/**" $ do
route idRoute
compile copyFileCompiler
match "css/*.scss" $ do
route $ setExtension "css"
compile $ compass
forM_ bibHeaders $ \(nick, title, flags) ->
create [fromCapture "bibs/*.html" nick] $ do
route idRoute
compile $
let itemCtx = mconcat
[ bibEntryContext
, functionField "doclink"
(\(i:_) _ -> return $ "files/docs/" ++ i ++ "paper.pdf")
, functionField "slidelink"
(\(i:_) _ -> return $ "files/slides/" ++ i ++ "slides.pdf")
, functionField "posterlink"
(\(i:_) _ -> return $ "files/poster/" ++ i ++ "poster.pdf")
]
biblioCtx = mconcat
[ field "bibtitle" (\_ -> return $ title)
, field "bibitems" $ return . itemBody
] in do
bibTpl <- loadBody "templates/bibitemtpl.html"
(bib2bib flags)
>>= bib2bibParse
>>= applyTemplateList bibTpl itemCtx
>>= makeItem
>>= loadAndApplyTemplate
"templates/biblisttpl.html" biblioCtx
>>= relativizeUrls
match "content/body.md" $ do
route $ setExtension "html"
compile $ do
let makeBibCtx (nick, _, _) =
field nick (\_ -> loadBody $ fromFilePath ("bibs/" ++ nick ++ ".html"))
secDiv = defaultHakyllWriterOptions { writerSectionDivs = True }
bodyCtx = mconcat $ map makeBibCtx bibHeaders in do
pandocCompilerWith defaultHakyllReaderOptions secDiv
>>= applyAsTemplate bodyCtx
>>= relativizeUrls
match "content/*.md" $ do
route $ setExtension "html"
compile $ do
pandocCompiler >>= relativizeUrls
match "index.html" $ do
route idRoute
compile $ do
contacts <- loadBody "content/contacts.md"
content <- loadBody "content/body.md"
let indexContext = mconcat
[ field "contacts" $ \_ -> return contacts
, field "content" $ \_ -> return content
]
getResourceBody
>>= applyAsTemplate indexContext
>>= loadAndApplyTemplate "templates/main.html" defaultContext
>>= relativizeUrls
match "templates/*" $ compile templateCompiler