1
0
Fork 0
mirror of https://code.naskya.net/repos/ndqEd synced 2025-01-10 22:36:45 +09:00

sharerOfferDepF: If parent is remote and child is mine, record TicketDepOffer

This commit is contained in:
fr33domlover 2020-06-21 09:06:02 +00:00
parent bc4248d7ca
commit 2cddadd679
2 changed files with 44 additions and 11 deletions

View file

@ -767,7 +767,7 @@ sharerOfferDepF now shrRecip author body dep uTarget = do
return $ (,) "Ran initial checks, doing the rest asynchronously" $ Just $ do return $ (,) "Ran initial checks, doing the rest asynchronously" $ Just $ do
manager <- asksSite appHttpManager manager <- asksSite appHttpManager
relevantParent <- relevantParent <-
for (parentRelevance shrRecip parent) $ \ (talid, patch) -> do for (ticketRelevance shrRecip parent) $ \ (talid, patch) -> do
(parentLtid, parentCtx) <- runSiteDBExcept $ do (parentLtid, parentCtx) <- runSiteDBExcept $ do
let getTcr tcr = do let getTcr tcr = do
let getRoid roid = do let getRoid roid = do
@ -844,10 +844,11 @@ sharerOfferDepF now shrRecip author body dep uTarget = do
return return
(u', objUriAuthority u, objFollowers obj, objTeam obj) (u', objUriAuthority u, objFollowers obj, objTeam obj)
return (talid, patch, parentLtid, parentCtx', childId, childCtx', childAuthor) return (talid, patch, parentLtid, parentCtx', childId, childCtx', childAuthor)
mhttp <- lift $ runSiteDB $ do mhttp <- runSiteDBExcept $ do
mractid <- insertToInbox now author body (personInbox personRecip) luOffer True mractid <- lift $ insertToInbox' now author body (personInbox personRecip) luOffer True
for mractid $ \ ractid -> do for mractid $ \ (ractid, ibiid) -> do
mremotesHttpFwd <- for msig $ \ sig -> do insertDepOffer ibiid parent child
mremotesHttpFwd <- lift $ for msig $ \ sig -> do
relevantFollowers <- askRelevantFollowers relevantFollowers <- askRelevantFollowers
let sieve = let sieve =
makeRecipientSet [] $ catMaybes makeRecipientSet [] $ catMaybes
@ -860,7 +861,7 @@ sharerOfferDepF now shrRecip author body dep uTarget = do
localRecipSieve' localRecipSieve'
sieve False False localRecips sieve False False localRecips
(sig,) <$> deliverRemoteDB_S (actbBL body) ractid (personIdent personRecip) sig remoteRecips (sig,) <$> deliverRemoteDB_S (actbBL body) ractid (personIdent personRecip) sig remoteRecips
mremotesHttpAccept <- for relevantParent $ \ ticketData@(_, _, parentLtid, _, childId, _, _) -> do mremotesHttpAccept <- lift $ for relevantParent $ \ ticketData@(_, _, parentLtid, _, childId, _, _) -> do
obiidAccept <- insertEmptyOutboxItem (personOutbox personRecip) now obiidAccept <- insertEmptyOutboxItem (personOutbox personRecip) now
tdid <- insertDep ractid parentLtid childId obiidAccept tdid <- insertDep ractid parentLtid childId obiidAccept
(docAccept, localRecipsAccept, remoteRecipsAccept, fwdHostsAccept) <- (docAccept, localRecipsAccept, remoteRecipsAccept, fwdHostsAccept) <-
@ -947,9 +948,9 @@ sharerOfferDepF now shrRecip author body dep uTarget = do
checkParentAndTarget (Left _) (Right _) = throwE "Local parent but remote target" checkParentAndTarget (Left _) (Right _) = throwE "Local parent but remote target"
checkParentAndTarget (Right _) (Left _) = throwE "Local target but remote parent" checkParentAndTarget (Right _) (Left _) = throwE "Local target but remote parent"
checkParentAndTarget (Right _) (Right _) = return () checkParentAndTarget (Right _) (Right _) = return ()
parentRelevance shr (Left (WorkItemSharerTicket shr' talid patch)) ticketRelevance shr (Left (WorkItemSharerTicket shr' talid patch))
| shr == shr' = Just (talid, patch) | shr == shr' = Just (talid, patch)
parentRelevance _ _ = Nothing ticketRelevance _ _ = Nothing
{- {-
getWorkItem getWorkItem
:: MonadIO m :: MonadIO m
@ -1071,9 +1072,28 @@ sharerOfferDepF now shrRecip author body dep uTarget = do
SharerR shr -> return shr SharerR shr -> return shr
_ -> throwE "Not a ticket author route" _ -> throwE "Not a ticket author route"
else return $ Right u else return $ Right u
insertDepOffer _ (Left _) _ = return ()
insertDepOffer ibiidOffer (Right _) child =
for_ (ticketRelevance shrRecip child) $ \ (talid, patch) -> do
ltid <-
if patch
then do
(_, Entity ltid _, _, _, _) <- do
mticket <- lift $ getSharerPatch shrRecip talid
fromMaybeE mticket $ "Child" <> ": No such sharer-patch"
return ltid
else do
(_, Entity ltid _, _, _) <- do
mticket <- lift $ getSharerTicket shrRecip talid
fromMaybeE mticket $ "Child" <> ": No such sharer-ticket"
return ltid
lift $ insert_ TicketDependencyOffer
{ ticketDependencyOfferOffer = ibiidOffer
, ticketDependencyOfferChild = ltid
}
askRelevantFollowers = do askRelevantFollowers = do
hashTALID <- getEncodeKeyHashid hashTALID <- getEncodeKeyHashid
return $ \ shr wi -> followers hashTALID <$> parentRelevance shr wi return $ \ shr wi -> followers hashTALID <$> ticketRelevance shr wi
where where
followers hashTALID (talid, patch) = followers hashTALID (talid, patch) =
let coll = let coll =

View file

@ -15,6 +15,7 @@
module Vervis.Federation.Util module Vervis.Federation.Util
( insertToInbox ( insertToInbox
, insertToInbox'
) )
where where
@ -45,7 +46,19 @@ insertToInbox
-> LocalURI -> LocalURI
-> Bool -> Bool
-> ReaderT SqlBackend m (Maybe RemoteActivityId) -> ReaderT SqlBackend m (Maybe RemoteActivityId)
insertToInbox now author body ibid luAct unread = do insertToInbox now author body ibid luAct unread =
fmap fst <$> insertToInbox' now author body ibid luAct unread
insertToInbox'
:: MonadIO m
=> UTCTime
-> RemoteAuthor
-> ActivityBody
-> InboxId
-> LocalURI
-> Bool
-> ReaderT SqlBackend m (Maybe (RemoteActivityId, InboxItemId))
insertToInbox' now author body ibid luAct unread = do
let iidAuthor = remoteAuthorInstance author let iidAuthor = remoteAuthorInstance author
roid <- roid <-
either entityKey id <$> insertBy' (RemoteObject iidAuthor luAct) either entityKey id <$> insertBy' (RemoteObject iidAuthor luAct)
@ -60,4 +73,4 @@ insertToInbox now author body ibid luAct unread = do
Nothing -> do Nothing -> do
delete ibiid delete ibiid
return Nothing return Nothing
Just _ -> return $ Just ractid Just _ -> return $ Just (ractid, ibiid)