diff --git a/site.hs b/site.hs index 58f30e3..0fff1d6 100644 --- a/site.hs +++ b/site.hs @@ -1,116 +1,122 @@ -------------------------------------------------------------------------------- {-# LANGUAGE OverloadedStrings #-} -import Data.Monoid (mappend) -import Hakyll + +import Data.Monoid (mappend) import qualified GHC.IO.Encoding as E +import Hakyll + -------------------------------------------------------------------------------- main :: IO () main = do - E.setLocaleEncoding E.utf8 - hakyllWith config $ do - match "images/*" $ do - route idRoute - compile copyFileCompiler + E.setLocaleEncoding E.utf8 + hakyllWith config $ do + match "images/*" $ do + route idRoute + compile copyFileCompiler - match "css/*" $ compile compressCssCompiler - create ["style.css"] $ do - route idRoute - compile $ do - csses <- loadAll "css/*.css" - makeItem $ unlines $ map itemBody csses + match "css/*" $ compile compressCssCompiler + create ["style.css"] $ do + route idRoute + compile $ do + csses <- loadAll "css/*.css" + makeItem $ unlines $ map itemBody csses - match (fromList ["about.markdown"]) $ do - route $ setExtension "html" - compile $ pandocCompiler - >>= loadAndApplyTemplate "templates/default.html" defaultContext - >>= relativizeUrls + match (fromList ["about.markdown"]) $ do + route $ setExtension "html" + compile $ + pandocCompiler + >>= loadAndApplyTemplate "templates/default.html" defaultContext + >>= relativizeUrls - tags <- buildTags "posts/*" (fromCapture "tags/*.html") + tags <- buildTags "posts/*" (fromCapture "tags/*.html") - match "posts/*" $ do - route $ setExtension "html" - compile $ pandocCompiler - >>= loadAndApplyTemplate "templates/post.html" (postCtxWithTags tags) - >>= loadAndApplyTemplate "templates/default.html" (postCtxWithTags tags) - >>= 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" (postCtxWithTags tags) (return posts) `mappend` - constField "title" "Archives" `mappend` - defaultContext + create ["archive.html"] $ do + route idRoute + compile $ do + posts <- recentFirst =<< loadAll "posts/*" + let archiveCtx = + listField "posts" (postCtxWithTags tags) (return posts) + `mappend` constField "title" "Archives" + `mappend` defaultContext - makeItem "" - >>= loadAndApplyTemplate "templates/archive.html" archiveCtx - >>= loadAndApplyTemplate "templates/default.html" archiveCtx - >>= relativizeUrls + makeItem "" + >>= loadAndApplyTemplate "templates/archive.html" archiveCtx + >>= loadAndApplyTemplate "templates/default.html" archiveCtx + >>= relativizeUrls - match "index.html" $ do - route idRoute - compile $ do - posts <- fmap (take 3) . recentFirst =<< loadAll "posts/*" - let indexCtx = - listField "posts" (postCtxWithTags tags) (return posts) `mappend` - field "tags" (\_ -> renderTagList tags) `mappend` - constField "title" "Welcome" `mappend` - defaultContext + match "index.html" $ do + route idRoute + compile $ do + posts <- fmap (take 3) . recentFirst =<< loadAll "posts/*" + let indexCtx = + listField "posts" (postCtxWithTags tags) (return posts) + `mappend` field "tags" (\_ -> renderTagList tags) + `mappend` constField "title" "Welcome" + `mappend` defaultContext - getResourceBody - >>= applyAsTemplate indexCtx - >>= loadAndApplyTemplate "templates/default.html" indexCtx - >>= relativizeUrls + getResourceBody + >>= applyAsTemplate indexCtx + >>= loadAndApplyTemplate "templates/default.html" indexCtx + >>= relativizeUrls - create ["sitemap.xml"] $ do - route idRoute - compile $ do - posts <- recentFirst =<< loadAll "posts/*" - let sitemapCtx = - constField "baseUrl" "sanchayanmaity.net" `mappend` - constField "title" "Sitemap" `mappend` - listField "posts" (postCtxWithTags tags) (return posts) `mappend` - postCtxWithTags tags + create ["sitemap.xml"] $ do + route idRoute + compile $ do + posts <- recentFirst =<< loadAll "posts/*" + let sitemapCtx = + constField "baseUrl" "sanchayanmaity.net" + `mappend` constField "title" "Sitemap" + `mappend` listField "posts" (postCtxWithTags tags) (return posts) + `mappend` postCtxWithTags tags - makeItem "" - >>= loadAndApplyTemplate "templates/sitemap.xml" sitemapCtx - >>= cleanIndexHtmls + makeItem "" + >>= loadAndApplyTemplate "templates/sitemap.xml" sitemapCtx + >>= cleanIndexHtmls - match "templates/*" $ compile templateBodyCompiler + match "templates/*" $ compile templateBodyCompiler - 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" (postCtxWithTags tags) (return posts) - `mappend` defaultContext + 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" (postCtxWithTags tags) (return posts) + `mappend` defaultContext - makeItem "" - >>= loadAndApplyTemplate "templates/tag.html" ctx - >>= loadAndApplyTemplate "templates/default.html" ctx - >>= relativizeUrls + makeItem "" + >>= loadAndApplyTemplate "templates/tag.html" ctx + >>= loadAndApplyTemplate "templates/default.html" ctx + >>= relativizeUrls -------------------------------------------------------------------------------- config :: Configuration -config = defaultConfiguration { - destinationDirectory = "public" -} +config = + defaultConfiguration + { destinationDirectory = "public" + } postCtx :: Context String postCtx = - dateField "date" "%B %e, %Y" `mappend` - defaultContext + dateField "date" "%B %e, %Y" + `mappend` defaultContext postCtxWithTags :: Tags -> Context String postCtxWithTags tags = tagsField "tags" tags `mappend` postCtx cleanIndexHtmls :: Item String -> Compiler (Item String) cleanIndexHtmls = return . fmap (replaceAll pattern replacement) - where - pattern = "/index.html" + where + pattern = "/index.html" replacement :: String -> String replacement = const "/"