rename join function to clarify it just joining a single vserver
This commit is contained in:
parent
8db8907163
commit
d2e4359a21
|
@ -3,7 +3,6 @@
|
|||
{-# LANGUAGE FlexibleContexts #-}
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TypeSynonymInstances #-}
|
||||
{- |
|
||||
Module : FediChord
|
||||
Description : An opinionated implementation of the EpiChord DHT by Leong et al.
|
||||
|
@ -40,7 +39,7 @@ module Hash2Pub.FediChord (
|
|||
, bsAsIpAddr
|
||||
, FediChordConf(..)
|
||||
, fediChordInit
|
||||
, fediChordJoin
|
||||
, fediChordVserverJoin
|
||||
, fediChordBootstrapJoin
|
||||
, tryBootstrapJoining
|
||||
, fediMainThreads
|
||||
|
@ -250,10 +249,10 @@ bootstrapQueryId nsSTM (bootstrapHost, bootstrapPort) targetID = do
|
|||
|
||||
-- | join a node to the DHT using the global node cache
|
||||
-- node's position.
|
||||
fediChordJoin :: LocalNodeStateSTM s -- ^ the local 'NodeState'
|
||||
fediChordVserverJoin :: LocalNodeStateSTM s -- ^ the local 'NodeState'
|
||||
-> IO (Either String (LocalNodeStateSTM s)) -- ^ the joined 'NodeState' after a
|
||||
-- successful join, otherwise an error message
|
||||
fediChordJoin nsSTM = do
|
||||
fediChordVserverJoin nsSTM = do
|
||||
ns <- readTVarIO nsSTM
|
||||
-- 1. get routed to the currently responsible node
|
||||
currentlyResponsible <- requestQueryID ns $ getNid ns
|
||||
|
@ -284,14 +283,13 @@ joinOnNewEntriesThread nsSTM = loop
|
|||
pure ()
|
||||
-- otherwise try joining
|
||||
FORWARD _ -> do
|
||||
joinResult <- fediChordJoin nsSTM
|
||||
joinResult <- fediChordVserverJoin nsSTM
|
||||
either
|
||||
-- on join failure, sleep and retry
|
||||
-- TODO: make delay configurable
|
||||
(const $ threadDelay (30 * 10^6) >> loop)
|
||||
(const $ pure ())
|
||||
joinResult
|
||||
emptyset = Set.empty -- because pattern matches don't accept qualified names
|
||||
|
||||
|
||||
-- | cache updater thread that waits for incoming NodeCache update instructions on
|
||||
|
@ -485,7 +483,7 @@ stabiliseThread nsSTM = forever $ do
|
|||
threadDelay (60 * 10^6)
|
||||
where
|
||||
-- | send a stabilise request to the n-th neighbour
|
||||
-- (specified by the provided getter function) and on failure retr
|
||||
-- (specified by the provided getter function) and on failure retry
|
||||
-- with the n+1-th neighbour.
|
||||
-- On success, return 2 lists: The failed nodes and the potential neighbours
|
||||
-- returned by the queried node.
|
||||
|
|
Loading…
Reference in a new issue