+++ /dev/null
----
-title: On tar pits (or, the second about)
-author: Lucian Mogoșanu
-date: April 29, 2016
----
-
-Humans' understanding of the universe is terrifyingly limited. Yet from
-thermodynamics we know (or we think we know) that by the arrow of
-entropy nature tends to fall into a general state of disorder. This is
-the zeroth tar pit.
-
-The first, second, third and so on up to the nth are most of the things,
-beasts, people and phenomena surrounding us, from the actual sticky
-thing to more metaphorical notions such as Kafka's perfect bureaucracy,
-or just the fat lady standing in front of you at the queue in the post
-office.
-
-In the same category lies a tar pit uniquely attributable to man, that
-creature more widely (although more and more narrowly) known as Zōon
-Politikon. It, like the Boltzmann constant itself, is also difficult to
-grasp, but you might know it as that feeling which (naturally!) keeps
-you from aspiring to become *more* human. It is laziness; it is
-stagnation; it is tiredness, and it is ultimately death.
-
-This blog, my, Lucian Mogoșanu's blog, describes its author's struggle
-through his own personal tar pit, as well as accounts and critiques of
-some of his times'. I hope I will have at least captured some of the
-more interesting ones, much to the amusement of future alien
-anthropologists.
-
-The Tar Pit is an ever incomplete and thus necessarily flawed
-publication. After all, tar pits might not even be enumerable.
-
-(Note: the previous [about page][about] was left online for historical
-reasons.)
-
-[about]: /about.html
+++ /dev/null
-{-# LANGUAGE OverloadedStrings #-}
-import Data.Monoid (mappend)
-import Text.Pandoc
-import Hakyll
-import Hakyll.Core.Configuration
-
--- wrapping it up
-main :: IO ()
-main = hakyllWith tarpitConfiguration $ do
- let pages = ["about.markdown", "about-2.markdown",
- "contact.markdown", "404.markdown",
- "403.markdown"]
- -- tags
- tags <- buildTags "posts/**" $ fromCapture "tags/*.html"
-
- -- content
- match "index.html" $ compileIndex tags
- match "css/*" compileCss
- match "posts/**" $ compilePosts tags
- match "uploads/**" $ compileUploads
- match "css/fonts/*" $ compileFonts
- match (fromList pages) compilePages
- create ["archive.html"] $ compileArchive tags
-
- -- tags rules
- tagsRules tags $ compileTags tags
-
- -- rss feed
- create ["rss.xml"] compileRss
-
- -- compile templates
- match "templates/*" $ compile templateCompiler
-
--- compilers go here
-compileIndex :: Tags -> Rules ()
-compileIndex tags = do
- route idRoute -- TODO: make a "copy to root" route?
- compile $ do
- posts <- loadAll "posts/**" >>= fmap (take 5) . recentFirst
- let indexCtx =
- listField "posts" postCtx (return posts) `mappend`
- defaultContext
-
- getResourceBody
- >>= applyAsTemplate indexCtx
- >>= loadAndApplyTemplate "templates/default.html" indexCtx
- >>= relativizeUrls
-
-compileCss :: Rules ()
-compileCss = do
- route idRoute
- compile compressCssCompiler
-
-compilePosts :: Tags -> Rules ()
-compilePosts tags = do
- route $ setExtension "html"
- let ctx = tagsCtx tags
- compile $ tarpitCompiler
- >>= saveSnapshot "content"
- >>= loadAndApplyTemplate "templates/post.html" ctx
- >>= loadAndApplyTemplate "templates/default.html" ctx
- >>= relativizeUrls
-
-compileUploads :: Rules ()
-compileUploads = do
- route idRoute
- compile copyFileCompiler
-
-compileFonts :: Rules ()
-compileFonts = compileUploads
-
-compilePages :: Rules ()
-compilePages = do
- route $ setExtension "html"
- compile $ tarpitCompiler
- >>= loadAndApplyTemplate "templates/default.html" defaultContext
- -- relative URLs break 404 pages, so don't do it here
- -- >>= relativizeUrls
-
-compileArchive :: Tags -> Rules ()
-compileArchive tags = do
- route idRoute
- compile $ do
- posts <- loadAll "posts/**" >>= recentFirst
- let archiveCtx =
- listField "posts" postCtx (return posts) `mappend`
- field "taglist" (const $ renderTagList tags) `mappend`
- constField "title" "Archive" `mappend`
- defaultContext
- makeItem ""
- >>= loadAndApplyTemplate "templates/archive.html" archiveCtx
- >>= loadAndApplyTemplate "templates/default.html" archiveCtx
- >>= relativizeUrls
-
-compileTags :: Tags -> String -> Pattern -> Rules ()
-compileTags tags tag pattern = do
- let title = "Posts tagged '" ++ tag ++ "'"
- route idRoute
- compile $ do
- posts <- loadAll pattern >>= recentFirst
- let tagCtx =
- constField "title" title `mappend`
- listField "posts" postCtx (return posts) `mappend`
- tagsCtx tags
- makeItem ""
- >>= loadAndApplyTemplate "templates/post-list.html" tagCtx
- >>= loadAndApplyTemplate "templates/default.html" tagCtx
- >>= relativizeUrls
-
-
-compileRss :: Rules ()
-compileRss = do
- -- shamelessly stolen from
- -- http://jaspervdj.be/hakyll/tutorials/05-snapshots-feeds.html
- route idRoute
- compile $ do
- let feedCtx =
- postCtx `mappend`
- teaserField "teaser" "content" `mappend`
- bodyField "description"
- applyTeaser = loadAndApplyTemplate "templates/teaser.html" feedCtx
- posts <- loadAllSnapshots "posts/**" "content"
- >>= mapM applyTeaser
- >>= fmap (take 7) . recentFirst
- renderRss tarpitFeed feedCtx posts
-
--- post context
-postCtx :: Context String
-postCtx = dateField "date" "%B %e, %Y" `mappend` defaultContext
-
-tagsCtx :: Tags -> Context String
-tagsCtx tags = tagsField "tags" tags `mappend` postCtx
-
--- hakyll configuration
-tarpitConfiguration :: Configuration
-tarpitConfiguration = defaultConfiguration
- { deployCommand = commStr }
- where
- commStr = "rsync -avz -e 'ssh -p 2200' "
- ++ "_site/* mogosanu.ro:/virtual/sites/thetarpit.org"
-
--- pandoc reader and writer options
-tarpitReaderOptions :: ReaderOptions
-tarpitReaderOptions = defaultHakyllReaderOptions
-
-tarpitWriterOptions :: WriterOptions
-tarpitWriterOptions = defaultHakyllWriterOptions
- { writerHTMLMathMethod = MathJax "" }
-
--- tarpit compiler
-tarpitCompiler :: Compiler (Item String)
-tarpitCompiler = pandocCompilerWith tarpitReaderOptions tarpitWriterOptions
-
--- support for RSS feeds
-tarpitFeed :: FeedConfiguration
-tarpitFeed = FeedConfiguration
- { feedTitle = "The Tar Pit"
- , feedDescription = "tarpit :: IO ()"
- , feedAuthorName = "Lucian Mogoșanu"
- , feedAuthorEmail = ""
- , feedRoot = "http://thetarpit.org"
- }
+++ /dev/null
-<?xml version="1.0" encoding="UTF-8"?>
-<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Strict//EN"
-"http://www.w3.org/TR/xhtml1/DTD/xhtml1-strict.dtd">
-<html xmlns="http://www.w3.org/1999/xhtml" xml:lang="en" lang="en">
-<head>
- <meta http-equiv="Content-Type" content="text/html; charset=UTF-8" />
- <title>The Tar Pit - $title$</title>
- <link rel="alternate" type="application/rss+xml" title="RSS" href="/rss.xml" />
- <link href='/css/fonts.css' rel='stylesheet' type='text/css' />
- <link rel="stylesheet" type="text/css" href="/css/default.css" />
- <link rel="stylesheet" type="text/css" href="/css/syntax.css" />
- <script type="text/javascript"
- src="http://cdn.mathjax.org/mathjax/latest/MathJax.js?config=TeX-AMS-MML_HTMLorMML">
- </script>
-</head>
-
-<body>
- <ul id="header">
- <li><a href="/">The Tar Pit</a></li>
- </ul>
- <ul id="navigation">
- <a href="/about-2.html">about</a>
- <a href="/archive.html">archive</a>
- <a href="/rss.xml">rss</a>
- </ul>
-
- <div id="content">
- <h1>$title$</h1>
- $body$
- </div>
-
- <div id="footer">
- Tarpit proudly generated by
- <a href="http://jaspervdj.be/hakyll">Hakyll</a>;
- <a href="http://creativecommons.org/licenses/by-nc-sa/3.0/">by-nc-sa</a>
- </div>
-<!-- so far, so good -->
-</body>
-</html>