summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Network/BitTorrent/Core/PeerAddr.hs6
-rw-r--r--src/Network/BitTorrent/Exchange/Wire.hs2
-rw-r--r--tests/Network/BitTorrent/Tracker/MessageSpec.hs2
3 files changed, 5 insertions, 5 deletions
diff --git a/src/Network/BitTorrent/Core/PeerAddr.hs b/src/Network/BitTorrent/Core/PeerAddr.hs
index 5173c4fc..77f042d5 100644
--- a/src/Network/BitTorrent/Core/PeerAddr.hs
+++ b/src/Network/BitTorrent/Core/PeerAddr.hs
@@ -56,7 +56,7 @@ instance Serialize PortNumber where
56-- | Peer address info normally extracted from peer list or peer 56-- | Peer address info normally extracted from peer list or peer
57-- compact list encoding. 57-- compact list encoding.
58data PeerAddr = PeerAddr { 58data PeerAddr = PeerAddr {
59 peerID :: !(Maybe PeerId) 59 peerId :: !(Maybe PeerId)
60 , peerIP :: {-# UNPACK #-} !HostAddress 60 , peerIP :: {-# UNPACK #-} !HostAddress
61 , peerPort :: {-# UNPACK #-} !PortNumber 61 , peerPort :: {-# UNPACK #-} !PortNumber
62 } deriving (Show, Eq, Ord, Typeable) 62 } deriving (Show, Eq, Ord, Typeable)
@@ -82,14 +82,14 @@ instance BEncode PeerAddr where
82-- For more info see: <http://www.bittorrent.org/beps/bep_0023.html> 82-- For more info see: <http://www.bittorrent.org/beps/bep_0023.html>
83-- 83--
84instance Serialize PeerAddr where 84instance Serialize PeerAddr where
85 put PeerAddr {..} = put peerID >> put peerPort 85 put PeerAddr {..} = put peerId >> put peerPort
86 {-# INLINE put #-} 86 {-# INLINE put #-}
87 get = PeerAddr Nothing <$> get <*> get 87 get = PeerAddr Nothing <$> get <*> get
88 {-# INLINE get #-} 88 {-# INLINE get #-}
89 89
90instance Pretty PeerAddr where 90instance Pretty PeerAddr where
91 pretty p @ PeerAddr {..} 91 pretty p @ PeerAddr {..}
92 | Just pid <- peerID = pretty (fingerprint pid) <+> "at" <+> paddr 92 | Just pid <- peerId = pretty (fingerprint pid) <+> "at" <+> paddr
93 | otherwise = paddr 93 | otherwise = paddr
94 where 94 where
95 paddr = text (show (peerSockAddr p)) 95 paddr = text (show (peerSockAddr p))
diff --git a/src/Network/BitTorrent/Exchange/Wire.hs b/src/Network/BitTorrent/Exchange/Wire.hs
index 1cf14809..2c8eb316 100644
--- a/src/Network/BitTorrent/Exchange/Wire.hs
+++ b/src/Network/BitTorrent/Exchange/Wire.hs
@@ -233,7 +233,7 @@ connectWire hs addr extCaps wire =
233 unless (hsInfoHash hs == hsInfoHash hs') $ do 233 unless (hsInfoHash hs == hsInfoHash hs') $ do
234 throwIO $ ProtocolError $ UnexpectedTopic (hsInfoHash hs') 234 throwIO $ ProtocolError $ UnexpectedTopic (hsInfoHash hs')
235 235
236 unless (hsPeerId hs' == fromMaybe (hsPeerId hs') (peerID addr)) $ do 236 unless (hsPeerId hs' == fromMaybe (hsPeerId hs') (peerId addr)) $ do
237 throwIO $ ProtocolError $ UnexpectedPeerId (hsPeerId hs') 237 throwIO $ ProtocolError $ UnexpectedPeerId (hsPeerId hs')
238 238
239 let caps = hsReserved hs <> hsReserved hs' 239 let caps = hsReserved hs <> hsReserved hs'
diff --git a/tests/Network/BitTorrent/Tracker/MessageSpec.hs b/tests/Network/BitTorrent/Tracker/MessageSpec.hs
index 8ae1a1cc..ac770905 100644
--- a/tests/Network/BitTorrent/Tracker/MessageSpec.hs
+++ b/tests/Network/BitTorrent/Tracker/MessageSpec.hs
@@ -46,7 +46,7 @@ validateInfo AnnounceQuery {..} AnnounceInfo {..} = do
46 respIncomplete `shouldSatisfy` isJust 46 respIncomplete `shouldSatisfy` isJust
47 respMinInterval `shouldSatisfy` isNothing 47 respMinInterval `shouldSatisfy` isNothing
48 respWarning `shouldSatisfy` isNothing 48 respWarning `shouldSatisfy` isNothing
49 peerList `shouldSatisfy` L.all (isNothing . peerID) 49 peerList `shouldSatisfy` L.all (isNothing . peerId)
50 fromJust respComplete + fromJust respIncomplete `shouldBe` L.length peerList 50 fromJust respComplete + fromJust respIncomplete `shouldBe` L.length peerList
51 where 51 where
52 peerList = getPeerList respPeers 52 peerList = getPeerList respPeers