summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent/Address.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network/BitTorrent/Address.hs')
-rw-r--r--src/Network/BitTorrent/Address.hs12
1 files changed, 6 insertions, 6 deletions
diff --git a/src/Network/BitTorrent/Address.hs b/src/Network/BitTorrent/Address.hs
index fea7139d..f8f29be5 100644
--- a/src/Network/BitTorrent/Address.hs
+++ b/src/Network/BitTorrent/Address.hs
@@ -99,7 +99,6 @@ import qualified Data.ByteString.Lazy.Builder as BS
99import Data.Char 99import Data.Char
100import Data.Convertible 100import Data.Convertible
101import Data.Default 101import Data.Default
102import Data.Foldable
103import Data.IP 102import Data.IP
104import Data.List as L 103import Data.List as L
105import Data.List.Split as L 104import Data.List.Split as L
@@ -165,13 +164,13 @@ instance Address IP where
165setPort :: PortNumber -> SockAddr -> SockAddr 164setPort :: PortNumber -> SockAddr -> SockAddr
166setPort port (SockAddrInet _ h ) = SockAddrInet port h 165setPort port (SockAddrInet _ h ) = SockAddrInet port h
167setPort port (SockAddrInet6 _ f h s) = SockAddrInet6 port f h s 166setPort port (SockAddrInet6 _ f h s) = SockAddrInet6 port f h s
168setPort _ (SockAddrUnix s ) = SockAddrUnix s 167setPort _ addr = addr
169{-# INLINE setPort #-} 168{-# INLINE setPort #-}
170 169
171getPort :: SockAddr -> Maybe PortNumber 170getPort :: SockAddr -> Maybe PortNumber
172getPort (SockAddrInet p _ ) = Just p 171getPort (SockAddrInet p _ ) = Just p
173getPort (SockAddrInet6 p _ _ _) = Just p 172getPort (SockAddrInet6 p _ _ _) = Just p
174getPort (SockAddrUnix _ ) = Nothing 173getPort _ = Nothing
175{-# INLINE getPort #-} 174{-# INLINE getPort #-}
176 175
177instance Address a => Address (NodeAddr a) where 176instance Address a => Address (NodeAddr a) where
@@ -689,7 +688,7 @@ newtype NodeDistance = NodeDistance BS.ByteString
689instance Pretty NodeDistance where 688instance Pretty NodeDistance where
690 pPrint (NodeDistance bs) = foldMap bitseq $ BS.unpack bs 689 pPrint (NodeDistance bs) = foldMap bitseq $ BS.unpack bs
691 where 690 where
692 listBits w = L.map (testBit w) (L.reverse [0..bitSize w - 1]) 691 listBits w = L.map (testBit w) (L.reverse [0..finiteBitSize w - 1])
693 bitseq = foldMap (int . fromEnum) . listBits 692 bitseq = foldMap (int . fromEnum) . listBits
694 693
695-- | distance(A,B) = |A xor B| Smaller values are closer. 694-- | distance(A,B) = |A xor B| Smaller values are closer.
@@ -1232,6 +1231,7 @@ bep42s addr (NodeId r) = mapMaybe (bep42 addr) rs
1232 where 1231 where
1233 rs = L.map (NodeId . change3bits r) [0..7] 1232 rs = L.map (NodeId . change3bits r) [0..7]
1234 1233
1234change3bits :: ByteString -> Word8 -> ByteString
1235change3bits bs n = BS.snoc (BS.init bs) (BS.last bs .&. 0xF8 .|. n) 1235change3bits bs n = BS.snoc (BS.init bs) (BS.last bs .&. 0xF8 .|. n)
1236 1236
1237-- | Modifies a purely random 'NodeId' to one that is related to a given 1237-- | Modifies a purely random 'NodeId' to one that is related to a given
@@ -1240,7 +1240,7 @@ bep42 :: Address a => a -> NodeId -> Maybe NodeId
1240bep42 addr (NodeId r) 1240bep42 addr (NodeId r)
1241 | Just ip <- fmap S.encode (fromAddr addr :: Maybe IPv4) 1241 | Just ip <- fmap S.encode (fromAddr addr :: Maybe IPv4)
1242 <|> fmap S.encode (fromAddr addr :: Maybe IPv6) 1242 <|> fmap S.encode (fromAddr addr :: Maybe IPv6)
1243 = genBucketSample' retr (NodeId $ crc $ masked ip) (3,0x07,0) 1243 = genBucketSample' retr (NodeId $ crc $ applyMask ip) (3,0x07,0)
1244 | otherwise 1244 | otherwise
1245 = Nothing 1245 = Nothing
1246 where 1246 where
@@ -1249,7 +1249,7 @@ bep42 addr (NodeId r)
1249 nbhood_select = BS.last r .&. 7 1249 nbhood_select = BS.last r .&. 7
1250 retr n = pure $ BS.drop (BS.length r - n) r 1250 retr n = pure $ BS.drop (BS.length r - n) r
1251 crc = S.encode . crc32c . BS.pack 1251 crc = S.encode . crc32c . BS.pack
1252 masked ip = case BS.zipWith (.&.) msk ip of 1252 applyMask ip = case BS.zipWith (.&.) msk ip of
1253 (b:bs) -> (b .|. shiftL nbhood_select 5) : bs 1253 (b:bs) -> (b .|. shiftL nbhood_select 5) : bs
1254 bs -> bs 1254 bs -> bs
1255 where msk | BS.length ip == 4 = ip4mask 1255 where msk | BS.length ip == 4 = ip4mask