forked from schmittlauch/Hash2Pub
choose and implement data structures for node state and cache
This commit is contained in:
parent
ce4cc385b8
commit
3f9452ab7e
|
@ -11,6 +11,15 @@ Modernised EpiChord + k-choices load balancing
|
|||
|
||||
module Hash2Pub.FediChord where
|
||||
|
||||
import qualified Data.Map.Strict as Map
|
||||
import qualified Data.String.UTF8 as U8S
|
||||
import Network.Socket
|
||||
import Data.Time.Clock.System
|
||||
|
||||
-- define protocol constants
|
||||
idBits :: Integer
|
||||
idBits = 256
|
||||
|
||||
newtype NodeID = NodeID { getNodeID :: Integer } deriving (Eq, Show, Enum)
|
||||
|
||||
instance Bounded NodeID where
|
||||
|
@ -26,9 +35,50 @@ instance Num NodeID where
|
|||
signum = NodeID . signum . getNodeID
|
||||
abs = NodeID . abs . getNodeID -- ToDo: make sure that at creation time only IDs within the range are used
|
||||
|
||||
-- Todo: Num Instanz selbst definieren
|
||||
-- Todo: Ist es sinnvoll, das hier Teil von Ord zu machen?
|
||||
-- NodeIDs on a ring are assigned an Ordering for finding a preceding node
|
||||
-- main idea: a node is preceding (LT) if the way forwards to the other node is smaller than the way backwards
|
||||
-- problem: equality of ways /= (a == b), so even equal-way paths don't return EQ. The equality-of-ways case is assigned to LT,
|
||||
-- as preceding EpiChord nodes are nodes <=.
|
||||
instance Ord NodeID where
|
||||
a `compare` b
|
||||
| getNodeID a == getNodeID b = EQ
|
||||
| wayForwards <= wayBackwards = LT
|
||||
| wayForwards > wayBackwards = GT
|
||||
where
|
||||
wayForwards = getNodeID (b - a)
|
||||
wayBackwards = getNodeID (a - b)
|
||||
|
||||
-- define protocol constants
|
||||
idBits :: Integer
|
||||
idBits = 256
|
||||
data NodeState = NodeState {
|
||||
id :: NodeID
|
||||
, domain :: String
|
||||
-- ^ full public domain name the node is reachable under
|
||||
, ipAddr :: HostAddress6
|
||||
-- the node's public IPv6 address
|
||||
, dhtPort :: PortNumber
|
||||
-- ^ port of the DHT itself
|
||||
, apPort :: Maybe PortNumber
|
||||
-- ^ port of the ActivityPub relay and storage service
|
||||
-- might have to be queried first
|
||||
, nodeCache :: Map.Map NodeID CacheEntry
|
||||
-- ^ EpiChord node cache with expiry times for nodes
|
||||
-- as the map is ordered, lookups for the closes preceding node can be done using `lookupLE`
|
||||
, successors :: [NodeID]
|
||||
, predecessors :: [NodeID]
|
||||
----- protocol parameters -----
|
||||
-- TODO: evaluate moving these somewhere else
|
||||
, kNeighbours :: Int
|
||||
-- ^ desired length of predecessor and successor list
|
||||
-- needs to be parameterisable for simulation purposes
|
||||
, lNumBestNodes :: Int
|
||||
-- ^ number of best next hops to provide
|
||||
-- needs to be parameterisable for simulation purposes
|
||||
, pNumParallelQueries :: Int
|
||||
-- ^ number of parallel sent queries
|
||||
-- needs to be parameterisable for simulation purposes
|
||||
}
|
||||
|
||||
type CacheEntry = ( NodeState, SystemTime)
|
||||
|
||||
-- Todo: DHT backend can learn potential initial bootstrapping points through the instances mentioned in the received AP-relay messages
|
||||
-- needs to know its own domain anyways for ID generation
|
||||
-- persist them on disk so they can be used for all following bootstraps
|
||||
|
|
|
@ -6,6 +6,13 @@ pkgs.mkShell {
|
|||
(pkgs.haskellPackages.ghcWithPackages (pkgs: with pkgs;
|
||||
[
|
||||
mtl
|
||||
cmdargs
|
||||
cryptonite # cryptographic hash functions
|
||||
utf8-string # could also be done with Data.Text
|
||||
HUnit
|
||||
network # sockets
|
||||
network-info # for getting local IP address
|
||||
time
|
||||
]))
|
||||
];
|
||||
}
|
||||
|
|
Loading…
Reference in a new issue