website/site.hs

107 lines
3.7 KiB
Haskell
Raw Permalink Normal View History

{-# LANGUAGE LambdaCase #-}
2021-11-01 10:42:02 +00:00
{-# LANGUAGE OverloadedStrings #-}
import Control.Monad.State
2023-12-28 20:50:52 +00:00
import Control.Monad
2021-11-01 10:42:02 +00:00
import Hakyll
2022-03-20 10:25:13 +00:00
import System.FilePath
import System.Process
import Text.Pandoc.Extensions
import Text.Pandoc.Options
2021-11-01 10:42:02 +00:00
main :: IO ()
2021-11-15 14:59:55 +00:00
main = hakyllWith config $ do
2021-12-27 16:07:40 +00:00
match ("images/*" .||. "resources/**" .||. "css/*.css" .||. "*.asc") $ do
route idRoute
compile copyFileCompiler
2021-11-01 10:42:02 +00:00
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
2022-01-08 20:16:45 +00:00
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
2021-11-01 10:42:02 +00:00
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
2022-01-08 20:16:45 +00:00
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
2022-01-08 20:16:45 +00:00
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"
2021-11-15 14:59:55 +00:00
config :: Configuration
config = defaultConfiguration {
deployCommand = "rsync -avP --delete \
\ --exclude blog --exclude cgi-bin --exclude .DS_Store \
2024-02-18 17:52:59 +00:00
\ --exclude .well-known _site/ tito@tilde.team:~/public_html"
2021-11-15 14:59:55 +00:00
}
postCtx :: Tags -> Context String
postCtx tags = mconcat
[ dateField "date" "%B %e, %Y"
, tagsField "tags" tags
, defaultContext
]
2021-11-01 10:42:02 +00:00
-- vim: ts=4:sts=4:sw=4:et