kompact-io-landing/site.hs

82 lines
2.5 KiB
Haskell

--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
import Data.Monoid (mappend)
import Hakyll
import System.FilePath (splitExtension, joinPath, splitDirectories, replaceExtension)
--------------------------------------------------------------------------------
main :: IO ()
main = hakyll $ do
match "content/favicon.png" $ do
route rmPrefix
compile copyFileCompiler
match "content/images/*" $ do
route rmPrefix
compile copyFileCompiler
match "content/scripts/*" $ do
route rmPrefix
compile copyFileCompiler
match "content/css/*" $ do
route rmPrefix
compile compressCssCompiler
match "content/fonts/*" $ do
route rmPrefix
compile copyFileCompiler
match "content/posts/*.md" $ do
route rmPrefixMd
compile $ pandocCompiler
>>= loadAndApplyTemplate "templates/post.html" postCtx
>>= loadAndApplyTemplate "templates/default.html" postCtx
>>= relativizeUrls
create ["blog.html"] $ do
route idRoute
compile $ do
posts <- recentFirst =<< loadAll "content/posts/*.md"
let archiveCtx =
listField "posts" postCtx (return posts) `mappend`
constField "title" "Blog" `mappend`
defaultContext
makeItem ""
>>= loadAndApplyTemplate "templates/blog.html" archiveCtx
>>= loadAndApplyTemplate "templates/default.html" archiveCtx
>>= relativizeUrls
match "content/index.md" $ do
route rmPrefixMd
compile $ do
let indexCtx = defaultContext
getResourceBody
>>= applyAsTemplate indexCtx
>>= loadAndApplyTemplate "templates/index.html" indexCtx
>>= relativizeUrls
match "templates/*" $ compile templateBodyCompiler
--------------------------------------------------------------------------------
postCtx :: Context String
postCtx =
dateField "date" "%Y-%m-%d" `mappend`
defaultContext
setExtensionInner :: String -> FilePath -> FilePath
setExtensionInner = flip replaceExtension
rmPrefixInner :: FilePath -> FilePath
rmPrefixInner = joinPath . tail . splitDirectories
rmPrefix :: Routes
rmPrefix = customRoute $ rmPrefixInner . toFilePath
rmPrefixMd = customRoute $ rmPrefixInner . setExtensionInner "html" . toFilePath