tests for NodeID ordering and NodeState creation #2

This commit is contained in:
Trolli Schmittlauch 2020-03-17 22:55:36 +01:00
parent bfde27cea6
commit 523c33482c
2 changed files with 46 additions and 2 deletions

View file

@ -71,7 +71,7 @@ instance Ord NodeID where
-- | represents a node and all its important state -- | represents a node and all its important state
data NodeState = NodeState { data NodeState = NodeState {
id :: NodeID nid :: NodeID
, domain :: String , domain :: String
-- ^ full public domain name the node is reachable under -- ^ full public domain name the node is reachable under
, ipAddr :: HostAddress6 , ipAddr :: HostAddress6
@ -97,7 +97,7 @@ data NodeState = NodeState {
, pNumParallelQueries :: Int , pNumParallelQueries :: Int
-- ^ number of parallel sent queries -- ^ number of parallel sent queries
-- needs to be parameterisable for simulation purposes -- needs to be parameterisable for simulation purposes
} } deriving (Show)
-- |an entry of the 'nodeCache' -- |an entry of the 'nodeCache'
type CacheEntry = ( type CacheEntry = (

View file

@ -0,0 +1,44 @@
module FediChordSpec where
import Test.Hspec
import Control.Exception
import qualified Data.Map.Strict as Map
import Hash2Pub.FediChord
spec :: Spec
spec = do
describe "NodeID" $ do
it "can store a numeral ID" $
getNodeID (mkNodeID 2342) `shouldBe` 2342
it "computes ID values within the modular bounds" $ do
getNodeID ((maxBound :: NodeID) + mkNodeID 2) < getNodeID (maxBound :: NodeID) `shouldBe` True
3 * (maxBound :: NodeID) `shouldBe` fromInteger (-3)
it "uses comparison in the context of preceding/ succeding nodes on a ring" $ do
mkNodeID 12 `compare` mkNodeID 12 `shouldBe` EQ
let
a = mkNodeID 3
b = mkNodeID 3 - mkNodeID 10
a > b `shouldBe` True
b < a `shouldBe` True
-- edge cases
(mkNodeID 5001 - mkNodeID 2^255) < 5001 `shouldBe` True
(mkNodeID 5001 - mkNodeID 2^255 - 1) < 5001 `shouldBe` False
it "throws an exception when @mkNodeID@ on out-of-bound values" $
pending
describe "NodeState" $ do
it "can be initialised" $ do
let ns = NodeState {
nid = mkNodeID 12
, domain = "herebedragons.social"
, ipAddr = (0x200116b8, 0x755ab1100, 0x7d6a12ab, 0xf0c5386e)
, dhtPort = 2342
, apPort = Nothing
, nodeCache = Map.empty
, successors = []
, predecessors = []
, kNeighbours = 3
, lNumBestNodes = 3
, pNumParallelQueries = 2
}
print ns