diff options
author | Sam Truzjan <pxqr.sta@gmail.com> | 2013-12-14 23:26:21 +0400 |
---|---|---|
committer | Sam Truzjan <pxqr.sta@gmail.com> | 2013-12-14 23:26:21 +0400 |
commit | 254a407eafe53d7d98b55a694b840f1af6fe5e75 (patch) | |
tree | 9464626052e0f05ce7e9d8b6fba147ce033d4498 /src/Network/BitTorrent/Core/PeerAddr.hs | |
parent | c7d84e12184430062305d1d4677a90df558484ea (diff) | |
parent | 8e4419d5bf7880ac862675dc4105cf6503c488bc (diff) |
Merge branch 'dev' of https://github.com/DanielG/bittorrent
Diffstat (limited to 'src/Network/BitTorrent/Core/PeerAddr.hs')
-rw-r--r-- | src/Network/BitTorrent/Core/PeerAddr.hs | 133 |
1 files changed, 112 insertions, 21 deletions
diff --git a/src/Network/BitTorrent/Core/PeerAddr.hs b/src/Network/BitTorrent/Core/PeerAddr.hs index e7a4ea61..1da4c81a 100644 --- a/src/Network/BitTorrent/Core/PeerAddr.hs +++ b/src/Network/BitTorrent/Core/PeerAddr.hs | |||
@@ -12,12 +12,18 @@ | |||
12 | {-# LANGUAGE StandaloneDeriving #-} | 12 | {-# LANGUAGE StandaloneDeriving #-} |
13 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | 13 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} |
14 | {-# LANGUAGE DeriveDataTypeable #-} | 14 | {-# LANGUAGE DeriveDataTypeable #-} |
15 | {-# LANGUAGE FlexibleInstances #-} | ||
16 | {-# LANGUAGE DeriveFunctor #-} | ||
15 | {-# OPTIONS -fno-warn-orphans #-} -- for PortNumber instances | 17 | {-# OPTIONS -fno-warn-orphans #-} -- for PortNumber instances |
16 | module Network.BitTorrent.Core.PeerAddr | 18 | module Network.BitTorrent.Core.PeerAddr |
17 | ( -- * Peer address | 19 | ( -- * Peer address |
18 | PeerAddr(..) | 20 | PeerAddr(..) |
19 | , defaultPorts | 21 | , defaultPorts |
20 | , peerSockAddr | 22 | , peerSockAddr |
23 | , mergeIPLists | ||
24 | , splitIPList | ||
25 | , IP, IPv4, IPv6 --re-export Data.IP constructors | ||
26 | , IPAddress () | ||
21 | ) where | 27 | ) where |
22 | 28 | ||
23 | import Control.Applicative | 29 | import Control.Applicative |
@@ -26,6 +32,8 @@ import Data.Aeson (ToJSON, FromJSON) | |||
26 | import Data.Aeson.TH | 32 | import Data.Aeson.TH |
27 | import Data.BEncode as BS | 33 | import Data.BEncode as BS |
28 | import Data.BEncode.BDict (BKey) | 34 | import Data.BEncode.BDict (BKey) |
35 | import Data.ByteString | ||
36 | import Data.ByteString.Char8 as BS8 | ||
29 | import Data.Bits | 37 | import Data.Bits |
30 | import Data.Char | 38 | import Data.Char |
31 | import Data.Default | 39 | import Data.Default |
@@ -35,10 +43,15 @@ import Data.Serialize as S | |||
35 | import Data.String | 43 | import Data.String |
36 | import Data.Typeable | 44 | import Data.Typeable |
37 | import Data.Word | 45 | import Data.Word |
46 | import Data.IP | ||
47 | import Data.Maybe | ||
48 | import Data.Foldable | ||
49 | import Data.Either | ||
38 | import Network.Socket | 50 | import Network.Socket |
39 | import Text.PrettyPrint | 51 | import Text.PrettyPrint |
40 | import Text.PrettyPrint.Class | 52 | import Text.PrettyPrint.Class |
41 | import Text.Read (readMaybe) | 53 | import Text.Read (readMaybe) |
54 | import qualified Text.ParserCombinators.ReadP as RP | ||
42 | import System.IO.Unsafe | 55 | import System.IO.Unsafe |
43 | 56 | ||
44 | import Data.Torrent.JSON | 57 | import Data.Torrent.JSON |
@@ -58,30 +71,74 @@ instance Serialize PortNumber where | |||
58 | put = putWord16be . fromIntegral | 71 | put = putWord16be . fromIntegral |
59 | {-# INLINE put #-} | 72 | {-# INLINE put #-} |
60 | 73 | ||
74 | class (Show i, Read i) => IPAddress i where | ||
75 | showIp :: i -> String | ||
76 | showIp = show | ||
77 | |||
78 | readIp :: String -> i | ||
79 | readIp = read | ||
80 | |||
81 | toHostAddr :: i -> Either HostAddress HostAddress6 | ||
82 | |||
83 | instance IPAddress IPv4 where | ||
84 | toHostAddr = Left . toHostAddress | ||
85 | |||
86 | instance IPAddress IPv6 where | ||
87 | toHostAddr = Right . toHostAddress6 | ||
88 | |||
89 | instance IPAddress IP where | ||
90 | toHostAddr (IPv4 ip) = toHostAddr ip | ||
91 | toHostAddr (IPv6 ip) = toHostAddr ip | ||
92 | |||
93 | |||
94 | deriving instance Typeable IP | ||
95 | deriving instance Typeable IPv4 | ||
96 | deriving instance Typeable IPv6 | ||
97 | |||
98 | ipToBEncode ip = BString $ BS8.pack $ showIp ip | ||
99 | ipFromBEncode (BString ip) = return $ readIp $ BS8.unpack ip | ||
100 | |||
101 | instance BEncode IP where | ||
102 | toBEncode = ipToBEncode | ||
103 | fromBEncode = ipFromBEncode | ||
104 | |||
105 | instance BEncode IPv4 where | ||
106 | toBEncode = ipToBEncode | ||
107 | fromBEncode = ipFromBEncode | ||
108 | |||
109 | instance BEncode IPv6 where | ||
110 | toBEncode = ipToBEncode | ||
111 | fromBEncode = ipFromBEncode | ||
112 | |||
113 | instance Serialize IPv4 where | ||
114 | put ip = put $ toHostAddress ip | ||
115 | get = fromHostAddress <$> get | ||
116 | |||
117 | instance Serialize IPv6 where | ||
118 | put ip = put $ toHostAddress6 ip | ||
119 | get = fromHostAddress6 <$> get | ||
120 | |||
61 | -- TODO check semantic of ord and eq instances | 121 | -- TODO check semantic of ord and eq instances |
62 | -- TODO use SockAddr instead of peerIP and peerPort | 122 | -- TODO use SockAddr instead of peerIP and peerPort |
63 | 123 | ||
64 | -- | Peer address info normally extracted from peer list or peer | 124 | -- | Peer address info normally extracted from peer list or peer |
65 | -- compact list encoding. | 125 | -- compact list encoding. |
66 | data PeerAddr = PeerAddr | 126 | data PeerAddr a = PeerAddr |
67 | { peerId :: !(Maybe PeerId) | 127 | { peerId :: !(Maybe PeerId) |
68 | , peerIP :: {-# UNPACK #-} !HostAddress | 128 | , peerAddr :: a |
69 | , peerPort :: {-# UNPACK #-} !PortNumber | 129 | , peerPort :: {-# UNPACK #-} !PortNumber |
70 | } deriving (Show, Eq, Ord, Typeable) | 130 | } deriving (Show, Eq, Typeable, Functor) |
71 | |||
72 | $(deriveJSON omitRecordPrefix ''PeerAddr) | ||
73 | 131 | ||
74 | peer_id_key, peer_ip_key, peer_port_key :: BKey | 132 | peer_id_key, peer_ip_key, peer_port_key :: BKey |
75 | peer_id_key = "peer id" | 133 | peer_id_key = "peer id" |
76 | peer_ip_key = "ip" | 134 | peer_ip_key = "ip" |
77 | peer_port_key = "port" | 135 | peer_port_key = "port" |
78 | 136 | ||
79 | -- FIXME do we need to byteswap peerIP in bencode instance? | ||
80 | -- | The tracker's 'announce response' compatible encoding. | 137 | -- | The tracker's 'announce response' compatible encoding. |
81 | instance BEncode PeerAddr where | 138 | instance (Typeable a, BEncode a) => BEncode (PeerAddr a) where |
82 | toBEncode PeerAddr {..} = toDict $ | 139 | toBEncode PeerAddr {..} = toDict $ |
83 | peer_id_key .=? peerId | 140 | peer_id_key .=? peerId |
84 | .: peer_ip_key .=! peerIP | 141 | .: peer_ip_key .=! peerAddr |
85 | .: peer_port_key .=! peerPort | 142 | .: peer_port_key .=! peerPort |
86 | .: endDict | 143 | .: endDict |
87 | 144 | ||
@@ -90,19 +147,32 @@ instance BEncode PeerAddr where | |||
90 | <*>! peer_ip_key | 147 | <*>! peer_ip_key |
91 | <*>! peer_port_key | 148 | <*>! peer_port_key |
92 | 149 | ||
150 | mergeIPLists :: [PeerAddr IPv4] -> Maybe [PeerAddr IPv6] -> [PeerAddr IP] | ||
151 | mergeIPLists v4 v6 = (fmap IPv4 `L.map` v4) | ||
152 | ++ (fmap IPv6 `L.map` Data.Foldable.concat v6) | ||
153 | |||
154 | splitIPList :: [PeerAddr IP] -> ([PeerAddr IPv4],[PeerAddr IPv6]) | ||
155 | splitIPList xs = partitionEithers $ toEither <$> xs | ||
156 | where | ||
157 | toEither :: PeerAddr IP -> Either (PeerAddr IPv4) (PeerAddr IPv6) | ||
158 | toEither pa@(PeerAddr _ (IPv4 _) _) = Left (ipv4 <$> pa) | ||
159 | toEither pa@(PeerAddr _ (IPv6 _) _) = Right (ipv6 <$> pa) | ||
160 | |||
161 | |||
93 | -- | The tracker's 'compact peer list' compatible encoding. The | 162 | -- | The tracker's 'compact peer list' compatible encoding. The |
94 | -- 'peerId' is always 'Nothing'. | 163 | -- 'peerId' is always 'Nothing'. |
95 | -- | 164 | -- |
96 | -- For more info see: <http://www.bittorrent.org/beps/bep_0023.html> | 165 | -- For more info see: <http://www.bittorrent.org/beps/bep_0023.html> |
97 | -- | 166 | -- |
98 | instance Serialize PeerAddr where | 167 | -- TODO: test byte order |
99 | put PeerAddr {..} = putWord32host peerIP >> put peerPort | 168 | instance (Serialize a) => Serialize (PeerAddr a) where |
100 | {-# INLINE put #-} | 169 | put PeerAddr {..} = |
101 | get = PeerAddr Nothing <$> getWord32host <*> get | 170 | put peerAddr >> put peerPort |
102 | {-# INLINE get #-} | 171 | get = |
172 | PeerAddr Nothing <$> get <*> get | ||
103 | 173 | ||
104 | -- | @127.0.0.1:6881@ | 174 | -- | @127.0.0.1:6881@ |
105 | instance Default PeerAddr where | 175 | instance Default (PeerAddr IPv4) where |
106 | def = "127.0.0.1:6881" | 176 | def = "127.0.0.1:6881" |
107 | 177 | ||
108 | -- inet_addr is pure; so it is safe to throw IO | 178 | -- inet_addr is pure; so it is safe to throw IO |
@@ -117,28 +187,49 @@ unsafeCatchIO m = unsafePerformIO $ | |||
117 | -- | 187 | -- |
118 | -- @peerPort \"127.0.0.1:6881\" == 6881@ | 188 | -- @peerPort \"127.0.0.1:6881\" == 6881@ |
119 | -- | 189 | -- |
120 | instance IsString PeerAddr where | 190 | instance IsString (PeerAddr IPv4) where |
121 | fromString str | 191 | fromString str |
122 | | [hostAddrStr, portStr] <- splitWhen (== ':') str | 192 | | [hostAddrStr, portStr] <- splitWhen (== ':') str |
123 | , Just hostAddr <- unsafeCatchIO $ inet_addr hostAddrStr | 193 | , hostAddr <- read hostAddrStr |
124 | , Just portNum <- toEnum <$> readMaybe portStr | 194 | , Just portNum <- toEnum <$> readMaybe portStr |
125 | = PeerAddr Nothing hostAddr portNum | 195 | = PeerAddr Nothing hostAddr portNum |
126 | | otherwise = error $ "fromString: unable to parse PeerAddr: " ++ str | 196 | | otherwise = error $ "fromString: unable to parse (PeerAddr IPv4): " ++ str |
197 | |||
198 | readsIPv6_port :: String -> [((IPv6, PortNumber), String)] | ||
199 | readsIPv6_port = RP.readP_to_S $ do | ||
200 | ip <- RP.char '[' *> (RP.readS_to_P reads) <* RP.char ']' | ||
201 | RP.char ':' | ||
202 | port <- toEnum <$> read <$> (RP.many1 $ RP.satisfy isDigit) <* RP.eof | ||
203 | return (ip,port) | ||
204 | |||
205 | instance IsString (PeerAddr IPv6) where | ||
206 | fromString str | ||
207 | | [((ip,port),"")] <- readsIPv6_port str = | ||
208 | PeerAddr Nothing ip port | ||
209 | | otherwise = error $ "fromString: unable to parse (PeerAddr IPv6): " ++ str | ||
127 | 210 | ||
128 | -- | fingerprint + "at" + dotted.host.inet.addr:port | 211 | -- | fingerprint + "at" + dotted.host.inet.addr:port |
129 | instance Pretty PeerAddr where | 212 | -- TODO: instances for IPv6, HostName |
213 | instance Pretty (PeerAddr IP) where | ||
130 | pretty p @ PeerAddr {..} | 214 | pretty p @ PeerAddr {..} |
131 | | Just pid <- peerId = pretty (fingerprint pid) <+> "at" <+> paddr | 215 | | Just pid <- peerId = pretty (fingerprint pid) <+> "at" <+> paddr |
132 | | otherwise = paddr | 216 | | otherwise = paddr |
133 | where | 217 | where |
134 | paddr = text (show (peerSockAddr p)) | 218 | paddr = text (show peerAddr ++ ":" ++ show peerPort) |
135 | 219 | ||
136 | -- | Ports typically reserved for bittorrent P2P listener. | 220 | -- | Ports typically reserved for bittorrent P2P listener. |
137 | defaultPorts :: [PortNumber] | 221 | defaultPorts :: [PortNumber] |
138 | defaultPorts = [6881..6889] | 222 | defaultPorts = [6881..6889] |
139 | 223 | ||
224 | resolvePeerAddr :: (IPAddress i) => PeerAddr HostName -> PeerAddr i | ||
225 | resolvePeerAddr = undefined | ||
226 | |||
140 | -- | Convert peer info from tracker response to socket address. Used | 227 | -- | Convert peer info from tracker response to socket address. Used |
141 | -- for establish connection between peers. | 228 | -- for establish connection between peers. |
142 | -- | 229 | -- |
143 | peerSockAddr :: PeerAddr -> SockAddr | 230 | peerSockAddr :: (IPAddress i) => PeerAddr i -> SockAddr |
144 | peerSockAddr = SockAddrInet <$> peerPort <*> peerIP | 231 | peerSockAddr PeerAddr {..} |
232 | | Left hAddr <- toHostAddr peerAddr = | ||
233 | SockAddrInet peerPort hAddr | ||
234 | | Right hAddr <- toHostAddr peerAddr = | ||
235 | SockAddrInet6 peerPort 0 hAddr 0 | ||