{-# LANGUAGE NoImplicitPrelude #-} module Bamboo.Theme.Blueprint.Atom.Post where import Bamboo.Helper.StateHelper hiding (uri) import Bamboo.Model.Post import Bamboo.Theme.Blueprint.Env hiding (name, style) import qualified Bamboo.Theme.Blueprint.Atom.Tag as Tag data RenderStyle = Summary | Full entry' :: State -> RenderStyle -> Post -> Html entry' s style x = div_class "post" << [entry_title, entry_mark, entry_body] where entry_title = title_link entry_body = div_class "entry" << show_content style entry_mark = p ! [theclass "small"] << [ post_date, post_tags, post_comments ] show_content Summary = x.markup_summary show_content Full = x.markup title_link = h2 << hotlink (s.env.slashed_script_name / x.uri) << x.title post_date = toHtml $ x.date.format_time "%b %e, %Y" post_tags = if x.tags.null then empty_html else " | " +++ "Published in " +++ x.tags.map (Tag.tag_link s) .intersperse (", ".toHtml) post_comments = if x.comment_size.is 0 then empty_html else " | " +++ hotlink ( x.uri / "#comments") << (x.comment_size.show ++ " Comments") entry :: State -> Post -> Html entry s = render_summary s (s.config.summary_for_root) render_summary :: State -> Bool -> Post -> Html render_summary s t = if t then entry' s Summary else entry' s Full