module Panda.View.Atom.Post where import Panda.Helper.Env hiding (name, title, date) import Prelude hiding ((.), (/), (^), id, span) import qualified Panda.Config.Global as G -- view import qualified Panda.View.Atom.Tag as Tag -- model import Panda.Model.Post -- render instance DataRenderer Post where render_data = entry -- instance helpers entry x = div_class "post" << [entry_title, entry_mark, entry_body] where entry_title = x.title_link entry_body = div_class "entry" << x.markup entry_mark = p ! [theclass "small"] << [ blog_date, blog_tags, blog_comments ].map (send_to x) title_link x = h2 << hotlink (entry_uri x) << x.title entry_uri x = G.root / ( uid x .id_to_resource ) blog_date x = toHtml $ x.date.formatCalendarTime defaultTimeLocale "%b %e, %Y" blog_tags x | x.tags.null = toHtml "" blog_tags x = " | " +++ "Published in " +++ x.tags.map Tag.tag_link .intersperse (", ".toHtml) blog_comments x | x.comment_size.is 0 = toHtml "" blog_comments x = " | " +++ hotlink ( entry_uri x / "#comments") << (x.comment_size.show ++ " Comments")