Eventually-decentralized project hosting and management platform

[[ 🗃 ^WvWbo vervis ]] :: [📥 Inbox] [📤 Outbox] [🐤 Followers] [🤝 Collaborators] [🛠 Changes]

Clone

HTTPS: darcs clone https://vervis.peers.community/repos/WvWbo

SSH: darcs clone USERNAME@vervis.peers.community:WvWbo

Tags

TODO

src / Vervis /

Actor2.hs

{- This file is part of Vervis.
 -
 - Written in 2019, 2020, 2022, 2023 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/>.
 -}

-- For the ugly existential-type trick that avoids Env depending on App
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

-- | Everything I'd put in 'Vervis.Actor' but currently depends on
-- 'Vervis.Foundation', and therefore needs a separate module.
module Vervis.Actor2
    ( -- * Sending messages to actors
      sendActivity
    , forwardActivity
    )
where

import Control.Concurrent.STM.TVar
import Control.Monad.IO.Class
import Control.Monad.Trans.Class
import Control.Monad.Trans.Except
import Data.Barbie
import Data.ByteString (ByteString)
import Data.Either
import Data.Hashable
import Data.List.NonEmpty (NonEmpty)
import Data.Text (Text)
import Data.Time.Clock
import Data.Traversable
import Data.Typeable
import Database.Persist.Sql
import GHC.Generics
import UnliftIO.Exception
import Web.Hashids

import qualified Data.Aeson as A
import qualified Data.ByteString.Lazy as BL
import qualified Data.List.NonEmpty as NE
import qualified Data.Text as T

import Control.Concurrent.Actor
import Crypto.ActorKey
import Network.FedURI
import Web.Actor
import Web.Actor.Deliver
import Web.Actor.Persist

import qualified Web.ActivityPub as AP

import Vervis.Actor
import Vervis.Data.Actor
import Vervis.FedURI
import Vervis.Foundation
import Vervis.Model hiding (Actor, Message)
import Vervis.Recipient (renderLocalActor, localRecipSieve')
import Vervis.Settings

instance StageWebRoute Env where
    type StageRoute Env = Route App
    askUrlRenderParams = do
        Env _ _ _ _ _ render <- askEnv
        case cast render of
            Nothing -> error "Env site isn't App"
            Just r -> pure r
    pageParamName _ = "page"

askLatestInstanceKey :: Act (Maybe (Route App, ActorKey))
askLatestInstanceKey = do
    maybeTVar <- asksEnv envActorKeys
    for maybeTVar $ \ tvar -> do
        (akey1, akey2, new1) <- liftIO $ readTVarIO tvar
        return $
            if new1
                then (ActorKey1R, akey1)
                else (ActorKey2R, akey2)

prepareSendIK
    :: (Route App, ActorKey)
    -> LocalActorBy KeyHashid
    -> OutboxItemId
    -> AP.Action URIMode
    -> Act (AP.Envelope URIMode)
prepareSendIK (keyR, akey) actorByHash itemID action = do
    itemHash <- encodeKeyHashid itemID
    let sign = actorKeySign akey
        actorR = renderLocalActor actorByHash
        idR = activityRoute actorByHash itemHash
    prepareToSend keyR sign True actorR idR action

prepareSendAK
    :: ActorId
    -> LocalActorBy KeyHashid
    -> OutboxItemId
    -> AP.Action URIMode
    -> ActDB (AP.Envelope URIMode)
prepareSendAK actorID actorByHash itemID action = do
    Entity keyID key <- do
        mk <- getBy $ UniqueSigKey actorID
        case mk of
            Nothing -> error "Actor has no keys!"
            Just k -> return k
    itemHash <- encodeKeyHashid itemID
    keyHash <- encodeKeyHashid keyID
    let keyR = stampRoute actorByHash keyHash
        sign = actorKeySign $ sigKeyMaterial key
        actorR = renderLocalActor actorByHash
        idR = activityRoute actorByHash itemHash
    prepareToSend keyR sign False actorR idR action

prepareSendP
    :: ActorId
    -> LocalActorBy KeyHashid
    -> OutboxItemId
    -> AP.Action URIMode
    -> ActDB (AP.Envelope URIMode)
prepareSendP actorID actorByHash itemID action = do
    maybeKey <- lift askLatestInstanceKey
    case maybeKey of
        Nothing -> prepareSendAK actorID actorByHash itemID action
        Just key -> lift $ prepareSendIK key actorByHash itemID action

prepareSendH
    :: ActorId
    -> LocalActorBy KeyHashid
    -> OutboxItemId
    -> AP.Action URIMode
    -> Act (AP.Envelope URIMode)
prepareSendH actorID actorByHash itemID action = do
    maybeKey <- askLatestInstanceKey
    case maybeKey of
        Nothing -> withDB $ prepareSendAK actorID actorByHash itemID action
        Just key -> prepareSendIK key actorByHash itemID action

-- | Given a list of local and remote recipients, which may include actors and
-- collections,
--
-- * Insert event to message queues of local actors listed
-- * Insert event to message queues of local members of local collections
--   listed
-- * Launch asynchronously sending activity to remote recipients and remote
--   member of local collections listed
--
-- This function reads the follower sets, remote recipient data and the
-- sender's signing key from the PostgreSQL database. Don't use it inside a
-- database transaction.
sendActivity
    :: LocalActorBy Key
    -- ^ Activity author and sender
    --
    -- * Its collections are excluded from requiring an owner, i.e.
    --   even if owner is required, this actor's collections will be delivered
    --   to, even if this actor isn't addressed
    -- * Its inbox is excluded from delivery, even if this actor is listed in
    --   the recipient set
    -> ActorId
    -- ^ Actor key for the sender, for fetching its signing key from the DB
    -> RecipientRoutes
    -- ^ Local recipients
    -> [(Host, NonEmpty LocalURI)]
    -- ^ Remote recipients
    -> [Host]
    -- ^ Instances for which the sender is approving to forward this activity
    -> OutboxItemId
    -- ^ DB ID of the item in the author's outbox
    -> Event
    -- ^ Event to send to local live actors
    -> AP.Action URIMode
    -- ^ Activity to send to remote actors
    -> Act ()
sendActivity senderByKey senderActorID localRecips remoteRecips fwdHosts itemID event action = do
    moreRemoteRecips <-
        let justSender = Just senderByKey
        in  sendToLocalActors event True justSender justSender localRecips
    envelope <- do
        senderByHash <- hashLocalActor senderByKey
        prepareSendH senderActorID senderByHash itemID action
    let (yesFwd, noFwd) =
            let remoteRecipsList =
                    concatMap
                        (\ ((_, h), rrs) -> NE.toList $ NE.map (decideFwd h . remoteRecipientId) rrs)
                        moreRemoteRecips
                moreList =
                    concatMap
                        (\ (h, lus) -> NE.toList $ NE.map (decideFwd h) lus)
                        remoteRecips
                allRemotes = remoteRecipsList ++ moreList
            in  partitionEithers allRemotes
    dt <- asksEnv stageDeliveryTheater
    liftIO $ do
        sendHttp dt (MethodDeliverLocal envelope True) yesFwd
        sendHttp dt (MethodDeliverLocal envelope False) noFwd
    where
    decideFwd h =
        if h `elem` fwdHosts
            then Left . ObjURI h
            else Right . ObjURI h

prepareForwardIK
    :: (Route App, ActorKey)
    -> LocalActorBy KeyHashid
    -> BL.ByteString
    -> ByteString
    -> Act (AP.Errand URIMode)
prepareForwardIK (keyR, akey) fwderByHash body proof = do
    let sign = actorKeySign akey
        fwderR = renderLocalActor fwderByHash
    prepareToForward keyR sign True fwderR body proof

prepareForwardAK
    :: ActorId
    -> LocalActorBy KeyHashid
    -> BL.ByteString
    -> ByteString
    -> ActDB (AP.Errand URIMode)
prepareForwardAK actorID fwderByHash body proof = do
    Entity keyID key <- do
        mk <- getBy $ UniqueSigKey actorID
        case mk of
            Nothing -> error "Actor has no keys!"
            Just k -> return k
    keyHash <- encodeKeyHashid keyID
    let keyR = stampRoute fwderByHash keyHash
        sign = actorKeySign $ sigKeyMaterial key
        fwderR = renderLocalActor fwderByHash
    prepareToForward keyR sign False fwderR body proof

prepareForwardP
    :: ActorId
    -> LocalActorBy KeyHashid
    -> BL.ByteString
    -> ByteString
    -> ActDB (AP.Errand URIMode)
prepareForwardP actorID fwderByHash body proof = do
    maybeKey <- lift askLatestInstanceKey
    case maybeKey of
        Nothing -> prepareForwardAK actorID fwderByHash body proof
        Just key -> lift $ prepareForwardIK key fwderByHash body proof

prepareForwardH
    :: ActorId
    -> LocalActorBy KeyHashid
    -> BL.ByteString
    -> ByteString
    -> Act (AP.Errand URIMode)
prepareForwardH actorID fwderByHash body proof = do
    maybeKey <- askLatestInstanceKey
    case maybeKey of
        Nothing -> withDB $ prepareForwardAK actorID fwderByHash body proof
        Just key -> prepareForwardIK key fwderByHash body proof

-- | Given a list of local recipients, which may include actors and
-- collections,
--
-- * Insert event to message queues of actors listed
-- * Insert event to message queues of local members of collections listed
-- * Launch asynchronously sending activity, with a forwarded signature, to
--   remote member of collections listed
--
-- This function reads remote recipient data and the sender's signing key from
-- the PostgreSQL database. Don't use it inside a database transaction.
forwardActivity
    :: BL.ByteString
    -> RecipientRoutes
    -> ByteString
    -> ActorId
    -> LocalActorBy Key
    -> RecipientRoutes
    -> Event
    -> Act ()
forwardActivity body localRecips sig fwderActorID fwderByKey sieve event = do
    remoteRecips <-
        let localRecipsFinal = localRecipSieve' sieve False False localRecips
            justSender = Just fwderByKey
        in  sendToLocalActors event False justSender justSender localRecipsFinal
    errand <- do
        fwderByHash <- hashLocalActor fwderByKey
        prepareForwardH fwderActorID fwderByHash body sig
    let remoteRecipsList =
            concatMap
                (\ ((_, h), rrs) -> NE.toList $ NE.map (ObjURI h . remoteRecipientId) rrs)
                remoteRecips
    dt <- asksEnv stageDeliveryTheater
    liftIO $ sendHttp dt (MethodForwardRemote errand) remoteRecipsList
[See repo JSON]