fix all previously working tests
This commit is contained in:
parent
061bce2b08
commit
22a6becf6b
2 changed files with 26 additions and 12 deletions
|
@ -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…
Add table
Add a link
Reference in a new issue