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 / Persist /

Ticket.hs

{- This file is part of Vervis.
 -
 - Written in 2022 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.Persist.Ticket
    ( getTicketResolve
    , getWorkItem
    , checkApplyDB
    , tryUnresolve
    )
where

import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Trans.Class
import Control.Monad.Trans.Except
import Control.Monad.Trans.Maybe
import Control.Monad.Trans.Reader
import Data.Bitraversable
import Data.List.NonEmpty (NonEmpty (..))
import Data.Maybe
import Data.Text (Text)
import Data.These
import Data.Traversable
import Database.Persist
import Database.Persist.Sql

import qualified Data.List.NonEmpty as NE

import Development.PatchMediaType
import Yesod.Hashids

import Control.Monad.Trans.Except.Local
import Data.Either.Local
import Database.Persist.Local

import Vervis.Access
import Vervis.Cloth
import Vervis.Data.Ticket
import Vervis.FedURI
import Vervis.Foundation
import Vervis.Model
import Vervis.Persist.Actor
import Vervis.Recipient

getTicketResolve (Entity _ tr, resolve) = do
    time <- outboxItemPublished <$> getJust (ticketResolveAccept tr)
    closer <- bitraverse getCloserLocal getCloserRemote resolve
    return (time, closer)
    where
    getCloserLocal (Entity _ trl) = do
        outboxID <-
            outboxItemOutbox <$>
                getJust (ticketResolveLocalActivity trl)
        Entity actorID actor <- do
            maybeActor <- getBy $ UniqueActorOutbox outboxID
            case maybeActor of
                Nothing -> error "No actor for outbox"
                Just a -> pure a
        actorByEntity <- getLocalActorEnt actorID
        person <-
            case actorByEntity of
                LocalActorPerson p -> pure p
                _ -> error "Surprise! Ticket closer isn't a Person"
        return (person, actor)
    getCloserRemote (Entity _ trr) = do
        ra <- getJust $ ticketResolveRemoteActor trr
        ro <- getJust $ remoteActorIdent ra
        i <- getJust $ remoteObjectInstance ro
        return (i, ro, ra)

getWorkItem :: MonadIO m => TicketId -> ReaderT SqlBackend m (WorkItemBy Key)
getWorkItem tid = do
    tracker <-
        requireEitherAlt
            (getBy $ UniqueTicketDeck tid)
            (getBy $ UniqueTicketLoom tid)
            "Neither TD nor TD found"
            "Both TD and TL found"
    return $
        case tracker of
            Left (Entity tdid td) -> WorkItemTicket (ticketDeckDeck td) tdid
            Right (Entity tlid tl) -> WorkItemCloth (ticketLoomLoom tl) tlid

-- | Given:
--
-- * A local tip (i.e. a repository or a branch), parsed from a URI
-- * A local bundle to apply to it, parsed from a URI
-- * A local or remote actor requesting to apply the bundle to the tip, already
--   known to be in our DB
-- * An activity URI provided by that actor as a capability, parsed from URI
--
-- Find the tip and the bundle in our DB, and verify that the loom hosting the
-- bundle is willing to accept the request from that specific actor to apply
-- that bundle to that repo. More specifically:
--
-- * Verify the tip matches the MR target
-- * Verify that the loom and the repo are linked
-- * Verify that a branch is specified if repo is Git, isn't specified if Darcs
-- * Verify the MR isn't already resolved
-- * Verify bundle is the latest version of the MR
-- * Verify the requester actor is authorized to apply
-- * Verify that patch type matches repo VCS type
--
-- Returns:
--
-- * The loom (so it can send an Accept after applying)
-- * The MR's ticket ID (so it can be marked as resolved after applying)
-- * The actual patch diffs, in first-to-last order
checkApplyDB
    :: Either PersonId RemoteActorId    -- ^ Actor requesting to apply
    -> (Either
            (LocalActorBy Key, LocalActorBy KeyHashid, OutboxItemId)
            FedURI
       )                                -- ^ Capability specified by the actor
    -> (RepoId, Maybe Text)             -- ^ Repository (or branch) to apply to
    -> (LoomId, TicketLoomId, BundleId) -- ^ Parsed bundle URI to apply
    -> ExceptT Text AppDB (Loom, TicketId, NonEmpty Text)
checkApplyDB actor capID (repoID, maybeBranch) (loomID, clothID, bundleID) = do

    -- Find the bundle and its loom in DB
    (loom, clothBranch, ticketID, maybeResolve, latest) <- do
        maybeBundle <- lift $ runMaybeT $ do
            (Entity _ loom, Entity _ cloth, Entity ticketID _, _author, resolve, proposal) <-
                MaybeT $ getCloth loomID clothID
            bundle <- MaybeT $ get bundleID
            guard $ bundleTicket bundle == clothID
            latest :| _prevs <-
                case justHere proposal of
                    Nothing ->
                        error "Why didn't getCloth find any bundles"
                    Just bundles -> return bundles
            return (loom, ticketLoomBranch cloth, ticketID, resolve, latest)
        fromMaybeE maybeBundle "Apply object bundle not found in DB"

    -- Verify the target repo/branch of the Apply is identical to the
    -- target repo/branch of the MR
    unless (maybeBranch == clothBranch) $
        throwE "Apply target != MR target"

    -- Find target repo in DB and verify it consents to being served by
    -- the loom
    unless (repoID == loomRepo loom) $
        throwE "MR target repo isn't the one served by the Apply object bundle's loom"
    repo <- getE repoID "Apply target: No such local repo in DB"
    unless (repoLoom repo == Just loomID) $
        throwE "Apply object bunde's loom doesn't have repo's consent to serve it"

    -- Verify that VCS type matches the presence of a branch:
    -- Branch specified for Git, isn't specified for Darcs
    case (repoVcs repo, maybeBranch) of
        (VCSDarcs, Nothing) -> pure ()
        (VCSGit, Just _) -> pure ()
        _ -> throwE "VCS type and branch presence mismatch"

    -- Verify the MR isn't already resolved and the bundle is the
    -- latest version
    unless (isNothing maybeResolve) $
        throwE "MR is already resolved"
    unless (bundleID == latest) $
        throwE "Bundle isn't the latest version"

    -- Verify the sender is authorized by the loom to apply a patch
    capability <-
        case capID of
            Left (capActor, _, capItem) -> return (capActor, capItem)
            Right _ -> throwE "Capability is a remote URI, i.e. not authored by the local loom"
    verifyCapability capability actor (GrantResourceLoom loomID)

    -- Get the patches from DB, verify VCS match just in case
    diffs <- do
        ps <-
            lift $ map entityVal <$>
                selectList [PatchBundle ==. bundleID] [Asc PatchId]
        let patchVCS = patchMediaTypeVCS . patchType
        case NE.nonEmpty ps of
            Nothing -> error "Bundle without patches"
            Just ne ->
                if all ((== repoVcs repo) . patchVCS) ne
                    then return $ NE.map patchContent ne
                    else throwE "Patch type mismatch with repo VCS type"

    return (loom, ticketID, diffs)

tryUnresolve (Left (_actorByKey, _actorEntity, itemID)) = do
    maybeResolve <- getBy $ UniqueTicketResolveLocalActivity itemID
    for maybeResolve $ \ (Entity resolveLocalID resolveLocal) -> do
        let resolveID = ticketResolveLocalTicket resolveLocal
        resolve <- getJust resolveID
        let ticketID = ticketResolveTicket resolve
        return
            ( delete resolveLocalID >> delete resolveID
            , ticketID
            )
tryUnresolve (Right remoteActivityID) = do
    maybeResolve <- getBy $ UniqueTicketResolveRemoteActivity remoteActivityID
    for maybeResolve $ \ (Entity resolveRemoteID resolveRemote) -> do
        let resolveID = ticketResolveRemoteTicket resolveRemote
        resolve <- getJust resolveID
        let ticketID = ticketResolveTicket resolve
        return
            ( delete resolveRemoteID >> delete resolveID
            , ticketID
            )
[See repo JSON]