angeley.es source

[[ 🗃 ^rwVmE website ]] :: [📥 Inbox] [📤 Outbox] [🐤 Followers] [🤝 Collaborators] [🛠 Commits]

Clone

HTTPS: git clone https://vervis.peers.community/repos/rwVmE

SSH: git clone USERNAME@vervis.peers.community:rwVmE

Branches

Tags

master ::

site.hs

{- Written in 2017, 2019, 2020 by fr33domlover <fr33domlover@riseup.net>.
 -
 - ♡ Copying is an act of love. Please copy, reuse and share.
 -
 - The author(s) have dedicated all copyright and related and neighboring
 - rights to this software to the public domain worldwide. This software is
 - distributed without any warranty.
 -
 - You should have received a copy of the CC0 Public Domain Dedication along
 - with this software. If not, see
 - <http://creativecommons.org/publicdomain/zero/1.0/>.
 -}

{-# LANGUAGE OverloadedStrings #-}

import Data.Monoid ((<>))
import Data.FileStore.Types (FileStore)
import Hakyll
import Hakyll.FileStore.Context (fsModificationTimeField)
import Hakyll.FileStore.Git.Context (gitStore)
import Hakyll.Web.Sass (sassCompilerWith)
import System.FilePath ((</>), dropExtension)
import Text.Sass.Options

sassOptions = SassOptions
    { sassPrecision         = 3
    , sassOutputStyle       = SassStyleCompressed
    , sassSourceComments    = False
    , sassSourceMapEmbed    = False
    , sassSourceMapContents = False
    , sassOmitSourceMapUrl  = True
    , sassIsIndentedSyntax  = True
    , sassIndent            = "    "
    , sassLinefeed          = "\n"
    , sassInputPath         = Nothing
    , sassOutputPath        = Nothing
    , sassPluginPaths       = Nothing
    , sassIncludePaths      = Nothing
    , sassSourceMapFile     = Nothing
    , sassSourceMapRoot     = Nothing
    , sassFunctions         = Nothing
    , sassHeaders           = Nothing
    , sassImporters         = Nothing
    , sassStripEncodingInfo = False
    }


feedConfiguration :: FeedConfiguration
feedConfiguration = FeedConfiguration
    { feedTitle       = "little red cabin"
    , feedDescription = ""
    , feedAuthorName  = ""
    , feedAuthorEmail = ""
    , feedRoot        = "https://angeley.es"
    }

fileStore :: FileStore
fileStore = gitStore

pageRoute :: Routes
pageRoute = customRoute $ (</> "index.html") . dropExtension . toFilePath

dateFormat :: String
dateFormat = "%B %e, %Y"

postCtx :: Context String
postCtx =
       dateField "date" dateFormat
    <> fsModificationTimeField fileStore "mtime" dateFormat
    <> defaultContext

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

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

    match "styles/default.sass" $ do
        route   $ setExtension "css"
        compile $ sassCompilerWith sassOptions

    match (fromList ["software.md"]) $ do
        route pageRoute
        compile $ pandocCompiler
            >>= loadAndApplyTemplate "templates/default.html" defaultContext
            >>= relativizeUrls

    create ["blog.atom"] $ do
        route idRoute
        compile $ do
            let feedCtx = postCtx `mappend` bodyField "description"
            posts <-
                fmap (take 30) . recentFirst =<<
                    loadAllSnapshots "posts/*" "content"
            renderAtom feedConfiguration feedCtx posts

    match "poems/*" $ do
        route pageRoute
        compile $ pandocCompiler
            >>= loadAndApplyTemplate "templates/poem.html"    postCtx
            >>= loadAndApplyTemplate "templates/default.html" postCtx
            >>= relativizeUrls

    match "private/poems/*" $ do
        route pageRoute
        compile $ pandocCompiler
            >>= loadAndApplyTemplate "templates/poem.html"    postCtx
            >>= loadAndApplyTemplate "templates/default.html" postCtx
            >>= relativizeUrls

    match "stories/*" $ do
        route pageRoute
        compile $ pandocCompiler
            >>= loadAndApplyTemplate "templates/poem.html"    postCtx
            >>= loadAndApplyTemplate "templates/default.html" postCtx
            >>= relativizeUrls

    match "private/stories/*" $ do
        route pageRoute
        compile $ pandocCompiler
            >>= loadAndApplyTemplate "templates/poem.html"    postCtx
            >>= loadAndApplyTemplate "templates/default.html" postCtx
            >>= relativizeUrls

    match "posts/*" $ do
        route pageRoute
        compile $ pandocCompiler
            >>= loadAndApplyTemplate "templates/poem.html"    postCtx
            >>= saveSnapshot "content"
            >>= loadAndApplyTemplate "templates/default.html" postCtx
            >>= relativizeUrls

    create ["private.html"] $ do
        route pageRoute
        compile $ do
            privPoems   <- chronological =<< loadAll "private/poems/*"
            privStories <- chronological =<< loadAll "private/stories/*"
            let poemCtx =
                       listField "privPoems"   postCtx (return privPoems)
                    <> listField "privStories" postCtx (return privStories)
                    <> constField "title" "Private"
                    <> defaultContext

            makeItem ""
                >>= loadAndApplyTemplate "templates/private.html" poemCtx
                >>= loadAndApplyTemplate "templates/default.html"  poemCtx
                >>= relativizeUrls

    match "as2-ext.jsonld" $ do
        route $ customRoute $ dropExtension . toFilePath
        compile copyFileCompiler

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

    match "templates/*" $ compile templateBodyCompiler
[See repo JSON]