Hash2Pub/Hash2Pub/test/FediChordSpec.hs

90 lines
3.9 KiB
Haskell
Raw Blame History

This file contains ambiguous Unicode characters

This file contains Unicode characters that might be confused with other characters. If you think that this is intentional, you can safely ignore this warning. Use the Escape button to reveal them.

{-# LANGUAGE OverloadedStrings #-}
module FediChordSpec where
import Test.Hspec
import Control.Exception
import Network.Socket
import qualified Data.Map.Strict as Map
import qualified Data.ByteString as BS
import Hash2Pub.FediChord
spec :: Spec
spec = do
-- define some sensible test data
let
nodeDomain = "example.social"
vs = 4
ip = tupleToHostAddress6 (0x2001, 0x16b8, 0x755a, 0xb110, 0x7d6a, 0x12ab, 0xf0c5, 0x386e)
describe "NodeID" $ do
it "can store a numeral ID" $
getNodeID (toNodeID 2342) `shouldBe` 2342
it "computes ID values within the modular bounds" $ do
getNodeID ((maxBound :: NodeID) + toNodeID 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
toNodeID 12 `compare` toNodeID 12 `shouldBe` EQ
let
a = toNodeID 3
b = toNodeID 3 - toNodeID 10
a > b `shouldBe` True
b < a `shouldBe` True
-- edge cases
(toNodeID 5001 - toNodeID 2^(255::Integer) < 5001) `shouldBe` True
(toNodeID 5001 - toNodeID 2^(255::Integer) - 1) < 5001 `shouldBe` False
it "throws an exception when @toNodeID@ on out-of-bound values"
pending
it "can be generated" $ do
genNodeIDBS ip nodeDomain vs `shouldBe` "\ACK\211\183&S\GS\214\247Xn8\216\232\195\247\162\182\253\210\SOHG7I\194\251\196\130\142RSx\219"
genNodeID ip nodeDomain vs `shouldBe` toNodeID 3087945874980469002564169693112490135217795916629034079089428181202645514459
describe "ByteString to Integer conversion" $
it "correctly interprets ByteStrings as unsigned big-endian integers" $ do
byteStringToUInteger (BS.pack $ replicate 32 0xff) `shouldBe` 2^(256::Integer)-1
byteStringToUInteger (BS.pack $ replicate 32 0x00) `shouldBe` 0
byteStringToUInteger (BS.pack [0x00, 0x03, 0xf6, 0x78, 0x10, 0x00]) `shouldBe` 17019965440
describe "key ID" $
it "can be generated" $ do
genKeyIDBS "#sometag" `shouldBe` "\178\239\146\131\166\SYN\ESC\209\205\&3\143\212\145@#\205T\219\152\191\229\ACK|\153<b\199p\147\182&l"
genKeyIDBS "#ÄปӥicоdeTag" `shouldBe` "\f\159\165|D*\SUB\180\SO\202\&0\158\148\238\STX FZ/\184\SOH\188\169\153\154\164\229\&2Ix\SUB\169"
genKeyID "#sometag" `shouldBe` 80934974700514031200587628522801847528706765451025022694022301350330549806700
genKeyID "#ÄปӥicоdeTag" `shouldBe` 5709825004658123480531764908635278432808461265905814952223156184506818894505
describe "NodeState" $ do
it "can be initialised" $ do
let ns = NodeState {
nid = toNodeID 12
, domain = nodeDomain
, ipAddr = ip
, dhtPort = 2342
, apPort = Nothing
, nodeCache = Map.empty
, successors = []
, predecessors = []
, kNeighbours = 3
, lNumBestNodes = 3
, pNumParallelQueries = 2
, jEntriesPerSlice = 2
}
print ns
it "can be initialised partly and then modified later" $ do
let ns = NodeState {
nid = undefined
, domain = nodeDomain
, ipAddr = ip
, dhtPort = 2342
, apPort = Nothing
, nodeCache = Map.empty
, successors = []
, predecessors = []
, kNeighbours = 3
, lNumBestNodes = 3
, pNumParallelQueries = 2
, jEntriesPerSlice = 2
}
nsReady = ns {
nid = genNodeID (ipAddr ns) (domain ns) 3
}
print nsReady