How this site is built using Hakyll

This site is built using the static site generator Hakyll.

The main benefits of this approach are in 3 areas:

  • Workflow: Being able to publish new content with minimal effort.
  • Security: Having a safe website without the need to constantly update some buggy CMS.
  • Speed: A fast website is good for SEO and usability (especially on mobile phones).

The following is from the file site.hs that compiles to one executable that gathers and transforms all the necessary content and puts it into one folder ready for uploading to the webserver. For more information check out the documentation on the Hakyll website.

{-# LANGUAGE OverloadedStrings #-}
import           Data.Monoid (mappend)
import           Hakyll


main :: IO ()
main = hakyll $ do

  
    match "img/*" $ do
        route   idRoute
        compile copyFileCompiler


    match "img-posts/*" $ do
        route   idRoute
        compile copyFileCompiler


    match "fonts/*" $ do
        route   idRoute
        compile copyFileCompiler


    match "css/*" $ do
        route   idRoute
        compile compressCssCompiler


    match "blog/*" $ do
      route $ setExtension "html"
      compile $ pandocCompiler
        >>= loadAndApplyTemplate "templates/post.html"    postCtx
        >>= saveSnapshot "content"
        >>= loadAndApplyTemplate "templates/default-onecolumn.html" postCtx
        >>= relativizeUrls


    match "site/index.md" $ do
      route $ setExtension "html"
      compile $ pandocCompiler
        >>= loadAndApplyTemplate "templates/default.html" defaultContext
        >>= relativizeUrls


    create ["archiv.html"] $ do
        route idRoute
        compile $ do
            posts <- recentFirst =<< loadAll "blog/*"
            let archiveCtx =
                    listField "posts" postCtx (return posts) `mappend`
                    listField "postlinks" postCtx (return posts) `mappend`                    
                    constField "title" "Archiv"            `mappend`
                    constField "metadesc" "Blog-Archiv von Uffizio mit Artikeln über Webseiten, Webshops und Webapplikationen aus technischer und betriebswirtschaftlicher Sicht." `mappend`
                    defaultContext

            makeItem ""
                >>= loadAndApplyTemplate "templates/archive.html" archiveCtx
                >>= loadAndApplyTemplate "templates/default.html" archiveCtx
                >>= relativizeUrls


    match "blog.html" $ do
        route idRoute
        compile $ do
            posts <- recentFirst =<< loadAll "blog/*"
            showposts <- recentFirst =<< loadAllSnapshots "blog/*" "content"
            let indexCtx =
                    listField "posts" postCtx (return posts) `mappend`
                    listField "showposts" postCtx (return $ take 1 $ showposts) `mappend`
                    listField "postlinks" postCtx (return $ tail $ posts) `mappend`
                    defaultContext

            getResourceBody
                >>= applyAsTemplate indexCtx
                >>= loadAndApplyTemplate "templates/default.html" indexCtx
                >>= relativizeUrls


    match staticPages $ do
        route   $ idRoute
        compile $ getResourceBody
            >>= loadAndApplyTemplate "templates/default.html" defaultContext
            >>= relativizeUrls


    match "templates/*" $ compile templateCompiler


    create ["sitemap.xml"] $ do
        route idRoute
        compile $ do
            posts <- recentFirst =<< loadAll "blog/*"
            let sitemapCtx =
                  listField "posts" sitemapPostCtx (return posts)
            makeItem ""
                >>= loadAndApplyTemplate "templates/sitemap.xml" sitemapCtx


    match staticFiles $ do
        route idRoute
        compile copyFileCompiler



staticPages = fromList ["index.html", "webseiten.html", "e-commerce.html", "internetmarketing.html"]
staticFiles = fromList ["sitemap.xml", "robots.txt", "humans.txt", "404.html"]



postCtx :: Context String
postCtx =
    dateField "date" "%d.%m.%Y" `mappend`
    defaultContext



sitemapPostCtx :: Context String
sitemapPostCtx =
    dateField "date" "%Y-%m-%d" `mappend`
    constField "baseUrl" "https://www.uffizio.ch" `mappend`
    defaultContext

Kontakt