rename join function to clarify it just joining a single vserver

This commit is contained in:
Trolli Schmittlauch 2020-08-15 17:37:06 +02:00
parent 8db8907163
commit d2e4359a21
2 changed files with 11 additions and 13 deletions

View file

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