diff options
author | Sam T <sta.cs.vsu@gmail.com> | 2013-04-21 00:01:22 +0400 |
---|---|---|
committer | Sam T <sta.cs.vsu@gmail.com> | 2013-04-21 00:01:22 +0400 |
commit | 3c32f381afea629e06e8f069e0a3fefc72c8732e (patch) | |
tree | 194a4ade1cf7dd4d747e39397a8170a6b253f749 /src/Network/BitTorrent/PeerID.hs | |
parent | 08bb327005c2f0dc517d0a74cf29e9f7f9b08e21 (diff) |
~ Rename modules.
Diffstat (limited to 'src/Network/BitTorrent/PeerID.hs')
-rw-r--r-- | src/Network/BitTorrent/PeerID.hs | 205 |
1 files changed, 205 insertions, 0 deletions
diff --git a/src/Network/BitTorrent/PeerID.hs b/src/Network/BitTorrent/PeerID.hs new file mode 100644 index 00000000..cef1fa58 --- /dev/null +++ b/src/Network/BitTorrent/PeerID.hs | |||
@@ -0,0 +1,205 @@ | |||
1 | -- TODO: tests | ||
2 | -- | | ||
3 | -- Copyright : (c) Sam T. 2013 | ||
4 | -- License : MIT | ||
5 | -- Maintainer : pxqr.sta@gmail.com | ||
6 | -- Stability : experimental | ||
7 | -- Portability : non-portable | ||
8 | -- | ||
9 | -- This module provides 'Peer' and 'PeerID' datatypes and all related | ||
10 | -- operations. | ||
11 | -- Recommended method for generation of the peer ID's is 'newPeerID', | ||
12 | -- though this module exports some other goodies for custom generation. | ||
13 | -- | ||
14 | {-# LANGUAGE OverloadedStrings, GeneralizedNewtypeDeriving #-} | ||
15 | module Network.BitTorrent.PeerID | ||
16 | ( -- * Peer addr | ||
17 | Peer(..) | ||
18 | , peerSockAddr, connectToPeer | ||
19 | |||
20 | -- * Peer identification | ||
21 | , PeerID (getPeerID) | ||
22 | |||
23 | -- ** Encoding styles | ||
24 | , azureusStyle, shadowStyle | ||
25 | |||
26 | -- ** Defaults | ||
27 | , defaultClientID, defaultVersionNumber | ||
28 | |||
29 | -- ** Generation | ||
30 | , newPeerID, timestampByteString | ||
31 | -- ** Extra | ||
32 | |||
33 | , byteStringPadded | ||
34 | ) where | ||
35 | |||
36 | import Control.Applicative | ||
37 | import Data.Word | ||
38 | import Data.Bits | ||
39 | import Data.BEncode | ||
40 | import Data.ByteString (ByteString) | ||
41 | import qualified Data.ByteString as B | ||
42 | import qualified Data.ByteString.Char8 as BC | ||
43 | import qualified Data.ByteString.Lazy as BL | ||
44 | import qualified Data.ByteString.Builder as B | ||
45 | import Data.Foldable (foldMap) | ||
46 | import Data.Monoid ((<>)) | ||
47 | import Data.Serialize | ||
48 | import Data.URLEncoded | ||
49 | import Data.Version (Version(Version), versionBranch) | ||
50 | import Data.Time.Clock (getCurrentTime) | ||
51 | import Data.Time.Format (formatTime) | ||
52 | import System.Locale (defaultTimeLocale) | ||
53 | import Network | ||
54 | import Network.Socket | ||
55 | |||
56 | |||
57 | -- TODO we have linker error here, so manual hardcoded version for a while. | ||
58 | -- import Paths_network_bittorrent (version) | ||
59 | version :: Version | ||
60 | version = Version [0, 10, 0, 0] [] | ||
61 | |||
62 | |||
63 | |||
64 | data Peer = Peer { | ||
65 | peerID :: Maybe PeerID | ||
66 | , peerIP :: HostAddress | ||
67 | , peerPort :: PortNumber | ||
68 | } deriving Show | ||
69 | |||
70 | -- TODO make platform independent, clarify htonl | ||
71 | -- | Convert peer info from tracker response to socket address. | ||
72 | -- Used for establish connection between peers. | ||
73 | -- | ||
74 | peerSockAddr :: Peer -> SockAddr | ||
75 | peerSockAddr = SockAddrInet <$> (g . peerPort) <*> (htonl . peerIP) | ||
76 | where | ||
77 | htonl :: Word32 -> Word32 | ||
78 | htonl d = | ||
79 | ((d .&. 0xff) `shiftL` 24) .|. | ||
80 | (((d `shiftR` 8 ) .&. 0xff) `shiftL` 16) .|. | ||
81 | (((d `shiftR` 16) .&. 0xff) `shiftL` 8) .|. | ||
82 | ((d `shiftR` 24) .&. 0xff) | ||
83 | |||
84 | g :: PortNumber -> PortNumber | ||
85 | g = id | ||
86 | |||
87 | -- ipv6 extension | ||
88 | -- | Tries to connect to peer using reasonable default parameters. | ||
89 | -- | ||
90 | connectToPeer :: Peer -> IO Socket | ||
91 | connectToPeer p = do | ||
92 | sock <- socket AF_INET Stream Network.Socket.defaultProtocol | ||
93 | connect sock (peerSockAddr p) | ||
94 | return sock | ||
95 | |||
96 | |||
97 | -- | Peer identifier is exactly 20 bytes long bytestring. | ||
98 | newtype PeerID = PeerID { getPeerID :: ByteString } | ||
99 | deriving (Show, Eq, Ord, BEncodable) | ||
100 | |||
101 | instance Serialize PeerID where | ||
102 | put = putByteString . getPeerID | ||
103 | get = PeerID <$> getBytes 20 | ||
104 | |||
105 | instance URLShow PeerID where | ||
106 | urlShow = BC.unpack . getPeerID | ||
107 | |||
108 | |||
109 | -- | Azureus-style encoding have the following layout: | ||
110 | -- | ||
111 | -- * 1 byte : '-' | ||
112 | -- | ||
113 | -- * 2 bytes: client id | ||
114 | -- | ||
115 | -- * 4 bytes: version number | ||
116 | -- | ||
117 | -- * 1 byte : '-' | ||
118 | -- | ||
119 | -- * 12 bytes: random number | ||
120 | -- | ||
121 | azureusStyle :: ByteString -- ^ 2 character client ID, padded with 'H'. | ||
122 | -> ByteString -- ^ Version number, padded with 'X'. | ||
123 | -> ByteString -- ^ Random number, padded with '0'. | ||
124 | -> PeerID -- ^ Azureus-style encoded peer ID. | ||
125 | azureusStyle cid ver rnd = PeerID $ BL.toStrict $ B.toLazyByteString $ | ||
126 | B.char8 '-' <> | ||
127 | byteStringPadded cid 2 'H' <> | ||
128 | byteStringPadded ver 4 'X' <> | ||
129 | B.char8 '-' <> | ||
130 | byteStringPadded rnd 12 '0' | ||
131 | |||
132 | -- | Shadow-style encoding have the following layout: | ||
133 | -- | ||
134 | -- * 1 byte : client id. | ||
135 | -- | ||
136 | -- * 0-4 bytes: version number. If less than 4 then padded with '-' char. | ||
137 | -- | ||
138 | -- * 15 bytes : random number. If length is less than 15 then padded with '0' char. | ||
139 | -- | ||
140 | shadowStyle :: Char -- ^ Client ID. | ||
141 | -> ByteString -- ^ Version number. | ||
142 | -> ByteString -- ^ Random number. | ||
143 | -> PeerID -- ^ Shadow style encoded peer ID. | ||
144 | shadowStyle cid ver rnd = PeerID $ BL.toStrict $ B.toLazyByteString $ | ||
145 | B.char8 cid <> | ||
146 | byteStringPadded ver 4 '-' <> | ||
147 | byteStringPadded rnd 15 '0' | ||
148 | |||
149 | |||
150 | -- | "HS" - 2 bytes long client identifier. | ||
151 | defaultClientID :: ByteString | ||
152 | defaultClientID = "HS" | ||
153 | |||
154 | -- | Gives exactly 4 bytes long version number for any version of the package. | ||
155 | -- Version is taken from .cabal. | ||
156 | defaultVersionNumber :: ByteString | ||
157 | defaultVersionNumber = B.take 4 (BC.pack (foldMap show (versionBranch version))) | ||
158 | |||
159 | -- | Gives 15 characters long decimal timestamp such that: | ||
160 | -- | ||
161 | -- * 6 bytes : first 6 characters from picoseconds obtained with %q. | ||
162 | -- | ||
163 | -- * 1 bytes : character '.' for readability. | ||
164 | -- | ||
165 | -- * 9..* bytes: number of whole seconds since the Unix epoch (!)REVERSED. | ||
166 | -- | ||
167 | -- Can be used both with shadow and azureus style encoding. This format is | ||
168 | -- used to make the ID's readable(for debugging) and more or less random. | ||
169 | -- | ||
170 | timestampByteString :: IO ByteString | ||
171 | timestampByteString = (BC.pack . format) <$> getCurrentTime | ||
172 | where | ||
173 | format t = take 6 (formatTime defaultTimeLocale "%q" t) ++ "." ++ | ||
174 | take 9 (reverse (formatTime defaultTimeLocale "%s" t)) | ||
175 | |||
176 | -- | Here we use Azureus-style encoding with the following args: | ||
177 | -- | ||
178 | -- * 'HS' for the client id. | ||
179 | -- | ||
180 | -- * Version of the package for the version number | ||
181 | -- | ||
182 | -- * UTC time day ++ day time for the random number. | ||
183 | -- | ||
184 | newPeerID :: IO PeerID | ||
185 | newPeerID = azureusStyle defaultClientID defaultVersionNumber | ||
186 | <$> timestampByteString | ||
187 | |||
188 | -- | Pad bytestring so it's becomes exactly request length. Conversion is done | ||
189 | -- like so: | ||
190 | -- | ||
191 | -- * length < size: Complete bytestring by given charaters. | ||
192 | -- | ||
193 | -- * length = size: Output bytestring as is. | ||
194 | -- | ||
195 | -- * length > size: Drop last (length - size) charaters from a given bytestring. | ||
196 | -- | ||
197 | byteStringPadded :: ByteString -- ^ bytestring to be padded. | ||
198 | -> Int -- ^ size of result builder. | ||
199 | -> Char -- ^ character used for padding. | ||
200 | -> B.Builder | ||
201 | byteStringPadded bs s c = | ||
202 | B.byteString (B.take s bs) <> | ||
203 | B.byteString (BC.replicate padLen c) | ||
204 | where | ||
205 | padLen = s - min (B.length bs) s \ No newline at end of file | ||