module Panda.View.Atom.Comment where
  
import Panda.Helper.Env hiding (title)
import Prelude hiding ((.), (/), (^), id, span)
import qualified Panda.Config.Global as G
import Panda.Helper.StateHelper
import Panda.Type.State hiding (uid)

-- 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  
  [ gravatar
  , cite << a
  , toHtml " says:"
  , br
  , p ! [theclass "small"] << comment_date x
  , x.markup
  ]
  where
    a = if x.author_link.null then x.author.toHtml else toHtml $ hotlink (x.author_link) << x.author
    gravatar = thediv ! [theclass "gravatar"] << image ! [src (gravatar_link x)]

comment_date x = toHtml $ x.date.format_date "%b %e, %Y at %I:%M %p"


-- form
human_test_question state = ["What", "is", state.show_left, state.show_op, state.show_right, "?"] .join " "

create state x = toHtml
  [ h2 ! [id "respond"] << "Leave a Response"
  , gui (G.root / "comment/create") ! [id "commentform"] <<
    [ field Author 22 1 "Name (required)"
    , field AuthorEmail 22 2 "Email (hidden)"
    , field AuthorLink 22 3 "Website"
    , field HumanHack 22 4 (human_test_question state)
    , empty_field
    , hidden_field LeftNumber (state.show_left)
    , hidden_field RightNumber (state.show_right)
    , hidden_field Operator (state.show_op)
    , p << hidden (show_data PostId) (x.uid.uid_to_post_id)
    , p << textarea ! [name (show_data Body), id "comment", cols "10", rows "20", strAttr "tabindex" "5"] << ""
    , p << submit "submit" "Submit Comment" ! [strAttr "tabindex" "6"]
    ]
  ]

field_with_value v x' s t m = p <<
  [ label ! [thefor x] << small << m
  , br 
  , textfield x ! [size (s.show), strAttr "tabindex" (t.show), value v]
  ]
  where x = x'.show_data

field x s t m = field_with_value "" x s t m

hidden_field x m = hidden_field_with_value m x m
hidden_field_with_value v x m = thespan ! [ thestyle "display: none;" ] << field_with_value v x 22 10 m

empty_field = hidden_field_with_value "" EmptyField "Leave this field empty:"