adjust tests to usage of RemoteCacheEntry

This commit is contained in:
Trolli Schmittlauch 2020-05-08 23:31:57 +02:00
parent e4d350b8fb
commit 666a9602ba
2 changed files with 28 additions and 14 deletions

View file

@ -7,6 +7,7 @@ module Hash2Pub.DHTProtocol
, deleteCacheEntry , deleteCacheEntry
, RemoteCacheEntry(..) , RemoteCacheEntry(..)
, toRemoteCacheEntry , toRemoteCacheEntry
, remoteNode_
, Action(..) , Action(..)
, ActionPayload(..) , ActionPayload(..)
, FediChordMessage(..) , FediChordMessage(..)
@ -148,6 +149,10 @@ toRemoteCacheEntry (NodeEntry _ ns ts) = Just $ RemoteCacheEntry ns ts
toRemoteCacheEntry (ProxyEntry _ (Just entry@NodeEntry{})) = toRemoteCacheEntry entry toRemoteCacheEntry (ProxyEntry _ (Just entry@NodeEntry{})) = toRemoteCacheEntry entry
toRemoteCacheEntry _ = Nothing toRemoteCacheEntry _ = Nothing
-- helper function for use in tests
remoteNode_ :: RemoteCacheEntry -> NodeState
remoteNode_ (RemoteCacheEntry ns _) = ns
-- cache operations -- cache operations
-- | update or insert a 'RemoteCacheEntry' into the cache, -- | update or insert a 'RemoteCacheEntry' into the cache,

View file

@ -78,7 +78,7 @@ spec = do
anotherID = toNodeID 2^(230::Integer)+1 anotherID = toNodeID 2^(230::Integer)+1
anotherNode = exampleNodeState { nid = anotherID} anotherNode = exampleNodeState { nid = anotherID}
maxNode = exampleNodeState { nid = maxBound} maxNode = exampleNodeState { nid = maxBound}
newCache = addCacheEntry exampleLocalNode 0 =<< addCacheEntry anotherNode 10 emptyCache newCache = addCacheWrapper (remoteEntryFromNow exampleLocalNode) =<< addCacheWrapper (remoteEntryFromNow anotherNode) emptyCache
it "entries can be added to a node cache and looked up again" $ do it "entries can be added to a node cache and looked up again" $ do
nC <- newCache nC <- newCache
-- the cache includes 2 additional proxy elements right from the start -- the cache includes 2 additional proxy elements right from the start
@ -90,7 +90,7 @@ spec = do
cacheLookup minBound emptyCache `shouldBe` Nothing cacheLookup minBound emptyCache `shouldBe` Nothing
cacheLookup maxBound emptyCache `shouldBe` Nothing cacheLookup maxBound emptyCache `shouldBe` Nothing
-- now store a node at that ID -- now store a node at that ID
cacheWithMaxNode <- addCacheEntry maxNode 0 =<< newCache cacheWithMaxNode <- addCacheWrapper (remoteEntryFromNow maxNode) =<< newCache
nid . cacheGetNodeStateUnvalidated <$> cacheLookup maxBound cacheWithMaxNode `shouldBe` Just maxBound nid . cacheGetNodeStateUnvalidated <$> cacheLookup maxBound cacheWithMaxNode `shouldBe` Just maxBound
it "looking up predecessor and successor works like on a modular ring" $ do it "looking up predecessor and successor works like on a modular ring" $ do
-- ignore empty proxy elements in initial cache -- ignore empty proxy elements in initial cache
@ -107,11 +107,11 @@ spec = do
nid. cacheGetNodeStateUnvalidated <$> cacheLookupPred (exampleID - 2) nC `shouldBe` Just anotherID nid. cacheGetNodeStateUnvalidated <$> cacheLookupPred (exampleID - 2) nC `shouldBe` Just anotherID
nid. cacheGetNodeStateUnvalidated <$> cacheLookupSucc (anotherID + 2) nC `shouldBe` Just exampleID nid. cacheGetNodeStateUnvalidated <$> cacheLookupSucc (anotherID + 2) nC `shouldBe` Just exampleID
-- now store a node in one of the ProxyEntries -- now store a node in one of the ProxyEntries
cacheWithProxyNodeEntry <- addCacheEntry maxNode 0 =<< newCache cacheWithProxyNodeEntry <- addCacheWrapper (remoteEntryFromNow maxNode) =<< newCache
nid. cacheGetNodeStateUnvalidated <$> cacheLookupPred (exampleID - 2) cacheWithProxyNodeEntry `shouldBe` Just maxBound nid. cacheGetNodeStateUnvalidated <$> cacheLookupPred (exampleID - 2) cacheWithProxyNodeEntry `shouldBe` Just maxBound
nid. cacheGetNodeStateUnvalidated <$> cacheLookupSucc (anotherID + 2) cacheWithProxyNodeEntry `shouldBe` Just maxBound nid. cacheGetNodeStateUnvalidated <$> cacheLookupSucc (anotherID + 2) cacheWithProxyNodeEntry `shouldBe` Just maxBound
it "entries can be deleted" $ do it "entries can be deleted" $ do
nC <- addCacheEntry maxNode 0 =<< newCache nC <- addCacheWrapper (remoteEntryFromNow maxNode) =<< newCache
let nc' = deleteCacheEntry maxBound . deleteCacheEntry anotherID $ nC let nc' = deleteCacheEntry maxBound . deleteCacheEntry anotherID $ nC
cacheLookup anotherID nc' `shouldBe` Nothing cacheLookup anotherID nc' `shouldBe` Nothing
cacheLookup maxBound nc' `shouldBe` Nothing cacheLookup maxBound nc' `shouldBe` Nothing
@ -128,22 +128,22 @@ spec = do
node3 = exampleNodeState { nid = nid3} node3 = exampleNodeState { nid = nid3}
nid4 = toNodeID 2^(9::Integer)+100 nid4 = toNodeID 2^(9::Integer)+100
node4 = exampleNodeState { nid = nid4} node4 = exampleNodeState { nid = nid4}
cacheWith2Entries = addCacheEntry node1 120 =<< addCacheEntry node2 0 emptyCache cacheWith2Entries = addCacheWrapper (remoteEntryFromNow node1) =<< addCacheWrapper (remoteEntryFromNow node2) emptyCache
cacheWith4Entries = addCacheEntry node3 110 =<< addCacheEntry node4 0 =<< cacheWith2Entries cacheWith4Entries = addCacheWrapper (remoteEntryFromNow node3) =<< addCacheWrapper (remoteEntryFromNow node4) =<< cacheWith2Entries
it "works on an empty cache" $ do it "works on an empty cache" $ do
incomingQuery exampleLocalNode emptyCache 3 (toNodeID 2^(9::Integer)+5) `shouldBe` FORWARD Set.empty incomingQuery exampleLocalNode emptyCache 3 (toNodeID 2^(9::Integer)+5) `shouldBe` FORWARD Set.empty
incomingQuery exampleLocalNode emptyCache 1 (toNodeID 2342) `shouldBe` FORWARD Set.empty incomingQuery exampleLocalNode emptyCache 1 (toNodeID 2342) `shouldBe` FORWARD Set.empty
it "works on a cache with less entries than needed" $ do it "works on a cache with less entries than needed" $ do
c2 <- cacheWith2Entries c2 <- cacheWith2Entries
let (FORWARD nodeset) = incomingQuery exampleLocalNode c2 4 (toNodeID 2^(9::Integer)+5) let (FORWARD nodeset) = incomingQuery exampleLocalNode c2 4 (toNodeID 2^(9::Integer)+5)
Set.map (nid . cacheGetNodeStateUnvalidated) nodeset `shouldBe` Set.fromList [ nid1, nid2 ] Set.map (nid . remoteNode_) nodeset `shouldBe` Set.fromList [ nid1, nid2 ]
it "works on a cache with sufficient entries" $ do it "works on a cache with sufficient entries" $ do
c4 <- cacheWith4Entries c4 <- cacheWith4Entries
let let
(FORWARD nodeset1) = incomingQuery exampleLocalNode c4 3 (toNodeID 2^(9::Integer)+5) (FORWARD nodeset1) = incomingQuery exampleLocalNode c4 3 (toNodeID 2^(9::Integer)+5)
(FORWARD nodeset2) = incomingQuery exampleLocalNode c4 1 (toNodeID 2^(9::Integer)+5) (FORWARD nodeset2) = incomingQuery exampleLocalNode c4 1 (toNodeID 2^(9::Integer)+5)
Set.map (nid . cacheGetNodeStateUnvalidated) nodeset1 `shouldBe` Set.fromList [nid4, nid2, nid3] Set.map (nid . remoteNode_) nodeset1 `shouldBe` Set.fromList [nid4, nid2, nid3]
Set.map (nid . cacheGetNodeStateUnvalidated) nodeset2 `shouldBe` Set.fromList [nid4] Set.map (nid . remoteNode_) nodeset2 `shouldBe` Set.fromList [nid4]
it "recognises the node's own responsibility" $ do it "recognises the node's own responsibility" $ do
nC <- cacheWith4Entries nC <- cacheWith4Entries
incomingQuery node1 nC 3 (toNodeID 2^(22::Integer)) `shouldBe` FOUND node1 incomingQuery node1 nC 3 (toNodeID 2^(22::Integer)) `shouldBe` FOUND node1
@ -151,7 +151,7 @@ spec = do
it "does not fail on nodes without neighbours (initial state)" $ do it "does not fail on nodes without neighbours (initial state)" $ do
nC <- cacheWith4Entries nC <- cacheWith4Entries
let (FORWARD nodeset) = incomingQuery exampleLocalNode nC 3 (toNodeID 11) let (FORWARD nodeset) = incomingQuery exampleLocalNode nC 3 (toNodeID 11)
Set.map (nid . cacheGetNodeStateUnvalidated ) nodeset `shouldBe` Set.fromList [nid4, nid2, nid3] Set.map (nid . remoteNode_ ) nodeset `shouldBe` Set.fromList [nid4, nid2, nid3]
describe "Messages can be encoded to and decoded from ASN.1" $ do describe "Messages can be encoded to and decoded from ASN.1" $ do
-- define test messages -- define test messages
@ -173,16 +173,16 @@ spec = do
} }
qidResPayload2 = QueryIDResponsePayload { qidResPayload2 = QueryIDResponsePayload {
queryResult = FORWARD $ Set.fromList [ queryResult = FORWARD $ Set.fromList [
NodeEntry False exampleNodeState (toEnum 23420001) RemoteCacheEntry exampleNodeState (toEnum 23420001)
, NodeEntry True (exampleNodeState {nid = fromInteger (-5)}) (toEnum 0) , RemoteCacheEntry (exampleNodeState {nid = fromInteger (-5)}) (toEnum 0)
] ]
} }
jResPayload = JoinResponsePayload { jResPayload = JoinResponsePayload {
joinSuccessors = someNodeIDs joinSuccessors = someNodeIDs
, joinPredecessors = someNodeIDs , joinPredecessors = someNodeIDs
, joinCache = [ , joinCache = [
NodeEntry False exampleNodeState (toEnum 23420001) RemoteCacheEntry exampleNodeState (toEnum 23420001)
, NodeEntry True (exampleNodeState {nid = fromInteger (-5)}) (toEnum 0) , RemoteCacheEntry (exampleNodeState {nid = fromInteger (-5)}) (toEnum 0)
] ]
} }
lResPayload = LeaveResponsePayload lResPayload = LeaveResponsePayload
@ -263,4 +263,13 @@ exampleVs = 4
exampleIp :: HostAddress6 exampleIp :: HostAddress6
exampleIp = tupleToHostAddress6 (0x2001, 0x16b8, 0x755a, 0xb110, 0x7d6a, 0x12ab, 0xf0c5, 0x386e) exampleIp = tupleToHostAddress6 (0x2001, 0x16b8, 0x755a, 0xb110, 0x7d6a, 0x12ab, 0xf0c5, 0x386e)
-- | helper function to create a 'RemoteCacheEntry' with the current time stamp
remoteEntryFromNow :: NodeState -> IO RemoteCacheEntry
remoteEntryFromNow ns = RemoteCacheEntry ns <$> getPOSIXTime
-- | helper function for chaining the IO actions of RemoteCacheEntry creation
-- and adding to cache
addCacheWrapper :: IO RemoteCacheEntry -> NodeCache -> IO NodeCache
addCacheWrapper entryIO nc = do
entry <- entryIO
addCacheEntry entry nc