justin-site/app/site.hs

111 lines
3.9 KiB
Haskell
Raw Normal View History

2018-02-17 18:18:06 +00:00
module Main where
--------------------------------------------------------------------------------
{-# 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
--------------------------------------------------------------------------------
bibHeaders :: [(String, [String])]
bibHeaders = [ ("drafts" , [ "-c", "$type='UNPUBLISHED'" ] )
, ("thesis" , [ "-c", "$type='PHDTHESIS'" ] )
, ("pubs" , [ "-c", "($type='INPROCEEDINGS' | $type='ARTICLE') & $reviewed='yes'" ] )
, ("invite" , [ "-c", "($type='INPROCEEDINGS' | $type='ARTICLE' | $type='INBOOK') & $reviewed='no'" ] )
]
2015-01-05 04:43:45 +00:00
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) "")
2015-01-05 04:43:45 +00:00
>>= makeItem
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
2018-02-17 18:18:06 +00:00
match (fromGlob "files/**") $ do
route idRoute
compile copyFileCompiler
2018-02-17 18:18:06 +00:00
match (fromGlob "images/**") $ do
2015-01-05 04:43:45 +00:00
route idRoute
compile copyFileCompiler
2018-02-17 18:18:06 +00:00
match (fromGlob "css/*.scss") $ do
route $ setExtension "css"
compile $ compass
2018-02-17 18:18:06 +00:00
match (fromGlob "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
2018-02-17 18:18:06 +00:00
match (fromGlob "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"))
2018-05-07 19:40:05 +00:00
makeBibCtx (nick, _) =
field nick (\_ -> loadBody $ fromFilePath ("bibs/" ++ nick ++ ".html"))
biblioContext = mconcat $ map makeBibCtx bibHeaders
indexContext = mconcat $ fmap loadSec contentSections
footerContext = field "footer" (\_ -> loadBody $ fromFilePath "content/footer.md")
getResourceBody
2018-05-07 19:40:05 +00:00
>>= applyAsTemplate (indexContext <> biblioContext <> footerContext <> defaultContext)
2015-01-05 04:43:45 +00:00
>>= relativizeUrls
2018-05-07 19:40:05 +00:00
forM_ bibHeaders $ \(nick, flags) ->
create [fromCapture (fromGlob "bibs/*.html") nick] $ do
route idRoute
compile $
let biblioCtx = mconcat
[ field "bibitems" $ return . itemBody ] in do
bibTpl <- loadBody $ fromFilePath "templates/bibitem.html"
(bib2bib flags)
>>= bib2bibParse
>>= applyTemplateList bibTpl bibEntryContext
>>= makeItem
>>= applyAsTemplate biblioCtx
>>= relativizeUrls
2018-02-17 18:18:06 +00:00
match (fromGlob "templates/*") $ compile templateCompiler