summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent/PeerWire
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network/BitTorrent/PeerWire')
-rw-r--r--src/Network/BitTorrent/PeerWire/ClientInfo.hs281
-rw-r--r--src/Network/BitTorrent/PeerWire/Handshake.hs4
-rw-r--r--src/Network/BitTorrent/PeerWire/Message.hs1
3 files changed, 2 insertions, 284 deletions
diff --git a/src/Network/BitTorrent/PeerWire/ClientInfo.hs b/src/Network/BitTorrent/PeerWire/ClientInfo.hs
deleted file mode 100644
index 629c883f..00000000
--- a/src/Network/BitTorrent/PeerWire/ClientInfo.hs
+++ /dev/null
@@ -1,281 +0,0 @@
1-- |
2-- Copyright : (c) Sam T. 2013
3-- License : MIT
4-- Maintainer : pxqr.sta@gmail.com
5-- Stability : experimental
6-- Portability : portable
7--
8-- This module detect client information such as version and
9-- implementation that can be later printed in human frienly
10-- form. Useful for debugging and logging.
11--
12-- > See http://bittorrent.org/beps/bep_0020.html for more information.
13--
14{-# LANGUAGE OverloadedStrings #-}
15module Network.BitTorrent.PeerWire.ClientInfo
16 ( ClientInfo(..), clientInfo, ppClientInfo, unknownClient
17
18 , ClientVersion, ppClientVersion
19 , ClientImpl(..), ppClientImpl
20
21-- , mkEnumTyDef, mkPars, nameMap
22 ) where
23
24import Control.Applicative
25--import Data.List
26import Data.ByteString (ByteString)
27import qualified Data.ByteString.Char8 as BC
28import Data.Serialize.Get
29
30import Network.BitTorrent.PeerID
31
32
33-- | All known client versions.
34data ClientImpl =
35 IUnknown
36 | IAres
37 | IArctic
38 | IAvicora
39 | IBitPump
40 | IAzureus
41 | IBitBuddy
42 | IBitComet
43 | IBitflu
44 | IBTG
45 | IBitRocket
46 | IBTSlave
47 | IBittorrentX
48 | IEnhancedCTorrent
49 | ICTorrent
50 | IDelugeTorrent
51 | IPropagateDataClient
52 | IEBit
53 | IElectricSheep
54 | IFoxTorrent
55 | IGSTorrent
56 | IHalite
57 | IlibHSbittorrent
58 | IHydranode
59 | IKGet
60 | IKTorrent
61 | ILH_ABC
62 | ILphant
63 | ILibtorrent
64 | ILibTorrent
65 | ILimeWire
66 | IMonoTorrent
67 | IMooPolice
68 | IMiro
69 | IMoonlightTorrent
70 | INetTransport
71 | IPando
72 | IqBittorrent
73 | IQQDownload
74 | IQt4TorrentExample
75 | IRetriever
76 | IShareaza
77 | ISwiftbit
78 | ISwarmScope
79 | ISymTorrent
80 | Isharktorrent
81 | ITorrentDotNET
82 | ITransmission
83 | ITorrentstorm
84 | ITuoTu
85 | IuLeecher
86 | IuTorrent
87 | IVagaa
88 | IBitLet
89 | IFireTorrent
90 | IXunlei
91 | IXanTorrent
92 | IXtorrent
93 | IZipTorrent
94 deriving (Show, Eq, Ord)
95
96parseImpl :: ByteString -> ClientImpl
97parseImpl = f . BC.unpack
98 where
99 f "AG" = IAres
100 f "A~" = IAres
101 f "AR" = IArctic
102 f "AV" = IAvicora
103 f "AX" = IBitPump
104 f "AZ" = IAzureus
105 f "BB" = IBitBuddy
106 f "BC" = IBitComet
107 f "BF" = IBitflu
108 f "BG" = IBTG
109 f "BR" = IBitRocket
110 f "BS" = IBTSlave
111 f "BX" = IBittorrentX
112 f "CD" = IEnhancedCTorrent
113 f "CT" = ICTorrent
114 f "DE" = IDelugeTorrent
115 f "DP" = IPropagateDataClient
116 f "EB" = IEBit
117 f "ES" = IElectricSheep
118 f "FT" = IFoxTorrent
119 f "GS" = IGSTorrent
120 f "HL" = IHalite
121 f "HS" = IlibHSbittorrent
122 f "HN" = IHydranode
123 f "KG" = IKGet
124 f "KT" = IKTorrent
125 f "LH" = ILH_ABC
126 f "LP" = ILphant
127 f "LT" = ILibtorrent
128 f "lt" = ILibTorrent
129 f "LW" = ILimeWire
130 f "MO" = IMonoTorrent
131 f "MP" = IMooPolice
132 f "MR" = IMiro
133 f "MT" = IMoonlightTorrent
134 f "NX" = INetTransport
135 f "PD" = IPando
136 f "qB" = IqBittorrent
137 f "QD" = IQQDownload
138 f "QT" = IQt4TorrentExample
139 f "RT" = IRetriever
140 f "S~" = IShareaza
141 f "SB" = ISwiftbit
142 f "SS" = ISwarmScope
143 f "ST" = ISymTorrent
144 f "st" = Isharktorrent
145 f "SZ" = IShareaza
146 f "TN" = ITorrentDotNET
147 f "TR" = ITransmission
148 f "TS" = ITorrentstorm
149 f "TT" = ITuoTu
150 f "UL" = IuLeecher
151 f "UT" = IuTorrent
152 f "VG" = IVagaa
153 f "WT" = IBitLet
154 f "WY" = IFireTorrent
155 f "XL" = IXunlei
156 f "XT" = IXanTorrent
157 f "XX" = IXtorrent
158 f "ZT" = IZipTorrent
159 f _ = IUnknown
160
161-- | Format client implementation info in human readable form.
162ppClientImpl :: ClientImpl -> String
163ppClientImpl = tail . show
164
165unknownImpl :: ClientImpl
166unknownImpl = IUnknown
167
168
169
170type ClientVersion = ByteString
171
172-- | Format client implementation version in human readable form.
173ppClientVersion :: ClientVersion -> String
174ppClientVersion = BC.unpack
175
176unknownVersion :: ClientVersion
177unknownVersion = "0000"
178
179
180-- | All useful infomation that can be obtained from a peer
181-- identifier.
182data ClientInfo = ClientInfo {
183 ciImpl :: ClientImpl
184 , ciVersion :: ClientVersion
185 } deriving (Show, Eq, Ord)
186
187-- | Format client implementation in human readable form.
188ppClientInfo :: ClientInfo -> String
189ppClientInfo ci = ppClientImpl (ciImpl ci) ++ " version "
190 ++ ppClientVersion (ciVersion ci)
191
192-- | Unrecognized client implementation.
193unknownClient :: ClientInfo
194unknownClient = ClientInfo unknownImpl unknownVersion
195
196-- | Tries to extract meaningful information from peer ID bytes. If
197-- peer id uses unknown coding style then client info returned is
198-- 'unknownClient'.
199--
200clientInfo :: PeerID -> ClientInfo
201clientInfo pid = either (const unknownClient) id $ runGet getCI (getPeerID pid)
202 where -- TODO other styles
203 getCI = do
204 _ <- getWord8
205 ClientInfo <$> (parseImpl <$> getByteString 2) <*> getByteString 4
206
207
208{-
209-- code used for generation; remove it later on
210
211mkEnumTyDef :: NM -> String
212mkEnumTyDef = unlines . map (" | I" ++) . nub . map snd
213
214mkPars :: NM -> String
215mkPars = unlines . map (\(code, impl) -> " f \"" ++ code ++ "\" = " ++ "I" ++ impl)
216
217type NM = [(String, String)]
218nameMap :: NM
219nameMap =
220 [ ("AG", "Ares")
221 , ("A~", "Ares")
222 , ("AR", "Arctic")
223 , ("AV", "Avicora")
224 , ("AX", "BitPump")
225 , ("AZ", "Azureus")
226 , ("BB", "BitBuddy")
227 , ("BC", "BitComet")
228 , ("BF", "Bitflu")
229 , ("BG", "BTG")
230 , ("BR", "BitRocket")
231 , ("BS", "BTSlave")
232 , ("BX", "BittorrentX")
233 , ("CD", "EnhancedCTorrent")
234 , ("CT", "CTorrent")
235 , ("DE", "DelugeTorrent")
236 , ("DP", "PropagateDataClient")
237 , ("EB", "EBit")
238 , ("ES", "ElectricSheep")
239 , ("FT", "FoxTorrent")
240 , ("GS", "GSTorrent")
241 , ("HL", "Halite")
242 , ("HS", "libHSnetwork_bittorrent")
243 , ("HN", "Hydranode")
244 , ("KG", "KGet")
245 , ("KT", "KTorrent")
246 , ("LH", "LH_ABC")
247 , ("LP", "Lphant")
248 , ("LT", "Libtorrent")
249 , ("lt", "LibTorrent")
250 , ("LW", "LimeWire")
251 , ("MO", "MonoTorrent")
252 , ("MP", "MooPolice")
253 , ("MR", "Miro")
254 , ("MT", "MoonlightTorrent")
255 , ("NX", "NetTransport")
256 , ("PD", "Pando")
257 , ("qB", "qBittorrent")
258 , ("QD", "QQDownload")
259 , ("QT", "Qt4TorrentExample")
260 , ("RT", "Retriever")
261 , ("S~", "Shareaza")
262 , ("SB", "Swiftbit")
263 , ("SS", "SwarmScope")
264 , ("ST", "SymTorrent")
265 , ("st", "sharktorrent")
266 , ("SZ", "Shareaza")
267 , ("TN", "TorrentDotNET")
268 , ("TR", "Transmission")
269 , ("TS", "Torrentstorm")
270 , ("TT", "TuoTu")
271 , ("UL", "uLeecher")
272 , ("UT", "uTorrent")
273 , ("VG", "Vagaa")
274 , ("WT", "BitLet")
275 , ("WY", "FireTorrent")
276 , ("XL", "Xunlei")
277 , ("XT", "XanTorrent")
278 , ("XX", "Xtorrent")
279 , ("ZT", "ZipTorrent")
280 ]
281-} \ No newline at end of file
diff --git a/src/Network/BitTorrent/PeerWire/Handshake.hs b/src/Network/BitTorrent/PeerWire/Handshake.hs
index 3fdb48be..e4d27f75 100644
--- a/src/Network/BitTorrent/PeerWire/Handshake.hs
+++ b/src/Network/BitTorrent/PeerWire/Handshake.hs
@@ -29,8 +29,8 @@ import Data.Torrent.InfoHash
29import Network 29import Network
30import Network.Socket.ByteString 30import Network.Socket.ByteString
31 31
32import Network.BitTorrent.PeerID 32import Network.BitTorrent.Peer.ID
33import Network.BitTorrent.PeerWire.ClientInfo 33import Network.BitTorrent.Peer.ClientInfo
34 34
35 35
36data Handshake = Handshake { 36data Handshake = Handshake {
diff --git a/src/Network/BitTorrent/PeerWire/Message.hs b/src/Network/BitTorrent/PeerWire/Message.hs
index 9cbc2e38..188f0572 100644
--- a/src/Network/BitTorrent/PeerWire/Message.hs
+++ b/src/Network/BitTorrent/PeerWire/Message.hs
@@ -5,7 +5,6 @@ module Network.BitTorrent.PeerWire.Message
5 ) where 5 ) where
6 6
7import Control.Applicative 7import Control.Applicative
8import Data.ByteString (ByteString)
9import qualified Data.ByteString as B 8import qualified Data.ByteString as B
10 9
11import Data.Serialize 10import Data.Serialize