-------------------------------------------------------------------------------- {-# LANGUAGE OverloadedStrings #-} import Control.Applicative ((<$>)) import Data.Monoid (mappend) import Hakyll import Data.Map as M import Data.Maybe (fromMaybe) config :: Configuration config = defaultConfiguration { deployCommand = "rsync -Havz _site/ rekado@elephly.net:/srv/disk1/rekado/elephly.net" } -------------------------------------------------------------------------------- main :: IO () main = hakyllWith config $ do match "css/*" $ do route idRoute compile compressCssCompiler match ( "js/libs/*" .||. "js/hyphenator/*" .||. "js/hyphenator/patterns/*" .||. "js/*" .||. "downies/*" .||. "downies/music/*" .||. "images/*" .||. "images/posts/*" .||. "favicon.ico" ) $ do route idRoute compile copyFileCompiler match ( "static/*.markdown" .||. "static/*/*.markdown" ) $ do route $ setExtension "html" `composeRoutes` gsubRoute "static/" (const "") compile $ pandocCompiler >>= loadAndApplyTemplate "templates/default.html" defaultContext >>= relativizeUrls match "static/*.html" $ do route $ gsubRoute "static/" (const "") compile $ do getResourceBody >>= loadAndApplyTemplate "templates/default.html" defaultContext >>= relativizeUrls match "posts/*.markdown" $ do route $ setExtension "html" compile defaultCompiler --itemTpl <- loadBody "templates/photo.html" --metadata <- getMetadata --let m = M.lookup "photo" metadata -- direct links match "posts/2010-03-28-elephly.markdown" $ version "direct" $ do route $ constRoute "elephly.html" compile defaultCompiler match "posts/2010-03-23-fur-man.markdown" $ version "direct" $ do route $ constRoute "fur-man.html" compile defaultCompiler -- blog post archive create ["posts/index.html"] $ do route idRoute compile $ do let archiveCtx = field "posts" (\_ -> postList recentFirst) `mappend` defaultContext makeItem "" >>= loadAndApplyTemplate "templates/archive.html" archiveCtx >>= loadAndApplyTemplate "templates/default.html" archiveCtx >>= relativizeUrls -- always show the most recent blog post create ["index.html"] $ do route idRoute compile $ do mostRecent <- (head . recentFirst) <$> loadAllSnapshots "posts/*.markdown" "non-relative" makeItem (itemBody mostRecent) >>= relativizeUrls match "templates/*" $ compile templateCompiler -------------------------------------------------------------------------------- postCtx :: Context String postCtx = dateField "date" "%B %e, %Y" `mappend` photoSnippet `mappend` flattrSnippet `mappend` licenseSnippet `mappend` defaultContext -- If a post declares a photo in the metadata header, -- build an image tag, otherwise ignore. photoSnippet :: Context String photoSnippet = field "photo-snippet" $ \item -> do metadata <- getMetadata (itemIdentifier item) case M.lookup "photo" metadata of Just file -> itemBody <$> loadAndApplyTemplate "templates/photo.html" postCtx item _ -> return "" -- If a post declares a flattr id in the metadata header, -- load the flattr snippet, otherwise ignore. flattrSnippet :: Context String flattrSnippet = field "flattr-snippet" $ \item -> do metadata <- getMetadata (itemIdentifier item) case M.lookup "flattr" metadata of Just _ -> itemBody <$> loadAndApplyTemplate "templates/flattr.html" postCtx item _ -> return "" licenseSnippet :: Context String licenseSnippet = field "license-snippet" $ \item -> do metadata <- getMetadata (itemIdentifier item) case M.lookup "license" metadata of Just _ -> itemBody <$> loadAndApplyTemplate "templates/license.html" postCtx item _ -> return "" -------------------------------------------------------------------------------- postList :: ([Item String] -> [Item String]) -> Compiler String postList sortFilter = do posts <- sortFilter <$> loadAll ("posts/*.markdown" .&&. hasNoVersion) itemTpl <- loadBody "templates/post-item.html" list <- applyTemplateList itemTpl postCtx posts return list defaultCompiler = pandocCompiler >>= loadAndApplyTemplate "templates/post.html" postCtx >>= loadAndApplyTemplate "templates/default.html" postCtx >>= saveSnapshot "non-relative" >>= relativizeUrls