module Panda.View.Atom.Comment where import Panda.Helper.Env hiding (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.Comment hiding (create) -- render instance DataRenderer Comment where render_data = entry entry x = toHtml [ cite << a , toHtml " says:" , br , p ! [theclass "small"] << comment_date x , x.markup ] where a = if x.url.null then x.author.toHtml else toHtml $ hotlink (x.url) << x.author comment_date x = toHtml $ x.date.formatCalendarTime defaultTimeLocale "%b %e, %Y at %I:%M %p" -- form instance FormRenderer Comment where render_form = create create x = toHtml [ h2 ! [id "respond"] << "Leave a Response" , gui (G.root / "comment/create") ! [id "commentform"] << [ field "author" 22 1 "Name (required)" , field "url" 22 2 "Website" , field "human-hack" 22 3 "What is 5 + 5 ?" , p << hidden "post_id" (x.uid.uid_to_post_id) , p << textarea ! [name "comment", id "comment", cols "10", rows "20", strAttr "tabindex" "4"] << "" , p << submit "submit" "Submit Comment" ! [strAttr "tabindex" "5"] ] ] field x s t m = p << [ label ! [thefor x] << small << m , br , textfield x ! [size (s.show), strAttr "tabindex" (t.show)] ]