rename isJoined
to reflect its scope on a single VS
This should be enough to close #76, as it was only used in the scope of a single LocalNodeState anyways.
This commit is contained in:
parent
0ee8f0dc43
commit
c208aeceaa
|
@ -38,7 +38,7 @@ module Hash2Pub.DHTProtocol
|
|||
, isPossibleSuccessor
|
||||
, isPossiblePredecessor
|
||||
, isInOwnResponsibilitySlice
|
||||
, isJoined
|
||||
, vsIsJoined
|
||||
, closestCachePredecessors
|
||||
)
|
||||
where
|
||||
|
@ -109,7 +109,7 @@ queryLocalCache ownState nCache lBestNodes targetID
|
|||
-- as target ID falls between own ID and first predecessor, it is handled by this node
|
||||
-- This only makes sense if the node is part of the DHT by having joined.
|
||||
-- A default answer to nodes querying an unjoined node is provided by 'respondQueryID'.
|
||||
| isJoined ownState && targetID `isInOwnResponsibilitySlice` ownState = FOUND . toRemoteNodeState $ ownState
|
||||
| vsIsJoined ownState && targetID `isInOwnResponsibilitySlice` ownState = FOUND . toRemoteNodeState $ ownState
|
||||
-- my interpretation: the "l best next hops" are the l-1 closest preceding nodes and
|
||||
-- the closest succeeding node (like with the p initiated parallel queries
|
||||
| otherwise = FORWARD $ closestSuccessor `Set.union` closestCachePredecessors (lBestNodes-1) targetID nCache
|
||||
|
@ -233,8 +233,8 @@ markCacheEntryAsVerified timestamp nid = RingMap . Map.adjust adjustFunc nid . g
|
|||
|
||||
-- | uses the successor and predecessor list of a node as an indicator for whether a
|
||||
-- node has properly joined the DHT
|
||||
isJoined :: LocalNodeState s -> Bool
|
||||
isJoined ns = not . all null $ [successors ns, predecessors ns]
|
||||
vsIsJoined :: LocalNodeState s -> Bool
|
||||
vsIsJoined ns = not . all null $ [successors ns, predecessors ns]
|
||||
|
||||
-- | the size limit to be used when serialising messages for sending
|
||||
sendMessageSize :: Num i => i
|
||||
|
@ -291,9 +291,9 @@ handleIncomingRequest nsSTM sendQ msgSet sourceAddr = do
|
|||
-- ToDo: figure out what happens if not joined
|
||||
QueryID -> Just <$> respondQueryID nsSTM msgSet
|
||||
-- only when joined
|
||||
Leave -> if isJoined ns then dropSpoofedIDs sourceIP nsSTM msgSet respondLeave else pure Nothing
|
||||
Stabilise -> if isJoined ns then dropSpoofedIDs sourceIP nsSTM msgSet respondStabilise else pure Nothing
|
||||
QueryLoad -> if isJoined ns then Just <$> respondQueryLoad nsSTM msgSet else pure Nothing
|
||||
Leave -> if vsIsJoined ns then dropSpoofedIDs sourceIP nsSTM msgSet respondLeave else pure Nothing
|
||||
Stabilise -> if vsIsJoined ns then dropSpoofedIDs sourceIP nsSTM msgSet respondStabilise else pure Nothing
|
||||
QueryLoad -> if vsIsJoined ns then Just <$> respondQueryLoad nsSTM msgSet else pure Nothing
|
||||
)
|
||||
-- for single part request, response starts with part number 1. For multipart requests, response starts with part number n+1.
|
||||
|
||||
|
@ -341,7 +341,7 @@ respondQueryID nsSTM msgSet = do
|
|||
cache <- readTVar $ nodeCacheSTM nsSnap
|
||||
let
|
||||
responsePayload = QueryIDResponsePayload {
|
||||
queryResult = if isJoined nsSnap
|
||||
queryResult = if vsIsJoined nsSnap
|
||||
then queryLocalCache nsSnap cache (fromIntegral $ queryLBestNodes senderPayload') (queryTargetID senderPayload')
|
||||
-- if not joined yet, attract responsibility for
|
||||
-- all keys to make bootstrapping possible
|
||||
|
@ -487,7 +487,7 @@ respondJoin nsSTM msgSet = do
|
|||
senderNS = sender aRequestPart
|
||||
-- if not joined yet, attract responsibility for
|
||||
-- all keys to make bootstrapping possible
|
||||
responsibilityLookup = if isJoined nsSnap then queryLocalCache nsSnap cache 1 (getNid senderNS) else FOUND (toRemoteNodeState nsSnap)
|
||||
responsibilityLookup = if vsIsJoined nsSnap then queryLocalCache nsSnap cache 1 (getNid senderNS) else FOUND (toRemoteNodeState nsSnap)
|
||||
thisNodeResponsible (FOUND _) = True
|
||||
thisNodeResponsible (FORWARD _) = False
|
||||
-- check whether the joining node falls into our responsibility
|
||||
|
|
|
@ -215,7 +215,7 @@ kChoicesNodeJoin nodeSTM bootstrapNode = do
|
|||
initialJoins = confKChoicesMaxVS conf `div` 2
|
||||
-- edge case: however small the target is, at least join 1 vs
|
||||
-- kCoicesVsJoin until target is met – unless there's already an active & joined VS causing enough load
|
||||
alreadyJoinedVss <- liftIO $ foldM (\sumAcc vsSTM -> readTVarIO vsSTM >>= (\vs -> pure . (+) sumAcc $ if isJoined vs then 1 else 0)) 0 $ vservers node
|
||||
alreadyJoinedVss <- liftIO $ foldM (\sumAcc vsSTM -> readTVarIO vsSTM >>= (\vs -> pure . (+) sumAcc $ if vsIsJoined vs then 1 else 0)) 0 $ vservers node
|
||||
unless (alreadyJoinedVss > 0 && compensatedLoadSum ownLoadStats >= joinLoadTarget) $ do
|
||||
joinedVss <- vsJoins vs0STM (totalCapacity ownLoadStats) (vservers node) joinLoadTarget (fromIntegral initialJoins - alreadyJoinedVss) nodeSTM
|
||||
if HMap.null joinedVss
|
||||
|
@ -339,7 +339,7 @@ convergenceSampleThread nodeSTM = forever $ do
|
|||
forM_ (vservers node) $ \nsSTM -> do
|
||||
nsSnap <- readTVarIO nsSTM
|
||||
parentNode <- readTVarIO $ parentRealNode nsSnap
|
||||
if isJoined nsSnap
|
||||
if vsIsJoined nsSnap
|
||||
then
|
||||
runExceptT (do
|
||||
-- joined node: choose random node, do queryIDLoop, compare result with own responsibility
|
||||
|
@ -647,7 +647,7 @@ checkCacheSliceInvariants :: LocalNodeState s
|
|||
-> [NodeID] -- ^ list of middle IDs of slices not
|
||||
-- ^ fulfilling the invariant
|
||||
checkCacheSliceInvariants ns
|
||||
| isJoined ns = checkPredecessorSlice jEntries (getNid ns) startBound lastPred <> checkSuccessorSlice jEntries (getNid ns) startBound lastSucc
|
||||
| vsIsJoined ns = checkPredecessorSlice jEntries (getNid ns) startBound lastPred <> checkSuccessorSlice jEntries (getNid ns) startBound lastSucc
|
||||
| otherwise = const []
|
||||
where
|
||||
jEntries = jEntriesPerSlice ns
|
||||
|
|
Loading…
Reference in a new issue