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.hs1172
1 files changed, 1172 insertions, 0 deletions
diff --git a/src/Network/BitTorrent/Address.hs b/src/Network/BitTorrent/Address.hs
new file mode 100644
index 00000000..eeb04c74
--- /dev/null
+++ b/src/Network/BitTorrent/Address.hs
@@ -0,0 +1,1172 @@
1-- |
2-- Module : Network.BitTorrent.Address
3-- Copyright : (c) Sam Truzjan 2013
4-- (c) Daniel Gröber 2013
5-- License : BSD3
6-- Maintainer : pxqr.sta@gmail.com
7-- Stability : provisional
8-- Portability : portable
9--
10-- Peer and Node addresses.
11--
12{-# LANGUAGE FlexibleInstances #-}
13{-# LANGUAGE RecordWildCards #-}
14{-# LANGUAGE StandaloneDeriving #-}
15{-# LANGUAGE ViewPatterns #-}
16{-# LANGUAGE GeneralizedNewtypeDeriving #-}
17{-# LANGUAGE MultiParamTypeClasses #-}
18{-# LANGUAGE DeriveDataTypeable #-}
19{-# LANGUAGE DeriveFunctor #-}
20{-# LANGUAGE TemplateHaskell #-}
21{-# OPTIONS -fno-warn-orphans #-}
22module Network.BitTorrent.Address
23 ( -- * Address
24 Address (..)
25 , fromAddr
26
27 -- ** IP
28 , IPv4
29 , IPv6
30 , IP (..)
31
32 -- * PeerId
33 -- $peer-id
34 , PeerId
35
36 -- ** Generation
37 , genPeerId
38 , timestamp
39 , entropy
40
41 -- ** Encoding
42 , azureusStyle
43 , shadowStyle
44 , defaultClientId
45 , defaultVersionNumber
46
47 -- * PeerAddr
48 -- $peer-addr
49 , PeerAddr(..)
50 , defaultPorts
51 , peerSockAddr
52 , peerSocket
53
54 -- * Node
55 -- ** Id
56 , NodeId
57 , testIdBit
58 , genNodeId
59 , NodeDistance
60 , distance
61
62 -- ** Info
63 , NodeAddr (..)
64 , NodeInfo (..)
65 , rank
66
67 -- * Fingerprint
68 -- $fingerprint
69 , Software (..)
70 , Fingerprint (..)
71 , libFingerprint
72 , fingerprint
73
74 -- * Utils
75 , libUserAgent
76 ) where
77
78import Control.Applicative
79import Control.Monad
80import Data.BEncode as BE
81import Data.BEncode as BS
82import Data.BEncode.BDict (BKey)
83import Data.Bits
84import Data.ByteString as BS
85import Data.ByteString.Internal as BS
86import Data.ByteString.Base16 as Base16
87import Data.ByteString.Char8 as BC
88import Data.ByteString.Char8 as BS8
89import qualified Data.ByteString.Lazy as BL
90import qualified Data.ByteString.Lazy.Builder as BS
91import Data.Char
92import Data.Convertible
93import Data.Default
94import Data.Foldable
95import Data.IP
96import Data.List as L
97import Data.List.Split as L
98import Data.Maybe (fromMaybe, catMaybes)
99import Data.Monoid
100import Data.Hashable
101import Data.Ord
102import Data.Serialize as S
103import Data.String
104import Data.Time
105import Data.Typeable
106import Data.Version
107import Data.Word
108import qualified Text.ParserCombinators.ReadP as RP
109import Text.Read (readMaybe)
110import Network.HTTP.Types.QueryLike
111import Network.Socket
112import Text.PrettyPrint as PP hiding ((<>))
113import Text.PrettyPrint.Class
114import System.Locale (defaultTimeLocale)
115import System.Entropy
116
117-- import Paths_bittorrent (version)
118
119{-----------------------------------------------------------------------
120-- Address
121-----------------------------------------------------------------------}
122
123instance Pretty UTCTime where
124 pretty = PP.text . show
125
126class (Eq a, Serialize a, Typeable a, Hashable a, Pretty a)
127 => Address a where
128 toSockAddr :: a -> SockAddr
129 fromSockAddr :: SockAddr -> Maybe a
130
131fromAddr :: (Address a, Address b) => a -> Maybe b
132fromAddr = fromSockAddr . toSockAddr
133
134-- | Note that port is zeroed.
135instance Address IPv4 where
136 toSockAddr = SockAddrInet 0 . toHostAddress
137 fromSockAddr (SockAddrInet _ h) = Just (fromHostAddress h)
138 fromSockAddr _ = Nothing
139
140-- | Note that port is zeroed.
141instance Address IPv6 where
142 toSockAddr h = SockAddrInet6 0 0 (toHostAddress6 h) 0
143 fromSockAddr (SockAddrInet6 _ _ h _) = Just (fromHostAddress6 h)
144 fromSockAddr _ = Nothing
145
146-- | Note that port is zeroed.
147instance Address IP where
148 toSockAddr (IPv4 h) = toSockAddr h
149 toSockAddr (IPv6 h) = toSockAddr h
150 fromSockAddr sa =
151 IPv4 <$> fromSockAddr sa
152 <|> IPv6 <$> fromSockAddr sa
153
154setPort :: PortNumber -> SockAddr -> SockAddr
155setPort port (SockAddrInet _ h ) = SockAddrInet port h
156setPort port (SockAddrInet6 _ f h s) = SockAddrInet6 port f h s
157setPort _ (SockAddrUnix s ) = SockAddrUnix s
158{-# INLINE setPort #-}
159
160getPort :: SockAddr -> Maybe PortNumber
161getPort (SockAddrInet p _ ) = Just p
162getPort (SockAddrInet6 p _ _ _) = Just p
163getPort (SockAddrUnix _ ) = Nothing
164{-# INLINE getPort #-}
165
166instance Address a => Address (NodeAddr a) where
167 toSockAddr NodeAddr {..} = setPort nodePort $ toSockAddr nodeHost
168 fromSockAddr sa = NodeAddr <$> fromSockAddr sa <*> getPort sa
169
170instance Address a => Address (PeerAddr a) where
171 toSockAddr PeerAddr {..} = setPort peerPort $ toSockAddr peerHost
172 fromSockAddr sa = PeerAddr Nothing <$> fromSockAddr sa <*> getPort sa
173
174{-----------------------------------------------------------------------
175-- Peer id
176-----------------------------------------------------------------------}
177-- $peer-id
178--
179-- 'PeerID' represent self assigned peer identificator. Ideally each
180-- host in the network should have unique peer id to avoid
181-- collisions, therefore for peer ID generation we use good entropy
182-- source. Peer ID is sent in /tracker request/, sent and received in
183-- /peer handshakes/ and used in DHT queries.
184--
185
186-- TODO use unpacked Word160 form (length is known statically)
187
188-- | Peer identifier is exactly 20 bytes long bytestring.
189newtype PeerId = PeerId { getPeerId :: ByteString }
190 deriving (Show, Eq, Ord, BEncode, Typeable)
191
192peerIdLen :: Int
193peerIdLen = 20
194
195-- | For testing purposes only.
196instance Default PeerId where
197 def = azureusStyle defaultClientId defaultVersionNumber ""
198
199instance Hashable PeerId where
200 hashWithSalt = hashUsing getPeerId
201 {-# INLINE hashWithSalt #-}
202
203instance Serialize PeerId where
204 put = putByteString . getPeerId
205 get = PeerId <$> getBytes peerIdLen
206
207instance QueryValueLike PeerId where
208 toQueryValue (PeerId pid) = Just pid
209 {-# INLINE toQueryValue #-}
210
211instance IsString PeerId where
212 fromString str
213 | BS.length bs == peerIdLen = PeerId bs
214 | otherwise = error $ "Peer id should be 20 bytes long: " ++ show str
215 where
216 bs = fromString str
217
218instance Pretty PeerId where
219 pretty = text . BC.unpack . getPeerId
220
221instance Convertible BS.ByteString PeerId where
222 safeConvert bs
223 | BS.length bs == peerIdLen = pure (PeerId bs)
224 | otherwise = convError "invalid length" bs
225
226------------------------------------------------------------------------
227
228-- | Pad bytestring so it's becomes exactly request length. Conversion
229-- is done like so:
230--
231-- * length < size: Complete bytestring by given charaters.
232--
233-- * length = size: Output bytestring as is.
234--
235-- * length > size: Drop last (length - size) charaters from a
236-- given bytestring.
237--
238byteStringPadded :: ByteString -- ^ bytestring to be padded.
239 -> Int -- ^ size of result builder.
240 -> Char -- ^ character used for padding.
241 -> BS.Builder
242byteStringPadded bs s c =
243 BS.byteString (BS.take s bs) <>
244 BS.byteString (BC.replicate padLen c)
245 where
246 padLen = s - min (BS.length bs) s
247
248-- | Azureus-style encoding have the following layout:
249--
250-- * 1 byte : '-'
251--
252-- * 2 bytes: client id
253--
254-- * 4 bytes: version number
255--
256-- * 1 byte : '-'
257--
258-- * 12 bytes: random number
259--
260azureusStyle :: ByteString -- ^ 2 character client ID, padded with 'H'.
261 -> ByteString -- ^ Version number, padded with 'X'.
262 -> ByteString -- ^ Random number, padded with '0'.
263 -> PeerId -- ^ Azureus-style encoded peer ID.
264azureusStyle cid ver rnd = PeerId $ BL.toStrict $ BS.toLazyByteString $
265 BS.char8 '-' <>
266 byteStringPadded cid 2 'H' <>
267 byteStringPadded ver 4 'X' <>
268 BS.char8 '-' <>
269 byteStringPadded rnd 12 '0'
270
271-- | Shadow-style encoding have the following layout:
272--
273-- * 1 byte : client id.
274--
275-- * 0-4 bytes: version number. If less than 4 then padded with
276-- '-' char.
277--
278-- * 15 bytes : random number. If length is less than 15 then
279-- padded with '0' char.
280--
281shadowStyle :: Char -- ^ Client ID.
282 -> ByteString -- ^ Version number.
283 -> ByteString -- ^ Random number.
284 -> PeerId -- ^ Shadow style encoded peer ID.
285shadowStyle cid ver rnd = PeerId $ BL.toStrict $ BS.toLazyByteString $
286 BS.char8 cid <>
287 byteStringPadded ver 4 '-' <>
288 byteStringPadded rnd 15 '0'
289
290
291-- | 'HS'- 2 bytes long client identifier.
292defaultClientId :: ByteString
293defaultClientId = "HS"
294
295-- | Gives exactly 4 bytes long version number for any version of the
296-- package. Version is taken from .cabal file.
297defaultVersionNumber :: ByteString
298defaultVersionNumber = BS.take 4 $ BC.pack $ foldMap show $
299 versionBranch myVersion
300 where
301 Fingerprint _ myVersion = libFingerprint
302
303------------------------------------------------------------------------
304
305-- | Gives 15 characters long decimal timestamp such that:
306--
307-- * 6 bytes : first 6 characters from picoseconds obtained with %q.
308--
309-- * 1 byte : character \'.\' for readability.
310--
311-- * 9..* bytes: number of whole seconds since the Unix epoch
312-- (!)REVERSED.
313--
314-- Can be used both with shadow and azureus style encoding. This
315-- format is used to make the ID's readable for debugging purposes.
316--
317timestamp :: IO ByteString
318timestamp = (BC.pack . format) <$> getCurrentTime
319 where
320 format t = L.take 6 (formatTime defaultTimeLocale "%q" t) ++ "." ++
321 L.take 9 (L.reverse (formatTime defaultTimeLocale "%s" t))
322
323-- | Gives 15 character long random bytestring. This is more robust
324-- method for generation of random part of peer ID than 'timestamp'.
325entropy :: IO ByteString
326entropy = getEntropy 15
327
328-- NOTE: entropy generates incorrrect peer id
329
330-- | Here we use 'azureusStyle' encoding with the following args:
331--
332-- * 'HS' for the client id; ('defaultClientId')
333--
334-- * Version of the package for the version number;
335-- ('defaultVersionNumber')
336--
337-- * UTC time day ++ day time for the random number. ('timestamp')
338--
339genPeerId :: IO PeerId
340genPeerId = azureusStyle defaultClientId defaultVersionNumber <$> timestamp
341
342{-----------------------------------------------------------------------
343-- Peer Addr
344-----------------------------------------------------------------------}
345-- $peer-addr
346--
347-- 'PeerAddr' is used to represent peer address. Currently it's
348-- just peer IP and peer port but this might change in future.
349--
350
351{-----------------------------------------------------------------------
352-- Port number
353-----------------------------------------------------------------------}
354
355instance BEncode PortNumber where
356 toBEncode = toBEncode . fromEnum
357 fromBEncode = fromBEncode >=> portNumber
358 where
359 portNumber :: Integer -> BS.Result PortNumber
360 portNumber n
361 | 0 <= n && n <= fromIntegral (maxBound :: Word16)
362 = pure $ fromIntegral n
363 | otherwise = decodingError $ "PortNumber: " ++ show n
364
365instance Serialize PortNumber where
366 get = fromIntegral <$> getWord16be
367 {-# INLINE get #-}
368 put = putWord16be . fromIntegral
369 {-# INLINE put #-}
370
371instance Hashable PortNumber where
372 hashWithSalt s = hashWithSalt s . fromEnum
373 {-# INLINE hashWithSalt #-}
374
375instance Pretty PortNumber where
376 pretty = PP.int . fromEnum
377 {-# INLINE pretty #-}
378
379{-----------------------------------------------------------------------
380-- IP addr
381-----------------------------------------------------------------------}
382
383class IPAddress i where
384 toHostAddr :: i -> Either HostAddress HostAddress6
385
386instance IPAddress IPv4 where
387 toHostAddr = Left . toHostAddress
388 {-# INLINE toHostAddr #-}
389
390instance IPAddress IPv6 where
391 toHostAddr = Right . toHostAddress6
392 {-# INLINE toHostAddr #-}
393
394instance IPAddress IP where
395 toHostAddr (IPv4 ip) = toHostAddr ip
396 toHostAddr (IPv6 ip) = toHostAddr ip
397 {-# INLINE toHostAddr #-}
398
399deriving instance Typeable IP
400deriving instance Typeable IPv4
401deriving instance Typeable IPv6
402
403ipToBEncode :: Show i => i -> BValue
404ipToBEncode ip = BString $ BS8.pack $ show ip
405{-# INLINE ipToBEncode #-}
406
407ipFromBEncode :: Read a => BValue -> BS.Result a
408ipFromBEncode (BString (BS8.unpack -> ipStr))
409 | Just ip <- readMaybe (ipStr) = pure ip
410 | otherwise = decodingError $ "IP: " ++ ipStr
411ipFromBEncode _ = decodingError $ "IP: addr should be a bstring"
412
413instance BEncode IP where
414 toBEncode = ipToBEncode
415 {-# INLINE toBEncode #-}
416 fromBEncode = ipFromBEncode
417 {-# INLINE fromBEncode #-}
418
419instance BEncode IPv4 where
420 toBEncode = ipToBEncode
421 {-# INLINE toBEncode #-}
422 fromBEncode = ipFromBEncode
423 {-# INLINE fromBEncode #-}
424
425instance BEncode IPv6 where
426 toBEncode = ipToBEncode
427 {-# INLINE toBEncode #-}
428 fromBEncode = ipFromBEncode
429 {-# INLINE fromBEncode #-}
430
431-- | When 'get'ing an IP it must be 'isolate'd to the appropriate
432-- number of bytes since we have no other way of telling which
433-- address type we are trying to parse
434instance Serialize IP where
435 put (IPv4 ip) = put ip
436 put (IPv6 ip) = put ip
437
438 get = do
439 n <- remaining
440 case n of
441 4 -> IPv4 <$> get
442 16 -> IPv6 <$> get
443 _ -> fail "Wrong number of bytes remaining to parse IP"
444
445instance Serialize IPv4 where
446 put = putWord32host . toHostAddress
447 get = fromHostAddress <$> getWord32host
448
449instance Serialize IPv6 where
450 put ip = put $ toHostAddress6 ip
451 get = fromHostAddress6 <$> get
452
453instance Pretty IPv4 where
454 pretty = PP.text . show
455 {-# INLINE pretty #-}
456
457instance Pretty IPv6 where
458 pretty = PP.text . show
459 {-# INLINE pretty #-}
460
461instance Pretty IP where
462 pretty = PP.text . show
463 {-# INLINE pretty #-}
464
465instance Hashable IPv4 where
466 hashWithSalt = hashUsing toHostAddress
467 {-# INLINE hashWithSalt #-}
468
469instance Hashable IPv6 where
470 hashWithSalt s a = hashWithSalt s (toHostAddress6 a)
471
472instance Hashable IP where
473 hashWithSalt s (IPv4 h) = hashWithSalt s h
474 hashWithSalt s (IPv6 h) = hashWithSalt s h
475
476{-----------------------------------------------------------------------
477-- Peer addr
478-----------------------------------------------------------------------}
479-- TODO check semantic of ord and eq instances
480
481-- | Peer address info normally extracted from peer list or peer
482-- compact list encoding.
483data PeerAddr a = PeerAddr
484 { peerId :: !(Maybe PeerId)
485
486 -- | This is usually 'IPv4', 'IPv6', 'IP' or unresolved
487 -- 'HostName'.
488 , peerHost :: !a
489
490 -- | The port the peer listenning for incoming P2P sessions.
491 , peerPort :: {-# UNPACK #-} !PortNumber
492 } deriving (Show, Eq, Ord, Typeable, Functor)
493
494peer_ip_key, peer_id_key, peer_port_key :: BKey
495peer_ip_key = "ip"
496peer_id_key = "peer id"
497peer_port_key = "port"
498
499-- | The tracker's 'announce response' compatible encoding.
500instance (Typeable a, BEncode a) => BEncode (PeerAddr a) where
501 toBEncode PeerAddr {..} = toDict $
502 peer_ip_key .=! peerHost
503 .: peer_id_key .=? peerId
504 .: peer_port_key .=! peerPort
505 .: endDict
506
507 fromBEncode = fromDict $ do
508 peerAddr <$>! peer_ip_key
509 <*>? peer_id_key
510 <*>! peer_port_key
511 where
512 peerAddr = flip PeerAddr
513
514-- | The tracker's 'compact peer list' compatible encoding. The
515-- 'peerId' is always 'Nothing'.
516--
517-- For more info see: <http://www.bittorrent.org/beps/bep_0023.html>
518--
519-- TODO: test byte order
520instance (Serialize a) => Serialize (PeerAddr a) where
521 put PeerAddr {..} = put peerHost >> put peerPort
522 get = PeerAddr Nothing <$> get <*> get
523
524-- | @127.0.0.1:6881@
525instance Default (PeerAddr IPv4) where
526 def = "127.0.0.1:6881"
527
528-- | @127.0.0.1:6881@
529instance Default (PeerAddr IP) where
530 def = IPv4 <$> def
531
532-- | Example:
533--
534-- @peerPort \"127.0.0.1:6881\" == 6881@
535--
536instance IsString (PeerAddr IPv4) where
537 fromString str
538 | [hostAddrStr, portStr] <- splitWhen (== ':') str
539 , Just hostAddr <- readMaybe hostAddrStr
540 , Just portNum <- toEnum <$> readMaybe portStr
541 = PeerAddr Nothing hostAddr portNum
542 | otherwise = error $ "fromString: unable to parse (PeerAddr IPv4): " ++ str
543
544instance Read (PeerAddr IPv4) where
545 readsPrec i = RP.readP_to_S $ do
546 ipv4 <- RP.readS_to_P (readsPrec i)
547 _ <- RP.char ':'
548 port <- toEnum <$> RP.readS_to_P (readsPrec i)
549 return $ PeerAddr Nothing ipv4 port
550
551readsIPv6_port :: String -> [((IPv6, PortNumber), String)]
552readsIPv6_port = RP.readP_to_S $ do
553 ip <- RP.char '[' *> (RP.readS_to_P reads) <* RP.char ']'
554 _ <- RP.char ':'
555 port <- toEnum <$> read <$> (RP.many1 $ RP.satisfy isDigit) <* RP.eof
556 return (ip,port)
557
558instance IsString (PeerAddr IPv6) where
559 fromString str
560 | [((ip,port),"")] <- readsIPv6_port str =
561 PeerAddr Nothing ip port
562 | otherwise = error $ "fromString: unable to parse (PeerAddr IPv6): " ++ str
563
564instance IsString (PeerAddr IP) where
565 fromString str
566 | '[' `L.elem` str = IPv6 <$> fromString str
567 | otherwise = IPv4 <$> fromString str
568
569-- | fingerprint + "at" + dotted.host.inet.addr:port
570-- TODO: instances for IPv6, HostName
571instance Pretty a => Pretty (PeerAddr a) where
572 pretty PeerAddr {..}
573 | Just pid <- peerId = pretty (fingerprint pid) <+> "at" <+> paddr
574 | otherwise = paddr
575 where
576 paddr = pretty peerHost <> ":" <> text (show peerPort)
577
578instance Hashable a => Hashable (PeerAddr a) where
579 hashWithSalt s PeerAddr {..} =
580 s `hashWithSalt` peerId `hashWithSalt` peerHost `hashWithSalt` peerPort
581
582-- | Ports typically reserved for bittorrent P2P listener.
583defaultPorts :: [PortNumber]
584defaultPorts = [6881..6889]
585
586_resolvePeerAddr :: (IPAddress i) => PeerAddr HostName -> PeerAddr i
587_resolvePeerAddr = undefined
588
589_peerSockAddr :: PeerAddr IP -> (Family, SockAddr)
590_peerSockAddr PeerAddr {..} =
591 case peerHost of
592 IPv4 ipv4 ->
593 (AF_INET, SockAddrInet peerPort (toHostAddress ipv4))
594 IPv6 ipv6 ->
595 (AF_INET6, SockAddrInet6 peerPort 0 (toHostAddress6 ipv6) 0)
596
597peerSockAddr :: PeerAddr IP -> SockAddr
598peerSockAddr = snd . _peerSockAddr
599
600-- | Create a socket connected to the address specified in a peerAddr
601peerSocket :: SocketType -> PeerAddr IP -> IO Socket
602peerSocket socketType pa = do
603 let (family, addr) = _peerSockAddr pa
604 sock <- socket family socketType defaultProtocol
605 connect sock addr
606 return sock
607
608{-----------------------------------------------------------------------
609-- Node info
610-----------------------------------------------------------------------}
611-- $node-info
612--
613-- A \"node\" is a client\/server listening on a UDP port
614-- implementing the distributed hash table protocol. The DHT is
615-- composed of nodes and stores the location of peers. BitTorrent
616-- clients include a DHT node, which is used to contact other nodes
617-- in the DHT to get the location of peers to download from using
618-- the BitTorrent protocol.
619
620-- TODO more compact representation ('ShortByteString's?)
621
622-- | Each node has a globally unique identifier known as the \"node
623-- ID.\"
624--
625-- Normally, /this/ node id should be saved between invocations
626-- of the client software.
627newtype NodeId = NodeId ByteString
628 deriving (Show, Eq, Ord, BEncode, Typeable)
629
630nodeIdSize :: Int
631nodeIdSize = 20
632
633-- | Meaningless node id, for testing purposes only.
634instance Default NodeId where
635 def = NodeId (BS.replicate nodeIdSize 0)
636
637instance Serialize NodeId where
638 get = NodeId <$> getByteString nodeIdSize
639 {-# INLINE get #-}
640 put (NodeId bs) = putByteString bs
641 {-# INLINE put #-}
642
643-- | ASCII encoded.
644instance IsString NodeId where
645 fromString str
646 | L.length str == nodeIdSize = NodeId (fromString str)
647 | otherwise = error "fromString: invalid NodeId length"
648 {-# INLINE fromString #-}
649
650-- | base16 encoded.
651instance Pretty NodeId where
652 pretty (NodeId nid) = PP.text $ BC.unpack $ Base16.encode nid
653
654-- | Test if the nth bit is set.
655testIdBit :: NodeId -> Word -> Bool
656testIdBit (NodeId bs) i
657 | fromIntegral i < nodeIdSize * 8
658 , (q, r) <- quotRem (fromIntegral i) 8
659 = testBit (BS.index bs q) r
660 | otherwise = False
661{-# INLINE testIdBit #-}
662
663-- TODO WARN is the 'system' random suitable for this?
664-- | Generate random NodeID used for the entire session.
665-- Distribution of ID's should be as uniform as possible.
666--
667genNodeId :: IO NodeId
668genNodeId = NodeId <$> getEntropy nodeIdSize
669
670------------------------------------------------------------------------
671
672-- | In Kademlia, the distance metric is XOR and the result is
673-- interpreted as an unsigned integer.
674newtype NodeDistance = NodeDistance BS.ByteString
675 deriving (Eq, Ord)
676
677instance Pretty NodeDistance where
678 pretty (NodeDistance bs) = foldMap bitseq $ BS.unpack bs
679 where
680 listBits w = L.map (testBit w) (L.reverse [0..bitSize w - 1])
681 bitseq = foldMap (int . fromEnum) . listBits
682
683-- | distance(A,B) = |A xor B| Smaller values are closer.
684distance :: NodeId -> NodeId -> NodeDistance
685distance (NodeId a) (NodeId b) = NodeDistance (BS.pack (BS.zipWith xor a b))
686
687------------------------------------------------------------------------
688
689data NodeAddr a = NodeAddr
690 { nodeHost :: !a
691 , nodePort :: {-# UNPACK #-} !PortNumber
692 } deriving (Eq, Typeable, Functor)
693
694instance Show a => Show (NodeAddr a) where
695 showsPrec i NodeAddr {..}
696 = showsPrec i nodeHost <> showString ":" <> showsPrec i nodePort
697
698instance Read (NodeAddr IPv4) where
699 readsPrec i x = [ (fromPeerAddr a, s) | (a, s) <- readsPrec i x ]
700
701-- | @127.0.0.1:6882@
702instance Default (NodeAddr IPv4) where
703 def = "127.0.0.1:6882"
704
705-- | KRPC compatible encoding.
706instance Serialize a => Serialize (NodeAddr a) where
707 get = NodeAddr <$> get <*> get
708 {-# INLINE get #-}
709 put NodeAddr {..} = put nodeHost >> put nodePort
710 {-# INLINE put #-}
711
712-- | Torrent file compatible encoding.
713instance BEncode a => BEncode (NodeAddr a) where
714 toBEncode NodeAddr {..} = toBEncode (nodeHost, nodePort)
715 {-# INLINE toBEncode #-}
716 fromBEncode b = uncurry NodeAddr <$> fromBEncode b
717 {-# INLINE fromBEncode #-}
718
719instance Hashable a => Hashable (NodeAddr a) where
720 hashWithSalt s NodeAddr {..} = hashWithSalt s (nodeHost, nodePort)
721 {-# INLINE hashWithSalt #-}
722
723instance Pretty ip => Pretty (NodeAddr ip) where
724 pretty NodeAddr {..} = pretty nodeHost <> ":" <> pretty nodePort
725
726-- | Example:
727--
728-- @nodePort \"127.0.0.1:6881\" == 6881@
729--
730instance IsString (NodeAddr IPv4) where
731 fromString = fromPeerAddr . fromString
732
733fromPeerAddr :: PeerAddr a -> NodeAddr a
734fromPeerAddr PeerAddr {..} = NodeAddr
735 { nodeHost = peerHost
736 , nodePort = peerPort
737 }
738
739------------------------------------------------------------------------
740
741data NodeInfo a = NodeInfo
742 { nodeId :: !NodeId
743 , nodeAddr :: !(NodeAddr a)
744 } deriving (Show, Eq, Functor)
745
746instance Eq a => Ord (NodeInfo a) where
747 compare = comparing nodeId
748
749-- | KRPC 'compact list' compatible encoding: contact information for
750-- nodes is encoded as a 26-byte string. Also known as "Compact node
751-- info" the 20-byte Node ID in network byte order has the compact
752-- IP-address/port info concatenated to the end.
753instance Serialize a => Serialize (NodeInfo a) where
754 get = NodeInfo <$> get <*> get
755 put NodeInfo {..} = put nodeId >> put nodeAddr
756
757instance Pretty ip => Pretty (NodeInfo ip) where
758 pretty NodeInfo {..} = pretty nodeId <> "@(" <> pretty nodeAddr <> ")"
759
760instance Pretty ip => Pretty [NodeInfo ip] where
761 pretty = PP.vcat . PP.punctuate "," . L.map pretty
762
763-- | Order by closeness: nearest nodes first.
764rank :: Eq ip => NodeId -> [NodeInfo ip] -> [NodeInfo ip]
765rank nid = L.sortBy (comparing (distance nid . nodeId))
766
767{-----------------------------------------------------------------------
768-- Fingerprint
769-----------------------------------------------------------------------}
770-- $fingerprint
771--
772-- 'Fingerprint' is used to identify the client implementation and
773-- version which also contained in 'Peer'. For exsample first 6
774-- bytes of peer id of this this library are @-HS0100-@ while for
775-- mainline we have @M4-3-6--@. We could extract this info and
776-- print in human-friendly form: this is useful for debugging and
777-- logging.
778--
779-- For more information see:
780-- <http://bittorrent.org/beps/bep_0020.html>
781--
782--
783-- NOTE: Do /not/ use this information to control client
784-- capabilities (such as supported enchancements), this should be
785-- done using 'Network.BitTorrent.Extension'!
786--
787
788-- TODO FIXME
789version :: Version
790version = Version [0, 0, 0, 3] []
791
792-- | List of registered client versions + 'IlibHSbittorrent' (this
793-- package) + 'IUnknown' (for not recognized software). All names are
794-- prefixed by \"I\" because some of them starts from lowercase letter
795-- but that is not a valid Haskell constructor name.
796--
797data Software =
798 IUnknown
799
800 | IMainline
801
802 | IABC
803 | IOspreyPermaseed
804 | IBTQueue
805 | ITribler
806 | IShadow
807 | IBitTornado
808
809-- UPnP(!) Bit Torrent !???
810-- 'U' - UPnP NAT Bit Torrent
811 | IBitLord
812 | IOpera
813 | IMLdonkey
814
815 | IAres
816 | IArctic
817 | IAvicora
818 | IBitPump
819 | IAzureus
820 | IBitBuddy
821 | IBitComet
822 | IBitflu
823 | IBTG
824 | IBitRocket
825 | IBTSlave
826 | IBittorrentX
827 | IEnhancedCTorrent
828 | ICTorrent
829 | IDelugeTorrent
830 | IPropagateDataClient
831 | IEBit
832 | IElectricSheep
833 | IFoxTorrent
834 | IGSTorrent
835 | IHalite
836 | IlibHSbittorrent
837 | IHydranode
838 | IKGet
839 | IKTorrent
840 | ILH_ABC
841 | ILphant
842 | ILibtorrent
843 | ILibTorrent
844 | ILimeWire
845 | IMonoTorrent
846 | IMooPolice
847 | IMiro
848 | IMoonlightTorrent
849 | INetTransport
850 | IPando
851 | IqBittorrent
852 | IQQDownload
853 | IQt4TorrentExample
854 | IRetriever
855 | IShareaza
856 | ISwiftbit
857 | ISwarmScope
858 | ISymTorrent
859 | Isharktorrent
860 | ITorrentDotNET
861 | ITransmission
862 | ITorrentstorm
863 | ITuoTu
864 | IuLeecher
865 | IuTorrent
866 | IVagaa
867 | IBitLet
868 | IFireTorrent
869 | IXunlei
870 | IXanTorrent
871 | IXtorrent
872 | IZipTorrent
873 deriving (Show, Eq, Ord, Enum, Bounded)
874
875parseSoftware :: ByteString -> Software
876parseSoftware = f . BC.unpack
877 where
878 f "AG" = IAres
879 f "A~" = IAres
880 f "AR" = IArctic
881 f "AV" = IAvicora
882 f "AX" = IBitPump
883 f "AZ" = IAzureus
884 f "BB" = IBitBuddy
885 f "BC" = IBitComet
886 f "BF" = IBitflu
887 f "BG" = IBTG
888 f "BR" = IBitRocket
889 f "BS" = IBTSlave
890 f "BX" = IBittorrentX
891 f "CD" = IEnhancedCTorrent
892 f "CT" = ICTorrent
893 f "DE" = IDelugeTorrent
894 f "DP" = IPropagateDataClient
895 f "EB" = IEBit
896 f "ES" = IElectricSheep
897 f "FT" = IFoxTorrent
898 f "GS" = IGSTorrent
899 f "HL" = IHalite
900 f "HS" = IlibHSbittorrent
901 f "HN" = IHydranode
902 f "KG" = IKGet
903 f "KT" = IKTorrent
904 f "LH" = ILH_ABC
905 f "LP" = ILphant
906 f "LT" = ILibtorrent
907 f "lt" = ILibTorrent
908 f "LW" = ILimeWire
909 f "MO" = IMonoTorrent
910 f "MP" = IMooPolice
911 f "MR" = IMiro
912 f "ML" = IMLdonkey
913 f "MT" = IMoonlightTorrent
914 f "NX" = INetTransport
915 f "PD" = IPando
916 f "qB" = IqBittorrent
917 f "QD" = IQQDownload
918 f "QT" = IQt4TorrentExample
919 f "RT" = IRetriever
920 f "S~" = IShareaza
921 f "SB" = ISwiftbit
922 f "SS" = ISwarmScope
923 f "ST" = ISymTorrent
924 f "st" = Isharktorrent
925 f "SZ" = IShareaza
926 f "TN" = ITorrentDotNET
927 f "TR" = ITransmission
928 f "TS" = ITorrentstorm
929 f "TT" = ITuoTu
930 f "UL" = IuLeecher
931 f "UT" = IuTorrent
932 f "VG" = IVagaa
933 f "WT" = IBitLet
934 f "WY" = IFireTorrent
935 f "XL" = IXunlei
936 f "XT" = IXanTorrent
937 f "XX" = IXtorrent
938 f "ZT" = IZipTorrent
939 f _ = IUnknown
940
941-- | Used to represent a not recognized implementation
942instance Default Software where
943 def = IUnknown
944 {-# INLINE def #-}
945
946-- | Example: @\"BitLet\" == 'IBitLet'@
947instance IsString Software where
948 fromString str
949 | Just impl <- L.lookup str alist = impl
950 | otherwise = error $ "fromString: not recognized " ++ str
951 where
952 alist = L.map mk [minBound..maxBound]
953 mk x = (L.tail $ show x, x)
954
955-- | Example: @pretty 'IBitLet' == \"IBitLet\"@
956instance Pretty Software where
957 pretty = text . L.tail . show
958
959-- | Just the '0' version.
960instance Default Version where
961 def = Version [0] []
962 {-# INLINE def #-}
963
964-- | For dot delimited version strings.
965-- Example: @fromString \"0.1.0.2\" == Version [0, 1, 0, 2]@
966--
967instance IsString Version where
968 fromString str
969 | Just nums <- chunkNums str = Version nums []
970 | otherwise = error $ "fromString: invalid version string " ++ str
971 where
972 chunkNums = sequence . L.map readMaybe . L.linesBy ('.' ==)
973
974instance Pretty Version where
975 pretty = text . showVersion
976
977-- | The all sensible infomation that can be obtained from a peer
978-- identifier or torrent /createdBy/ field.
979data Fingerprint = Fingerprint Software Version
980 deriving (Show, Eq, Ord)
981
982-- | Unrecognized client implementation.
983instance Default Fingerprint where
984 def = Fingerprint def def
985 {-# INLINE def #-}
986
987-- | Example: @\"BitComet-1.2\" == ClientInfo IBitComet (Version [1, 2] [])@
988instance IsString Fingerprint where
989 fromString str
990 | _ : ver <- _ver = Fingerprint (fromString impl) (fromString ver)
991 | otherwise = error $ "fromString: invalid client info string" ++ str
992 where
993 (impl, _ver) = L.span ((/=) '-') str
994
995instance Pretty Fingerprint where
996 pretty (Fingerprint s v) = pretty s <+> "version" <+> pretty v
997
998-- | Fingerprint of this (the bittorrent library) package. Normally,
999-- applications should introduce its own fingerprints, otherwise they
1000-- can use 'libFingerprint' value.
1001--
1002libFingerprint :: Fingerprint
1003libFingerprint = Fingerprint IlibHSbittorrent version
1004
1005-- | HTTP user agent of this (the bittorrent library) package. Can be
1006-- used in HTTP tracker requests.
1007libUserAgent :: String
1008libUserAgent = render (pretty IlibHSbittorrent <> "/" <> pretty version)
1009
1010{-----------------------------------------------------------------------
1011-- For torrent file
1012-----------------------------------------------------------------------}
1013-- TODO collect information about createdBy torrent field
1014{-
1015renderImpl :: ClientImpl -> Text
1016renderImpl = T.pack . L.tail . show
1017
1018renderVersion :: Version -> Text
1019renderVersion = undefined
1020
1021renderClientInfo :: ClientInfo -> Text
1022renderClientInfo ClientInfo {..} = renderImpl ciImpl <> "/" <> renderVersion ciVersion
1023
1024parseClientInfo :: Text -> ClientImpl
1025parseClientInfo t = undefined
1026-}
1027{-
1028-- code used for generation; remove it later on
1029
1030mkEnumTyDef :: NM -> String
1031mkEnumTyDef = unlines . map (" | I" ++) . nub . map snd
1032
1033mkPars :: NM -> String
1034mkPars = unlines . map (\(code, impl) -> " f \"" ++ code ++ "\" = " ++ "I" ++ impl)
1035
1036type NM = [(String, String)]
1037nameMap :: NM
1038nameMap =
1039 [ ("AG", "Ares")
1040 , ("A~", "Ares")
1041 , ("AR", "Arctic")
1042 , ("AV", "Avicora")
1043 , ("AX", "BitPump")
1044 , ("AZ", "Azureus")
1045 , ("BB", "BitBuddy")
1046 , ("BC", "BitComet")
1047 , ("BF", "Bitflu")
1048 , ("BG", "BTG")
1049 , ("BR", "BitRocket")
1050 , ("BS", "BTSlave")
1051 , ("BX", "BittorrentX")
1052 , ("CD", "EnhancedCTorrent")
1053 , ("CT", "CTorrent")
1054 , ("DE", "DelugeTorrent")
1055 , ("DP", "PropagateDataClient")
1056 , ("EB", "EBit")
1057 , ("ES", "ElectricSheep")
1058 , ("FT", "FoxTorrent")
1059 , ("GS", "GSTorrent")
1060 , ("HL", "Halite")
1061 , ("HS", "libHSnetwork_bittorrent")
1062 , ("HN", "Hydranode")
1063 , ("KG", "KGet")
1064 , ("KT", "KTorrent")
1065 , ("LH", "LH_ABC")
1066 , ("LP", "Lphant")
1067 , ("LT", "Libtorrent")
1068 , ("lt", "LibTorrent")
1069 , ("LW", "LimeWire")
1070 , ("MO", "MonoTorrent")
1071 , ("MP", "MooPolice")
1072 , ("MR", "Miro")
1073 , ("MT", "MoonlightTorrent")
1074 , ("NX", "NetTransport")
1075 , ("PD", "Pando")
1076 , ("qB", "qBittorrent")
1077 , ("QD", "QQDownload")
1078 , ("QT", "Qt4TorrentExample")
1079 , ("RT", "Retriever")
1080 , ("S~", "Shareaza")
1081 , ("SB", "Swiftbit")
1082 , ("SS", "SwarmScope")
1083 , ("ST", "SymTorrent")
1084 , ("st", "sharktorrent")
1085 , ("SZ", "Shareaza")
1086 , ("TN", "TorrentDotNET")
1087 , ("TR", "Transmission")
1088 , ("TS", "Torrentstorm")
1089 , ("TT", "TuoTu")
1090 , ("UL", "uLeecher")
1091 , ("UT", "uTorrent")
1092 , ("VG", "Vagaa")
1093 , ("WT", "BitLet")
1094 , ("WY", "FireTorrent")
1095 , ("XL", "Xunlei")
1096 , ("XT", "XanTorrent")
1097 , ("XX", "Xtorrent")
1098 , ("ZT", "ZipTorrent")
1099 ]
1100-}
1101
1102-- TODO use regexps
1103
1104-- | Tries to extract meaningful information from peer ID bytes. If
1105-- peer id uses unknown coding style then client info returned is
1106-- 'def'.
1107--
1108fingerprint :: PeerId -> Fingerprint
1109fingerprint pid = either (const def) id $ runGet getCI (getPeerId pid)
1110 where
1111 getCI = do
1112 leading <- BS.w2c <$> getWord8
1113 case leading of
1114 '-' -> Fingerprint <$> getAzureusImpl <*> getAzureusVersion
1115 'M' -> Fingerprint <$> pure IMainline <*> getMainlineVersion
1116 'e' -> Fingerprint <$> getBitCometImpl <*> getBitCometVersion
1117 'F' -> Fingerprint <$> getBitCometImpl <*> getBitCometVersion
1118 c -> do
1119 c1 <- w2c <$> S.lookAhead getWord8
1120 if c1 == 'P'
1121 then do
1122 _ <- getWord8
1123 Fingerprint <$> pure IOpera <*> getOperaVersion
1124 else Fingerprint <$> pure (getShadowImpl c) <*> getShadowVersion
1125
1126 getMainlineVersion = do
1127 str <- BC.unpack <$> getByteString 7
1128 let mnums = L.filter (not . L.null) $ L.linesBy ('-' ==) str
1129 return $ Version (fromMaybe [] $ sequence $ L.map readMaybe mnums) []
1130
1131 getAzureusImpl = parseSoftware <$> getByteString 2
1132 getAzureusVersion = mkVer <$> getByteString 4
1133 where
1134 mkVer bs = Version [fromMaybe 0 $ readMaybe $ BC.unpack bs] []
1135
1136 getBitCometImpl = do
1137 bs <- getByteString 3
1138 S.lookAhead $ do
1139 _ <- getByteString 2
1140 lr <- getByteString 4
1141 return $
1142 if lr == "LORD" then IBitLord else
1143 if bs == "UTB" then IBitComet else
1144 if bs == "xbc" then IBitComet else def
1145
1146 getBitCometVersion = do
1147 x <- getWord8
1148 y <- getWord8
1149 return $ Version [fromIntegral x, fromIntegral y] []
1150
1151 getOperaVersion = do
1152 str <- BC.unpack <$> getByteString 4
1153 return $ Version [fromMaybe 0 $ readMaybe str] []
1154
1155 getShadowImpl 'A' = IABC
1156 getShadowImpl 'O' = IOspreyPermaseed
1157 getShadowImpl 'Q' = IBTQueue
1158 getShadowImpl 'R' = ITribler
1159 getShadowImpl 'S' = IShadow
1160 getShadowImpl 'T' = IBitTornado
1161 getShadowImpl _ = IUnknown
1162
1163 decodeShadowVerNr :: Char -> Maybe Int
1164 decodeShadowVerNr c
1165 | '0' < c && c <= '9' = Just (fromEnum c - fromEnum '0')
1166 | 'A' < c && c <= 'Z' = Just ((fromEnum c - fromEnum 'A') + 10)
1167 | 'a' < c && c <= 'z' = Just ((fromEnum c - fromEnum 'a') + 36)
1168 | otherwise = Nothing
1169
1170 getShadowVersion = do
1171 str <- BC.unpack <$> getByteString 5
1172 return $ Version (catMaybes $ L.map decodeShadowVerNr str) []