Created
May 11, 2019 20:24
-
-
Save MagnificentPako/61f7fe6d4d810ed82220c87cae025540 to your computer and use it in GitHub Desktop.
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
-------------------------------------------------------------------------------- | |
{-# LANGUAGE OverloadedStrings #-} | |
import Control.Monad (forM_) | |
import Data.List (isSuffixOf, lines) | |
import Data.Monoid (mappend) | |
import Hakyll | |
import System.FilePath (takeBaseName, takeDirectory, (</>)) | |
-------------------------------------------------------------------------------- | |
main :: IO () | |
main = hakyll $ do | |
match "images/*" $ do | |
route idRoute | |
compile copyFileCompiler | |
match "css/*" $ do | |
route idRoute | |
compile compressCssCompiler | |
match (fromList ["about.md", "contact.md"]) $ do | |
route $ cleanRoute | |
compile $ pandocCompiler | |
>>= loadAndApplyTemplate "templates/default.html" defaultContext | |
>>= relativizeUrls | |
>>= cleanIndexUrls | |
tags <- buildTags "posts/*" (fromCapture "tags/*.html") | |
tagsRules tags $ \tag pat -> do | |
route $ cleanRoute | |
compile $ do | |
posts <- recentFirst =<< loadAll pat | |
let ctx = postCtxWithTags tags | |
postsField = listField "posts" postCtx (pure posts) | |
titleField = constField "title" ("Posts tagged \"" ++ tag ++ "\"") | |
indexCtx = postsField <> titleField <> defaultContext | |
makeItem "" >>= loadAndApplyTemplate "templates/post-list.html" indexCtx | |
>>= loadAndApplyTemplate "templates/default.html" indexCtx | |
>>= relativizeUrls | |
>>= cleanIndexUrls | |
match "posts/*" $ do | |
route $ cleanRoute | |
compile $ pandocCompiler | |
>>= loadAndApplyTemplate "templates/post.html" (postCtxWithTags tags) | |
>>= loadAndApplyTemplate "templates/default.html" (postCtxWithTags tags) | |
>>= relativizeUrls | |
>>= cleanIndexUrls | |
create ["archive.html"] $ do | |
route $ cleanRoute | |
compile $ do | |
posts <- recentFirst =<< loadAll "posts/*" | |
let archiveCtx = | |
listField "posts" (postCtx) (return posts) `mappend` | |
constField "title" "Archives" `mappend` | |
defaultContext | |
makeItem "" | |
>>= loadAndApplyTemplate "templates/archive.html" archiveCtx | |
>>= loadAndApplyTemplate "templates/default.html" archiveCtx | |
>>= relativizeUrls | |
>>= cleanIndexUrls | |
match "index.html" $ do | |
route idRoute | |
compile $ do | |
posts <- recentFirst =<< loadAll "posts/*" | |
let indexCtx = | |
listField "posts" postCtx (return posts) `mappend` | |
constField "title" "Home" `mappend` | |
defaultContext | |
getResourceBody | |
>>= applyAsTemplate indexCtx | |
>>= loadAndApplyTemplate "templates/default.html" indexCtx | |
>>= relativizeUrls | |
>>= cleanIndexUrls | |
match "templates/*" $ compile templateCompiler | |
-------------------------------------------------------------------------------- | |
postCtx :: Context String | |
postCtx = | |
dateField "date" "%B %e, %Y" `mappend` | |
defaultContext | |
cleanRoute :: Routes | |
cleanRoute = customRoute createIndexRoute | |
where | |
createIndexRoute ident = takeDirectory p </> takeBaseName p </> "index.html" | |
where p = toFilePath ident | |
cleanIndexUrls :: Item String -> Compiler (Item String) | |
cleanIndexUrls = return . fmap (withUrls cleanIndex) | |
cleanIndexHtmls :: Item String -> Compiler (Item String) | |
cleanIndexHtmls = return . fmap (replaceAll pattern replacement) | |
where | |
pattern = "/index.html" | |
replacement = const "/" | |
cleanIndex :: String -> String | |
cleanIndex url | |
| idx `isSuffixOf` url = take (length url - length idx) url | |
| otherwise = url | |
where idx = "index.html" | |
postCtxWithTags :: Tags -> Context String | |
postCtxWithTags tags = tagsField "tags" tags `mappend` postCtx |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment