Skip to content

Instantly share code, notes, and snippets.

@jeffbr13
Created June 27, 2013 22:39
Show Gist options
  • Save jeffbr13/5881045 to your computer and use it in GitHub Desktop.
Save jeffbr13/5881045 to your computer and use it in GitHub Desktop.
An attempt-in-progress at ordering posts by file modification time.
--------------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings, TupleSections #-}
import Control.Monad
import Data.List
import qualified Data.Map as M
import Data.Maybe
import Data.Ord
import Data.Monoid (mappend)
import Hakyll
import qualified Text.Pandoc.Options as Pandoc.Options
--------------------------------------------------------------------------------
config :: Configuration
config = defaultConfiguration
{ deployCommand = "..."}
pandocWriterOptions :: Pandoc.Options.WriterOptions
pandocWriterOptions = defaultHakyllWriterOptions
{ Pandoc.Options.writerHtml5 = True
, Pandoc.Options.writerHtmlQTags = True
--, Pandoc.Options.writerNumberSections = True
--, Pandoc.Options.writerNumberOffset = [1]
, Pandoc.Options.writerSectionDivs = True
, Pandoc.Options.writerTableOfContents = True
}
--------------------------------------------------------------------------------
main :: IO ()
main = hakyllWith config $ do
match "templates/*" $ compile templateCompiler
-- copy site icon to `favicon.ico`
match "images/favicon.ico" $ do
route (constRoute "favicon.ico")
compile copyFileCompiler
match "images/*" $ do
route idRoute
compile copyFileCompiler
match "scss/app.scss" $do
route $ gsubRoute "scss/" (const "css/") `composeRoutes` setExtension "css"
compile $ getResourceString
>>= withItemBody (unixFilter "sass" ["-s", "--scss", "--compass", "--style", "compressed"])
>>= return . fmap compressCss
-- copy humans.txt and robots.txt to web root
match (fromList ["humans.txt", "robots.txt"]) $ do
route idRoute
compile copyFileCompiler
-- Compile static pages to web root with Pandoc
match (fromList ["cv.md"]) $ do
route $ setExtension ""
compile $ pandocCompilerWith defaultHakyllReaderOptions pandocWriterOptions
>>= loadAndApplyTemplate "templates/base.html" defaultContext
>>= relativizeUrls
match "posts/*" $ do
route $ setExtension ""
compile $ pandocCompilerWith defaultHakyllReaderOptions pandocWriterOptions
>>= loadAndApplyTemplate "templates/post.html" postCtx
>>= loadAndApplyTemplate "templates/base.html" postCtx
>>= relativizeUrls
create ["archive"] $ do
route idRoute
compile $ do
let archiveCtx =
listField "posts" postCtx (mtimeOrdered =<< loadAll "posts/*") `mappend`
defaultContext
makeItem ""
>>= loadAndApplyTemplate "templates/archive.html" archiveCtx
>>= loadAndApplyTemplate "templates/base.html" archiveCtx
>>= relativizeUrls
match "index.html" $ do
route idRoute
compile $ do
posts <- loadAll "posts/*"
let indexCtx =
listField "posts" postCtx (return posts) `mappend`
defaultContext
getResourceBody
>>= applyAsTemplate indexCtx
>>= loadAndApplyTemplate "templates/base.html" indexCtx
>>= relativizeUrls
--------------------------------------------------------------------------------
postCtx :: Context String
postCtx =
modificationTimeField "mtime" "%a, %d %b %Y %H:%M:%S %Z" `mappend`
defaultContext
-- TODO: get title from Pandoc, perhaps w/ field :: String -> (Item a -> Compiler String) -> Context a
mtimeOrdered :: [Item a] -> Compiler [Item a]
mtimeOrdered items = do
itemsWithTime <- forM items $ \item -> do
mtime <- getMetadataField (itemIdentifier item) "mtime"
return (mtime,item)
return (map snd (sortBy (comparing fst) itemsWithTime))
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment