{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} ------------------------------------------------------------------------------- -- | -- Module : Yesod.Comments.Management -- Copyright : Patrick Brisbin -- License : as-is -- -- Maintainer : Patrick Brisbin -- Stability : unstable -- Portability : unportable -- -- This module allows for self-management of comments by any -- authenticating commenter on your site. -- -- The use, add a route like so: -- -- > /comments CommentsAdminR CommentsAdmin getCommentsAdmin -- -- Then place a link somewhere to @CommentsAdminR OverviewR@. -- -- The overview page will show all of the comments (grouped by thread) -- that the currently logged in user has left on the site along with -- links to view more details, edit the comment content, or delete the -- comment entirely. -- ------------------------------------------------------------------------------- module Yesod.Comments.Management ( CommentsAdmin , CommentsAdminRoute(..) , getCommentsAdmin ) where import Yesod import Yesod.Auth import Yesod.Comments.Core import Yesod.Goodies.Markdown import Control.Monad (forM, unless) import Data.List (nub, sort) import Data.Time (UTCTime, formatTime) import System.Locale (defaultTimeLocale, rfc822DateFormat) import Language.Haskell.TH.Syntax hiding (lift) data CommentsAdmin = CommentsAdmin getCommentsAdmin :: a -> CommentsAdmin getCommentsAdmin = const CommentsAdmin mkYesodSub "CommentsAdmin" [ ClassP ''YesodAuth [ VarT $ mkName "master" ] , ClassP ''YesodComments [ VarT $ mkName "master" ] ] [parseRoutes| / OverviewR GET /view/#ThreadId/#CommentId ViewR GET /edit/#ThreadId/#CommentId EditR GET POST /delete/#ThreadId/#CommentId DeleteR GET |] getOverviewR :: (YesodAuth m, YesodComments m) => GHandler CommentsAdmin m RepHtml getOverviewR = do _ <- requireAuthId threads <- getThreadedComments defaultLayout $ do setTitle "Comments administration" addStyling [whamlet|

Comments overview
$if null threads

No comments found. $else $forall thread <- threads ^{showThreadedComments thread} |] getViewR :: (YesodAuth m, YesodComments m) => ThreadId -> CommentId -> GHandler CommentsAdmin m RepHtml getViewR tid cid = withUserComment tid cid $ \comment -> defaultLayout $ do setTitle "View comment" addStyling [whamlet|

View comment
Thread: #{tid}
Comment Id: #{cid}
Source IP: #{ipAddress comment}
Time stamp: #{formatTimeStamp $ timeStamp comment}

Comment:

#{markdownToHtml $ content comment} ^{updateLinks comment} |] where formatTimeStamp :: UTCTime -> String -- todo: make my own format formatTimeStamp = formatTime defaultTimeLocale rfc822DateFormat getEditR :: (YesodAuth m, YesodComments m) => ThreadId -> CommentId -> GHandler CommentsAdmin m RepHtml getEditR tid cid = withUserComment tid cid $ \comment -> do tm <- getRouteToMaster ((res, form), enctype) <- runFormPost $ commentFormEdit comment defaultLayout $ do setTitle "Edit comment" handleFormEdit (tm OverviewR) res comment addStyling [whamlet|

Edit comment

Update comment
^{form}

Comments are parsed as pandoc-style markdown |] postEditR :: (YesodAuth m, YesodComments m) => ThreadId -> CommentId -> GHandler CommentsAdmin m RepHtml postEditR = getEditR getDeleteR :: (YesodAuth m, YesodComments m) => ThreadId -> CommentId -> GHandler CommentsAdmin m RepHtml getDeleteR tid cid = withUserComment tid cid $ \comment -> do tm <- getRouteToMaster deleteComment comment setMessage "comment deleted." redirect RedirectTemporary $ tm OverviewR getThreadedComments :: (YesodAuth m, YesodComments m) => GHandler s m [(ThreadId, [Comment])] getThreadedComments = do allComments <- loadComments Nothing allThreads <- forM allComments $ \comment -> do mine <- isCommentingUser comment return $ if mine then [threadId comment] else [] forM (sort . nub $ concat allThreads) $ \tid -> return (tid, filter ((== tid) . threadId) allComments) showThreadedComments :: (YesodAuth m, YesodComments m) => (ThreadId, [Comment]) -> GWidget CommentsAdmin m () showThreadedComments (tid, comments) = [whamlet|

#{tid} $forall comment <- comments ^{showThreadComment comment} |] where showThreadComment :: (YesodAuth m, YesodComments m) => Comment -> GWidget CommentsAdmin m () showThreadComment comment = do mine <- lift $ isCommentingUser comment [whamlet| $if mine
^{showCommentAuth comment} ^{updateLinks comment} $else