re-strucuture fediChordInit flow to also do the bootstrapping
This commit is contained in:
parent
12dfc56a73
commit
0ab6ee9c8f
25
app/Main.hs
25
app/Main.hs
|
@ -18,29 +18,10 @@ main = do
|
||||||
-- ToDo: parse and pass config
|
-- ToDo: parse and pass config
|
||||||
-- probably use `tomland` for that
|
-- probably use `tomland` for that
|
||||||
(fConf, sConf) <- readConfig
|
(fConf, sConf) <- readConfig
|
||||||
-- TODO: first initialise 'RealNode', then the vservers
|
|
||||||
-- ToDo: load persisted caches, bootstrapping nodes …
|
-- ToDo: load persisted caches, bootstrapping nodes …
|
||||||
(serverSock, thisNode) <- fediChordInit fConf (runService sConf :: DHT d => d -> IO (PostService d))
|
(fediThreads, thisNode) <- fediChordInit fConf (runService sConf :: DHT d => d -> IO (PostService d))
|
||||||
-- currently no masking is necessary, as there is nothing to clean up
|
-- wait for all DHT threads to terminate, this keeps the main thread running
|
||||||
nodeCacheWriterThread <- forkIO $ nodeCacheWriter thisNode
|
wait fediThreads
|
||||||
-- try joining the DHT using one of the provided bootstrapping nodes
|
|
||||||
joinedState <- tryBootstrapJoining thisNode
|
|
||||||
either (\err -> do
|
|
||||||
-- handle unsuccessful join
|
|
||||||
|
|
||||||
putStrLn $ err <> " Error joining, start listening for incoming requests anyways"
|
|
||||||
print =<< readTVarIO thisNode
|
|
||||||
-- launch thread attempting to join on new cache entries
|
|
||||||
_ <- forkIO $ joinOnNewEntriesThread thisNode
|
|
||||||
wait =<< async (fediMainThreads serverSock thisNode)
|
|
||||||
)
|
|
||||||
(\joinedNS -> do
|
|
||||||
-- launch main eventloop with successfully joined state
|
|
||||||
putStrLn "successful join"
|
|
||||||
wait =<< async (fediMainThreads serverSock thisNode)
|
|
||||||
)
|
|
||||||
joinedState
|
|
||||||
pure ()
|
|
||||||
|
|
||||||
|
|
||||||
readConfig :: IO (FediChordConf, ServiceConf)
|
readConfig :: IO (FediChordConf, ServiceConf)
|
||||||
|
|
|
@ -98,38 +98,59 @@ import Debug.Trace (trace)
|
||||||
fediChordInit :: (Service s (RealNodeSTM s))
|
fediChordInit :: (Service s (RealNodeSTM s))
|
||||||
=> FediChordConf
|
=> FediChordConf
|
||||||
-> (RealNodeSTM s -> IO (s (RealNodeSTM s))) -- ^ runner function for service
|
-> (RealNodeSTM s -> IO (s (RealNodeSTM s))) -- ^ runner function for service
|
||||||
-> IO (Socket, RealNodeSTM s)
|
-> IO (Async (), RealNodeSTM s)
|
||||||
fediChordInit initConf serviceRunner = do
|
fediChordInit initConf serviceRunner = do
|
||||||
emptyLookupCache <- newTVarIO Map.empty
|
emptyLookupCache <- newTVarIO Map.empty
|
||||||
let realNode = RealNode {
|
cacheSTM <- newTVarIO initCache
|
||||||
vservers = HMap.empty
|
cacheQ <- atomically newTQueue
|
||||||
|
let realNode = RealNode
|
||||||
|
{ vservers = HMap.empty
|
||||||
, nodeConfig = initConf
|
, nodeConfig = initConf
|
||||||
, bootstrapNodes = confBootstrapNodes initConf
|
, bootstrapNodes = confBootstrapNodes initConf
|
||||||
, lookupCacheSTM = emptyLookupCache
|
, lookupCacheSTM = emptyLookupCache
|
||||||
, nodeService = undefined
|
, nodeService = undefined
|
||||||
}
|
, globalNodeCacheSTM = cacheSTM
|
||||||
|
, globalCacheWriteQueue = cacheQ
|
||||||
|
}
|
||||||
realNodeSTM <- newTVarIO realNode
|
realNodeSTM <- newTVarIO realNode
|
||||||
|
serverSock <- mkServerSocket (confIP initConf) (fromIntegral $ confDhtPort initConf)
|
||||||
-- launch service and set the reference in the RealNode
|
-- launch service and set the reference in the RealNode
|
||||||
serv <- serviceRunner realNodeSTM
|
serv <- serviceRunner realNodeSTM
|
||||||
atomically . modifyTVar' realNodeSTM $ \rn -> rn { nodeService = serv }
|
atomically . modifyTVar' realNodeSTM $ \rn -> rn { nodeService = serv }
|
||||||
|
-- prepare for joining: start node cache writer thread
|
||||||
|
-- currently no masking is necessary, as there is nothing to clean up
|
||||||
|
nodeCacheWriterThread <- forkIO $ nodeCacheWriter realNodeSTM
|
||||||
-- TODO: k-choices way of joining, so far just initialise a single vserver
|
-- TODO: k-choices way of joining, so far just initialise a single vserver
|
||||||
firstVS <- nodeStateInit realNodeSTM
|
firstVS <- nodeStateInit realNodeSTM 0
|
||||||
firstVSSTM <- newTVarIO firstVS
|
firstVSSTM <- newTVarIO firstVS
|
||||||
-- add vserver to list at RealNode
|
-- add vserver to list at RealNode
|
||||||
atomically . modifyTVar' realNodeSTM $ \rn -> rn { vservers = HMap.insert (getNid firstVS) firstVSSTM (vservers rn) }
|
atomically . modifyTVar' realNodeSTM $ \rn -> rn { vservers = HMap.insert (getNid firstVS) firstVSSTM (vservers rn) }
|
||||||
serverSock <- mkServerSocket (confIP initConf) (fromIntegral $ confDhtPort initConf)
|
-- try joining the DHT using one of the provided bootstrapping nodes
|
||||||
pure (serverSock, realNodeSTM)
|
joinedState <- tryBootstrapJoining firstVSSTM
|
||||||
|
fediThreadsAsync <- either (\err -> do
|
||||||
|
-- handle unsuccessful join
|
||||||
|
|
||||||
|
putStrLn $ err <> " Error joining, start listening for incoming requests anyways"
|
||||||
|
-- launch thread attempting to join on new cache entries
|
||||||
|
_ <- forkIO $ joinOnNewEntriesThread firstVSSTM
|
||||||
|
async (fediMainThreads serverSock firstVSSTM)
|
||||||
|
)
|
||||||
|
(\joinedNS -> do
|
||||||
|
-- launch main eventloop with successfully joined state
|
||||||
|
putStrLn "successful join"
|
||||||
|
async (fediMainThreads serverSock firstVSSTM)
|
||||||
|
)
|
||||||
|
joinedState
|
||||||
|
pure (fediThreadsAsync, realNodeSTM)
|
||||||
|
|
||||||
-- | initialises the 'NodeState' for this local node.
|
-- | initialises the 'NodeState' for this local node.
|
||||||
-- Separated from 'fediChordInit' to be usable in tests.
|
-- Separated from 'fediChordInit' to be usable in tests.
|
||||||
nodeStateInit :: Service s (RealNodeSTM s) => RealNodeSTM s -> IO (LocalNodeState s)
|
nodeStateInit :: Service s (RealNodeSTM s) => RealNodeSTM s -> Integer -> IO (LocalNodeState s)
|
||||||
nodeStateInit realNodeSTM = do
|
nodeStateInit realNodeSTM vsID' = do
|
||||||
realNode <- readTVarIO realNodeSTM
|
realNode <- readTVarIO realNodeSTM
|
||||||
cacheSTM <- newTVarIO initCache
|
|
||||||
q <- atomically newTQueue
|
|
||||||
let
|
let
|
||||||
conf = nodeConfig realNode
|
conf = nodeConfig realNode
|
||||||
vsID = 0
|
vsID = vsID'
|
||||||
containedState = RemoteNodeState {
|
containedState = RemoteNodeState {
|
||||||
domain = confDomain conf
|
domain = confDomain conf
|
||||||
, ipAddr = confIP conf
|
, ipAddr = confIP conf
|
||||||
|
@ -140,8 +161,8 @@ nodeStateInit realNodeSTM = do
|
||||||
}
|
}
|
||||||
initialState = LocalNodeState {
|
initialState = LocalNodeState {
|
||||||
nodeState = containedState
|
nodeState = containedState
|
||||||
, nodeCacheSTM = cacheSTM
|
, nodeCacheSTM = globalNodeCacheSTM realNode
|
||||||
, cacheWriteQueue = q
|
, cacheWriteQueue = globalCacheWriteQueue realNode
|
||||||
, successors = []
|
, successors = []
|
||||||
, predecessors = []
|
, predecessors = []
|
||||||
, kNeighbours = 3
|
, kNeighbours = 3
|
||||||
|
@ -336,12 +357,12 @@ joinOnNewEntriesThread nsSTM = loop
|
||||||
|
|
||||||
-- | cache updater thread that waits for incoming NodeCache update instructions on
|
-- | cache updater thread that waits for incoming NodeCache update instructions on
|
||||||
-- the node's cacheWriteQueue and then modifies the NodeCache as the single writer.
|
-- the node's cacheWriteQueue and then modifies the NodeCache as the single writer.
|
||||||
nodeCacheWriter :: LocalNodeStateSTM s -> IO ()
|
nodeCacheWriter :: RealNodeSTM s -> IO ()
|
||||||
nodeCacheWriter nsSTM =
|
nodeCacheWriter nodeSTM = do
|
||||||
|
node <- readTVarIO nodeSTM
|
||||||
forever $ atomically $ do
|
forever $ atomically $ do
|
||||||
ns <- readTVar nsSTM
|
cacheModifier <- readTQueue $ globalCacheWriteQueue node
|
||||||
cacheModifier <- readTQueue $ cacheWriteQueue ns
|
modifyTVar' (globalNodeCacheSTM node) cacheModifier
|
||||||
modifyTVar' (nodeCacheSTM ns) cacheModifier
|
|
||||||
|
|
||||||
|
|
||||||
-- | Periodically iterate through cache, clean up expired entries and verify unverified ones
|
-- | Periodically iterate through cache, clean up expired entries and verify unverified ones
|
||||||
|
|
|
@ -161,6 +161,13 @@ data RealNode s = RealNode
|
||||||
-- ^ nodes to be used as bootstrapping points, new ones learned during operation
|
-- ^ nodes to be used as bootstrapping points, new ones learned during operation
|
||||||
, lookupCacheSTM :: TVar LookupCache
|
, lookupCacheSTM :: TVar LookupCache
|
||||||
-- ^ a global cache of looked up keys and their associated nodes
|
-- ^ a global cache of looked up keys and their associated nodes
|
||||||
|
, globalNodeCacheSTM :: TVar NodeCache
|
||||||
|
-- ^ EpiChord node cache with expiry times for nodes.
|
||||||
|
-- Shared between all vservers, each 'LocalNodeState' holds a reference to
|
||||||
|
-- the same TVar for avoiding unnecessary reads of parent node
|
||||||
|
, globalCacheWriteQueue :: TQueue (NodeCache -> NodeCache)
|
||||||
|
-- ^ cache updates are not written directly to the 'globalNodeCacheSTM'
|
||||||
|
-- but queued and processed by a single thread
|
||||||
, nodeService :: s (RealNodeSTM s)
|
, nodeService :: s (RealNodeSTM s)
|
||||||
}
|
}
|
||||||
|
|
||||||
|
@ -190,9 +197,9 @@ data LocalNodeState s = LocalNodeState
|
||||||
{ nodeState :: RemoteNodeState
|
{ nodeState :: RemoteNodeState
|
||||||
-- ^ represents common data present both in remote and local node representations
|
-- ^ represents common data present both in remote and local node representations
|
||||||
, nodeCacheSTM :: TVar NodeCache
|
, nodeCacheSTM :: TVar NodeCache
|
||||||
-- ^ EpiChord node cache with expiry times for nodes
|
-- ^ reference to the 'globalNodeCacheSTM'
|
||||||
, cacheWriteQueue :: TQueue (NodeCache -> NodeCache)
|
, cacheWriteQueue :: TQueue (NodeCache -> NodeCache)
|
||||||
-- ^ cache updates are not written directly to the 'nodeCache' but queued and
|
-- ^ reference to the 'globalCacheWriteQueue
|
||||||
, successors :: [RemoteNodeState] -- could be a set instead as these are ordered as well
|
, successors :: [RemoteNodeState] -- could be a set instead as these are ordered as well
|
||||||
-- ^ successor nodes in ascending order by distance
|
-- ^ successor nodes in ascending order by distance
|
||||||
, predecessors :: [RemoteNodeState]
|
, predecessors :: [RemoteNodeState]
|
||||||
|
|
Loading…
Reference in a new issue