summaryrefslogblamecommitdiffstats
path: root/site.hs
blob: 8284c2f24675aa70f1935dcdf19af8a30387a992 (plain) (tree)
1
2
3
4


                                                                                
                                                                                                                                         

















                                                                                






                                











































































































                                                                                                     

                                                 









                                                                  




                                                                




















                                                                         
--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
import           Data.Monoid (mappend)
import           System.FilePath ((</>), (<.>), splitExtension, splitFileName, takeDirectory, stripExtension, takeFileName, takeBaseName)
import           Hakyll


--------------------------------------------------------------------------------
main :: IO ()
main = hakyll $ do
    match "assets/*" $ do
        route   idRoute
        compile copyFileCompiler

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

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

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

    match "sw.min.js" $ do
        route   idRoute
        compile copyFileCompiler

    match "style.css" $ do
        route   idRoute
        compile compressCssCompiler

    match (fromList ["about.md", "contact.md"]) $ do
        route   $ setExtension "html" `composeRoutes` appendIndex
        compile $ pandocCompiler
            >>= loadAndApplyTemplate "templates/base.html" defaultContext
            >>= relativizeUrls

    -- build up tags
    tags <- buildTags "posts/*" (fromCapture "tags/*.html")
    tagsRules tags $ \tag pattern -> do
        let title = "posts tagged \"" ++ tag ++ "\""
        route appendIndex
        compile $ do
            posts <- recentFirst =<< loadAll pattern
            let ctx = constField "title" title
                      `mappend` listField "posts" (postCtxWithTags tags) (return posts)
                      `mappend` defaultContext

            makeItem ""
                >>= loadAndApplyTemplate "templates/tag.html" ctx
                >>= loadAndApplyTemplate "templates/base.html" ctx
                >>= relativizeUrls

    match "posts/*" $ do
        route $ setExtension "html" `composeRoutes`
                dateFolders         `composeRoutes`
                appendIndex
        compile $ pandocCompiler
            >>= saveSnapshot "article-text"
            >>= loadAndApplyTemplate "templates/post.html" (postCtxWithTags tags)
            >>= saveSnapshot "content"
            >>= loadAndApplyTemplate "templates/base.html" (postCtxWithTags tags)
            >>= relativizeUrls

    match "posts/*" $ version "raw" $ do
        route   idRoute
        compile getResourceBody

    create ["archives.html"] $ do
        route appendIndex
        compile $ do
            posts <- recentFirst =<< loadAll ("posts/*" .&&. hasNoVersion)
            let archiveCtx =
                    listField "posts" postCtx (return posts) `mappend`
                    constField "title" "archives"            `mappend`
                    defaultContext

            makeItem ""
                >>= loadAndApplyTemplate "templates/archives.html" archiveCtx
                >>= loadAndApplyTemplate "templates/base.html" archiveCtx
                >>= relativizeUrls


    match "index.html" $ do
        route idRoute
        compile $ do
            posts <- recentFirst =<< loadAllSnapshots ("posts/*" .&&. hasNoVersion) "article-text"
            let indexCtx =
                    listField "posts" postCtx (return posts) `mappend`
                    defaultContext

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

    match "templates/*" $ compile templateBodyCompiler

    create ["feed.xml"] $ do
        route idRoute
        compile $ do
            let feedCtx = postCtx `mappend` bodyField "description"
            posts <- fmap (take 10) . recentFirst =<<
                loadAllSnapshots ("posts/*" .&&. hasNoVersion) "content"
            renderAtom feedConfig feedCtx posts

    create ["sitemap.xml"] $ do
        route idRoute
        compile $ do
            -- load and sort the posts
            posts <- recentFirst =<< loadAll "posts/*"

            -- load individual pages from a list (globs DO NOT work here)
            singlePages <- loadAll (fromList ["about.md", "contact.md", "archives.html", "feed.xml"])

                           -- mappend the posts and singlePages together
            let pages = posts <> singlePages

                           -- create the `pages` field with the postCtx
                           -- and return the `pages` value for it
                sitemapCtx = 
                    constField "root" root <>
                    listField "pages" postCtx (return pages)

            -- make the item and apply our sitemap template
            makeItem ""
                >>= loadAndApplyTemplate "templates/sitemap.xml" sitemapCtx


--------------------------------------------------------------------------------
postCtx :: Context String
postCtx =
    constField "root" root      `mappend`
    dateField "date" "%Y-%m-%d" `mappend`
    idFieldFromPath "id"        `mappend`
    teaserField "teaser" "article-text" `mappend`
    dropIndexHtml "url"         `mappend`
    defaultContext

postCtxWithTags :: Tags -> Context String
postCtxWithTags tags = tagsField "tags" tags `mappend` postCtx

appendIndex :: Routes
appendIndex = customRoute $
    (\(p, e) -> p </> "index" <.> e) . splitExtension . toFilePath


idFieldFromPath :: String -> Context a
idFieldFromPath key = mapContext transform (pathField key) where
     transform path = takeBaseName path

dropIndexHtml :: String -> Context a
dropIndexHtml key = mapContext transform (urlField key) where
    transform url = case splitFileName url of
                        (p, "index.html") -> takeDirectory p
                        _                 -> url

dateFolders :: Routes
dateFolders =
    gsubRoute "/[0-9]{4}-[0-9]{2}-[0-9]{2}-" $ replaceAll "-" (const "/")

root :: String
root = "https://infoculture.pub"

feedConfig :: FeedConfiguration
feedConfig = FeedConfiguration
    { feedTitle = "info{culture}"
    , feedDescription = "cultivating informatics"
    , feedAuthorName = "cel ❀"
    , feedAuthorEmail = "cel@infoculture.pub"
    , feedRoot = "https://infoculture.pub"
    }