Compare commits

..

No commits in common. "d293cc05d148ebe7b9019afffcfdab5ff44719d5" and "e91f317a8e3346b381f85ad8380e14b4b374ddce" have entirely different histories.

4 changed files with 16 additions and 57 deletions

View file

@ -16,13 +16,10 @@ main = do
-- ToDo: parse and pass config
-- probably use `tomland` for that
conf <- readConfig
-- TODO: first initialise 'RealNode', then the vservers
-- ToDo: load persisted caches, bootstrapping nodes …
(serverSock, thisNode) <- fediChordInit conf
-- currently no masking is necessary, as there is nothing to clean up
cacheWriterThread <- forkIO $ cacheWriter thisNode
thisNodeSnap <- readTVarIO thisNode
realNode <- readTVarIO $ parentRealNode thisNodeSnap
-- try joining the DHT using one of the provided bootstrapping nodes
let
tryJoining (bn:bns) = do
@ -31,7 +28,7 @@ main = do
Left err -> putStrLn ("join error: " <> err) >> tryJoining bns
Right joined -> pure $ Right joined
tryJoining [] = pure $ Left "Exhausted all bootstrap points for joining."
joinedState <- tryJoining $ bootstrapNodes realNode
joinedState <- tryJoining $ confBootstrapNodes conf
either (\err -> do
-- handle unsuccessful join

View file

@ -41,7 +41,6 @@ module Hash2Pub.FediChord (
, fediChordJoin
, fediChordBootstrapJoin
, fediMainThreads
, RealNode (..)
, nodeStateInit
, mkServerSocket
, mkSendSocket
@ -91,36 +90,27 @@ import Debug.Trace (trace)
-- | initialise data structures, compute own IDs and bind to listening socket
-- ToDo: load persisted state, thus this function already operates in IO
fediChordInit :: FediChordConf -> IO (Socket, LocalNodeStateSTM)
fediChordInit initConf = do
let realNode = RealNode {
vservers = []
, nodeConfig = initConf
, bootstrapNodes = confBootstrapNodes initConf
}
realNodeSTM <- newTVarIO realNode
initialState <- nodeStateInit realNodeSTM
fediChordInit conf = do
initialState <- nodeStateInit conf
initialStateSTM <- newTVarIO initialState
serverSock <- mkServerSocket (getIpAddr initialState) (getDhtPort initialState)
pure (serverSock, initialStateSTM)
-- | initialises the 'NodeState' for this local node.
-- Separated from 'fediChordInit' to be usable in tests.
nodeStateInit :: RealNodeSTM -> IO LocalNodeState
nodeStateInit realNodeSTM = do
realNode <- readTVarIO realNodeSTM
nodeStateInit :: FediChordConf -> IO LocalNodeState
nodeStateInit conf = do
cacheSTM <- newTVarIO initCache
q <- atomically newTQueue
let
conf = nodeConfig realNode
vsID = 0
containedState = RemoteNodeState {
domain = confDomain conf
, ipAddr = confIP conf
, nid = genNodeID (confIP conf) (confDomain conf) $ fromInteger vsID
, nid = genNodeID (confIP conf) (confDomain conf) 0
, dhtPort = toEnum $ confDhtPort conf
, servicePort = 0
, vServerID = vsID
}
, vServerID = 0
}
initialState = LocalNodeState {
nodeState = containedState
, nodeCacheSTM = cacheSTM
@ -131,7 +121,6 @@ nodeStateInit realNodeSTM = do
, lNumBestNodes = 3
, pNumParallelQueries = 2
, jEntriesPerSlice = 2
, parentRealNode = realNodeSTM
}
pure initialState
@ -198,7 +187,7 @@ joinOnNewEntriesThread nsSTM = loop
case queryLocalCache nsSnap cache 1 (getNid nsSnap) of
-- empty cache, block until cache changes and then retry
(FORWARD s) | Set.null s -> retry
result -> pure (result, cache)
result -> pure (result, cache)
case lookupResult of
-- already joined
FOUND _ -> do

View file

@ -13,8 +13,6 @@ module Hash2Pub.FediChordTypes (
, LocalNodeState (..)
, LocalNodeStateSTM
, RemoteNodeState (..)
, RealNode (..)
, RealNodeSTM
, setSuccessors
, setPredecessors
, NodeCache
@ -134,19 +132,6 @@ a `localCompare` b
wayForwards = getNodeID (b - a)
wayBackwards = getNodeID (a - b)
-- | Data for managing the virtual server nodes of this real node.
-- Also contains shared data and config values.
-- TODO: more data structures for k-choices bookkeeping
data RealNode = RealNode
{ vservers :: [LocalNodeStateSTM]
-- ^ references to all active versers
, nodeConfig :: FediChordConf
-- ^ holds the initial configuration read at program start
, bootstrapNodes :: [(String, PortNumber)]
-- ^ nodes to be used as bootstrapping points, new ones learned during operation
}
type RealNodeSTM = TVar RealNode
-- | represents a node and all its important state
data RemoteNodeState = RemoteNodeState
@ -187,8 +172,6 @@ data LocalNodeState = LocalNodeState
-- ^ number of parallel sent queries
, jEntriesPerSlice :: Int
-- ^ number of desired entries per cache slice
, parentRealNode :: RealNodeSTM
-- ^ the parent node managing this vserver instance
}
deriving (Show, Eq)

View file

@ -1,13 +1,12 @@
{-# LANGUAGE OverloadedStrings #-}
module FediChordSpec where
import Control.Concurrent.STM.TVar
import Control.Exception
import Data.ASN1.Parse (runParseASN1)
import qualified Data.ByteString as BS
import qualified Data.Map.Strict as Map
import Data.Maybe (fromJust, isJust)
import qualified Data.Set as Set
import Data.ASN1.Parse (runParseASN1)
import qualified Data.ByteString as BS
import qualified Data.Map.Strict as Map
import Data.Maybe (fromJust, isJust)
import qualified Data.Set as Set
import Data.Time.Clock.POSIX
import Network.Socket
import Test.Hspec
@ -293,20 +292,11 @@ exampleNodeState = RemoteNodeState {
}
exampleLocalNode :: IO LocalNodeState
exampleLocalNode = nodeStateInit =<< (newTVarIO $ RealNode {
vservers = []
, nodeConfig = exampleFediConf
, bootstrapNodes = confBootstrapNodes exampleFediConf
})
exampleFediConf :: FediChordConf
exampleFediConf = FediChordConf {
exampleLocalNode = nodeStateInit $ FediChordConf {
confDomain = "example.social"
, confIP = exampleIp
, confDhtPort = 2342
}
exampleNodeDomain :: String
exampleNodeDomain = "example.social"
exampleVs :: (Integral i) => i