2019-01-19 10:56:50 +09:00
|
|
|
{- This file is part of Vervis.
|
|
|
|
-
|
|
|
|
- Written in 2019 by fr33domlover <fr33domlover@riseup.net>.
|
|
|
|
-
|
|
|
|
- ♡ 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.Inbox
|
|
|
|
( getInboxR
|
|
|
|
, postInboxR
|
2019-03-22 14:17:54 +09:00
|
|
|
, getPublishR
|
2019-01-22 00:54:57 +09:00
|
|
|
, getOutboxR
|
2019-03-29 06:08:30 +09:00
|
|
|
, getOutboxItemR
|
2019-01-22 00:54:57 +09:00
|
|
|
, postOutboxR
|
2019-02-07 19:34:33 +09:00
|
|
|
, getActorKey1R
|
|
|
|
, getActorKey2R
|
2019-01-19 10:56:50 +09:00
|
|
|
)
|
|
|
|
where
|
|
|
|
|
|
|
|
import Prelude
|
|
|
|
|
|
|
|
import Control.Applicative ((<|>))
|
|
|
|
import Control.Concurrent.STM.TVar (readTVarIO, modifyTVar')
|
|
|
|
import Control.Exception (displayException)
|
2019-03-10 15:42:03 +09:00
|
|
|
import Control.Monad
|
2019-01-19 10:56:50 +09:00
|
|
|
import Control.Monad.IO.Class (liftIO)
|
2019-03-22 07:57:15 +09:00
|
|
|
import Control.Monad.Logger.CallStack
|
2019-01-19 10:56:50 +09:00
|
|
|
import Control.Monad.STM (atomically)
|
2019-03-10 15:42:03 +09:00
|
|
|
import Control.Monad.Trans.Except
|
2019-02-22 08:59:53 +09:00
|
|
|
import Control.Monad.Trans.Maybe
|
2019-01-19 10:56:50 +09:00
|
|
|
import Crypto.Error (CryptoFailable (..))
|
|
|
|
import Crypto.PubKey.Ed25519 (publicKey, signature, verify)
|
2019-01-22 00:54:57 +09:00
|
|
|
import Data.Aeson
|
2019-01-19 10:56:50 +09:00
|
|
|
import Data.Bifunctor (first, second)
|
2019-02-15 08:27:40 +09:00
|
|
|
import Data.Foldable (for_)
|
2019-01-19 10:56:50 +09:00
|
|
|
import Data.HashMap.Strict (HashMap)
|
2019-01-22 00:54:57 +09:00
|
|
|
import Data.List.NonEmpty (NonEmpty (..))
|
2019-04-19 12:14:12 +09:00
|
|
|
import Data.Maybe
|
2019-02-07 19:34:33 +09:00
|
|
|
import Data.PEM (PEM (..))
|
2019-01-19 10:56:50 +09:00
|
|
|
import Data.Text (Text)
|
2019-01-22 00:54:57 +09:00
|
|
|
import Data.Text.Encoding (encodeUtf8)
|
2019-01-19 10:56:50 +09:00
|
|
|
import Data.Text.Lazy.Encoding (decodeUtf8)
|
|
|
|
import Data.Time.Clock (UTCTime, getCurrentTime)
|
|
|
|
import Data.Time.Interval (TimeInterval, toTimeUnit)
|
|
|
|
import Data.Time.Units (Second)
|
2019-02-15 08:27:40 +09:00
|
|
|
import Database.Persist (Entity (..), getBy, insertBy, insert_)
|
2019-01-19 10:56:50 +09:00
|
|
|
import Network.HTTP.Client (Manager, HttpException, requestFromURI)
|
2019-01-19 11:57:58 +09:00
|
|
|
import Network.HTTP.Simple (httpJSONEither, getResponseBody, setRequestManager, addRequestHeader)
|
2019-01-22 00:54:57 +09:00
|
|
|
import Network.HTTP.Types.Header (hDate, hHost)
|
2019-01-19 10:56:50 +09:00
|
|
|
import Text.Blaze.Html (Html)
|
2019-02-12 20:53:24 +09:00
|
|
|
import Text.Shakespeare.I18N (RenderMessage)
|
2019-01-19 10:56:50 +09:00
|
|
|
import UnliftIO.Exception (try)
|
2019-01-22 00:54:57 +09:00
|
|
|
import Yesod.Auth (requireAuth)
|
2019-02-12 20:53:24 +09:00
|
|
|
import Yesod.Core (ContentType, defaultLayout, whamlet, toHtml, HandlerSite)
|
2019-02-07 19:34:33 +09:00
|
|
|
import Yesod.Core.Content (TypedContent)
|
2019-01-19 10:56:50 +09:00
|
|
|
import Yesod.Core.Json (requireJsonBody)
|
|
|
|
import Yesod.Core.Handler
|
2019-02-12 20:53:24 +09:00
|
|
|
import Yesod.Form.Fields (Textarea (..), textField, textareaField)
|
|
|
|
import Yesod.Form.Functions
|
|
|
|
import Yesod.Form.Types
|
2019-01-22 00:54:57 +09:00
|
|
|
import Yesod.Persist.Core (runDB, get404)
|
2019-01-19 10:56:50 +09:00
|
|
|
|
|
|
|
import qualified Data.ByteString.Char8 as BC (unpack)
|
|
|
|
import qualified Data.CaseInsensitive as CI (mk)
|
2019-01-22 00:54:57 +09:00
|
|
|
import qualified Data.HashMap.Strict as M (lookup, insert, adjust, fromList)
|
2019-03-05 00:47:22 +09:00
|
|
|
import qualified Data.Text as T (pack, unpack, concat)
|
2019-01-22 00:54:57 +09:00
|
|
|
import qualified Data.Text.Lazy as TL (toStrict)
|
2019-03-14 11:30:36 +09:00
|
|
|
import qualified Data.Vector as V
|
2019-01-19 10:56:50 +09:00
|
|
|
import qualified Network.Wai as W (requestMethod, rawPathInfo, requestHeaders)
|
|
|
|
|
|
|
|
import Network.HTTP.Signature hiding (Algorithm (..))
|
2019-01-19 13:21:56 +09:00
|
|
|
import Yesod.HttpSignature (verifyRequestSignature)
|
2019-01-19 10:56:50 +09:00
|
|
|
|
|
|
|
import qualified Network.HTTP.Signature as S (Algorithm (..))
|
|
|
|
|
2019-02-12 20:53:24 +09:00
|
|
|
import Data.Aeson.Encode.Pretty.ToEncoding
|
2019-03-22 07:57:15 +09:00
|
|
|
import Data.Aeson.Local
|
2019-03-10 02:12:43 +09:00
|
|
|
import Database.Persist.Local
|
2019-02-08 08:08:28 +09:00
|
|
|
import Network.FedURI
|
2019-01-22 00:54:57 +09:00
|
|
|
import Web.ActivityPub
|
2019-02-12 20:53:24 +09:00
|
|
|
import Yesod.Auth.Unverified
|
2019-03-23 11:05:30 +09:00
|
|
|
import Yesod.FedURI
|
2019-03-29 12:25:32 +09:00
|
|
|
import Yesod.Hashids
|
2019-01-22 00:54:57 +09:00
|
|
|
|
2019-02-07 19:34:33 +09:00
|
|
|
import Vervis.ActorKey
|
2019-03-22 07:57:15 +09:00
|
|
|
import Vervis.Federation
|
2019-01-22 00:54:57 +09:00
|
|
|
import Vervis.Foundation
|
|
|
|
import Vervis.Model
|
2019-03-25 09:17:24 +09:00
|
|
|
import Vervis.Model.Ident
|
2019-03-10 02:12:43 +09:00
|
|
|
import Vervis.RemoteActorStore
|
2019-03-25 09:17:24 +09:00
|
|
|
import Vervis.Settings
|
2019-01-19 10:56:50 +09:00
|
|
|
|
|
|
|
getInboxR :: Handler Html
|
|
|
|
getInboxR = do
|
|
|
|
acts <- liftIO . readTVarIO =<< getsYesod appActivities
|
|
|
|
defaultLayout
|
|
|
|
[whamlet|
|
|
|
|
<p>
|
|
|
|
Welcome to the ActivityPub inbox test page! It's the beginning of
|
|
|
|
federation support in Vervis. Currently POSTing activities
|
|
|
|
doesn't do anything, they're just verified and the results are
|
2019-02-12 20:53:24 +09:00
|
|
|
displayed on this page. To test, go to another Vervis instance's
|
|
|
|
outbox page, submit an activity, and come back here to see
|
|
|
|
results.
|
2019-01-19 10:56:50 +09:00
|
|
|
<p>Last 10 activities posted:
|
|
|
|
<ul>
|
2019-03-22 07:57:15 +09:00
|
|
|
$forall (time, report) <- acts
|
2019-01-19 10:56:50 +09:00
|
|
|
<li>
|
|
|
|
<div>#{show time}
|
2019-03-22 07:57:15 +09:00
|
|
|
$case report
|
|
|
|
$of ActivityReportHandlerError e
|
|
|
|
<div>Handler error:
|
2019-01-19 10:56:50 +09:00
|
|
|
<div>#{e}
|
2019-03-22 07:57:15 +09:00
|
|
|
$of ActivityReportWorkerError ct o e
|
2019-01-19 10:56:50 +09:00
|
|
|
<div><code>#{BC.unpack ct}
|
|
|
|
<div><pre>#{decodeUtf8 o}
|
2019-03-22 07:57:15 +09:00
|
|
|
<div>#{displayException e}
|
|
|
|
$of ActivityReportUsed msg
|
|
|
|
<div>#{msg}
|
|
|
|
$of ActivityReportUnused ct o msg
|
|
|
|
<div><code>#{BC.unpack ct}
|
|
|
|
<div><pre>#{decodeUtf8 o}
|
|
|
|
<div>#{msg}
|
2019-01-19 10:56:50 +09:00
|
|
|
|]
|
|
|
|
|
|
|
|
postInboxR :: Handler ()
|
|
|
|
postInboxR = do
|
2019-03-25 09:17:24 +09:00
|
|
|
federation <- getsYesod $ appFederation . appSettings
|
|
|
|
unless federation badMethod
|
2019-01-19 10:56:50 +09:00
|
|
|
now <- liftIO getCurrentTime
|
|
|
|
r <- runExceptT $ getActivity now
|
|
|
|
case r of
|
2019-03-22 07:57:15 +09:00
|
|
|
Right (ct, (WithValue raw d@(Doc h a), (iid, rsid))) ->
|
|
|
|
forkHandler (handleWorkerError now ct d) $ do
|
2019-03-24 00:45:44 +09:00
|
|
|
(msg, stored) <- handleInboxActivity raw h iid rsid a
|
2019-03-22 07:57:15 +09:00
|
|
|
if stored
|
|
|
|
then recordUsed now msg
|
|
|
|
else recordUnused now ct d msg
|
|
|
|
Left e -> do
|
|
|
|
recordError now e
|
|
|
|
notAuthenticated
|
2019-01-19 10:56:50 +09:00
|
|
|
where
|
|
|
|
liftE = ExceptT . pure
|
2019-03-22 07:57:15 +09:00
|
|
|
handleWorkerError now ct d e = do
|
|
|
|
logError $ "postInboxR worker error: " <> T.pack (displayException e)
|
|
|
|
recordActivity now $ ActivityReportWorkerError ct (encodePretty d) e
|
|
|
|
recordActivity now item = do
|
|
|
|
acts <- getsYesod appActivities
|
|
|
|
liftIO $ atomically $ modifyTVar' acts $ \ vec ->
|
|
|
|
let vec' = (now, item) `V.cons` vec
|
|
|
|
in if V.length vec' > 10
|
|
|
|
then V.init vec'
|
|
|
|
else vec'
|
|
|
|
recordUsed now msg = recordActivity now $ ActivityReportUsed msg
|
|
|
|
recordUnused now ct d msg = recordActivity now $ ActivityReportUnused ct (encodePretty d) msg
|
|
|
|
recordError now e = recordActivity now $ ActivityReportHandlerError e
|
2019-04-12 09:56:27 +09:00
|
|
|
getActivity :: UTCTime -> ExceptT String Handler (ContentType, (WithValue (Doc Activity), (InstanceId, RemoteActorId)))
|
2019-01-19 10:56:50 +09:00
|
|
|
getActivity now = do
|
|
|
|
contentType <- do
|
|
|
|
ctypes <- lookupHeaders "Content-Type"
|
|
|
|
liftE $ case ctypes of
|
|
|
|
[] -> Left "Content-Type not specified"
|
|
|
|
[x] -> case x of
|
|
|
|
"application/activity+json" -> Right x
|
|
|
|
"application/ld+json; profile=\"https://www.w3.org/ns/activitystreams\"" -> Right x
|
|
|
|
_ -> Left "Unknown Content-Type"
|
|
|
|
_ -> Left "More than one Content-Type given"
|
2019-01-19 13:21:56 +09:00
|
|
|
HttpSigVerResult result <- ExceptT . fmap (first displayException) $ verifyRequestSignature now
|
2019-03-22 06:38:59 +09:00
|
|
|
(h, luActor) <- f2l . actorDetailId <$> liftE result
|
2019-03-22 07:57:15 +09:00
|
|
|
ActorDetail uActor iid rsid <- liftE result
|
|
|
|
let (h, luActor) = f2l uActor
|
2019-03-24 00:29:50 +09:00
|
|
|
wv@(WithValue _ (Doc h' a)) <- requireJsonBody
|
2019-03-10 15:42:03 +09:00
|
|
|
unless (h == h') $
|
|
|
|
throwE "Activity host doesn't match signature key host"
|
2019-03-14 08:37:58 +09:00
|
|
|
unless (activityActor a == luActor) $
|
2019-03-10 15:42:03 +09:00
|
|
|
throwE "Activity's actor != Signature key's actor"
|
2019-03-22 07:57:15 +09:00
|
|
|
return (contentType, (wv, (iid, rsid)))
|
2019-01-22 00:54:57 +09:00
|
|
|
|
2019-02-12 20:53:24 +09:00
|
|
|
{-
|
2019-01-22 00:54:57 +09:00
|
|
|
jsonField :: (FromJSON a, ToJSON a) => Field Handler a
|
|
|
|
jsonField = checkMMap fromTextarea toTextarea textareaField
|
|
|
|
where
|
|
|
|
toTextarea = Textarea . TL.toStrict . encodePrettyToLazyText
|
|
|
|
fromTextarea = return . first T.pack . eitherDecodeStrict' . encodeUtf8 . unTextarea
|
2019-02-12 20:53:24 +09:00
|
|
|
-}
|
2019-01-22 00:54:57 +09:00
|
|
|
|
2019-02-12 20:53:24 +09:00
|
|
|
fedUriField
|
|
|
|
:: (Monad m, RenderMessage (HandlerSite m) FormMessage) => Field m FedURI
|
|
|
|
fedUriField = Field
|
|
|
|
{ fieldParse = parseHelper $ \ t ->
|
|
|
|
case parseFedURI t of
|
|
|
|
Left e -> Left $ MsgInvalidUrl $ T.pack e <> ": " <> t
|
|
|
|
Right u -> Right u
|
|
|
|
, fieldView = \theId name attrs val isReq ->
|
|
|
|
[whamlet|<input ##{theId} name=#{name} *{attrs} type=url :isReq:required value=#{either id renderFedURI val}>|]
|
|
|
|
, fieldEnctype = UrlEncoded
|
|
|
|
}
|
|
|
|
|
2019-04-19 12:14:12 +09:00
|
|
|
ticketField
|
|
|
|
:: (Route App -> LocalURI) -> Field Handler (Text, ShrIdent, PrjIdent, Int)
|
|
|
|
ticketField encodeRouteLocal = checkMMap toTicket fromTicket fedUriField
|
2019-01-22 00:54:57 +09:00
|
|
|
where
|
2019-04-19 12:14:12 +09:00
|
|
|
toTicket uTicket = runExceptT $ do
|
|
|
|
let (hTicket, luTicket) = f2l uTicket
|
|
|
|
route <-
|
|
|
|
case decodeRouteLocal luTicket of
|
|
|
|
Nothing -> throwE ("Not a valid route" :: Text)
|
|
|
|
Just r -> return r
|
|
|
|
case route of
|
|
|
|
TicketR shr prj num -> return (hTicket, shr, prj, num)
|
|
|
|
_ -> throwE "Not a ticket route"
|
|
|
|
fromTicket (h, shr, prj, num) =
|
|
|
|
l2f h $ encodeRouteLocal $ TicketR shr prj num
|
|
|
|
|
|
|
|
activityForm :: Form ((Text, ShrIdent, PrjIdent, Int), Maybe FedURI, Text)
|
|
|
|
activityForm html = do
|
|
|
|
enc <- getEncodeRouteLocal
|
|
|
|
flip renderDivs html $ (,,)
|
|
|
|
<$> areq (ticketField enc) "Ticket" (Just deft)
|
|
|
|
<*> aopt fedUriField "Replying to" (Just $ Just defp)
|
|
|
|
<*> areq textField "Message" (Just defmsg)
|
|
|
|
where
|
|
|
|
deft = ("forge.angeley.es", text2shr "fr33", text2prj "sandbox", 1)
|
|
|
|
defp = FedURI "forge.angeley.es" "/s/fr33/m/2f1a7" ""
|
2019-03-22 08:56:47 +09:00
|
|
|
defmsg = "Hi! I'm testing federation. Can you see my message? :)"
|
2019-01-22 00:54:57 +09:00
|
|
|
|
2019-03-29 06:08:30 +09:00
|
|
|
activityWidget :: ShrIdent -> Widget -> Enctype -> Widget
|
|
|
|
activityWidget shr widget enctype =
|
2019-01-22 00:54:57 +09:00
|
|
|
[whamlet|
|
2019-02-12 20:53:24 +09:00
|
|
|
<p>
|
|
|
|
This is a federation test page. Provide a recepient actor URI and
|
|
|
|
message text, and a Create activity creating a new Note will be sent
|
|
|
|
to the destination server.
|
2019-03-29 06:08:30 +09:00
|
|
|
<form method=POST action=@{OutboxR shr} enctype=#{enctype}>
|
2019-01-22 00:54:57 +09:00
|
|
|
^{widget}
|
|
|
|
<input type=submit>
|
|
|
|
|]
|
|
|
|
|
2019-03-29 06:08:30 +09:00
|
|
|
getUserShrIdent :: Handler ShrIdent
|
|
|
|
getUserShrIdent = do
|
|
|
|
Entity _ p <- requireVerifiedAuth
|
|
|
|
s <- runDB $ get404 $ personIdent p
|
|
|
|
return $ sharerIdent s
|
|
|
|
|
2019-03-22 14:17:54 +09:00
|
|
|
getPublishR :: Handler Html
|
|
|
|
getPublishR = do
|
2019-03-29 06:08:30 +09:00
|
|
|
shr <- getUserShrIdent
|
2019-01-22 00:54:57 +09:00
|
|
|
((_result, widget), enctype) <- runFormPost activityForm
|
2019-03-29 06:08:30 +09:00
|
|
|
defaultLayout $ activityWidget shr widget enctype
|
2019-01-22 00:54:57 +09:00
|
|
|
|
2019-03-29 06:08:30 +09:00
|
|
|
getOutboxR :: ShrIdent -> Handler TypedContent
|
2019-03-22 14:17:54 +09:00
|
|
|
getOutboxR = error "Not implemented yet"
|
|
|
|
|
2019-03-29 12:25:32 +09:00
|
|
|
getOutboxItemR :: ShrIdent -> KeyHashid OutboxItem -> Handler TypedContent
|
2019-03-29 06:08:30 +09:00
|
|
|
getOutboxItemR = error "Not implemented yet"
|
|
|
|
|
|
|
|
postOutboxR :: ShrIdent -> Handler Html
|
2019-04-19 12:14:12 +09:00
|
|
|
postOutboxR shrAuthor = do
|
2019-03-25 09:17:24 +09:00
|
|
|
federation <- getsYesod $ appFederation . appSettings
|
|
|
|
unless federation badMethod
|
2019-01-22 00:54:57 +09:00
|
|
|
((result, widget), enctype) <- runFormPost activityForm
|
2019-04-19 12:14:12 +09:00
|
|
|
elmid <- runExceptT $ do
|
|
|
|
((hTicket, shrTicket, prj, num), muParent, msg) <-
|
|
|
|
case result of
|
|
|
|
FormMissing -> throwE "Field(s) missing"
|
|
|
|
FormFailure _l -> throwE "Invalid input, see below"
|
|
|
|
FormSuccess r -> return r
|
|
|
|
encodeRouteFed <- getEncodeRouteFed
|
|
|
|
encodeRouteLocal <- getEncodeRouteLocal
|
|
|
|
let encodeRecipRoute = l2f hTicket . encodeRouteLocal
|
|
|
|
uTicket = encodeRecipRoute $ TicketR shrTicket prj num
|
|
|
|
now <- liftIO getCurrentTime
|
|
|
|
let (hLocal, luAuthor) = f2l $ encodeRouteFed $ SharerR shrAuthor
|
|
|
|
recips =
|
|
|
|
[ ProjectR shrTicket prj
|
|
|
|
, TicketParticipantsR shrTicket prj num
|
|
|
|
, TicketTeamR shrTicket prj num
|
2019-04-18 19:38:01 +09:00
|
|
|
]
|
2019-04-19 12:14:12 +09:00
|
|
|
note = Note
|
|
|
|
{ noteId = Nothing
|
|
|
|
, noteAttrib = luAuthor
|
|
|
|
, noteAudience = Audience
|
|
|
|
{ audienceTo = map encodeRecipRoute recips
|
|
|
|
, audienceBto = []
|
|
|
|
, audienceCc = []
|
|
|
|
, audienceBcc = []
|
|
|
|
, audienceGeneral = []
|
|
|
|
}
|
|
|
|
, noteReplyTo = Just $ fromMaybe uTicket muParent
|
|
|
|
, noteContext = Just uTicket
|
|
|
|
, notePublished = Just now
|
|
|
|
, noteContent = msg
|
|
|
|
}
|
|
|
|
ExceptT $ handleOutboxNote hLocal note
|
|
|
|
case elmid of
|
|
|
|
Left err -> setMessage $ toHtml err
|
|
|
|
Right lmid -> do
|
|
|
|
lmkhid <- encodeKeyHashid lmid
|
|
|
|
renderUrl <- getUrlRender
|
|
|
|
let u = renderUrl $ MessageR shrAuthor lmkhid
|
|
|
|
setMessage $ toHtml $ "Message created! ID: " <> u
|
|
|
|
defaultLayout $ activityWidget shrAuthor widget enctype
|
2019-02-07 19:34:33 +09:00
|
|
|
|
|
|
|
getActorKey :: ((ActorKey, ActorKey, Bool) -> ActorKey) -> Route App -> Handler TypedContent
|
2019-03-20 21:01:10 +09:00
|
|
|
getActorKey choose route = selectRep $ provideAP $ do
|
2019-02-07 19:34:33 +09:00
|
|
|
actorKey <-
|
|
|
|
liftIO . fmap (actorKeyPublicBin . choose) . readTVarIO =<<
|
|
|
|
getsYesod appActorKeys
|
2019-03-23 11:05:30 +09:00
|
|
|
route2uri <- getEncodeRouteFed
|
2019-02-22 08:59:53 +09:00
|
|
|
let (host, id_) = f2l $ route2uri route
|
2019-03-20 21:01:10 +09:00
|
|
|
return $ Doc host PublicKey
|
|
|
|
{ publicKeyId = id_
|
|
|
|
, publicKeyExpires = Nothing
|
|
|
|
, publicKeyOwner = OwnerInstance
|
|
|
|
, publicKeyMaterial = actorKey
|
|
|
|
--, publicKeyAlgo = Just AlgorithmEd25519
|
|
|
|
}
|
2019-02-07 19:34:33 +09:00
|
|
|
|
|
|
|
getActorKey1R :: Handler TypedContent
|
|
|
|
getActorKey1R = getActorKey (\ (k1, _, _) -> k1) ActorKey1R
|
|
|
|
|
|
|
|
getActorKey2R :: Handler TypedContent
|
2019-03-06 10:49:55 +09:00
|
|
|
getActorKey2R = getActorKey (\ (_, k2, _) -> k2) ActorKey2R
|