summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorSam Truzjan <pxqr.sta@gmail.com>2013-11-21 01:09:32 +0400
committerSam Truzjan <pxqr.sta@gmail.com>2013-11-21 01:09:32 +0400
commitfc4d96d32ad986ec36e511588cb6078d4ad2323a (patch)
tree774d19821b9689a3bd74f17bd84afd15b6a19061 /src
parent1d251b08f470363a0e3de3894b21c5ada797113d (diff)
Add documentation to PeerAddr module
Diffstat (limited to 'src')
-rw-r--r--src/Network/BitTorrent/Core/PeerAddr.hs21
-rw-r--r--src/Network/BitTorrent/Core/PeerId.hs1
2 files changed, 14 insertions, 8 deletions
diff --git a/src/Network/BitTorrent/Core/PeerAddr.hs b/src/Network/BitTorrent/Core/PeerAddr.hs
index 0eeaae9d..73aa69fd 100644
--- a/src/Network/BitTorrent/Core/PeerAddr.hs
+++ b/src/Network/BitTorrent/Core/PeerAddr.hs
@@ -5,8 +5,8 @@
5-- Stability : experimental 5-- Stability : experimental
6-- Portability : portable 6-- Portability : portable
7-- 7--
8-- 'PeerAddr' is used to represent peer location. Currently it's 8-- 'PeerAddr' is used to represent peer address. Currently it's
9-- just peer IP and peer port but this might be changed later. 9-- just peer IP and peer port but this might change in future.
10-- 10--
11{-# LANGUAGE TemplateHaskell #-} 11{-# LANGUAGE TemplateHaskell #-}
12{-# LANGUAGE StandaloneDeriving #-} 12{-# LANGUAGE StandaloneDeriving #-}
@@ -53,22 +53,24 @@ instance Serialize PortNumber where
53 {-# INLINE put #-} 53 {-# INLINE put #-}
54 54
55-- TODO check semantic of ord and eq instances 55-- TODO check semantic of ord and eq instances
56-- TODO use SockAddr instead of peerIP and peerPort
56 57
57-- | Peer address info normally extracted from peer list or peer 58-- | Peer address info normally extracted from peer list or peer
58-- compact list encoding. 59-- compact list encoding.
59data PeerAddr = PeerAddr { 60data PeerAddr = PeerAddr {
60 peerID :: Maybe PeerId 61 peerID :: !(Maybe PeerId)
61 , peerIP :: {-# UNPACK #-} !HostAddress 62 , peerIP :: {-# UNPACK #-} !HostAddress
62 , peerPort :: {-# UNPACK #-} !PortNumber 63 , peerPort :: {-# UNPACK #-} !PortNumber
63 } deriving (Show, Eq, Ord, Typeable) 64 } deriving (Show, Eq, Ord, Typeable)
64 65
65$(deriveJSON (L.map toLower . L.dropWhile isLower) ''PeerAddr) 66$(deriveJSON (L.map toLower . L.dropWhile isLower) ''PeerAddr)
66 67
68-- | The tracker "announce query" compatible encoding.
67instance BEncode PeerAddr where 69instance BEncode PeerAddr where
68 toBEncode (PeerAddr pid pip pport) = toDict $ 70 toBEncode (PeerAddr pid pip pport) = toDict $
69 "peer id" .=? pid 71 "peer id" .=? pid
70 .: "ip" .=! pip 72 .: "ip" .=! pip
71 .: "port" .=! pport 73 .: "port" .=! pport
72 .: endDict 74 .: endDict
73 75
74 fromBEncode = fromDict $ do 76 fromBEncode = fromDict $ do
@@ -76,12 +78,15 @@ instance BEncode PeerAddr where
76 <*>! "ip" 78 <*>! "ip"
77 <*>! "port" 79 <*>! "port"
78 80
81-- | The tracker "compact peer list" compatible encoding. The
82-- 'peerId' is always 'Nothing'.
79instance Serialize PeerAddr where 83instance Serialize PeerAddr where
80 put PeerAddr {..} = put peerID >> put peerPort 84 put PeerAddr {..} = put peerID >> put peerPort
81 {-# INLINE put #-} 85 {-# INLINE put #-}
82 get = PeerAddr Nothing <$> get <*> get 86 get = PeerAddr Nothing <$> get <*> get
83 {-# INLINE get #-} 87 {-# INLINE get #-}
84 88
89-- | For more info see: <http://www.bittorrent.org/beps/bep_0023.html>
85getCompactPeerList :: S.Get [PeerAddr] 90getCompactPeerList :: S.Get [PeerAddr]
86getCompactPeerList = many get 91getCompactPeerList = many get
87 92
@@ -112,8 +117,8 @@ connectToPeer p = do
112 117
113-- | Pretty print peer address in human readable form. 118-- | Pretty print peer address in human readable form.
114ppPeer :: PeerAddr -> Doc 119ppPeer :: PeerAddr -> Doc
115ppPeer p @ PeerAddr {..} = case peerID of 120ppPeer p @ PeerAddr {..}
116 Just pid -> ppClientInfo (clientInfo pid) <+> "at" <+> paddr 121 | Just pid <- peerID = ppClientInfo (clientInfo pid) <+> "at" <+> paddr
117 Nothing -> paddr 122 | otherwise = paddr
118 where 123 where
119 paddr = text (show (peerSockAddr p)) 124 paddr = text (show (peerSockAddr p))
diff --git a/src/Network/BitTorrent/Core/PeerId.hs b/src/Network/BitTorrent/Core/PeerId.hs
index a32aa990..1ae55913 100644
--- a/src/Network/BitTorrent/Core/PeerId.hs
+++ b/src/Network/BitTorrent/Core/PeerId.hs
@@ -61,6 +61,7 @@ import Paths_bittorrent (version)
61 61
62import Data.Torrent.Client 62import Data.Torrent.Client
63 63
64-- TODO use unpacked form (length is known statically)
64 65
65-- | Peer identifier is exactly 20 bytes long bytestring. 66-- | Peer identifier is exactly 20 bytes long bytestring.
66newtype PeerId = PeerId { getPeerId :: ByteString } 67newtype PeerId = PeerId { getPeerId :: ByteString }