module Panda.View.Theme.BluePrint.Comment where import Panda.Helper.Env hiding (body, date) import Prelude hiding ((.), (/), (^), id, span) import qualified Panda.Type.State as State import Panda.Model.Comment import qualified Panda.Model.Post as Post -- view import Panda.View.Theme.BluePrint.Helper import Panda.View.Theme.BluePrint.Template.Template list [] = [] list xs = [ h2 ! [id "comments"] << "Responses" , olist ! [theclass "commentlist" ] << xs.zip (cycle ["comments-alt", ""]).map (splash entry) ] entry alt x = li ! [theclass alt] << [ 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" -- create = spaceHtml create post = [ h2 ! [id "respond"] << "Leave a Response" , gui "/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" (post.Post.uid) , 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)] ]