{-# OPTIONS_GHC -fno-warn-name-shadowing #-} {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} ------------------------------------------------------------------------------- -- | -- Module : Yesod.Comments.Management -- Copyright : Patrick Brisbin -- License : as-is -- -- Maintainer : Patrick Brisbin -- Stability : unstable -- Portability : unportable -- -- > /comments CommentsAdminR CommentsAdmin getCommentsAdmin -- ------------------------------------------------------------------------------- module Yesod.Comments.Management ( getCommentsAdmin , module Yesod.Comments.Management.Routes ) where import Yesod import Yesod.Auth import Yesod.Comments.Core import Yesod.Comments.Utils import Yesod.Comments.Form import Yesod.Comments.View import Yesod.Comments.Management.Routes import Control.Monad (forM, unless) import Data.List (sortBy, nub) import Data.Text (Text) import Data.Time (UTCTime) getCommentsAdmin :: a -> CommentsAdmin getCommentsAdmin = const CommentsAdmin instance YesodComments master => YesodSubDispatch CommentsAdmin (HandlerT master IO) where yesodSubDispatch = $(mkYesodSubDispatch resourcesCommentsAdmin) type Handler a = forall master. YesodComments master => HandlerT CommentsAdmin (HandlerT master IO) a getCommentsR :: Handler RepHtml getCommentsR = lift $ do comments <- getThreadedComments layout "Your comments" [whamlet| $forall (t, cs) <- comments

#{t}
^{showComments cs} |] getEditCommentR :: ThreadId -> CommentId -> Handler RepHtml getEditCommentR thread cid = do ud@(UserDetails _ name email) <- lift $ requireUserDetails -- TODO: Duplication with withUserComment comment <- lift $ do mcomment <- csGet commentStorage thread cid case mcomment of Just comment -> do _ <- requireAuthId mine <- isCommentingUser comment unless mine $ permissionDenied "you can only manage your own comments" return comment Nothing -> notFound ((res, form), enctype) <- lift $ runFormPost (commentForm thread ud (Just comment)) case res of FormSuccess cf -> do lift $ csUpdate commentStorage comment $ comment { cContent = formComment cf } setMessage "comment updated." redirect CommentsR _ -> return () -- TODO: Duplication with runFormWith lift $ layout "Edit comment" [whamlet|