{-# LANGUAGE NoImplicitPrelude #-} module Bamboo.View.Atom.Post where import Bamboo.Helper.StateHelper hiding (uri) import Bamboo.Model.Post import Bamboo.View.Env hiding (name, title, style) import qualified Bamboo.View.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 = x.title_link entry_body = div_class "entry" << show_content style entry_mark = p ! [theclass "small"] << [ post_date, post_tags, post_comments ].map (send_to x) show_content Summary = x.markup_summary show_content Full = x.markup title_link y = h2 << hotlink (y.uri) << y.title post_date y = toHtml $ y.date.format_time "%b %e, %Y" post_tags y | y.tags.null = empty_html post_tags y = " | " +++ "Published in " +++ y.tags.map (Tag.tag_link s) .intersperse (", ".toHtml) post_comments y | y.comment_size.is 0 = empty_html post_comments y = " | " +++ hotlink ( y.uri / "#comments") << (y.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