{-# LANGUAGE OverloadedStrings, RankNTypes, StandaloneDeriving, FlexibleInstances #-} import Hakyll import Data.Monoid (Monoid(..), mconcat, (<>)) import Control.Monad (liftM, forM_) import Data.Char (toLower, isSpace, isAlphaNum) 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.Function (on) import Data.Default import Text.Pandoc import Text.Pandoc.Walk (query) import Text.Pandoc.Error import Control.Applicative (Alternative(..), Applicative(..)) import qualified Crypto.Hash.SHA256 as SHA256 (hash) import qualified Data.ByteString.Char8 as CBS import Data.Hex import System.FilePath (takeBaseName, (), (<.>)) main :: IO () main = hakyllWith config $ do match "templates/*" $ compile templateCompiler match "css/*" $ do route idRoute compile copyFileCompiler match "posts/*" $ do route $ setExtension ".html" compile $ do getResourceBody >>= saveSnapshot "content" pandocCompiler >>= loadAndApplyTemplate "templates/default.html" defaultContext >>= relativizeUrls math <- getMath "posts/*" mathTranslation' forM_ math $ \(deps, mathStr) -> rulesExtraDependencies (map IdentifierDependency deps) $ create [mathTranslation' mathStr] $ do route idRoute compile $ do makeItem $ mathStr tags <- buildTags "posts/*" tagTranslation' >>= addTag "All Posts" "posts/*" tagsRules tags $ \tag pattern -> do route idRoute compile $ do let ctx = mconcat [ constField "title" tag , listField "posts" defaultContext $ chronological =<< loadAll pattern , constField "rss" $ "/rss" tagTranslation tag <.> "rss" , defaultContext ] makeItem "" >>= loadAndApplyTemplate "templates/post-list.html" ctx >>= loadAndApplyTemplate "templates/default.html" ctx >>= relativizeUrls let tags' = tags { tagsMakeId = fromFilePath . (\b -> "rss" b <.> "rss") . takeBaseName . toFilePath . tagsMakeId tags} tagsRules tags' $ \tag pattern -> do route idRoute compile $ do let feedCtx = mconcat [ bodyField "description" , defaultContext ] renderRss (feedConfig tag) feedCtx =<< loadAllSnapshots pattern "content" match "index.md" $ rulesExtraDependencies [tagsDependency tags] $ do route $ setExtension ".html" compile $ do let ctx = mconcat [ listField "tags" defaultContext $ mapM (\(k, _) -> renderTag k tags) $ tagsMap tags , constField "title" "Index" , constField "rss" "/rss/all-posts.rss" , defaultContext ] item <- getResourceBody pandocCompilerWith def (def { writerEmailObfuscation = NoObfuscation }) >>= loadAndApplyTemplate "templates/index.html" ctx >>= loadAndApplyTemplate "templates/default.html" ctx >>= relativizeUrls deriving instance Eq (Item String) feedConfig :: String -> FeedConfiguration feedConfig tagName = FeedConfiguration { feedTitle = "dirty-haskell.org: " ++ tagName , feedDescription = "dirty-haskell.org — A Blog." , feedAuthorName = "G. Kleen" , feedAuthorEmail = "blog@dirty-haskell.org" , feedRoot = "https://dirty-haskell.org" } renderTag :: String -- ^ Tag name -> Tags -> Compiler (Item String) renderTag tag tags = do ellipsisItem <- makeItem "" let ids = fromMaybe [] $ lookup tag $ tagsMap tags postCtx = mconcat [ listField "posts" (ellipsisContext ellipsisItem) $ liftM (withEllipsis ellipsisItem) $ chronological =<< mapM load ids , constField "title" tag , constField "rss" ("rss" tagTranslation tag <.> "rss") , constField "url" ("tags" tagTranslation tag <.> "html") , defaultContext ] makeItem "" >>= loadAndApplyTemplate "templates/post-list.html" postCtx >>= loadAndApplyTemplate "templates/tag.html" postCtx where ellipsisContext item = mconcat [ boolField "ellipsis" (== item) , defaultContext ] boolField name f = field name (\i -> if f i then pure (error $ unwords ["no string value for bool field:",name]) else empty) withEllipsis ellipsisItem xs | length xs > max = ellipsisItem : takeEnd (max - 1) xs | otherwise = xs takeEnd i = reverse . take i . reverse max = 4 tagTranslation' :: String -> Identifier tagTranslation' = fromCapture "tags/*.html" . tagTranslation tagTranslation :: String -> String tagTranslation = mapMaybe charTrans where charTrans c | isSpace c = Just '-' | isAlphaNum c = Just $ toLower c | otherwise = Nothing mathTranslation' :: String -> Identifier mathTranslation' = fromCapture "math/*.svg" . CBS.unpack . hex . SHA256.hash . CBS.pack addTag :: MonadMetadata m => String -> Pattern -> Tags -> m Tags addTag name pattern tags = do ids <- getMatches pattern return $ tags { tagsMap = tagsMap tags ++ [(name, ids)] } getMath :: Pattern -> (String -> Identifier) -> Rules [([Identifier], String)] getMath pattern makeId = do ids <- getMatches pattern mathStrs <- concat `liftM` mapM (\id -> map ((,) [id]) `liftM` getMath' (toFilePath' id)) ids return $ mergeGroups $ groupBy ((==) `on` snd) $ mathStrs where getMath' :: FilePath -> Rules [String] getMath' path = preprocess (query extractMath `liftM` readPandoc' path) extractMath :: Inline -> [String] extractMath (Math _ str) = [str] extractMath _ = [] mergeGroups :: [[([Identifier], String)]] -> [([Identifier], String)] mergeGroups = map mergeGroups' . filter (not . null) mergeGroups' :: [([Identifier], String)] -> ([Identifier], String) mergeGroups' xs@((_, str):_) = (concatMap fst xs, str) readPandoc' :: FilePath -> IO Pandoc readPandoc' path = readFile path >>= either fail return . result' where result' str = case result str of Left (ParseFailure err) -> Left $ "parse failed: " ++ err Left (ParsecError _ err) -> Left $ "parse failed: " ++ show err Right item' -> Right item' result str = reader defaultHakyllReaderOptions (fileType path) str reader ro t = case t of DocBook -> readDocBook ro Html -> readHtml ro LaTeX -> readLaTeX ro LiterateHaskell t' -> reader (addExt ro Ext_literate_haskell) t' Markdown -> readMarkdown ro MediaWiki -> readMediaWiki ro OrgMode -> readOrg ro Rst -> readRST ro Textile -> readTextile ro _ -> error $ "I don't know how to read a file of " ++ "the type " ++ show t ++ " for: " ++ path addExt ro e = ro {readerExtensions = Set.insert e $ readerExtensions ro} toFilePath' :: Identifier -> FilePath toFilePath' = (providerDirectory config ) . toFilePath config :: Configuration config = defaultConfiguration { providerDirectory = "provider" , deployCommand = "rsync -av --progress -c --delete-delay -m _site/ gkleen@surtr.yggdrasil.li:/var/www/dirty-haskell.org/" }