fix all previously working tests
This commit is contained in:
parent
061bce2b08
commit
22a6becf6b
|
@ -18,6 +18,7 @@ module Hash2Pub.FediChordTypes (
|
|||
, CacheEntry(..)
|
||||
, RingEntry(..)
|
||||
, RingMap(..)
|
||||
, rMapSize
|
||||
, cacheGetNodeStateUnvalidated
|
||||
, initCache
|
||||
, cacheEntries
|
||||
|
@ -39,7 +40,8 @@ import Control.Exception
|
|||
import Data.Function (on)
|
||||
import Data.List (delete, nub, sortBy)
|
||||
import qualified Data.Map.Strict as Map
|
||||
import Data.Maybe (fromMaybe, isJust, mapMaybe)
|
||||
import Data.Maybe (fromMaybe, isJust, isNothing,
|
||||
mapMaybe)
|
||||
import qualified Data.Set as Set
|
||||
import Data.Time.Clock.POSIX
|
||||
import Network.Socket
|
||||
|
@ -253,6 +255,7 @@ data RingEntry a = KeyEntry a
|
|||
|
||||
-- | 'RingEntry' type for usage as a node cache
|
||||
data CacheEntry = CacheEntry Bool RemoteNodeState POSIXTime
|
||||
deriving (Show, Eq)
|
||||
|
||||
|
||||
-- | as a compromise, only KeyEntry components are ordered by their NodeID
|
||||
|
@ -308,6 +311,18 @@ cacheLookup :: NodeID -- ^lookup key
|
|||
-> Maybe CacheEntry
|
||||
cacheLookup = rMapLookup
|
||||
|
||||
-- | returns number of present 'KeyEntry' in a properly initialised 'RingMap'
|
||||
rMapSize :: (HasKeyID a, Integral i)
|
||||
=> RingMap a
|
||||
-> i
|
||||
rMapSize rmap = fromIntegral $ Map.size innerMap - oneIfEntry minBound - oneIfEntry maxBound
|
||||
where
|
||||
innerMap = getRingMap rmap
|
||||
oneIfEntry :: Integral i => NodeID -> i
|
||||
oneIfEntry nid
|
||||
| isNothing (rMapLookup nid rmap) = 1
|
||||
| otherwise = 0
|
||||
|
||||
-- | a wrapper around lookup functions, making the lookup redirectable by a @ProxyEntry@
|
||||
-- to simulate a modular ring
|
||||
lookupWrapper :: HasKeyID a
|
||||
|
@ -371,10 +386,8 @@ cacheLookupPred = rMapLookupPred
|
|||
-- transfer difference now - entry to other node
|
||||
|
||||
-- | return the @NodeState@ data from a cache entry without checking its validation status
|
||||
cacheGetNodeStateUnvalidated :: RingEntry CacheEntry -> RemoteNodeState
|
||||
cacheGetNodeStateUnvalidated (KeyEntry (CacheEntry _ nState _)) = nState
|
||||
cacheGetNodeStateUnvalidated (ProxyEntry _ (Just entry)) = cacheGetNodeStateUnvalidated entry
|
||||
cacheGetNodeStateUnvalidated _ = error "trying to pure empty node state, please report a bug"
|
||||
cacheGetNodeStateUnvalidated :: CacheEntry -> RemoteNodeState
|
||||
cacheGetNodeStateUnvalidated (CacheEntry _ nState _) = nState
|
||||
|
||||
-- | converts a 'HostAddress6' IP address to a big-endian strict ByteString
|
||||
ipAddrAsBS :: HostAddress6 -> BS.ByteString
|
||||
|
|
|
@ -2,11 +2,11 @@
|
|||
module FediChordSpec where
|
||||
|
||||
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
|
||||
|
@ -14,6 +14,7 @@ import Test.Hspec
|
|||
import Hash2Pub.ASN1Coding
|
||||
import Hash2Pub.DHTProtocol
|
||||
import Hash2Pub.FediChord
|
||||
import Hash2Pub.FediChordTypes
|
||||
|
||||
spec :: Spec
|
||||
spec = do
|
||||
|
@ -79,8 +80,8 @@ spec = do
|
|||
newCache = addCacheEntryPure 10 (RemoteCacheEntry exampleNodeState 10) (addCacheEntryPure 10 (RemoteCacheEntry anotherNode 10) emptyCache)
|
||||
exampleID = nid exampleNodeState
|
||||
it "entries can be added to a node cache and looked up again" $ do
|
||||
-- the cache includes 2 additional proxy elements right from the start
|
||||
Map.size newCache - Map.size emptyCache `shouldBe` 2
|
||||
rMapSize emptyCache `shouldBe` 0
|
||||
rMapSize newCache `shouldBe` 2
|
||||
-- normal entry lookup
|
||||
nid . cacheGetNodeStateUnvalidated <$> cacheLookup anotherID newCache `shouldBe` Just anotherID
|
||||
nid . cacheGetNodeStateUnvalidated <$> cacheLookup (anotherID+1) newCache `shouldBe` Nothing
|
||||
|
|
Loading…
Reference in a new issue