{-# LANGUAGE FlexibleContexts, OverloadedStrings, RecordWildCards #-} {-# OPTIONS_GHC -F -pgmFtrhsx #-} module Theme where import Clckwrks import Clckwrks.Monad import Data.Text (Text) import HSP import Paths_clckwrks_theme_bootstrap (getDataDir) theme :: Theme theme = Theme { themeName = "bootstrap-theme" , _themeTemplate = pageTemplate , themeBlog = blog , themeDataDir = getDataDir } pageTemplate :: ( EmbedAsChild (ClckT ClckURL (ServerPartT IO)) headers , EmbedAsChild (ClckT ClckURL (ServerPartT IO)) body ) => Text -> headers -> body -> XMLGenT (ClckT ClckURL (ServerPartT IO)) XML pageTemplate ttl hdr bdy = <% ttl %> <% hdr %> <% googleAnalytics %>

<% ttl %>

<% bdy %> postsHTML :: XMLGenT (Clck ClckURL) XML postsHTML = do posts <- getPosts
    <% mapM postHTML posts %>
postHTML :: Page -> XMLGenT (Clck ClckURL) XML postHTML Page{..} =
  • <% pageTitle %>

    <% pageDate %> <% pageSrc %>

    permalink

  • blog :: XMLGenT (Clck ClckURL) XML blog = do ttl <- lift getBlogTitle pageTemplate ttl () $ <%>

    <% ttl %>

    <% postsHTML %>