{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE FlexibleContexts #-} ------------------------------------------------------------------------------- -- | -- Module : Yesod.Comments.View -- Copyright : (c) Patrick Brisbin 2010 -- License : as-is -- -- Maintainer : pbrisbin@gmail.com -- Stability : unstable -- Portability : unportable -- ------------------------------------------------------------------------------- module Yesod.Comments.View ( showComments , showComment ) where import Yesod import Yesod.Comments.Core import Yesod.Comments.Utils import Yesod.Markdown import Data.Time.Format.Human import Data.Monoid (mempty) showComments :: YesodComments m => [Comment] -> WidgetT m IO () showComments comments = [whamlet|
$if not $ null comments

#{helper $ length comments}: $forall comment <- comments ^{showComment comment} |] where -- pluralize comments helper :: Int -> String helper 0 = "no comments" helper 1 = "1 comment" helper n = show n ++ " comments" showComment :: YesodComments m => Comment -> WidgetT m IO () showComment comment = do mine <- handlerToWidget $ isCommentingUser comment commentTimestamp <- handlerToWidget . liftIO . humanReadableTime $ cTimeStamp comment UserDetails _ name email <- handlerToWidget $ commentUserDetails comment let anchor = "comment_" ++ show (commentId comment) [whamlet|

#{commentTimestamp} , #{name} wrote:

#{markdownToHtml $ cContent comment} $if mine