diff options
author | James Crayne <jim.crayne@gmail.com> | 2019-09-28 13:43:29 -0400 |
---|---|---|
committer | Joe Crayne <joe@jerkface.net> | 2020-01-01 19:27:53 -0500 |
commit | 11987749fc6e6d3e53ea737d46d5ab13a16faeb8 (patch) | |
tree | 5716463275c2d3e902889db619908ded2a73971c /src/Network/Tox/NodeId.hs | |
parent | add2c76bced51fde5e9917e7449ef52be70faf87 (diff) |
Factor out some new libraries
word64-map:
Data.Word64Map
network-addr:
Network.Address
tox-crypto:
Crypto.Tox
lifted-concurrent:
Control.Concurrent.Lifted.Instrument
Control.Concurrent.Async.Lifted.Instrument
psq-wrap:
Data.Wrapper.PSQInt
Data.Wrapper.PSQ
minmax-psq:
Data.MinMaxPSQ
tasks:
Control.Concurrent.Tasks
kad:
Network.Kademlia
Network.Kademlia.Bootstrap
Network.Kademlia.Routing
Network.Kademlia.CommonAPI
Network.Kademlia.Persistence
Network.Kademlia.Search
Diffstat (limited to 'src/Network/Tox/NodeId.hs')
-rw-r--r-- | src/Network/Tox/NodeId.hs | 731 |
1 files changed, 0 insertions, 731 deletions
diff --git a/src/Network/Tox/NodeId.hs b/src/Network/Tox/NodeId.hs deleted file mode 100644 index 9a9c893a..00000000 --- a/src/Network/Tox/NodeId.hs +++ /dev/null | |||
@@ -1,731 +0,0 @@ | |||
1 | {- LANGUAGE ApplicativeDo -} | ||
2 | {-# LANGUAGE BangPatterns #-} | ||
3 | {-# LANGUAGE CPP #-} | ||
4 | {-# LANGUAGE DataKinds #-} | ||
5 | {-# LANGUAGE DeriveDataTypeable #-} | ||
6 | {-# LANGUAGE DeriveFunctor #-} | ||
7 | {-# LANGUAGE DeriveTraversable #-} | ||
8 | {-# LANGUAGE ExistentialQuantification #-} | ||
9 | {-# LANGUAGE FlexibleInstances #-} | ||
10 | {-# LANGUAGE GADTs #-} | ||
11 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
12 | {-# LANGUAGE KindSignatures #-} | ||
13 | {-# LANGUAGE LambdaCase #-} | ||
14 | {-# LANGUAGE PatternSynonyms #-} | ||
15 | {-# LANGUAGE ScopedTypeVariables #-} | ||
16 | {-# LANGUAGE StandaloneDeriving #-} | ||
17 | {-# LANGUAGE TupleSections #-} | ||
18 | {- LANGUAGE TypeApplications -} | ||
19 | module Network.Tox.NodeId | ||
20 | ( NodeInfo(..) | ||
21 | , NodeId | ||
22 | , nodeInfo | ||
23 | , nodeAddr | ||
24 | , zeroID | ||
25 | , key2id | ||
26 | , id2key | ||
27 | , getIP | ||
28 | , xorNodeId | ||
29 | , testNodeIdBit | ||
30 | , sampleNodeId | ||
31 | , NoSpam(..) | ||
32 | , NoSpamId(..) | ||
33 | , noSpamIdToHex | ||
34 | , parseNoSpamId | ||
35 | , nospam64 | ||
36 | , nospam16 | ||
37 | , verifyChecksum | ||
38 | , ToxContact(..) | ||
39 | , ToxProgress(..) | ||
40 | , parseToken32 | ||
41 | , showToken32 | ||
42 | ) where | ||
43 | |||
44 | import Control.Applicative | ||
45 | import Control.Arrow | ||
46 | import Control.Monad | ||
47 | #ifdef CRYPTONITE_BACKPORT | ||
48 | import Crypto.Error.Types (CryptoFailable (..), | ||
49 | throwCryptoError) | ||
50 | #else | ||
51 | import Crypto.Error | ||
52 | #endif | ||
53 | |||
54 | import Crypto.PubKey.Curve25519 | ||
55 | import qualified Data.Aeson as JSON | ||
56 | ;import Data.Aeson (FromJSON, ToJSON, (.=)) | ||
57 | import Data.Bits.ByteString () | ||
58 | import qualified Data.ByteArray as BA | ||
59 | ;import Data.ByteArray as BA (ByteArrayAccess) | ||
60 | import qualified Data.ByteString as B | ||
61 | ;import Data.ByteString (ByteString) | ||
62 | import qualified Data.ByteString.Base16 as Base16 | ||
63 | import qualified Data.ByteString.Base64 as Base64 | ||
64 | import qualified Data.ByteString.Char8 as C8 | ||
65 | import Data.Char | ||
66 | import Data.Data | ||
67 | import Data.Hashable | ||
68 | #if MIN_VERSION_iproute(1,7,4) | ||
69 | import Data.IP hiding (fromSockAddr) | ||
70 | #else | ||
71 | import Data.IP | ||
72 | #endif | ||
73 | import Data.List | ||
74 | import Data.Maybe | ||
75 | import Data.Serialize as S | ||
76 | import Data.Word | ||
77 | import Foreign.Storable | ||
78 | import GHC.TypeLits | ||
79 | import Network.Address hiding (nodePort) | ||
80 | import System.IO.Unsafe (unsafeDupablePerformIO) | ||
81 | import qualified Text.ParserCombinators.ReadP as RP | ||
82 | import Text.Read hiding (get) | ||
83 | import Data.Bits | ||
84 | import Crypto.Tox | ||
85 | import Foreign.Ptr | ||
86 | import Data.Function | ||
87 | import System.Endian | ||
88 | import qualified Data.Text as Text | ||
89 | ;import Data.Text (Text) | ||
90 | import Util (splitJID) | ||
91 | |||
92 | -- | perform io for hashes that do allocation and ffi. | ||
93 | -- unsafeDupablePerformIO is used when possible as the | ||
94 | -- computation is pure and the output is directly linked | ||
95 | -- to the input. we also do not modify anything after it has | ||
96 | -- been returned to the user. | ||
97 | unsafeDoIO :: IO a -> a | ||
98 | #if __GLASGOW_HASKELL__ > 704 | ||
99 | unsafeDoIO = unsafeDupablePerformIO | ||
100 | #else | ||
101 | unsafeDoIO = unsafePerformIO | ||
102 | #endif | ||
103 | |||
104 | unpackPublicKey :: ByteArrayAccess bs => bs -> [Word64] | ||
105 | unpackPublicKey bs = loop 0 | ||
106 | where loop i | ||
107 | | i == (BA.length bs `div` 8) = [] | ||
108 | | otherwise = | ||
109 | let !v = unsafeDoIO $ BA.withByteArray bs (\p -> fromBE64 <$> peekElemOff p i) | ||
110 | in v : loop (i+1) | ||
111 | |||
112 | packPublicKey :: BA.ByteArray bs => [Word64] -> bs | ||
113 | packPublicKey ws = BA.allocAndFreeze (8 * length ws) $ | ||
114 | flip fix ws $ \loop ys ptr -> case ys of | ||
115 | [] -> return () | ||
116 | x:xs -> do poke ptr (toBE64 x) | ||
117 | loop xs (plusPtr ptr 8) | ||
118 | {-# NOINLINE packPublicKey #-} | ||
119 | |||
120 | -- We represent the node id redundantly in two formats. The [Word64] format is | ||
121 | -- convenient for short-circuiting xor/distance comparisons. The PublicKey | ||
122 | -- format is convenient for encryption. | ||
123 | data NodeId = NodeId [Word64] !(Maybe PublicKey) | ||
124 | deriving Data | ||
125 | |||
126 | instance Data PublicKey where | ||
127 | -- Data a => (forall d b . Data d => c (d -> b) -> d -> c b) -> (forall g . g -> c g) -> a -> c a | ||
128 | gfoldl f z txt = z (throwCryptoError . publicKey) `f` (BA.convert txt :: ByteString) | ||
129 | toConstr _ = error "Crypto.PubKey.Curve25519.toConstr" | ||
130 | gunfold _ _ = error "Crypto.PubKey.Curve25519.gunfold" | ||
131 | #if MIN_VERSION_base(4,2,0) | ||
132 | dataTypeOf _ = mkNoRepType "Crypto.PubKey.Curve25519.PublicKey" | ||
133 | #else | ||
134 | dataTypeOf _ = mkNorepType "Crypto.PubKey.Curve25519.PublicKey" | ||
135 | #endif | ||
136 | |||
137 | |||
138 | instance Eq NodeId where | ||
139 | (NodeId ws _) == (NodeId xs _) | ||
140 | = ws == xs | ||
141 | |||
142 | instance Ord NodeId where | ||
143 | compare (NodeId ws _) (NodeId xs _) = compare ws xs | ||
144 | |||
145 | instance Sized NodeId where size = ConstSize 32 | ||
146 | |||
147 | key2id :: PublicKey -> NodeId | ||
148 | key2id k = NodeId (unpackPublicKey k) (Just k) | ||
149 | |||
150 | bs2id :: ByteString -> NodeId | ||
151 | bs2id bs = uncurry NodeId . (unpackPublicKey &&& Just) $ throwCryptoError . publicKey $ bs | ||
152 | |||
153 | id2key :: NodeId -> PublicKey | ||
154 | id2key (NodeId ws (Just key)) = key | ||
155 | id2key (NodeId key Nothing) = throwCryptoError . publicKey $ (packPublicKey key :: BA.Bytes) | ||
156 | |||
157 | zeroKey :: PublicKey | ||
158 | zeroKey = throwCryptoError $ publicKey $ B.replicate 32 0 | ||
159 | |||
160 | zeroID :: NodeId | ||
161 | zeroID = NodeId (replicate 4 0) (Just zeroKey) | ||
162 | |||
163 | -- | Convert to and from a Base64 variant that uses .- instead of +/. | ||
164 | nmtoken64 :: Bool -> Char -> Char | ||
165 | nmtoken64 False '.' = '+' | ||
166 | nmtoken64 False '-' = '/' | ||
167 | nmtoken64 True '+' = '.' | ||
168 | nmtoken64 True '/' = '-' | ||
169 | nmtoken64 _ c = c | ||
170 | |||
171 | -- | Parse 43-digit base64 token into 32-byte bytestring. | ||
172 | parseToken32 :: String -> Either String ByteString | ||
173 | parseToken32 str = fmap (BA.drop 1) $ Base64.decode $ C8.pack $ 'A':map (nmtoken64 False) (take 43 str) | ||
174 | |||
175 | -- | Encode 32-byte bytestring as 43-digit base64 token. | ||
176 | showToken32 :: ByteArrayAccess bin => bin -> String | ||
177 | showToken32 bs = map (nmtoken64 True) $ C8.unpack $ BA.drop 1 $ Base64.encode $ BA.cons 0 $ BA.convert bs | ||
178 | |||
179 | instance Read NodeId where | ||
180 | readsPrec _ str | ||
181 | | (bs,_) <- Base16.decode (C8.pack $ take 64 str) | ||
182 | , CryptoPassed pub <- publicKey bs -- B.length bs == 32 | ||
183 | = [ (key2id pub, drop (2 * B.length bs) str) ] | ||
184 | | Right bs <- parseToken32 str | ||
185 | , CryptoPassed pub <- publicKey bs -- B.length bs == 32 | ||
186 | = [ (key2id pub, drop 43 str) ] | ||
187 | | otherwise = [] | ||
188 | |||
189 | instance Show NodeId where | ||
190 | show nid = showToken32 $ id2key nid | ||
191 | |||
192 | instance S.Serialize NodeId where | ||
193 | get = key2id <$> getPublicKey | ||
194 | put nid = putPublicKey $ id2key nid | ||
195 | |||
196 | instance Hashable NodeId where | ||
197 | hashWithSalt salt (NodeId ws _) = hashWithSalt salt (head ws) | ||
198 | |||
199 | testNodeIdBit :: NodeId -> Word -> Bool | ||
200 | testNodeIdBit (NodeId ws _) i -- TODO: Optmize: use ByteArray key if it's available. | ||
201 | | fromIntegral i < 256 -- 256 bits | ||
202 | , (q, r) <- quotRem (fromIntegral i) 64 | ||
203 | = testBit (ws !! q) (63 - r) | ||
204 | | otherwise = False | ||
205 | |||
206 | xorNodeId :: NodeId -> NodeId -> NodeId | ||
207 | xorNodeId (NodeId xs _) (NodeId ys _) = NodeId (zipWith xor xs ys) Nothing | ||
208 | |||
209 | sampleNodeId :: Applicative m => (Int -> m ByteString) -> NodeId -> (Int,Word8,Word8) -> m NodeId | ||
210 | sampleNodeId gen (NodeId self k) (q,m,b) | ||
211 | | q <= 0 = bs2id <$> gen 32 | ||
212 | | q >= 32 = pure (NodeId self k) | ||
213 | | let (qw,r) = (q+7) `divMod` 8 -- How many Word64 to prepend? | ||
214 | bw = shiftL (fromIntegral b) (8*(7-r)) | ||
215 | mw = bw - 1 :: Word64 | ||
216 | (hd, t0 : _) = splitAt (qw-1) self | ||
217 | h = xor bw (complement mw .&. t0) | ||
218 | = flip fmap (gen $ 8 * (4 - (qw-1)) ) $ \bs -> | ||
219 | let (w:ws) = unpackPublicKey bs | ||
220 | in NodeId (hd ++ (h .|. (w .&. mw)) : ws) Nothing | ||
221 | |||
222 | data NodeInfo = NodeInfo | ||
223 | { nodeId :: NodeId | ||
224 | , nodeIP :: IP | ||
225 | , nodePort :: PortNumber | ||
226 | } | ||
227 | deriving (Eq,Ord) | ||
228 | |||
229 | nodeInfo :: NodeId -> SockAddr -> Either String NodeInfo | ||
230 | nodeInfo nid saddr | ||
231 | | Just ip <- fromSockAddr saddr | ||
232 | , Just port <- sockAddrPort saddr = Right $ NodeInfo nid ip port | ||
233 | | otherwise = Left "Address family not supported." | ||
234 | |||
235 | |||
236 | instance ToJSON NodeInfo where | ||
237 | toJSON (NodeInfo nid (IPv4 ip) port) | ||
238 | = JSON.object [ "public_key" .= show nid | ||
239 | , "ipv4" .= show ip | ||
240 | , "port" .= (fromIntegral port :: Int) | ||
241 | ] | ||
242 | toJSON (NodeInfo nid (IPv6 ip6) port) | ||
243 | | Just ip <- un4map ip6 | ||
244 | = JSON.object [ "public_key" .= show nid | ||
245 | , "ipv4" .= show ip | ||
246 | , "port" .= (fromIntegral port :: Int) | ||
247 | ] | ||
248 | | otherwise | ||
249 | = JSON.object [ "public_key" .= show nid | ||
250 | , "ipv6" .= show ip6 | ||
251 | , "port" .= (fromIntegral port :: Int) | ||
252 | ] | ||
253 | instance FromJSON NodeInfo where | ||
254 | parseJSON (JSON.Object v) = do | ||
255 | nidstr <- v JSON..: "public_key" | ||
256 | ip6str <- v JSON..:? "ipv6" | ||
257 | ip4str <- v JSON..:? "ipv4" | ||
258 | portnum <- v JSON..: "port" | ||
259 | ip <- maybe empty (return . IPv6) (ip6str >>= readMaybe) | ||
260 | <|> maybe empty (return . IPv4) (ip4str >>= readMaybe) | ||
261 | let (bs,_) = Base16.decode (C8.pack nidstr) | ||
262 | enid = Base64.decode (C8.pack $ 'A' : map (nmtoken64 False) nidstr) | ||
263 | idbs <- (guard (B.length bs == 32) >> return bs) | ||
264 | <|> either fail (return . B.drop 1) enid | ||
265 | return $ NodeInfo (bs2id idbs) ip (fromIntegral (portnum :: Word16)) | ||
266 | |||
267 | getIP :: Word8 -> S.Get IP | ||
268 | getIP 0x02 = IPv4 <$> S.get | ||
269 | getIP 0x0a = IPv6 <$> S.get | ||
270 | getIP 0x82 = IPv4 <$> S.get -- TODO: TCP | ||
271 | getIP 0x8a = IPv6 <$> S.get -- TODO: TCP | ||
272 | getIP x = fail ("unsupported address family ("++show x++")") | ||
273 | |||
274 | instance Sized NodeInfo where | ||
275 | size = VarSize $ \(NodeInfo nid ip port) -> | ||
276 | case ip of | ||
277 | IPv4 _ -> 39 -- 35 + 4 = 1 + 4 + 2 + 32 | ||
278 | IPv6 _ -> 51 -- 35 + 16 = 1 + 16 + 2 + 32 | ||
279 | |||
280 | instance S.Serialize NodeInfo where | ||
281 | get = do | ||
282 | addrfam <- S.get :: S.Get Word8 | ||
283 | let fallback = do -- FIXME: Handle unrecognized address families. | ||
284 | IPv6 <$> S.get | ||
285 | return $ IPv6 (read "::" :: IPv6) | ||
286 | ip <- getIP addrfam <|> fallback | ||
287 | port <- S.get :: S.Get PortNumber | ||
288 | nid <- S.get | ||
289 | return $ NodeInfo nid ip port | ||
290 | |||
291 | put (NodeInfo nid ip port) = do | ||
292 | case ip of | ||
293 | IPv4 ip4 -> S.put (2 :: Word8) >> S.put ip4 | ||
294 | IPv6 ip6 -> S.put (10 :: Word8) >> S.put ip6 | ||
295 | S.put port | ||
296 | S.put nid | ||
297 | |||
298 | hexdigit :: Char -> Bool | ||
299 | hexdigit c = ('0' <= c && c <= '9') || ( 'a' <= c && c <= 'f') || ( 'A' <= c && c <= 'F') | ||
300 | |||
301 | b64digit :: Char -> Bool | ||
302 | b64digit '.' = True | ||
303 | b64digit '+' = True | ||
304 | b64digit '-' = True | ||
305 | b64digit '/' = True | ||
306 | b64digit c = ('0' <= c && c <= '9') || ( 'a' <= c && c <= 'z') || ( 'A' <= c && c <= 'Z') | ||
307 | |||
308 | ip_w_port :: Int -> RP.ReadP (IP, PortNumber) | ||
309 | ip_w_port i = do | ||
310 | ip <- RP.between (RP.char '[') (RP.char ']') | ||
311 | (IPv6 <$> RP.readS_to_P (readsPrec i)) | ||
312 | RP.+++ (IPv4 <$> RP.readS_to_P (readsPrec i)) | ||
313 | _ <- RP.char ':' | ||
314 | port <- toEnum <$> RP.readS_to_P (readsPrec i) | ||
315 | return (ip, port) | ||
316 | |||
317 | |||
318 | instance Read NodeInfo where | ||
319 | readsPrec i = RP.readP_to_S $ do | ||
320 | RP.skipSpaces | ||
321 | let n = 43 -- characters in node id. | ||
322 | parseAddr = RP.between (RP.char '(') (RP.char ')') (RP.munch (/=')')) | ||
323 | RP.+++ RP.munch (\c -> not (isSpace c) && not (c `elem` ("{}()"::[Char]))) | ||
324 | nodeidAt = do (is64,hexhash) <- | ||
325 | fmap (True,) (sequence $ replicate n (RP.satisfy b64digit)) | ||
326 | RP.+++ fmap (False,) (sequence $ replicate 64 (RP.satisfy isHexDigit)) | ||
327 | RP.char '@' RP.+++ RP.satisfy isSpace | ||
328 | addrstr <- parseAddr | ||
329 | nid <- if is64 | ||
330 | then case Base64.decode $ C8.pack $ 'A' : map (nmtoken64 False) hexhash of | ||
331 | Right bs | B.length bs - 1==32 -> return (bs2id $ BA.drop 1 bs) | ||
332 | _ -> fail "Bad node id." | ||
333 | else case Base16.decode $ C8.pack hexhash of | ||
334 | (bs,rem) | B.length bs == 32 && B.null rem -> return (bs2id bs) | ||
335 | _ -> fail "Bad node id." | ||
336 | return (nid,addrstr) | ||
337 | (nid,addrstr) <- ( nodeidAt RP.+++ ( (zeroID,) <$> parseAddr) ) | ||
338 | (ip,port) <- case RP.readP_to_S (ip_w_port i) addrstr of | ||
339 | [] -> fail "Bad address." | ||
340 | ((ip,port),_):_ -> return (ip,port) | ||
341 | return $ NodeInfo nid ip port | ||
342 | |||
343 | -- The Hashable instance depends only on the IP address and port number. | ||
344 | -- | ||
345 | -- TODO: Why is the node id excluded? | ||
346 | instance Hashable NodeInfo where | ||
347 | hashWithSalt s ni = hashWithSalt s (nodeIP ni , nodePort ni) | ||
348 | {-# INLINE hashWithSalt #-} | ||
349 | |||
350 | |||
351 | instance Show NodeInfo where | ||
352 | showsPrec _ (NodeInfo nid ip port) = | ||
353 | shows nid . ('@' :) . showsip . (':' :) . shows port | ||
354 | where | ||
355 | showsip | ||
356 | | IPv4 ip4 <- ip = shows ip4 | ||
357 | | IPv6 ip6 <- ip , Just ip4 <- un4map ip6 = shows ip4 | ||
358 | | otherwise = ('[' :) . shows ip . (']' :) | ||
359 | |||
360 | |||
361 | |||
362 | |||
363 | {- | ||
364 | type NodeId = PubKey | ||
365 | |||
366 | pattern NodeId bs = PubKey bs | ||
367 | |||
368 | -- TODO: This should probably be represented by Curve25519.PublicKey, but | ||
369 | -- ByteString has more instances... | ||
370 | newtype PubKey = PubKey ByteString | ||
371 | deriving (Eq,Ord,Data, ByteArrayAccess, Bits, Hashable) | ||
372 | |||
373 | instance Serialize PubKey where | ||
374 | get = PubKey <$> getBytes 32 | ||
375 | put (PubKey bs) = putByteString bs | ||
376 | |||
377 | instance Show PubKey where | ||
378 | show (PubKey bs) = C8.unpack $ Base16.encode bs | ||
379 | |||
380 | instance FiniteBits PubKey where | ||
381 | finiteBitSize _ = 256 | ||
382 | |||
383 | instance Read PubKey where | ||
384 | readsPrec _ str | ||
385 | | (bs, xs) <- Base16.decode $ C8.pack str | ||
386 | , B.length bs == 32 | ||
387 | = [ (PubKey bs, drop 64 str) ] | ||
388 | | otherwise = [] | ||
389 | |||
390 | |||
391 | |||
392 | |||
393 | data NodeInfo = NodeInfo | ||
394 | { nodeId :: NodeId | ||
395 | , nodeIP :: IP | ||
396 | , nodePort :: PortNumber | ||
397 | } | ||
398 | deriving (Eq,Ord,Data) | ||
399 | |||
400 | instance Data PortNumber where | ||
401 | dataTypeOf _ = mkNoRepType "PortNumber" | ||
402 | toConstr _ = error "PortNumber.toConstr" | ||
403 | gunfold _ _ = error "PortNumber.gunfold" | ||
404 | |||
405 | instance ToJSON NodeInfo where | ||
406 | toJSON (NodeInfo nid (IPv4 ip) port) | ||
407 | = JSON.object [ "public_key" .= show nid | ||
408 | , "ipv4" .= show ip | ||
409 | , "port" .= (fromIntegral port :: Int) | ||
410 | ] | ||
411 | toJSON (NodeInfo nid (IPv6 ip6) port) | ||
412 | | Just ip <- un4map ip6 | ||
413 | = JSON.object [ "public_key" .= show nid | ||
414 | , "ipv4" .= show ip | ||
415 | , "port" .= (fromIntegral port :: Int) | ||
416 | ] | ||
417 | | otherwise | ||
418 | = JSON.object [ "public_key" .= show nid | ||
419 | , "ipv6" .= show ip6 | ||
420 | , "port" .= (fromIntegral port :: Int) | ||
421 | ] | ||
422 | instance FromJSON NodeInfo where | ||
423 | parseJSON (JSON.Object v) = do | ||
424 | nidstr <- v JSON..: "public_key" | ||
425 | ip6str <- v JSON..:? "ipv6" | ||
426 | ip4str <- v JSON..:? "ipv4" | ||
427 | portnum <- v JSON..: "port" | ||
428 | ip <- maybe empty (return . IPv6) (ip6str >>= readMaybe) | ||
429 | <|> maybe empty (return . IPv4) (ip4str >>= readMaybe) | ||
430 | let (bs,_) = Base16.decode (C8.pack nidstr) | ||
431 | guard (B.length bs == 32) | ||
432 | return $ NodeInfo (NodeId bs) ip (fromIntegral (portnum :: Word16)) | ||
433 | |||
434 | getIP :: Word8 -> S.Get IP | ||
435 | getIP 0x02 = IPv4 <$> S.get | ||
436 | getIP 0x0a = IPv6 <$> S.get | ||
437 | getIP 0x82 = IPv4 <$> S.get -- TODO: TCP | ||
438 | getIP 0x8a = IPv6 <$> S.get -- TODO: TCP | ||
439 | getIP x = fail ("unsupported address family ("++show x++")") | ||
440 | |||
441 | instance S.Serialize NodeInfo where | ||
442 | get = do | ||
443 | addrfam <- S.get :: S.Get Word8 | ||
444 | ip <- getIP addrfam | ||
445 | port <- S.get :: S.Get PortNumber | ||
446 | nid <- S.get | ||
447 | return $ NodeInfo nid ip port | ||
448 | |||
449 | put (NodeInfo nid ip port) = do | ||
450 | case ip of | ||
451 | IPv4 ip4 -> S.put (2 :: Word8) >> S.put ip4 | ||
452 | IPv6 ip6 -> S.put (10 :: Word8) >> S.put ip6 | ||
453 | S.put port | ||
454 | S.put nid | ||
455 | |||
456 | -- node format: | ||
457 | -- [uint8_t family (2 == IPv4, 10 == IPv6, 130 == TCP IPv4, 138 == TCP IPv6)] | ||
458 | -- [ip (in network byte order), length=4 bytes if ipv4, 16 bytes if ipv6] | ||
459 | -- [port (in network byte order), length=2 bytes] | ||
460 | -- [char array (node_id), length=32 bytes] | ||
461 | -- | ||
462 | |||
463 | |||
464 | hexdigit :: Char -> Bool | ||
465 | hexdigit c = ('0' <= c && c <= '9') || ( 'a' <= c && c <= 'f') || ( 'A' <= c && c <= 'F') | ||
466 | |||
467 | instance Read NodeInfo where | ||
468 | readsPrec i = RP.readP_to_S $ do | ||
469 | RP.skipSpaces | ||
470 | let n = 64 -- characters in node id. | ||
471 | parseAddr = RP.between (RP.char '(') (RP.char ')') (RP.munch (/=')')) | ||
472 | RP.+++ RP.munch (not . isSpace) | ||
473 | nodeidAt = do hexhash <- sequence $ replicate n (RP.satisfy hexdigit) | ||
474 | RP.char '@' RP.+++ RP.satisfy isSpace | ||
475 | addrstr <- parseAddr | ||
476 | nid <- case Base16.decode $ C8.pack hexhash of | ||
477 | (bs,_) | B.length bs==32 -> return (PubKey bs) | ||
478 | _ -> fail "Bad node id." | ||
479 | return (nid,addrstr) | ||
480 | (nid,addrstr) <- ( nodeidAt RP.+++ ( (zeroID,) <$> parseAddr) ) | ||
481 | let raddr = do | ||
482 | ip <- RP.between (RP.char '[') (RP.char ']') | ||
483 | (IPv6 <$> RP.readS_to_P (readsPrec i)) | ||
484 | RP.+++ (IPv4 <$> RP.readS_to_P (readsPrec i)) | ||
485 | _ <- RP.char ':' | ||
486 | port <- toEnum <$> RP.readS_to_P (readsPrec i) | ||
487 | return (ip, port) | ||
488 | |||
489 | (ip,port) <- case RP.readP_to_S raddr addrstr of | ||
490 | [] -> fail "Bad address." | ||
491 | ((ip,port),_):_ -> return (ip,port) | ||
492 | return $ NodeInfo nid ip port | ||
493 | |||
494 | |||
495 | -- The Hashable instance depends only on the IP address and port number. | ||
496 | instance Hashable NodeInfo where | ||
497 | hashWithSalt s ni = hashWithSalt s (nodeIP ni , nodePort ni) | ||
498 | {-# INLINE hashWithSalt #-} | ||
499 | |||
500 | |||
501 | instance Show NodeInfo where | ||
502 | showsPrec _ (NodeInfo nid ip port) = | ||
503 | shows nid . ('@' :) . showsip . (':' :) . shows port | ||
504 | where | ||
505 | showsip | ||
506 | | IPv4 ip4 <- ip = shows ip4 | ||
507 | | IPv6 ip6 <- ip , Just ip4 <- un4map ip6 = shows ip4 | ||
508 | | otherwise = ('[' :) . shows ip . (']' :) | ||
509 | |||
510 | nodeInfo :: NodeId -> SockAddr -> Either String NodeInfo | ||
511 | nodeInfo nid saddr | ||
512 | | Just ip <- fromSockAddr saddr | ||
513 | , Just port <- sockAddrPort saddr = Right $ NodeInfo nid ip port | ||
514 | | otherwise = Left "Address family not supported." | ||
515 | |||
516 | zeroID :: NodeId | ||
517 | zeroID = PubKey $ B.replicate 32 0 | ||
518 | |||
519 | -} | ||
520 | |||
521 | nodeAddr :: NodeInfo -> SockAddr | ||
522 | nodeAddr (NodeInfo _ ip port) = setPort port $ toSockAddr ip | ||
523 | |||
524 | |||
525 | newtype ForwardPath (n::Nat) = ForwardPath ByteString | ||
526 | deriving (Eq, Ord,Data) | ||
527 | |||
528 | {- | ||
529 | class KnownNat n => OnionPacket n where | ||
530 | mkOnion :: ReturnPath n -> Packet -> Packet | ||
531 | instance OnionPacket 0 where mkOnion _ = id | ||
532 | instance OnionPacket 3 where mkOnion = OnionResponse3 | ||
533 | -} | ||
534 | |||
535 | data NoSpam = NoSpam !Word32 !(Maybe Word16) | ||
536 | deriving (Eq,Ord,Show) | ||
537 | |||
538 | instance Serialize NoSpam where | ||
539 | get = NoSpam <$> get <*> get | ||
540 | put (NoSpam w32 w16) = do | ||
541 | put w32 | ||
542 | put w16 | ||
543 | |||
544 | -- Utilizes Data.Serialize format for Word32 nospam and Word16 checksum. | ||
545 | instance Read NoSpam where | ||
546 | readsPrec d s = case break isSpace s of | ||
547 | ('$':ws ,rs) | (length ws == 8) -> base64decode rs (NoSpam <$> get <*> (Just <$> get)) ws | ||
548 | ('0':'x':ws,rs) | (length ws == 12) -> base16decode rs (NoSpam <$> get <*> (Just <$> get)) ws | ||
549 | _ -> [] | ||
550 | |||
551 | base64decode :: Monad m => t1 -> Get t -> String -> m (t, t1) | ||
552 | base64decode rs getter s = | ||
553 | either fail (\a -> return (a,rs)) | ||
554 | $ runGet getter | ||
555 | =<< Base64.decode (C8.pack $ map (nmtoken64 False) s) | ||
556 | |||
557 | base16decode :: Monad m => t1 -> Get t -> String -> m (t, t1) | ||
558 | base16decode rs getter s = | ||
559 | either fail (\a -> return (a,rs)) | ||
560 | $ runGet getter | ||
561 | $ fst | ||
562 | $ Base16.decode (C8.pack s) | ||
563 | |||
564 | verifyChecksum :: PublicKey -> Word16 -> Either String () | ||
565 | verifyChecksum _ _ = return () -- TODO | ||
566 | |||
567 | data NoSpamId = NoSpamId NoSpam PublicKey | ||
568 | deriving (Eq,Ord) | ||
569 | |||
570 | noSpamIdToHex :: NoSpamId -> String | ||
571 | noSpamIdToHex (NoSpamId nspam pub) = C8.unpack (Base16.encode $ BA.convert pub) | ||
572 | ++ nospam16 nspam | ||
573 | |||
574 | nospam16 :: NoSpam -> String | ||
575 | nospam16 (NoSpam w32 Nothing) = n ++ "????" | ||
576 | where n = take 8 $ nospam16 (NoSpam w32 (Just 0)) | ||
577 | nospam16 (NoSpam w32 (Just w16)) = C8.unpack $ Base16.encode $ runPut $ do | ||
578 | put w32 | ||
579 | put w16 | ||
580 | |||
581 | nospam64 :: NoSpam -> String | ||
582 | nospam64 (NoSpam w32 Nothing) = n ++ "???" | ||
583 | where n = take 5 $ nospam64 (NoSpam w32 (Just 0)) | ||
584 | nospam64 (NoSpam w32 (Just w16)) = map (nmtoken64 True) $ C8.unpack $ Base64.encode $ runPut $ do | ||
585 | put w32 | ||
586 | put w16 | ||
587 | |||
588 | instance Show NoSpamId where | ||
589 | show (NoSpamId nspam pub) = '$' : nospam64 nspam ++ "@" ++ show (key2id pub) ++ ".tox" | ||
590 | |||
591 | instance Read NoSpamId where | ||
592 | readsPrec d s = either fail id $ do | ||
593 | (jid,xs) <- Right $ break isSpace s | ||
594 | nsid <- parseNoSpamId $ Text.pack jid | ||
595 | return [(nsid,xs)] | ||
596 | |||
597 | parseNoSpamHex :: Text -> Either String NoSpamId | ||
598 | parseNoSpamHex hex = Right $ NoSpamId (read $ "0x"++nospamsum) (id2key $ read hkey) | ||
599 | where | ||
600 | (hkey,nospamsum) = splitAt 64 $ Text.unpack hex | ||
601 | |||
602 | parseNoSpamId :: Text -> Either String NoSpamId | ||
603 | parseNoSpamId spec | Text.length spec == 76 | ||
604 | , Text.all isHexDigit spec = parseNoSpamHex spec | ||
605 | | otherwise = parseNoSpamJID spec | ||
606 | |||
607 | parseNoSpamJID :: Text -> Either String NoSpamId | ||
608 | parseNoSpamJID jid = do | ||
609 | (u,h) <- maybe (Left "Invalid JID.") Right | ||
610 | $ let (mu,h,_) = splitJID jid | ||
611 | in fmap (, h) mu | ||
612 | base64 <- case splitAt 43 $ Text.unpack h of | ||
613 | (base64,".tox") -> Right base64 | ||
614 | _ -> Left "Hostname should be 43 base64 digits followed by .tox." | ||
615 | pub <- id2key <$> readEither base64 | ||
616 | let ustr = Text.unpack u | ||
617 | case ustr of | ||
618 | '$' : b64digits -> solveBase64NoSpamID b64digits pub | ||
619 | '0' : 'x' : hexdigits -> do nospam <- readEither ('0':'x':hexdigits) | ||
620 | return $ NoSpamId nospam pub | ||
621 | _ -> Left "Missing nospam." | ||
622 | |||
623 | solveBase64NoSpamID :: String -> PublicKey -> Either String NoSpamId | ||
624 | solveBase64NoSpamID b64digits pub = do | ||
625 | NoSpam nospam mx <- readEither $ '$' : map (\case; '?' -> '0'; c -> c) b64digits | ||
626 | maybe (const $ Left "missing checksum") (flip ($)) mx $ \x -> do | ||
627 | let nlo = fromIntegral (0x0FFFF .&. nospam) :: Word16 | ||
628 | nhi = fromIntegral (0x0FFFF .&. (nospam `shiftR` 16)) :: Word16 | ||
629 | sum = x `xor` nlo `xor` nhi `xor` xorsum pub | ||
630 | -- Find any question mark indices. | ||
631 | qs = catMaybes $ zipWith (\case; '?' -> Just ; _ -> const Nothing) b64digits [0..7] | ||
632 | -- Break up the /sum/ into a numbered list of two-bit non-zero nibbles. | ||
633 | ns = filter (\case; (_,0) -> False; _ -> True) | ||
634 | $ zip [0..7] | ||
635 | $ unfoldr (\s -> Just (s .&. 0xC000, s `shiftL` 2)) sum | ||
636 | -- Represent the nospam value as a Word64 | ||
637 | n64 = shiftL (fromIntegral nospam) 32 .|. shiftL (fromIntegral x) 16 :: Word64 | ||
638 | |||
639 | -- q=0 1 2 3 4 5 6 7 | ||
640 | -- 012 345 670 123 456 701 234 567 | ||
641 | nibblePlace n q = case mod (n - 3 * q) 8 of | ||
642 | p | p < 3 -> Just (q,p) | ||
643 | _ -> Nothing | ||
644 | |||
645 | solve [] !ac = Right ac | ||
646 | solve ((n,b):ns) !ac = do | ||
647 | -- Find nibble p of question-digit q that corresponds to nibble n. | ||
648 | (q,p) <- maybe (Left "Unsolvable nospam.") Right | ||
649 | $ foldr (<|>) Nothing $ map (nibblePlace n) qs | ||
650 | let bitpos = q * 6 + p * 2 | ||
651 | ac' = ac `xor` shiftR (fromIntegral b `shiftL` 48) bitpos | ||
652 | solve ns ac' | ||
653 | n64' <- solve ns n64 | ||
654 | let nospam' = fromIntegral (n64' `shiftR` 32) | ||
655 | cksum' = fromIntegral (n64' `shiftR` 16) | ||
656 | return $ NoSpamId (NoSpam nospam' (Just cksum')) pub | ||
657 | |||
658 | -- | This type indicates a roster-link relationship between a local toxid and a | ||
659 | -- remote toxid. Note that these toxids are represented as the type 'NodeId' | ||
660 | -- even though they are long-term keys rather than the public keys of Tox DHT | ||
661 | -- nodes. | ||
662 | data ToxContact = ToxContact NodeId{-me-} NodeId{-them-} | ||
663 | deriving (Eq,Ord) | ||
664 | |||
665 | instance Show ToxContact where show = show . showToxContact_ | ||
666 | |||
667 | showToxContact_ :: ToxContact -> String | ||
668 | showToxContact_ (ToxContact me them) = show me ++ ":" ++ show them | ||
669 | |||
670 | -- | This type indicates the progress of a tox encrypted friend link | ||
671 | -- connection. Two scenarios are illustrated below. The parenthesis show the | ||
672 | -- current 'G.Status' 'ToxProgress' of the session. | ||
673 | -- | ||
674 | -- | ||
675 | -- Perfect handshake scenario: | ||
676 | -- | ||
677 | -- Peer 1 Peer 2 | ||
678 | -- (InProgress AcquiringCookie) (Dormant/InProgress AcquiringCookie) | ||
679 | -- Cookie request -> | ||
680 | -- <- Cookie response | ||
681 | -- (InProgress AwaitingHandshake) (Dormant/InProgress AcquiringCookie) | ||
682 | -- Handshake packet -> | ||
683 | -- * accepts connection | ||
684 | -- (InProgress AwaitingSessionPacket) | ||
685 | -- <- Handshake packet | ||
686 | -- *accepts connection | ||
687 | -- (InProgress AwaitingSessionPacket) | ||
688 | -- Encrypted packet -> <- Encrypted packet | ||
689 | -- *confirms connection *confirms connection | ||
690 | -- (Established) (Established) | ||
691 | -- | ||
692 | -- Connection successful. | ||
693 | -- | ||
694 | -- Encrypted packets -> <- Encrypted packets | ||
695 | -- | ||
696 | -- | ||
697 | -- | ||
698 | -- | ||
699 | -- More realistic handshake scenario: | ||
700 | -- Peer 1 Peer 2 | ||
701 | -- (InProgress AcquiringCookie) (Dormant/InProgress AcquiringCookie) | ||
702 | -- Cookie request -> *packet lost* | ||
703 | -- Cookie request -> | ||
704 | -- <- Cookie response | ||
705 | -- (InProgress AwaitingHandshake) (Dormant/InProgress AcquiringCookie) | ||
706 | -- | ||
707 | -- *Peer 2 randomly starts new connection to peer 1 | ||
708 | -- (InProgress AcquiringCookie) | ||
709 | -- <- Cookie request | ||
710 | -- Cookie response -> | ||
711 | -- (InProgress AwaitingHandshake) | ||
712 | -- | ||
713 | -- Handshake packet -> <- Handshake packet | ||
714 | -- *accepts connection * accepts connection | ||
715 | -- (InProgress AwaitingSessionPacket) (InProgress AwaitingSessionPacket) | ||
716 | -- | ||
717 | -- Encrypted packet -> <- Encrypted packet | ||
718 | -- *confirms connection *confirms connection | ||
719 | -- (Established) (Established) | ||
720 | -- | ||
721 | -- Connection successful. | ||
722 | -- | ||
723 | -- Encrypted packets -> <- Encrypted packets | ||
724 | data ToxProgress | ||
725 | = AwaitingDHTKey -- ^ Waiting to receive their DHT key. | ||
726 | | AcquiringIPAddress -- ^ Searching DHT to obtain their node's IP & port. | ||
727 | | AcquiringCookie -- ^ Attempting to obtain a cookie. | ||
728 | | AwaitingHandshake -- ^ Waiting to receive a handshake. | ||
729 | | AwaitingSessionPacket -- ^ Connection is "accepted" but not yet "confirmed". | ||
730 | deriving (Eq,Ord,Enum,Show) | ||
731 | |||