{-# LANGUAGE OverloadedStrings #-} -------------------------------------------------------------------- -- | -- Copyright : (c) Stephen Diehl 2013 -- License : MIT -- Maintainer: stephen.m.diehl@gmail.com -- Stability : experimental -- Portability: non-portable -- -------------------------------------------------------------------- module Main where {-# LANGUAGE OverloadedStrings #-} import Data.Monoid (mappend) import Hakyll import Text.Pandoc import qualified Data.Map as M import Data.Maybe (isJust) import Text.Pandoc.Highlighting import Hakyll.Images ( loadImage , scaleImageCompiler ) -------------------------------------------------------------------- -- Contexts -------------------------------------------------------------------- postCtx :: Context String postCtx = dateField "date" "%B %e, %Y" `mappend` mathCtx `mappend` defaultContext mathCtx :: Context String mathCtx = field "mathjax" $ \item -> do metadata <- getMetadata $ itemIdentifier item return "" return $ if isJust $ lookupString "mathjax" metadata then "<script type=\"text/javascript\" src=\"https://cdnjs.cloudflare.com/ajax/libs/mathjax/2.7.0/MathJax.js?config=TeX-AMS_HTML\"></script>" else "" courseCtx posts title = listField "posts" postCtx (return posts) `mappend` constField "title" title `mappend` defaultContext archiveCtx posts = listField "posts" postCtx (return posts) `mappend` constField "title" "Archives" `mappend` defaultContext indexCtx posts = listField "posts" postCtx (return posts) `mappend` constField "title" "Home" `mappend` defaultContext -------------------------------------------------------------------- -- Rules -------------------------------------------------------------------- static :: Rules () static = do match "fonts/*" $ do route idRoute compile $ copyFileCompiler match "img/*" $ do route idRoute compile $ copyFileCompiler match "css/*" $ do route idRoute compile compressCssCompiler match "js/*" $ do route idRoute compile $ copyFileCompiler resize :: Rules () resize = do match "img/thumbnails/**.png" $ do route idRoute compile $ loadImage >>= scaleImageCompiler 140 140 pages :: Rules () pages = do match "pages/*" $ do route $ setExtension "html" compile $ getResourceBody >>= loadAndApplyTemplate "templates/page.html" postCtx >>= relativizeUrls posts :: Rules () posts = do match "posts/*" $ do route $ setExtension "html" -- compile $ myPandocCompiler compile $ bibtexCompiler >>= loadAndApplyTemplate "templates/post.html" postCtx >>= relativizeUrls archive :: Rules () archive = do create ["archive.html"] $ do route idRoute compile $ do posts <- recentFirst =<< loadAll "posts/*" makeItem "" >>= loadAndApplyTemplate "templates/archive.html" (archiveCtx posts) >>= relativizeUrls cours :: Rules () cours = do match "cours/*" $ do route $ setExtension "html" -- compile $ myPandocCompiler compile $ bibtexCompiler >>= loadAndApplyTemplate "templates/post.html" postCtx >>= relativizeUrls conc :: Rules () conc = do create ["prog_conc.html"] $ do route idRoute compile $ do posts <- recentFirst =<< loadAll "cours/*" makeItem "" >>= loadAndApplyTemplate "templates/archive.html" (courseCtx posts "Programmation concurrente") >>= relativizeUrls index :: Rules () index = do match "index.html" $ do route idRoute compile $ do posts <- recentFirst =<< loadAll "posts/*" getResourceBody >>= applyAsTemplate (indexCtx posts) >>= relativizeUrls templates :: Rules () templates = match "templates/*" $ compile templateCompiler -------------------------------------------------------------------- -- Configuration -------------------------------------------------------------------- myPandocCompiler :: Compiler (Item String) myPandocCompiler = pandocCompilerWith defaultHakyllReaderOptions pandocOptions pandocOptions :: WriterOptions pandocOptions = defaultHakyllWriterOptions { writerExtensions = defaultPandocExtensions , writerHTMLMathMethod = MathJax "" } -- Pandoc extensions used by the myPandocCompiler defaultPandocExtensions :: Extensions defaultPandocExtensions = let extensions = [ -- Pandoc Extensions: http://pandoc.org/MANUAL.html#extensions -- Math extensions Ext_tex_math_dollars , Ext_tex_math_double_backslash , Ext_latex_macros -- Code extensions , Ext_fenced_code_blocks , Ext_backtick_code_blocks , Ext_fenced_code_attributes , Ext_inline_code_attributes -- Inline code attributes (e.g. `<$>`{.haskell}) -- Markdown extensions , Ext_implicit_header_references -- We also allow implicit header references (instead of inserting <a> tags) , Ext_definition_lists -- Definition lists based on PHP Markdown , Ext_yaml_metadata_block -- Allow metadata to be speficied by YAML syntax , Ext_superscript -- Superscripts (2^10^ is 1024) , Ext_subscript -- Subscripts (H~2~O is water) , Ext_footnotes -- Footnotes ([^1]: Here is a footnote) ] defaultExtensions = writerExtensions defaultHakyllWriterOptions in foldr enableExtension defaultExtensions extensions bibtexCompiler :: Compiler (Item String) bibtexCompiler = do getResourceBody >>= withItemBody (unixFilter "pandoc" ["-F" , "pandoc-numbering" , "-F" , "pandoc-crossref" , "-t" , "markdown" ]) >>= readPandocWith defaultHakyllReaderOptions >>= return . writePandocWith pandocOptions cfg :: Configuration cfg = defaultConfiguration main :: IO () main = hakyllWith cfg $ do pages posts cours conc archive index templates resize static