pinealservo-com/site.hs

88 lines
2.9 KiB
Haskell

--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
import Data.Monoid (mappend)
import Data.Default
import Hakyll
-- Configuration
frontPagePosts = 5
hakyllConfig :: Configuration
hakyllConfig = def { deployCommand = "cd _site; cp -R * /opt/appdata/letsencrypt/config/www" }
--------------------------------------------------------------------------------
main :: IO ()
main = hakyllWith hakyllConfig $ do
match "images/*" $ do
route idRoute
compile copyFileCompiler
match "css/*.css" $ do
route idRoute
compile compressCssCompiler
match "css/*.hs" $ do
route $ setExtension "css"
compile $ getResourceString >>= withItemBody (unixFilter "stack" ["runhaskell", "--"])
>>= return . fmap compressCss
match "*.markdown" $ do
route $ setExtension "html"
compile $ pandocCompiler
>>= loadAndApplyTemplate "templates/default.html" defaultContext
>>= relativizeUrls
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) `mappend`
constField "title" "Archives" `mappend`
defaultContext
makeItem ""
>>= loadAndApplyTemplate "templates/archive.html" archiveCtx
>>= loadAndApplyTemplate "templates/default.html" archiveCtx
>>= relativizeUrls
match "index.html" $ do
route idRoute
compile $ do
allPosts <- fmap (take frontPagePosts) . recentFirst
=<< loadAllSnapshots "posts/*" "content"
let indexCtx =
listField "posts" postCtx (return allPosts) `mappend`
defaultNoTitleContext
getResourceBody
>>= applyAsTemplate indexCtx
>>= loadAndApplyTemplate "templates/default.html" indexCtx
>>= relativizeUrls
match "templates/*" $ compile templateCompiler
--------------------------------------------------------------------------------
defaultNoTitleContext :: Context String
defaultNoTitleContext =
bodyField "body" `mappend`
metadataField `mappend`
urlField "url" `mappend`
pathField "path" `mappend`
missingField
postCtx :: Context String
postCtx =
dateField "date" "%B %e, %Y" `mappend`
defaultContext