local cache query lookup + some validation considerations

no unit tests done so far
This commit is contained in:
Trolli Schmittlauch 2020-04-11 22:21:31 +02:00
parent e13dac4ded
commit 8d9697c1ef
3 changed files with 58 additions and 1 deletions

View file

@ -58,7 +58,7 @@ library
exposed-modules: Hash2Pub.FediChord exposed-modules: Hash2Pub.FediChord
-- Modules included in this library but not exported. -- Modules included in this library but not exported.
other-modules: Hash2Pub.Utils other-modules: Hash2Pub.Utils, Hash2Pub.DHTProtocol
-- LANGUAGE extensions used by modules in this package. -- LANGUAGE extensions used by modules in this package.
other-extensions: GeneralizedNewtypeDeriving, DataKinds, OverloadedStrings other-extensions: GeneralizedNewtypeDeriving, DataKinds, OverloadedStrings

View file

@ -0,0 +1,49 @@
{-# LANGUAGE OverloadedStrings #-}
module Hash2Pub.DHTProtocol
( QueryResponse (..)
, incomingQuery
)
where
import Data.Maybe (catMaybes)
import qualified Data.Map.Strict as M
import Hash2Pub.FediChord
( NodeID
, NodeState (..)
, cacheGetNodeStateUnvalidated
, NodeCache
, CacheEntry
)
data QueryResponse = FORWARD [CacheEntry] -- ^return closest nodes from local cache.
-- whole cache entry is returned for making
-- the entry time stamp available to the
-- protocol serialiser
| FOUND NodeState -- ^node is the responsible node for queried ID
-- TODO: evaluate more fine-grained argument passing to allow granular locking
-- | look up an ID to either claim responsibility for it or return the closest l nodes from the local cache
incomingQuery :: NodeState -> NodeCache -> Int -> NodeID -> QueryResponse
incomingQuery ownState nCache lBestNodes targetID
-- as target ID falls between own ID and first predecessor, it is handled by this node
| targetID <= nid ownState && targetID > (head . predecessors) ownState = FOUND ownState
-- my interpretation: the "l best next hops" are the l-1 closest preceding nodes and
-- the closest succeeding node (like with the p initiated parallel queries
| otherwise = FORWARD . catMaybes $ closestSuccessor : closestPredecessors
where
closestSuccessor :: Maybe CacheEntry
closestSuccessor = snd <$> M.lookupGT targetID nCache
closestPredecessors :: [Maybe CacheEntry]
closestPredecessors = closestPredecessor (lBestNodes-1) $ nid ownState
closestPredecessor :: (Integral n) => n -> NodeID -> [Maybe CacheEntry]
closestPredecessor 0 _ = []
closestPredecessor remainingLookups lastID =
let result = predecessorLookup nCache lastID
in
case result of
Nothing -> []
Just nPred -> result:closestPredecessor (remainingLookups-1) (nid . cacheGetNodeStateUnvalidated $ nPred)
predecessorLookup :: NodeCache -> NodeID -> Maybe CacheEntry
predecessorLookup nCache' lastID = snd <$> M.lookupLT lastID nCache'

View file

@ -14,7 +14,9 @@ module Hash2Pub.FediChord (
, getNodeID , getNodeID
, toNodeID , toNodeID
, NodeState (..) , NodeState (..)
, NodeCache
, CacheEntry , CacheEntry
, cacheGetNodeStateUnvalidated
, genNodeID , genNodeID
, genNodeIDBS , genNodeIDBS
, genKeyID , genKeyID
@ -100,7 +102,9 @@ data NodeState = NodeState {
-- ^ EpiChord node cache with expiry times for nodes -- ^ EpiChord node cache with expiry times for nodes
-- as the map is ordered, lookups for the closes preceding node can be done using @lookupLT@ -- as the map is ordered, lookups for the closes preceding node can be done using @lookupLT@
, successors :: [NodeID] -- could be a set instead as these are ordered as well , successors :: [NodeID] -- could be a set instead as these are ordered as well
-- ^ successor nodes in ascending order by distance
, predecessors :: [NodeID] , predecessors :: [NodeID]
-- ^ predecessor nodes in ascending order by distance
----- protocol parameters ----- ----- protocol parameters -----
-- TODO: evaluate moving these somewhere else -- TODO: evaluate moving these somewhere else
, kNeighbours :: Int , kNeighbours :: Int
@ -126,6 +130,10 @@ type CacheEntry = (
, SystemTime , SystemTime
) -- ^ ( a node's validation status, data, timestamp for cache entry expiration ) ) -- ^ ( a node's validation status, data, timestamp for cache entry expiration )
-- | return the @NodeState@ data from a cache entry without checking its validation status
cacheGetNodeStateUnvalidated :: CacheEntry -> NodeState
cacheGetNodeStateUnvalidated (_, nState, _) = nState
-- | generates a 256 bit long NodeID using SHAKE128, represented as ByteString -- | generates a 256 bit long NodeID using SHAKE128, represented as ByteString
genNodeIDBS :: HostAddress6 -- ^a node's IPv6 address genNodeIDBS :: HostAddress6 -- ^a node's IPv6 address
-> String -- ^a node's 1st and 2nd level domain name -> String -- ^a node's 1st and 2nd level domain name