diff options
Diffstat (limited to 'src/Network')
-rw-r--r-- | src/Network/BitTorrent/Address.hs | 58 |
1 files changed, 45 insertions, 13 deletions
diff --git a/src/Network/BitTorrent/Address.hs b/src/Network/BitTorrent/Address.hs index a72a8a07..ed02f7ff 100644 --- a/src/Network/BitTorrent/Address.hs +++ b/src/Network/BitTorrent/Address.hs | |||
@@ -26,6 +26,8 @@ module Network.BitTorrent.Address | |||
26 | ( -- * Address | 26 | ( -- * Address |
27 | Address (..) | 27 | Address (..) |
28 | , fromAddr | 28 | , fromAddr |
29 | , PortNumber | ||
30 | , SockAddr | ||
29 | 31 | ||
30 | -- ** IP | 32 | -- ** IP |
31 | , IPv4 | 33 | , IPv4 |
@@ -81,16 +83,18 @@ module Network.BitTorrent.Address | |||
81 | 83 | ||
82 | -- * Utils | 84 | -- * Utils |
83 | , libUserAgent | 85 | , libUserAgent |
86 | , sockAddrPort | ||
87 | , getBindAddress | ||
84 | ) where | 88 | ) where |
85 | 89 | ||
86 | import Control.Applicative | 90 | import Control.Applicative |
87 | import Control.Monad | 91 | import Control.Monad |
92 | import Control.Exception (onException) | ||
88 | import Data.BEncode as BE | 93 | import Data.BEncode as BE |
89 | import Data.BEncode as BS | ||
90 | import Data.BEncode.BDict (BKey) | 94 | import Data.BEncode.BDict (BKey) |
91 | import Data.Bits | 95 | import Data.Bits |
92 | import Data.ByteString as BS | 96 | import qualified Data.ByteString as BS |
93 | import Data.ByteString.Internal as BS | 97 | import qualified Data.ByteString.Internal as BS |
94 | import Data.ByteString.Base16 as Base16 | 98 | import Data.ByteString.Base16 as Base16 |
95 | import Data.ByteString.Char8 as BC | 99 | import Data.ByteString.Char8 as BC |
96 | import Data.ByteString.Char8 as BS8 | 100 | import Data.ByteString.Char8 as BS8 |
@@ -167,19 +171,21 @@ setPort port (SockAddrInet6 _ f h s) = SockAddrInet6 port f h s | |||
167 | setPort _ addr = addr | 171 | setPort _ addr = addr |
168 | {-# INLINE setPort #-} | 172 | {-# INLINE setPort #-} |
169 | 173 | ||
170 | getPort :: SockAddr -> Maybe PortNumber | 174 | -- | Obtains the port associated with a socket address |
171 | getPort (SockAddrInet p _ ) = Just p | 175 | -- if one is associated with it. |
172 | getPort (SockAddrInet6 p _ _ _) = Just p | 176 | sockAddrPort :: SockAddr -> Maybe PortNumber |
173 | getPort _ = Nothing | 177 | sockAddrPort (SockAddrInet p _ ) = Just p |
174 | {-# INLINE getPort #-} | 178 | sockAddrPort (SockAddrInet6 p _ _ _) = Just p |
179 | sockAddrPort _ = Nothing | ||
180 | {-# INLINE sockAddrPort #-} | ||
175 | 181 | ||
176 | instance Address a => Address (NodeAddr a) where | 182 | instance Address a => Address (NodeAddr a) where |
177 | toSockAddr NodeAddr {..} = setPort nodePort $ toSockAddr nodeHost | 183 | toSockAddr NodeAddr {..} = setPort nodePort $ toSockAddr nodeHost |
178 | fromSockAddr sa = NodeAddr <$> fromSockAddr sa <*> getPort sa | 184 | fromSockAddr sa = NodeAddr <$> fromSockAddr sa <*> sockAddrPort sa |
179 | 185 | ||
180 | instance Address a => Address (PeerAddr a) where | 186 | instance Address a => Address (PeerAddr a) where |
181 | toSockAddr PeerAddr {..} = setPort peerPort $ toSockAddr peerHost | 187 | toSockAddr PeerAddr {..} = setPort peerPort $ toSockAddr peerHost |
182 | fromSockAddr sa = PeerAddr Nothing <$> fromSockAddr sa <*> getPort sa | 188 | fromSockAddr sa = PeerAddr Nothing <$> fromSockAddr sa <*> sockAddrPort sa |
183 | 189 | ||
184 | {----------------------------------------------------------------------- | 190 | {----------------------------------------------------------------------- |
185 | -- Peer id | 191 | -- Peer id |
@@ -366,7 +372,7 @@ instance BEncode PortNumber where | |||
366 | toBEncode = toBEncode . fromEnum | 372 | toBEncode = toBEncode . fromEnum |
367 | fromBEncode = fromBEncode >=> portNumber | 373 | fromBEncode = fromBEncode >=> portNumber |
368 | where | 374 | where |
369 | portNumber :: Integer -> BS.Result PortNumber | 375 | portNumber :: Integer -> BE.Result PortNumber |
370 | portNumber n | 376 | portNumber n |
371 | | 0 <= n && n <= fromIntegral (maxBound :: Word16) | 377 | | 0 <= n && n <= fromIntegral (maxBound :: Word16) |
372 | = pure $ fromIntegral n | 378 | = pure $ fromIntegral n |
@@ -414,7 +420,7 @@ ipToBEncode :: Show i => i -> BValue | |||
414 | ipToBEncode ip = BString $ BS8.pack $ show ip | 420 | ipToBEncode ip = BString $ BS8.pack $ show ip |
415 | {-# INLINE ipToBEncode #-} | 421 | {-# INLINE ipToBEncode #-} |
416 | 422 | ||
417 | ipFromBEncode :: Read a => BValue -> BS.Result a | 423 | ipFromBEncode :: Read a => BValue -> BE.Result a |
418 | ipFromBEncode (BString (BS8.unpack -> ipStr)) | 424 | ipFromBEncode (BString (BS8.unpack -> ipStr)) |
419 | | Just ip <- readMaybe (ipStr) = pure ip | 425 | | Just ip <- readMaybe (ipStr) = pure ip |
420 | | otherwise = decodingError $ "IP: " ++ ipStr | 426 | | otherwise = decodingError $ "IP: " ++ ipStr |
@@ -1166,7 +1172,7 @@ fingerprint pid = either (const def) id $ runGet getCI (getPeerId pid) | |||
1166 | 'e' -> Fingerprint <$> getBitCometImpl <*> getBitCometVersion | 1172 | 'e' -> Fingerprint <$> getBitCometImpl <*> getBitCometVersion |
1167 | 'F' -> Fingerprint <$> getBitCometImpl <*> getBitCometVersion | 1173 | 'F' -> Fingerprint <$> getBitCometImpl <*> getBitCometVersion |
1168 | c -> do | 1174 | c -> do |
1169 | c1 <- w2c <$> S.lookAhead getWord8 | 1175 | c1 <- BS.w2c <$> S.lookAhead getWord8 |
1170 | if c1 == 'P' | 1176 | if c1 == 'P' |
1171 | then do | 1177 | then do |
1172 | _ <- getWord8 | 1178 | _ <- getWord8 |
@@ -1252,3 +1258,29 @@ bep42 addr (NodeId r) | |||
1252 | bs -> bs | 1258 | bs -> bs |
1253 | where msk | BS.length ip == 4 = ip4mask | 1259 | where msk | BS.length ip == 4 = ip4mask |
1254 | | otherwise = ip6mask | 1260 | | otherwise = ip6mask |
1261 | |||
1262 | |||
1263 | -- | Given a string specifying a port (numeric or service name) | ||
1264 | -- and a flag indicating whether you want to support IPv6, this | ||
1265 | -- function will return a SockAddr to bind to. If the input | ||
1266 | -- is not understood as a port number, zero will be set in order | ||
1267 | -- to ask the system for an unused port. | ||
1268 | -- | ||
1269 | -- TODO: Also interpret local ip address specifications in the input | ||
1270 | -- string. | ||
1271 | getBindAddress :: String -> Bool -> IO SockAddr | ||
1272 | getBindAddress listenPortString enabled6 = do | ||
1273 | -- Bind addresses for localhost | ||
1274 | xs <- getAddrInfo (Just (defaultHints {addrFlags = [AI_PASSIVE] })) | ||
1275 | Nothing | ||
1276 | (Just listenPortString) | ||
1277 | `onException` return [] | ||
1278 | -- We prefer IPv6 because that can also handle connections from IPv4 | ||
1279 | -- clients... | ||
1280 | let (x6s,x4s) = partition (\s -> addrFamily s == AF_INET6) xs | ||
1281 | listenAddr = | ||
1282 | case if enabled6 then x6s++x4s else x4s of | ||
1283 | AddrInfo { addrAddress = listenAddr } : _ -> listenAddr | ||
1284 | _ -> SockAddrInet6 (parsePort listenPortString) 0 iN6ADDR_ANY 0 | ||
1285 | where parsePort s = fromMaybe 0 $ readMaybe s | ||
1286 | return listenAddr | ||