1234567891011121314151617181920212223242526272829303132333435363738394041424344454647484950515253545556575859606162636465666768697071727374757677787980818283848586878889909192 |
- --------------------------------------------------------------------------------
- {-# LANGUAGE OverloadedStrings #-}
- import Data.Monoid (mappend)
- import Hakyll
- --------------------------------------------------------------------------------
- main :: IO ()
- main = hakyll $ do
- match "images/*" $ do
- route idRoute
- compile copyFileCompiler
- match "css/*" $ do
- route idRoute
- compile compressCssCompiler
- match "resume_jmelesky.pdf" $ do
- route idRoute
- compile copyFileCompiler
- match "*.md" $ do
- route $ setExtension "html"
- compile $ pandocCompiler
- >>= loadAndApplyTemplate "templates/default.html" defaultContext
- >>= relativizeUrls
- tags <- buildTags "posts/*" (fromCapture "tags/*.html")
- tagsRules tags $ \tag pattern -> do
- let title = "Posts tagged \"" ++ tag ++ "\""
- route idRoute
- compile $ do
- posts <- recentFirst =<< loadAll pattern
- let ctx = constField "title" title
- `mappend` listField "posts" postCtx (return posts)
- `mappend` defaultContext
- makeItem ""
- >>= loadAndApplyTemplate "templates/tag.html" ctx
- >>= loadAndApplyTemplate "templates/default.html" ctx
- >>= relativizeUrls
- match "posts/*" $ do
- route $ setExtension "html"
- compile $ pandocCompiler
- >>= loadAndApplyTemplate "templates/post.html" (postCtxWithTags tags)
- >>= loadAndApplyTemplate "templates/default.html" (postCtxWithTags tags)
- >>= relativizeUrls
- create ["archive.html"] $ do
- route idRoute
- compile $ do
- posts <- recentFirst =<< loadAll "posts/*"
- let archiveCtx =
- listField "posts" postCtx (return posts) `mappend`
- constField "title" "Archives" `mappend`
- defaultContext
- makeItem ""
- >>= loadAndApplyTemplate "templates/archive.html" archiveCtx
- >>= loadAndApplyTemplate "templates/default.html" archiveCtx
- >>= relativizeUrls
- match "index.html" $ do
- route idRoute
- compile $ do
- posts <- recentFirst =<< loadAll "posts/*"
- let indexCtx =
- listField "posts" postCtx (return posts) `mappend`
- constField "title" "Home" `mappend`
- defaultContext
- getResourceBody
- >>= applyAsTemplate indexCtx
- >>= loadAndApplyTemplate "templates/default.html" indexCtx
- >>= relativizeUrls
- match "templates/*" $ compile templateBodyCompiler
- --------------------------------------------------------------------------------
- postCtx :: Context String
- postCtx =
- dateField "date" "%B %e, %Y" `mappend`
- defaultContext
- postCtxWithTags :: Tags -> Context String
- postCtxWithTags tags = tagsField "tags" tags `mappend` postCtx
|