5b332a87be
Dropping from a cluster drops from every node of the cluster. Including nodes that the cluster does not think have the content. This is different from GET and CHECKPRESENT, which do trust the cluster's location log. The difference is that removing from a cluster should make 100% the content is gone from every node. So doing extra work is ok. Compare with CHECKPRESENT where checking every node could make it very expensive, and the worst that can happen in a false negative is extra work being done. Extended the P2P protocol with FAILURE-PLUS to handle the case where a drop from one node succeeds, but a drop from another node fails. In that case the entire cluster drop has failed. Note that SUCCESS-PLUS is returned when dropping from a proxied remote that is not a cluster, when the protocol version supports it. This is because P2P.Proxy does not know when it's proxying for a single node cluster vs for a remote that is not a cluster.
104 lines
3.4 KiB
Haskell
104 lines
3.4 KiB
Haskell
{- clusters
|
|
-
|
|
- Copyright 2024 Joey Hess <id@joeyh.name>
|
|
-
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
|
-}
|
|
|
|
{-# LANGUAGE RankNTypes #-}
|
|
|
|
module Annex.Cluster where
|
|
|
|
import Annex.Common
|
|
import qualified Annex
|
|
import Types.Cluster
|
|
import Logs.Cluster
|
|
import P2P.Proxy
|
|
import P2P.Protocol
|
|
import P2P.IO
|
|
import Annex.Proxy
|
|
import Logs.Location
|
|
import Types.Command
|
|
import Remote.List
|
|
import qualified Remote
|
|
import qualified Types.Remote as Remote
|
|
|
|
import qualified Data.Map as M
|
|
import qualified Data.Set as S
|
|
|
|
{- Proxy to a cluster. -}
|
|
proxyCluster
|
|
:: ClusterUUID
|
|
-> CommandPerform
|
|
-> ServerMode
|
|
-> ClientSide
|
|
-> (forall a. ((a -> CommandPerform) -> Annex (Either ProtoFailure a) -> CommandPerform))
|
|
-> CommandPerform
|
|
proxyCluster clusteruuid proxydone servermode clientside protoerrhandler = do
|
|
getClientProtocolVersion (fromClusterUUID clusteruuid) clientside
|
|
withclientversion protoerrhandler
|
|
where
|
|
proxymethods = ProxyMethods
|
|
{ removedContent = \u k -> logChange k u InfoMissing
|
|
, addedContent = \u k -> logChange k u InfoPresent
|
|
}
|
|
|
|
withclientversion (Just (clientmaxversion, othermsg)) = do
|
|
-- The protocol versions supported by the nodes are not
|
|
-- known at this point, and would be too expensive to
|
|
-- determine. Instead, pick the newest protocol version
|
|
-- that we and the client both speak.
|
|
let protocolversion = min maxProtocolVersion clientmaxversion
|
|
selectnode <- clusterProxySelector clusteruuid protocolversion
|
|
proxy proxydone proxymethods servermode clientside
|
|
(fromClusterUUID clusteruuid)
|
|
selectnode protocolversion othermsg protoerrhandler
|
|
withclientversion Nothing = proxydone
|
|
|
|
clusterProxySelector :: ClusterUUID -> ProtocolVersion -> Annex ProxySelector
|
|
clusterProxySelector clusteruuid protocolversion = do
|
|
nodes <- (fromMaybe S.empty . M.lookup clusteruuid . clusterUUIDs)
|
|
<$> getClusters
|
|
clusternames <- annexClusters <$> Annex.getGitConfig
|
|
remotes <- filter (isnode nodes clusternames) <$> remoteList
|
|
remotesides <- mapM (proxySshRemoteSide protocolversion) remotes
|
|
return $ ProxySelector
|
|
{ proxyCHECKPRESENT = nodecontaining remotesides
|
|
, proxyGET = nodecontaining remotesides
|
|
-- Send the key to every node that does not yet contain it.
|
|
, proxyPUT = \k -> do
|
|
locs <- S.fromList <$> loggedLocations k
|
|
return $ filter (flip S.notMember locs . remoteUUID) remotesides
|
|
-- Remove the key from every node that contains it.
|
|
-- But, since it's possible the location log for some nodes
|
|
-- could be out of date, actually try to remove from every
|
|
-- node.
|
|
, proxyREMOVE = const (pure remotesides)
|
|
-- Content is not locked on the cluster as a whole,
|
|
-- instead it can be locked on individual nodes that are
|
|
-- proxied to the client.
|
|
, proxyLOCKCONTENT = const (pure Nothing)
|
|
, proxyUNLOCKCONTENT = pure Nothing
|
|
}
|
|
where
|
|
-- Nodes of the cluster have remote.name.annex-cluster-node
|
|
-- containing its name.
|
|
isnode nodes clusternames r =
|
|
case remoteAnnexClusterNode (Remote.gitconfig r) of
|
|
Nothing -> False
|
|
Just names
|
|
| any (isclustername clusternames) names ->
|
|
flip S.member nodes $
|
|
ClusterNodeUUID $ Remote.uuid r
|
|
| otherwise -> False
|
|
|
|
isclustername clusternames name =
|
|
M.lookup name clusternames == Just clusteruuid
|
|
|
|
nodecontaining remotesides k = do
|
|
locs <- S.fromList <$> loggedLocations k
|
|
case filter (flip S.member locs . remoteUUID) remotesides of
|
|
-- TODO: Avoid always using same remote
|
|
(r:_) -> return (Just r)
|
|
[] -> return Nothing
|
|
|