forked from schmittlauch/Hash2Pub
fix some warnings
This commit is contained in:
parent
84a48e63c2
commit
9d20589cf8
|
@ -1,4 +1,4 @@
|
|||
{-# LANGUAGE GeneralizedNewtypeDeriving, DataKinds #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving, DataKinds, OverloadedStrings #-}
|
||||
{- |
|
||||
Module : FediChord
|
||||
Description : An opinionated implementation of the EpiChord DHT by Leong et al.
|
||||
|
@ -21,7 +21,6 @@ module Hash2Pub.FediChord (
|
|||
) where
|
||||
|
||||
import qualified Data.Map.Strict as Map
|
||||
import qualified Data.String.UTF8 as U8S
|
||||
import Network.Socket
|
||||
import Data.Time.Clock.System
|
||||
import Control.Exception
|
||||
|
@ -122,13 +121,13 @@ genNodeIDBS :: HostAddress6 -- ^a node's IPv6 address
|
|||
-> String -- ^a node's 1st and 2nd level domain name
|
||||
-> Word8 -- ^the used vserver ID
|
||||
-> BS.ByteString -- ^the NodeID as a 256bit ByteString big-endian unsigned integer
|
||||
genNodeIDBS ipaddr@(a, b, _, _) domain vserver =
|
||||
hashIpaddrUpper `BS.append` hashID domain' `BS.append` hashIpaddLower
|
||||
genNodeIDBS (a, b, _, _) nodeDomain vserver =
|
||||
hashIpaddrUpper `BS.append` hashID nodeDomain' `BS.append` hashIpaddLower
|
||||
where
|
||||
vsBS = BS.pack [vserver] -- attention: only works for vserver IDs up to 255
|
||||
-- TODO: this is inefficient and possibly better done with binary-strict
|
||||
ipaddrNet = (BL.toStrict . BB.toLazyByteString . mconcat $ map BB.word32BE [a, b]) `BS.append` vsBS
|
||||
domain' = BSU.fromString domain `BS.append` vsBS
|
||||
nodeDomain' = BSU.fromString nodeDomain `BS.append` vsBS
|
||||
hashID bstr = BS.pack . BA.unpack $ (hash bstr :: Digest (SHAKE128 128))
|
||||
(hashIpaddrUpper, hashIpaddLower) = BS.splitAt 64 $ hashID ipaddrNet
|
||||
|
||||
|
@ -137,7 +136,7 @@ genNodeID :: HostAddress6 -- ^a node's IPv6 address
|
|||
-> String -- ^a node's 1st and 2nd level domain name
|
||||
-> Word8 -- ^the used vserver ID
|
||||
-> NodeID -- ^the generated @NodeID@
|
||||
genNodeID ip domain vs = NodeID . byteStringToUInteger $ genNodeIDBS ip domain vs
|
||||
genNodeID ip nodeDomain vs = NodeID . byteStringToUInteger $ genNodeIDBS ip nodeDomain vs
|
||||
|
||||
|
||||
-- | parses the bit pattern of a ByteString as an unsigned Integer in Big Endian order
|
||||
|
@ -146,9 +145,9 @@ byteStringToUInteger :: BS.ByteString -> Integer
|
|||
byteStringToUInteger bs = sum $ parsedBytes 0 bs
|
||||
where
|
||||
parsedBytes :: Integer -> BS.ByteString -> [ Integer ]
|
||||
parsedBytes offset bs = case BS.unsnoc bs of
|
||||
parsedBytes offset uintBs = case BS.unsnoc uintBs of
|
||||
Nothing -> []
|
||||
Just (bs, w) -> parseWithOffset offset w : parsedBytes (offset+1) bs
|
||||
Just (bs', w) -> parseWithOffset offset w : parsedBytes (offset+1) bs'
|
||||
|
||||
parseWithOffset :: Integer -> Word8 -> Integer
|
||||
parseWithOffset 0 word = toInteger word -- a shift of 0 is always 0
|
||||
|
|
|
@ -31,11 +31,11 @@ spec = do
|
|||
pending
|
||||
it "can be generated" $ do
|
||||
let
|
||||
domain = "example.social"
|
||||
nodeDomain = "example.social"
|
||||
vs = 4
|
||||
ip = tupleToHostAddress6 (0x2001, 0x16b8, 0x755a, 0xb110, 0x7d6a, 0x12aab, 0xf0c5, 0x386e)
|
||||
genNodeIDBS ip domain 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 domain vs `shouldBe` toNodeID 3087945874980469002564169693112490135217795916629034079089428181202645514459
|
||||
ip = tupleToHostAddress6 (0x2001, 0x16b8, 0x755a, 0xb110, 0x7d6a, 0x12ab, 0xf0c5, 0x386e)
|
||||
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
|
||||
|
@ -47,7 +47,7 @@ spec = do
|
|||
let ns = NodeState {
|
||||
nid = toNodeID 12
|
||||
, domain = "herebedragons.social"
|
||||
, ipAddr = (0x200116b8, 0x755ab1100, 0x7d6a12ab, 0xf0c5386e)
|
||||
, ipAddr = tupleToHostAddress6 (0x2001, 0x16b8, 0x755a, 0xb110, 0x7d6a, 0x12ab, 0xf0c5, 0x386e)
|
||||
, dhtPort = 2342
|
||||
, apPort = Nothing
|
||||
, nodeCache = Map.empty
|
||||
|
|
Loading…
Reference in a new issue