-------------------------------------------------------------------------------- {-# LANGUAGE OverloadedStrings #-} import Data.Monoid ((<>)) import Hakyll import Hakyll.Favicon (faviconsRules, faviconsField) -------------------------------------------------------------------------------- muraConf :: Configuration muraConf = defaultConfiguration { destinationDirectory = "_http" , storeDirectory = "_store" , tmpDirectory = "_tmp" , providerDirectory = "_input" } -- Our default context for pages ctx :: Context String ctx = defaultContext <> faviconsField main :: IO () main = hakyllWith muraConf $ do faviconsRules "icons/favicon.svg" match "images/*" $ do route idRoute compile copyFileCompiler match "css/*" $ do route idRoute compile compressCssCompiler match (fromList ["about.md", "contact.md", "links.md"]) $ do route $ setExtension "html" compile $ pandocCompiler >>= loadAndApplyTemplate "templates/default.html" ctx >>= relativizeUrls -- Render Atom + Rss feeds create ["atom.xml"] $ do route idRoute (compileFeed renderAtom) create ["rss.xml"] $ do route idRoute (compileFeed renderRss) match "posts/*" $ do route $ setExtension "html" compile $ pandocCompiler >>= loadAndApplyTemplate "templates/post.html" postCtx >>= saveSnapshot "content" >>= loadAndApplyTemplate "templates/default.html" postCtx >>= relativizeUrls create ["archive.html"] $ do route idRoute compile $ do posts <- recentFirst =<< loadAll "posts/*" let archiveCtx = listField "posts" postCtx (return posts) <> constField "title" "archives" <> ctx makeItem "" >>= loadAndApplyTemplate "templates/archive.html" archiveCtx >>= loadAndApplyTemplate "templates/default.html" archiveCtx >>= relativizeUrls match "index.html" $ do route idRoute compile $ do -- posts <- recentFirst =<< loadAll "posts/*" posts <- (return . (take 7)) =<< recentFirst =<< loadAll "posts/*" let indexCtx = listField "posts" postCtx (return posts) <> constField "title" "ホームページ" <> ctx getResourceBody >>= applyAsTemplate indexCtx >>= loadAndApplyTemplate "templates/index.html" indexCtx >>= loadAndApplyTemplate "templates/default.html" indexCtx >>= relativizeUrls match "templates/*" $ compile templateBodyCompiler -------------------------------------------------------------------------------- ---- Agnememnon the Fuck-Upperer - Conquerer of Small Type Declarations compileFeed :: (FeedConfiguration -> Context String -> [Item String] -> Compiler (Item String) ) -> Rules () -- For those left alive, this abstracts out creating -- Atom and RSS feeds compileFeed f = compile $ do let feedCtx = postCtx <> bodyField "description" posts <- fmap (take 10) . recentFirst =<< loadAllSnapshots "posts/*" "content" f feedConfig feedCtx posts -- The configuration for our Atom/RSS feeds feedConfig :: FeedConfiguration feedConfig = FeedConfiguration { feedTitle = "be 萌え online blog" , feedDescription = "a blog of misconstruedⓂ️monologues" , feedAuthorName = "i am the walrus" , feedAuthorEmail = "blog@bemoe.online" , feedRoot = "https://blog.bemoe.online" } postCtx :: Context String postCtx = dateField "date" "%Y年%_m月%e日" <> ctx