{-# LANGUAGE RecordWildCards #-} {-# OPTIONS_GHC -F -pgmFtrhsx #-} module Clckwrks.Page.BlogPage where import Clckwrks import Clckwrks.Page.API import Clckwrks.Page.Monad import Clckwrks.Page.Types import Clckwrks.Page.URL import Control.Monad.State (get) postsHTML :: XMLGenT PageM XML postsHTML = do posts <- getPosts
    <% mapM postHTML posts %>
postHTML :: Page -> XMLGenT PageM XML postHTML Page{..} =
  • <% pageTitle %>

    <% pageDate %> <% (markupToContent pageSrc) :: PageM Content %>

    permalink

  • blog :: PageM Response blog = do ttl <- getBlogTitle cs <- get bdy <- unXMLGenT $
    <% postsHTML %>
    clckT2PageT $ themeTemplate (plugins cs) ttl () bdy