From 8152c250c54b6be6533eecf393d38c83b4c66348 Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Sun, 24 Jan 2016 09:25:11 +0000 Subject: Site redesign --- src/Site.hs | 19 ++++++++++++++----- 1 file changed, 14 insertions(+), 5 deletions(-) (limited to 'src') diff --git a/src/Site.hs b/src/Site.hs index 98a598f..c1e4854 100644 --- a/src/Site.hs +++ b/src/Site.hs @@ -9,13 +9,16 @@ import Data.Maybe (mapMaybe, fromMaybe) import Data.Map (Map) import qualified Data.Map as Map import qualified Data.Set as Set -import Data.List (take, reverse, nub, groupBy, concatMap) +import Data.List (take, reverse, nub, groupBy, concatMap, intersperse) import Data.Function (on) import Data.Default import Text.Pandoc import Text.Pandoc.Walk (query, walkM) import Text.Pandoc.Error import Control.Applicative (Alternative(..), Applicative(..)) +import Text.Blaze.Html (toHtml, toValue, (!)) +import qualified Text.Blaze.Html5 as H +import qualified Text.Blaze.Html5.Attributes as A import System.FilePath (takeBaseName, (), (<.>)) @@ -45,16 +48,20 @@ main = hakyllWith config $ do saveSnapshot "alignment" $ fmap snd item return $ fmap fst item + tags <- buildTags "posts/*" tagTranslation' >>= addTag "All Posts" "posts/*" + match "posts/*" $ do route $ setExtension ".html" compile $ do + let ctx = mconcat [ defaultContext + , dateField "published" "%F" + , tagsFieldWith getTags (\tag _ -> Just . H.li $ H.a ! A.href (toValue . toUrl $ "tags" tagTranslation tag <.> "html") $ toHtml tag) (mconcat . intersperse "\n") "tagList" tags + ] getResourceBody >>= saveSnapshot "content" pandocCompilerWithTransformM defaultHakyllReaderOptions defaultHakyllWriterOptions mathTransform - >>= loadAndApplyTemplate "templates/default.html" defaultContext + >>= loadAndApplyTemplate "templates/default.html" ctx >>= relativizeUrls - tags <- buildTags "posts/*" tagTranslation' >>= addTag "All Posts" "posts/*" - tagsRules tags $ \tag pattern -> do route idRoute compile $ do @@ -89,7 +96,9 @@ main = hakyllWith config $ do , defaultContext ] item <- getResourceBody - pandocCompilerWith def (def { writerEmailObfuscation = NoObfuscation }) + {-pandocCompilerWith def (def { writerEmailObfuscation = NoObfuscation }) + >>=-} + makeItem "" >>= loadAndApplyTemplate "templates/index.html" ctx >>= loadAndApplyTemplate "templates/default.html" ctx >>= relativizeUrls -- cgit v1.2.3