-------------------------------------------------------------------------------- {-# LANGUAGE OverloadedStrings #-} import Control.Applicative ((<$>)) import Data.Monoid ((<>),mappend,mconcat) import Hakyll import Hakyll.Convert.Blogger import Debug.Trace -------------------------------------------------------------------------------- main :: IO () main = hakyll $ do match "images/*" $ do route idRoute compile copyFileCompiler match "css/*" $ do route idRoute compile compressCssCompiler match (fromList ["about.markdown"]) $ do route $ setExtension "html" compile $ pandocCompiler >>= loadAndApplyTemplate "templates/default.html" defaultContext >>= relativizeUrls -- distilled <- match koweycodePattern $ compile bloggerCompiler -- tags0 <- buildTags "posts/*" (fromCapture "tags/*.html") tags <- buildTags koweycodePattern (fromCapture "tags/*.html") {- match "posts/*" $ do route $ setExtension "html" compile $ pandocCompiler >>= loadAndApplyTemplate "templates/post.html" (postCtx tags) >>= loadAndApplyTemplate "templates/default.html" (postCtx tags) >>= relativizeUrls -} match koweycodePattern $ do route $ setExtension "html" compile $ pandocCompiler -- TODO shouldn't be needed >>= loadAndApplyTemplate "templates/post.html" (postCtx tags) >>= loadAndApplyTemplate "templates/default.html" (postCtx tags) >>= relativizeUrls -- Post tags tagsRules tags $ \tag pattern -> do let title = "Posts tagged " ++ tag archiveCtx = archiveContext "Posts tagged" tags pattern -- Copied from posts, need to refactor route idRoute compile $ do list <- postList tags pattern recentFirst makeItem "" >>= loadAndApplyTemplate "templates/archive.html" archiveCtx >>= loadAndApplyTemplate "templates/default.html" defaultContext >>= relativizeUrls {- -- Create RSS feed as well version "rss" $ do route $ setExtension "xml" compile $ loadAllSnapshots pattern "content" >>= fmap (take 10) . recentFirst >>= renderAtom (feedConfiguration title) feedCtx -} let plainPattern = "posts/*" create ["archive.html"] $ do route idRoute compile $ do let archiveCtx = archiveContext "Archives" tags koweycodePattern makeItem "" >>= loadAndApplyTemplate "templates/archive.html" archiveCtx >>= loadAndApplyTemplate "templates/default.html" archiveCtx >>= relativizeUrls match "index.html" $ do route idRoute compile $ do let indexCtx = field "posts" $ \_ -> postList tags koweycodePattern (fmap (take 3) . recentFirst) getResourceBody >>= applyAsTemplate indexCtx >>= loadAndApplyTemplate "templates/default.html" (postCtx tags) >>= relativizeUrls match "templates/*" $ compile templateCompiler where koweycodePattern = "koweycode/**" archiveContext title tags pattern = field "posts" (const getList) `mappend` constField "title" title `mappend` defaultContext where getList = postList tags pattern recentFirst -------------------------------------------------------------------------------- {- postCtx :: Context String postCtx = dateField "date" "%e %B %Y" `mappend` defaultContext -} postCtx :: Tags -> Context String postCtx tags = mconcat [ modificationTimeField "mtime" "%U" , dateField "date" "%e %B %Y" , tagsField "tags" tags , defaultContext ] -------------------------------------------------------------------------------- postList :: Tags -> Pattern -> ([Item String] -> Compiler [Item String]) -> Compiler String postList tags pattern sortFilter = do posts <- sortFilter =<< loadAll pattern itemTpl <- loadBody "templates/post-item.html" applyTemplateList itemTpl (postCtx tags) posts {- postList :: ([Item String] -> [Item String]) -> Compiler String postList sortFilter = do posts1_ <- loadAll "posts/*" --posts2_ <- loadAll "koweycode/*/*/*" let posts1 = posts1_ posts2 = [] let posts = sortFilter (posts1 ++ posts2) itemTpl <- loadBody "templates/post-item.html" list <- applyTemplateList itemTpl postCtx posts return list -} {- oldPostList :: ([Item String] -> [Item String]) -> Compiler String oldPostList sortFilter = do posts <- sortFilter <$> loadAll "koweycode/*/*/*" itemTpl <- loadBody "templates/post-item.html" list <- applyTemplateList itemTpl postCtx posts return list -}