-------------------------------------------------------------------------------- {-# LANGUAGE OverloadedStrings #-} import Data.Monoid (mappend) import Hakyll import Data.List (sortBy, sortOn) import Data.Time (formatTime, defaultTimeLocale) -------------------------------------------------------------------------------- main :: IO () main = hakyllWith defaultConfiguration $ do match "well-known/*" $ do route (customRoute (prepend '.'. toFilePath)) compile copyFileCompiler 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 "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 prepend :: a -> [a] -> [a] prepend = (:)