module Panda.View.Theme.BluePrint.Post where -- env import Panda.Helper.Env import Prelude hiding ((.), (/), (^), id, span) import qualified Panda.Type.State as State -- model import Panda.Model.Post as Post import qualified Panda.Model.Comment as Comment -- view import Panda.View.Theme.BluePrint.Helper import qualified Panda.View.Theme.BluePrint.Comment as CommentV import Panda.View.Theme.BluePrint.Template.Template -- HTML -- render single entry entry x = div_class "post" << [entry_title, entry_mark, entry_body] where entry_title = x.title_link entry_body = div_class "entry" << x.Post.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.Post.title entry_uri x = "/" ++ Post.uid x .id_to_resource blog_date x = toHtml $ x.Post.date.formatCalendarTime defaultTimeLocale "%b %e, %Y" blog_tags x | x.tags.null = toHtml "" blog_tags x = " | " +++ "Published in " +++ x.tags.map 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") tag_link s = toHtml $ hotlink ("/tag/" ++ s ) << s -- entry view view state xs x = (x.entry +++ CommentV.list xs +++ CommentV.create x).page state -- list view list state = for_current_page p >>> map entry >>> (+++ nav p "/") >>> page state where p = state.State.pager