2016-05-20 01:58:23 +09:00
|
|
|
{- This file is part of Vervis.
|
|
|
|
-
|
2019-03-16 01:36:02 +09:00
|
|
|
- Written in 2016, 2019 by fr33domlover <fr33domlover@riseup.net>.
|
2016-05-20 01:58:23 +09:00
|
|
|
-
|
|
|
|
- ♡ Copying is an act of love. Please copy, reuse and share.
|
|
|
|
-
|
|
|
|
- The author(s) have dedicated all copyright and related and neighboring
|
|
|
|
- rights to this software to the public domain worldwide. This software is
|
|
|
|
- distributed without any warranty.
|
|
|
|
-
|
|
|
|
- You should have received a copy of the CC0 Public Domain Dedication along
|
|
|
|
- with this software. If not, see
|
|
|
|
- <http://creativecommons.org/publicdomain/zero/1.0/>.
|
|
|
|
-}
|
|
|
|
|
|
|
|
module Vervis.Handler.Discussion
|
|
|
|
( getDiscussion
|
2019-03-16 01:36:02 +09:00
|
|
|
, getDiscussionMessage
|
2016-05-22 05:01:31 +09:00
|
|
|
, getTopReply
|
|
|
|
, postTopReply
|
2016-05-20 07:07:25 +09:00
|
|
|
, getReply
|
|
|
|
, postReply
|
2016-05-20 01:58:23 +09:00
|
|
|
)
|
|
|
|
where
|
|
|
|
|
|
|
|
import Prelude
|
|
|
|
|
2019-03-16 01:36:02 +09:00
|
|
|
import Control.Monad
|
2016-05-20 01:58:23 +09:00
|
|
|
import Control.Monad.IO.Class (liftIO)
|
2019-03-23 05:46:42 +09:00
|
|
|
import Data.Maybe
|
2016-05-20 01:58:23 +09:00
|
|
|
import Data.Time.Clock (getCurrentTime)
|
2016-05-20 07:07:25 +09:00
|
|
|
import Database.Persist
|
2019-03-23 05:46:42 +09:00
|
|
|
import Database.Persist.Sql
|
|
|
|
import Data.Traversable
|
2016-05-20 01:58:23 +09:00
|
|
|
import Text.Blaze.Html (Html)
|
2016-05-20 07:07:25 +09:00
|
|
|
import Yesod.Auth (requireAuthId)
|
2019-03-23 05:46:42 +09:00
|
|
|
import Yesod.Core
|
2019-03-16 01:36:02 +09:00
|
|
|
import Yesod.Core.Handler
|
2016-05-20 07:07:25 +09:00
|
|
|
import Yesod.Form.Functions (runFormPost)
|
|
|
|
import Yesod.Form.Types (FormResult (..))
|
2016-05-20 01:58:23 +09:00
|
|
|
import Yesod.Persist.Core (runDB, get404, getBy404)
|
|
|
|
|
2019-03-20 17:07:37 +09:00
|
|
|
import Network.FedURI
|
2019-03-23 05:46:42 +09:00
|
|
|
import Web.ActivityPub
|
|
|
|
import Yesod.FedURI
|
2019-03-29 12:25:32 +09:00
|
|
|
import Yesod.Hashids
|
2019-03-23 05:46:42 +09:00
|
|
|
|
|
|
|
import Database.Persist.Local
|
|
|
|
import Yesod.Persist.Local
|
2019-03-20 17:07:37 +09:00
|
|
|
|
|
|
|
import Vervis.Discussion
|
2016-05-20 07:07:25 +09:00
|
|
|
import Vervis.Form.Discussion
|
2019-03-23 05:46:42 +09:00
|
|
|
import Vervis.Foundation
|
2016-05-20 01:58:23 +09:00
|
|
|
import Vervis.Model
|
2019-03-23 05:46:42 +09:00
|
|
|
import Vervis.Model.Ident
|
|
|
|
import Vervis.Settings
|
2016-05-20 01:58:23 +09:00
|
|
|
import Vervis.Widget.Discussion
|
|
|
|
|
2016-05-22 06:27:12 +09:00
|
|
|
getDiscussion
|
2019-03-16 01:36:02 +09:00
|
|
|
:: (MessageId -> Route App)
|
|
|
|
-> Route App
|
|
|
|
-> AppDB DiscussionId
|
|
|
|
-> Handler Html
|
2016-05-22 06:27:12 +09:00
|
|
|
getDiscussion reply topic getdid =
|
|
|
|
defaultLayout $ discussionW getdid topic reply
|
2016-05-20 01:58:23 +09:00
|
|
|
|
2019-03-20 17:07:37 +09:00
|
|
|
getNode :: AppDB DiscussionId -> MessageId -> AppDB MessageTreeNode
|
|
|
|
getNode getdid mid = do
|
|
|
|
did <- getdid
|
|
|
|
m <- get404 mid
|
|
|
|
unless (messageRoot m == did) notFound
|
|
|
|
mlocal <- getBy $ UniqueLocalMessage mid
|
|
|
|
mremote <- getBy $ UniqueRemoteMessage mid
|
|
|
|
author <- case (mlocal, mremote) of
|
|
|
|
(Nothing, Nothing) -> fail "Message with no author"
|
|
|
|
(Just _, Just _) -> fail "Message used as both local and remote"
|
|
|
|
(Just (Entity lmid lm), Nothing) -> do
|
|
|
|
p <- getJust $ localMessageAuthor lm
|
|
|
|
s <- getJust $ personIdent p
|
|
|
|
return $ MessageTreeNodeLocal lmid s
|
|
|
|
(Nothing, Just (Entity _rmid rm)) -> do
|
|
|
|
rs <- getJust $ remoteMessageAuthor rm
|
2019-04-12 09:56:27 +09:00
|
|
|
i <- getJust $ remoteActorInstance rs
|
2019-03-20 17:07:37 +09:00
|
|
|
return $ MessageTreeNodeRemote $
|
2019-04-12 09:56:27 +09:00
|
|
|
l2f (instanceHost i) (remoteActorIdent rs)
|
2019-03-20 17:07:37 +09:00
|
|
|
return $ MessageTreeNode mid m author
|
|
|
|
|
2019-03-23 05:46:42 +09:00
|
|
|
{-
|
2019-03-22 04:06:52 +09:00
|
|
|
getNodeL :: AppDB DiscussionId -> LocalMessageId -> AppDB MessageTreeNode
|
|
|
|
getNodeL getdid lmid = do
|
|
|
|
did <- getdid
|
|
|
|
lm <- get404 lmid
|
|
|
|
let mid = localMessageRest lm
|
|
|
|
m <- getJust mid
|
|
|
|
unless (messageRoot m == did) notFound
|
|
|
|
p <- getJust $ localMessageAuthor lm
|
|
|
|
s <- getJust $ personIdent p
|
|
|
|
return $ MessageTreeNode mid m $ MessageTreeNodeLocal lmid s
|
2019-03-23 05:46:42 +09:00
|
|
|
-}
|
2019-03-22 04:06:52 +09:00
|
|
|
|
2019-03-23 05:46:42 +09:00
|
|
|
getDiscussionMessage :: ShrIdent -> LocalMessageId -> Handler TypedContent
|
|
|
|
getDiscussionMessage shr lmid = selectRep $ provideAP $ runDB $ do
|
|
|
|
sid <- getKeyBy404 $ UniqueSharer shr
|
|
|
|
pid <- getKeyBy404 $ UniquePersonIdent sid
|
|
|
|
lm <- get404 lmid
|
|
|
|
unless (localMessageAuthor lm == pid) notFound
|
|
|
|
m <- getJust $ localMessageRest lm
|
|
|
|
route2fed <- getEncodeRouteFed
|
2019-04-11 22:26:57 +09:00
|
|
|
uContext <- do
|
2019-03-23 05:46:42 +09:00
|
|
|
let did = messageRoot m
|
|
|
|
mt <- getValBy $ UniqueTicketDiscussion did
|
|
|
|
mrd <- getValBy $ UniqueRemoteDiscussion did
|
|
|
|
case (mt, mrd) of
|
|
|
|
(Nothing, Nothing) -> fail $ "DiscussionId #" ++ show did ++ " has no context"
|
|
|
|
(Just _, Just _) -> fail $ "DiscussionId #" ++ show did ++ " has both ticket and remote contexts"
|
|
|
|
(Just t, Nothing) -> do
|
|
|
|
j <- getJust $ ticketProject t
|
|
|
|
s <- getJust $ projectSharer j
|
2019-03-23 11:57:34 +09:00
|
|
|
let shr = sharerIdent s
|
|
|
|
prj = projectIdent j
|
2019-04-11 22:26:57 +09:00
|
|
|
return $ route2fed $ TicketR shr prj $ ticketNumber t
|
2019-03-23 05:46:42 +09:00
|
|
|
(Nothing, Just rd) -> do
|
2019-04-11 22:26:57 +09:00
|
|
|
i <- getJust $ remoteDiscussionInstance rd
|
|
|
|
return $ l2f (instanceHost i) (remoteDiscussionIdent rd)
|
2019-03-23 05:46:42 +09:00
|
|
|
muParent <- for (messageParent m) $ \ midParent -> do
|
|
|
|
mlocal <- getBy $ UniqueLocalMessage midParent
|
|
|
|
mremote <- getValBy $ UniqueRemoteMessage midParent
|
|
|
|
case (mlocal, mremote) of
|
|
|
|
(Nothing, Nothing) -> fail "Message with no author"
|
|
|
|
(Just _, Just _) -> fail "Message used as both local and remote"
|
|
|
|
(Just (Entity lmidParent lmParent), Nothing) -> do
|
|
|
|
p <- getJust $ localMessageAuthor lmParent
|
|
|
|
s <- getJust $ personIdent p
|
2019-03-29 12:25:32 +09:00
|
|
|
lmhidParent <- encodeKeyHashid lmidParent
|
2019-03-23 05:46:42 +09:00
|
|
|
return $ route2fed $ MessageR (sharerIdent s) lmhidParent
|
|
|
|
(Nothing, Just rmParent) -> do
|
|
|
|
rs <- getJust $ remoteMessageAuthor rmParent
|
2019-04-12 09:56:27 +09:00
|
|
|
i <- getJust $ remoteActorInstance rs
|
|
|
|
return $ l2f (instanceHost i) (remoteActorIdent rs)
|
2019-03-23 05:46:42 +09:00
|
|
|
|
|
|
|
host <- getsYesod $ appInstanceHost . appSettings
|
|
|
|
route2local <- getEncodeRouteLocal
|
2019-03-29 12:25:32 +09:00
|
|
|
lmhid <- encodeKeyHashid lmid
|
2019-03-23 05:46:42 +09:00
|
|
|
return $ Doc host Note
|
2019-03-23 11:05:30 +09:00
|
|
|
{ noteId = Just $ route2local $ MessageR shr lmhid
|
2019-03-23 05:46:42 +09:00
|
|
|
, noteAttrib = route2local $ SharerR shr
|
2019-04-11 22:26:57 +09:00
|
|
|
, noteAudience = error "TODO noteAudience"
|
2019-03-23 05:46:42 +09:00
|
|
|
, noteReplyTo = Just $ fromMaybe uContext muParent
|
|
|
|
, noteContext = Just uContext
|
|
|
|
, notePublished = Just $ messageCreated m
|
|
|
|
, noteContent = messageContent m
|
|
|
|
}
|
2016-05-20 07:07:25 +09:00
|
|
|
|
2016-05-22 05:01:31 +09:00
|
|
|
getTopReply :: Route App -> Handler Html
|
|
|
|
getTopReply replyP = do
|
|
|
|
((_result, widget), enctype) <- runFormPost newMessageForm
|
|
|
|
defaultLayout $(widgetFile "discussion/top-reply")
|
|
|
|
|
|
|
|
postTopReply
|
|
|
|
:: Route App
|
2019-03-20 17:07:37 +09:00
|
|
|
-> (LocalMessageId -> Route App)
|
2016-05-22 05:01:31 +09:00
|
|
|
-> AppDB DiscussionId
|
|
|
|
-> Handler Html
|
|
|
|
postTopReply replyP after getdid = do
|
|
|
|
((result, widget), enctype) <- runFormPost newMessageForm
|
|
|
|
now <- liftIO getCurrentTime
|
|
|
|
case result of
|
|
|
|
FormSuccess nm -> do
|
|
|
|
author <- requireAuthId
|
|
|
|
mnum <- runDB $ do
|
|
|
|
did <- getdid
|
2019-03-20 17:07:37 +09:00
|
|
|
mid <- insert Message
|
|
|
|
{ messageCreated = now
|
|
|
|
, messageContent = nmContent nm
|
|
|
|
, messageParent = Nothing
|
|
|
|
, messageRoot = did
|
|
|
|
}
|
|
|
|
lmid <- insert LocalMessage
|
2019-03-29 06:08:30 +09:00
|
|
|
{ localMessageAuthor = author
|
|
|
|
, localMessageRest = mid
|
|
|
|
, localMessageUnlinkedParent = Nothing
|
2019-03-20 17:07:37 +09:00
|
|
|
}
|
|
|
|
return lmid
|
2016-05-22 05:01:31 +09:00
|
|
|
setMessage "Message submitted."
|
|
|
|
redirect $ after mnum
|
|
|
|
FormMissing -> do
|
|
|
|
setMessage "Field(s) missing."
|
|
|
|
defaultLayout $(widgetFile "discussion/top-reply")
|
|
|
|
FormFailure _l -> do
|
|
|
|
setMessage "Message submission failed, see errors below."
|
|
|
|
defaultLayout $(widgetFile "discussion/top-reply")
|
|
|
|
|
2016-05-20 07:07:25 +09:00
|
|
|
getReply
|
2019-03-16 01:36:02 +09:00
|
|
|
:: (MessageId -> Route App)
|
|
|
|
-> (MessageId -> Route App)
|
2016-05-20 07:40:54 +09:00
|
|
|
-> AppDB DiscussionId
|
2019-03-16 01:36:02 +09:00
|
|
|
-> MessageId
|
2016-05-20 07:07:25 +09:00
|
|
|
-> Handler Html
|
2019-03-16 01:36:02 +09:00
|
|
|
getReply replyG replyP getdid mid = do
|
2019-03-20 17:07:37 +09:00
|
|
|
mtn <- runDB $ getNode getdid mid
|
2016-05-20 07:07:25 +09:00
|
|
|
now <- liftIO getCurrentTime
|
|
|
|
((_result, widget), enctype) <- runFormPost newMessageForm
|
|
|
|
defaultLayout $(widgetFile "discussion/reply")
|
|
|
|
|
|
|
|
postReply
|
2019-03-16 01:36:02 +09:00
|
|
|
:: (MessageId -> Route App)
|
|
|
|
-> (MessageId -> Route App)
|
2019-03-20 17:07:37 +09:00
|
|
|
-> (LocalMessageId -> Route App)
|
2016-05-20 07:40:54 +09:00
|
|
|
-> AppDB DiscussionId
|
2019-03-16 01:36:02 +09:00
|
|
|
-> MessageId
|
2016-05-20 07:07:25 +09:00
|
|
|
-> Handler Html
|
2019-03-16 01:36:02 +09:00
|
|
|
postReply replyG replyP after getdid mid = do
|
2016-05-20 07:07:25 +09:00
|
|
|
((result, widget), enctype) <- runFormPost newMessageForm
|
|
|
|
now <- liftIO getCurrentTime
|
|
|
|
case result of
|
|
|
|
FormSuccess nm -> do
|
|
|
|
author <- requireAuthId
|
2019-03-16 01:36:02 +09:00
|
|
|
msgid <- runDB $ do
|
2016-05-20 07:40:54 +09:00
|
|
|
did <- getdid
|
2019-03-16 01:36:02 +09:00
|
|
|
parent <- do
|
|
|
|
message <- get404 mid
|
|
|
|
unless (messageRoot message == did) notFound
|
|
|
|
return mid
|
2019-03-20 17:07:37 +09:00
|
|
|
mid <- insert Message
|
|
|
|
{ messageCreated = now
|
|
|
|
, messageContent = nmContent nm
|
|
|
|
, messageParent = Just parent
|
|
|
|
, messageRoot = did
|
|
|
|
}
|
|
|
|
lmid <- insert LocalMessage
|
2019-03-29 06:08:30 +09:00
|
|
|
{ localMessageAuthor = author
|
|
|
|
, localMessageRest = mid
|
|
|
|
, localMessageUnlinkedParent = Nothing
|
2019-03-20 17:07:37 +09:00
|
|
|
}
|
|
|
|
return lmid
|
2016-05-20 07:07:25 +09:00
|
|
|
setMessage "Message submitted."
|
2019-03-16 01:36:02 +09:00
|
|
|
redirect $ after msgid
|
2016-05-20 07:07:25 +09:00
|
|
|
FormMissing -> do
|
|
|
|
setMessage "Field(s) missing."
|
2019-03-20 17:07:37 +09:00
|
|
|
mtn <- runDB $ getNode getdid mid
|
2016-05-20 07:07:25 +09:00
|
|
|
defaultLayout $(widgetFile "discussion/reply")
|
|
|
|
FormFailure _l -> do
|
|
|
|
setMessage "Message submission failed, see errors below."
|
2019-03-20 17:07:37 +09:00
|
|
|
mtn <- runDB $ getNode getdid mid
|
2016-05-20 07:07:25 +09:00
|
|
|
defaultLayout $(widgetFile "discussion/reply")
|