{-# LANGUAGE NoImplicitPrelude #-} module Bamboo.View.Atom.Post where import Bamboo.Helper.Env hiding (name, title) import Bamboo.Helper.StateHelper hiding (uri) -- view import qualified Bamboo.View.Atom.Tag as Tag -- model import Bamboo.Model.Post -- render instance DataRenderer Post where render_data = entry Full data RenderStyle = Summary | Full -- instance helpers entry 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 x entry_mark = p ! [theclass "small"] << [ post_date, post_tags, post_comments ].map (send_to x) show_content Summary x = x.markup_summary show_content Full x = x.markup -- post could also be a summary render_summary flag = if flag then entry Summary else render_data title_link x = h2 << hotlink (x.uri) << x.title post_date x = toHtml $ x.date.format_time "%b %e, %Y" post_tags x | x.tags.null = empty_html post_tags x = " | " +++ "Published in " +++ x.tags.map Tag.tag_link .intersperse (", ".toHtml) post_comments x | x.comment_size.is 0 = empty_html post_comments x = " | " +++ hotlink ( x.uri / "#comments") << (x.comment_size.show ++ " Comments")