{-# LANGUAGE OverloadedStrings #-} module Archive where import System.Directory import qualified Data.Text as T import qualified Data.Text.IO as T import Site import Text.StringTemplate import Post import Constant archiveTemplate = do templates <- directoryGroup "templates" :: IO (STGroup T.Text) return $ maybe (newSTMP "generic.st not found") id (getStringTemplate "generic" templates) makeTableRow :: Post -> T.Text makeTableRow p = let a = T.append in "" `a` "" `a` (title p) `a` "" `a` "" `a` (date p) `a` "" `a` "" `a` (comment p) `a` "" `a` "" makeTable :: [Post] -> T.Text makeTable ps = let a = T.append in "" `a` "" `a` T.unlines (map makeTableRow ps) `a` "
TitleDateComment
" renderGenericArchive site template content = render $ setAttribute "site" site $ setAttribute "content" content template renderArchive = do posts <- getAllPosts template <- archiveTemplate site <- readSite return $ renderGenericArchive site template (makeTable $ reverse posts) writeArchive :: T.Text -> IO () writeArchive html = do let a = T.append mkdir $ sitePath ++ "archive/" T.writeFile (sitePath ++ "archive/index.html") html generateArchive = renderArchive >>= writeArchive >> putStrLn "Generated archive"