website/site.hs

107 lines
3.7 KiB
Haskell

{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
import Control.Monad.State
import Control.Monad
import Hakyll
import System.FilePath
import System.Process
import Text.Pandoc.Extensions
import Text.Pandoc.Options
main :: IO ()
main = hakyllWith config $ do
match ("images/*" .||. "resources/**" .||. "css/*.css" .||. "*.asc") $ do
route idRoute
compile copyFileCompiler
match "css/style.scss" $ do
route $ setExtension "css"
compile $ getResourceString
>>= withItemBody (unixFilter "sass" ["--stdin"])
>>= return . fmap compressCss
tags <- buildTags "posts/*" (fromCapture "tags/*.html")
match "index.html" $ do
route $ idRoute
compile $ do
posts <- loadAll "posts/*" >>= recentFirst >>= pure . (take 5)
let ctx = listField "posts" (postCtx tags) (pure posts)
<> constField "title" "Home"
<> defaultContext
getResourceBody
>>= applyAsTemplate ctx
>>= loadAndApplyTemplate "templates/default.html" ctx
>>= relativizeUrls
match "*.md" $ do
route $ setExtension "html"
compile $ pandocCompiler
>>= loadAndApplyTemplate "templates/default.html" defaultContext
>>= relativizeUrls
match "templates/*" $ compile templateBodyCompiler
match "posts/*.md" $ do
let ctx = postCtx tags
route $ setExtension "html"
compile $ pandocCompiler
>>= loadAndApplyTemplate "templates/post.html" ctx
>>= loadAndApplyTemplate "templates/default.html" ctx
>>= relativizeUrls
tagsRules tags $ \tag pattern -> do
route $ idRoute
compile $ do
posts <- loadAll pattern >>= recentFirst
let ctx = constField "title" ("Posts tagged " ++ tag)
<> listField "posts" (postCtx tags) (pure posts)
<> defaultContext
makeItem ""
>>= loadAndApplyTemplate "templates/posts.html" ctx
>>= loadAndApplyTemplate "templates/default.html" ctx
>>= relativizeUrls
create ["posts.html"] $ do
route $ idRoute
compile $ do
posts <- loadAll "posts/*" >>= recentFirst
let ctx = constField "title" "Posts"
<> listField "posts" (postCtx tags) (pure posts)
<> defaultContext
makeItem ""
>>= loadAndApplyTemplate "templates/posts.html" ctx
>>= loadAndApplyTemplate "templates/default.html" ctx
>>= relativizeUrls
match "Tito_Sacchi_CV.tex" $ do
route $ setExtension "pdf"
compile $ getResourceBody >>= lualatex
lualatex :: Item String -> Compiler (Item TmpFile)
lualatex texSource = do
TmpFile toplevel <- newTmpFile "tmp.tex"
unsafeCompiler $ do
writeFile toplevel $ itemBody texSource
void $ system $ unwords
[ "lualatex", "-halt-on-error"
, "-output-directory", takeDirectory toplevel
, toplevel, ">/dev/null", "2>&1"]
makeItem $ TmpFile $ toplevel `replaceExtension` "pdf"
config :: Configuration
config = defaultConfiguration {
deployCommand = "rsync -avP --delete \
\ --exclude blog --exclude cgi-bin --exclude .DS_Store \
\ --exclude .well-known _site/ tito@tilde.team:~/public_html"
}
postCtx :: Tags -> Context String
postCtx tags = mconcat
[ dateField "date" "%B %e, %Y"
, tagsField "tags" tags
, defaultContext
]
-- vim: ts=4:sts=4:sw=4:et