-------------------------------------------------------------------------------- {-# LANGUAGE OverloadedStrings #-} import Data.Monoid (mappend) import Hakyll import Data.List (sortBy, sortOn) import Data.Time (formatTime, defaultTimeLocale) -------------------------------------------------------------------------------- main :: IO () main = hakyllWith defaultConfiguration{ deployCommand = "ipfs add -Q -r _site" } $do match "images/*" $ do route idRoute compile copyFileCompiler match "resources/*" $ do route idRoute compile copyFileCompiler match "css/*" $ do route idRoute compile compressCssCompiler match "js/*" $ do route idRoute compile compressCssCompiler match (fromList ["index.markdown", "contact.markdown"]) $ do route $ setExtension "html" compile $ pandocCompiler >>= loadAndApplyTemplate "templates/default.html" defaultContext >>= relativizeUrls match "posts/incomplete/*" $ do route $ setExtension "html" compile $ pandocCompiler >>= loadAndApplyTemplate "templates/post.html" postCtx >>= loadAndApplyTemplate "templates/default.html" postCtx >>= relativizeUrls match "posts/guides/*" $ do route $ setExtension "html" compile $ pandocCompiler >>= loadAndApplyTemplate "templates/post.html" postCtx >>= loadAndApplyTemplate "templates/default.html" postCtx >>= relativizeUrls match "posts/brainstorming/*" $ do route $ setExtension "html" compile $ pandocCompiler >>= loadAndApplyTemplate "templates/post.html" postCtx >>= loadAndApplyTemplate "templates/default.html" postCtx >>= relativizeUrls create ["guides.html"] $ do route idRoute compile $ do posts <- modFirst =<< loadAll "posts/guides/*" let archiveCtx = listField "posts" postCtx (return posts) `mappend` constField "title" "Guides" `mappend` defaultContext makeItem "" >>= loadAndApplyTemplate "templates/guides.html" archiveCtx >>= loadAndApplyTemplate "templates/default.html" archiveCtx >>= relativizeUrls match "templates/*" $ compile templateBodyCompiler modFirst :: [Item a] -> Compiler [Item a] modFirst = fmap reverse . modified where modified = sortByM (getItemModificationTime . itemIdentifier) sortByM f xs = map fst . sortOn snd <$> mapM (\x -> (,) x <$> f x) xs -------------------------------------------------------------------------------- postCtx :: Context String postCtx = dateField "date" "%B %e, %Y" `mappend` modifiedField "modified" "%B %e, %Y" `mappend` defaultContext where modifiedField key format = field key $ \i -> do time <- getItemModificationTime $ itemIdentifier i return $ formatTime defaultTimeLocale format time