-------------------------------------------------------------------------------- {-# LANGUAGE OverloadedStrings #-} import Data.Monoid import Control.Monad (forM_) import Hakyll import HakyllBibTex import System.Process import Text.Pandoc.Options import Text.Regex config :: Configuration config = defaultConfiguration { deployCommand = "echo `pwd`; ./scripts/deploy.sh" } -------------------------------------------------------------------------------- bibHeaders :: [(String, [String])] bibHeaders = [ ("draft" , [ "-c", "$type='UNPUBLISHED'" ] ) , ("confs" , [ "-c", "$type='INPROCEEDINGS'" ] ) , ("journal", [ "-c", "$type='ARTICLE'" ] ) ] bibSources :: [String] bibSources = [ "bibs/header.bib" , "bibs/myrefs.bib" ] contentSections :: [String] contentSections = [ "contacts", "about", "news", "biblio" ] -------------------------------------------------------------------------------- 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) "") >>= makeItem bib2bibParse :: Item String -> Compiler [Item BibEntry] bib2bibParse file = let (BibFile bf) = parseBibFile (itemBody file) in sequence $ fmap makeItem bf -------------------------------------------------------------------------------- main :: IO () main = hakyllWith config $ do match "files/**" $ do route idRoute compile copyFileCompiler match "images/**" $ do route idRoute compile copyFileCompiler match "css/*.scss" $ do route $ setExtension "css" compile $ compass forM_ bibHeaders $ \(nick, 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/posters/" ++ i ++ "poster.pdf") ] biblioCtx = mconcat [ 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/biblio.md" $ do route $ setExtension "html" compile $ do let makeBibCtx (nick, _) = field nick (\_ -> loadBody $ fromFilePath ("bibs/" ++ nick ++ ".html")) secDiv = defaultHakyllWriterOptions { writerSectionDivs = True } biblioCtx = mconcat $ map makeBibCtx bibHeaders in do pandocCompilerWith defaultHakyllReaderOptions secDiv >>= applyAsTemplate biblioCtx >>= relativizeUrls match "content/*.md" $ do route $ setExtension "html" compile $ do let secDiv = defaultHakyllWriterOptions { writerSectionDivs = True } pandocCompilerWith defaultHakyllReaderOptions secDiv >>= relativizeUrls match "index.html" $ do route idRoute compile $ do let loadSec sec = field sec (\_ -> loadBody (fromFilePath $ "content/" ++ sec ++ ".md")) mainContext = mconcat $ fmap loadSec contentSections indexContext = field "footer" (\_ -> loadBody "content/footer.md") `mappend` defaultContext getResourceBody >>= applyAsTemplate mainContext >>= loadAndApplyTemplate "templates/main.html" indexContext >>= relativizeUrls match "templates/*" $ compile templateCompiler