diff options
-rw-r--r-- | src/Crypto/Tox.hs | 38 | ||||
-rw-r--r-- | src/Network/Tox.hs | 2 | ||||
-rw-r--r-- | src/Network/Tox/DHT/Handlers.hs | 32 | ||||
-rw-r--r-- | src/Network/Tox/DHT/Transport.hs | 88 | ||||
-rw-r--r-- | src/Network/Tox/Onion/Handlers.hs | 16 | ||||
-rw-r--r-- | src/Network/Tox/Onion/Transport.hs | 74 | ||||
-rw-r--r-- | src/Network/Tox/Transport.hs | 2 | ||||
-rw-r--r-- | todo.txt | 10 |
8 files changed, 126 insertions, 136 deletions
diff --git a/src/Crypto/Tox.hs b/src/Crypto/Tox.hs index 645ca53e..ed8ec59e 100644 --- a/src/Crypto/Tox.hs +++ b/src/Crypto/Tox.hs | |||
@@ -20,11 +20,11 @@ module Crypto.Tox | |||
20 | , Encrypted | 20 | , Encrypted |
21 | , Encrypted8(..) | 21 | , Encrypted8(..) |
22 | , type (∘)(..) | 22 | , type (∘)(..) |
23 | , Assym(..) | 23 | , Asymm(..) |
24 | , getAssym | 24 | , getAsymm |
25 | , getAliasedAssym | 25 | , getAliasedAsymm |
26 | , putAssym | 26 | , putAsymm |
27 | , putAliasedAssym | 27 | , putAliasedAsymm |
28 | , Plain | 28 | , Plain |
29 | , encodePlain | 29 | , encodePlain |
30 | , decodePlain | 30 | , decodePlain |
@@ -326,34 +326,34 @@ zeros24 = BA.take 24 zs where Nonce32 zs = zeros32 | |||
326 | -- | `32` | sender's DHT public key | | 326 | -- | `32` | sender's DHT public key | |
327 | -- | `24` | nonce | | 327 | -- | `24` | nonce | |
328 | -- | `?` | encrypted message | | 328 | -- | `?` | encrypted message | |
329 | data Assym a = Assym | 329 | data Asymm a = Asymm |
330 | { senderKey :: PublicKey | 330 | { senderKey :: PublicKey |
331 | , assymNonce :: Nonce24 | 331 | , asymmNonce :: Nonce24 |
332 | , assymData :: a | 332 | , asymmData :: a |
333 | } | 333 | } |
334 | deriving (Functor,Foldable,Traversable, Show) | 334 | deriving (Functor,Foldable,Traversable, Show) |
335 | 335 | ||
336 | instance Sized a => Sized (Assym a) where | 336 | instance Sized a => Sized (Asymm a) where |
337 | size = case size of | 337 | size = case size of |
338 | ConstSize a -> ConstSize $ a + 24 + 32 | 338 | ConstSize a -> ConstSize $ a + 24 + 32 |
339 | VarSize f -> VarSize $ \Assym { assymData = x } -> f x + 24 + 32 | 339 | VarSize f -> VarSize $ \Asymm { asymmData = x } -> f x + 24 + 32 |
340 | 340 | ||
341 | -- | Field order: senderKey, then nonce This is the format used by | 341 | -- | Field order: senderKey, then nonce This is the format used by |
342 | -- Ping/Pong/GetNodes/SendNodes. | 342 | -- Ping/Pong/GetNodes/SendNodes. |
343 | -- | 343 | -- |
344 | -- See 'getAliasedAssym' if the nonce precedes the key. | 344 | -- See 'getAliasedAsymm' if the nonce precedes the key. |
345 | getAssym :: Serialize a => Get (Assym a) | 345 | getAsymm :: Serialize a => Get (Asymm a) |
346 | getAssym = Assym <$> getPublicKey <*> get <*> get | 346 | getAsymm = Asymm <$> getPublicKey <*> get <*> get |
347 | 347 | ||
348 | putAssym :: Serialize a => Assym a -> Put | 348 | putAsymm :: Serialize a => Asymm a -> Put |
349 | putAssym (Assym key nonce dta) = putPublicKey key >> put nonce >> put dta | 349 | putAsymm (Asymm key nonce dta) = putPublicKey key >> put nonce >> put dta |
350 | 350 | ||
351 | -- | Field order: nonce, and then senderKey. | 351 | -- | Field order: nonce, and then senderKey. |
352 | getAliasedAssym :: Serialize a => Get (Assym a) | 352 | getAliasedAsymm :: Serialize a => Get (Asymm a) |
353 | getAliasedAssym = flip Assym <$> get <*> getPublicKey <*> get | 353 | getAliasedAsymm = flip Asymm <$> get <*> getPublicKey <*> get |
354 | 354 | ||
355 | putAliasedAssym :: Serialize a => Assym a -> Put | 355 | putAliasedAsymm :: Serialize a => Asymm a -> Put |
356 | putAliasedAssym (Assym key nonce dta) = put nonce >> putPublicKey key >> put dta | 356 | putAliasedAsymm (Asymm key nonce dta) = put nonce >> putPublicKey key >> put dta |
357 | 357 | ||
358 | newtype SymmetricKey = SymmetricKey ByteString | 358 | newtype SymmetricKey = SymmetricKey ByteString |
359 | 359 | ||
diff --git a/src/Network/Tox.hs b/src/Network/Tox.hs index 908691df..987f742c 100644 --- a/src/Network/Tox.hs +++ b/src/Network/Tox.hs | |||
@@ -208,7 +208,7 @@ newClient drg net classify selfAddr handlers modifytbl modifynet = do | |||
208 | data Tox = Tox | 208 | data Tox = Tox |
209 | { toxDHT :: DHT.Client | 209 | { toxDHT :: DHT.Client |
210 | , toxOnion :: Onion.Client RouteId | 210 | , toxOnion :: Onion.Client RouteId |
211 | , toxToRoute :: Transport String Onion.Rendezvous (Assym (Encrypted Onion.DataToRoute)) | 211 | , toxToRoute :: Transport String Onion.Rendezvous (Asymm (Encrypted Onion.DataToRoute)) |
212 | , toxCrypto :: Transport String SockAddr NetCrypto | 212 | , toxCrypto :: Transport String SockAddr NetCrypto |
213 | , toxCryptoKeys :: TransportCrypto | 213 | , toxCryptoKeys :: TransportCrypto |
214 | , toxRouting :: DHT.Routing | 214 | , toxRouting :: DHT.Routing |
diff --git a/src/Network/Tox/DHT/Handlers.hs b/src/Network/Tox/DHT/Handlers.hs index a3f13ac7..4f891316 100644 --- a/src/Network/Tox/DHT/Handlers.hs +++ b/src/Network/Tox/DHT/Handlers.hs | |||
@@ -188,29 +188,29 @@ type Message = DHTMessage ((,) Nonce8) | |||
188 | type Client = QR.Client String PacketKind TransactionId NodeInfo Message | 188 | type Client = QR.Client String PacketKind TransactionId NodeInfo Message |
189 | 189 | ||
190 | 190 | ||
191 | wrapAssym :: TransactionId -> NodeInfo -> NodeInfo -> (Nonce8 -> dta) -> Assym dta | 191 | wrapAsymm :: TransactionId -> NodeInfo -> NodeInfo -> (Nonce8 -> dta) -> Asymm dta |
192 | wrapAssym (TransactionId n8 n24) src dst dta = Assym | 192 | wrapAsymm (TransactionId n8 n24) src dst dta = Asymm |
193 | { senderKey = id2key $ nodeId src | 193 | { senderKey = id2key $ nodeId src |
194 | , assymNonce = n24 | 194 | , asymmNonce = n24 |
195 | , assymData = dta n8 | 195 | , asymmData = dta n8 |
196 | } | 196 | } |
197 | 197 | ||
198 | serializer :: PacketKind | 198 | serializer :: PacketKind |
199 | -> (Assym (Nonce8,ping) -> Message) | 199 | -> (Asymm (Nonce8,ping) -> Message) |
200 | -> (Message -> Maybe (Assym (Nonce8,pong))) | 200 | -> (Message -> Maybe (Asymm (Nonce8,pong))) |
201 | -> MethodSerializer TransactionId NodeInfo Message PacketKind ping (Maybe pong) | 201 | -> MethodSerializer TransactionId NodeInfo Message PacketKind ping (Maybe pong) |
202 | serializer pktkind mkping mkpong = MethodSerializer | 202 | serializer pktkind mkping mkpong = MethodSerializer |
203 | { methodTimeout = \tid addr -> return (addr, 5000000) | 203 | { methodTimeout = \tid addr -> return (addr, 5000000) |
204 | , method = pktkind | 204 | , method = pktkind |
205 | -- wrapQuery :: tid -> addr -> addr -> qry -> x | 205 | -- wrapQuery :: tid -> addr -> addr -> qry -> x |
206 | , wrapQuery = \tid src dst ping -> mkping $ wrapAssym tid src dst (, ping) | 206 | , wrapQuery = \tid src dst ping -> mkping $ wrapAsymm tid src dst (, ping) |
207 | -- unwrapResponse :: x -> b | 207 | -- unwrapResponse :: x -> b |
208 | , unwrapResponse = fmap (snd . assymData) . mkpong | 208 | , unwrapResponse = fmap (snd . asymmData) . mkpong |
209 | } | 209 | } |
210 | 210 | ||
211 | 211 | ||
212 | unpong :: Message -> Maybe (Assym (Nonce8,Pong)) | 212 | unpong :: Message -> Maybe (Asymm (Nonce8,Pong)) |
213 | unpong (DHTPong assym) = Just assym | 213 | unpong (DHTPong asymm) = Just asymm |
214 | unpong _ = Nothing | 214 | unpong _ = Nothing |
215 | 215 | ||
216 | showHex :: BA.ByteArrayAccess ba => ba -> String | 216 | showHex :: BA.ByteArrayAccess ba => ba -> String |
@@ -223,8 +223,8 @@ ping client addr = do | |||
223 | hPutStrLn stderr $ show addr ++ " -pong-> " ++ show reply | 223 | hPutStrLn stderr $ show addr ++ " -pong-> " ++ show reply |
224 | maybe (return False) (\Pong -> return True) $ join reply | 224 | maybe (return False) (\Pong -> return True) $ join reply |
225 | 225 | ||
226 | unsendNodes :: Message -> Maybe (Assym (Nonce8,SendNodes)) | 226 | unsendNodes :: Message -> Maybe (Asymm (Nonce8,SendNodes)) |
227 | unsendNodes (DHTSendNodes assym) = Just assym | 227 | unsendNodes (DHTSendNodes asymm) = Just asymm |
228 | unsendNodes _ = Nothing | 228 | unsendNodes _ = Nothing |
229 | 229 | ||
230 | unwrapNodes :: SendNodes -> ( [NodeInfo], [NodeInfo], () ) | 230 | unwrapNodes :: SendNodes -> ( [NodeInfo], [NodeInfo], () ) |
@@ -285,18 +285,18 @@ transitionCommittee committee _ = return $ return () | |||
285 | type Handler = MethodHandler String TransactionId NodeInfo Message | 285 | type Handler = MethodHandler String TransactionId NodeInfo Message |
286 | 286 | ||
287 | isPing :: (f Ping -> Ping) -> DHTMessage f -> Either String Ping | 287 | isPing :: (f Ping -> Ping) -> DHTMessage f -> Either String Ping |
288 | isPing unpack (DHTPing a) = Right $ unpack $ assymData a | 288 | isPing unpack (DHTPing a) = Right $ unpack $ asymmData a |
289 | isPing _ _ = Left "Bad ping" | 289 | isPing _ _ = Left "Bad ping" |
290 | 290 | ||
291 | mkPong :: TransactionId -> NodeInfo -> NodeInfo -> Pong -> DHTMessage ((,) Nonce8) | 291 | mkPong :: TransactionId -> NodeInfo -> NodeInfo -> Pong -> DHTMessage ((,) Nonce8) |
292 | mkPong tid src dst pong = DHTPong $ wrapAssym tid src dst (, pong) | 292 | mkPong tid src dst pong = DHTPong $ wrapAsymm tid src dst (, pong) |
293 | 293 | ||
294 | isGetNodes :: (f GetNodes -> GetNodes) -> DHTMessage f -> Either String GetNodes | 294 | isGetNodes :: (f GetNodes -> GetNodes) -> DHTMessage f -> Either String GetNodes |
295 | isGetNodes unpack (DHTGetNodes a) = Right $ unpack $ assymData a | 295 | isGetNodes unpack (DHTGetNodes a) = Right $ unpack $ asymmData a |
296 | isGetNodes _ _ = Left "Bad GetNodes" | 296 | isGetNodes _ _ = Left "Bad GetNodes" |
297 | 297 | ||
298 | mkSendNodes :: TransactionId -> NodeInfo -> NodeInfo -> SendNodes -> DHTMessage ((,) Nonce8) | 298 | mkSendNodes :: TransactionId -> NodeInfo -> NodeInfo -> SendNodes -> DHTMessage ((,) Nonce8) |
299 | mkSendNodes tid src dst sendnodes = DHTSendNodes $ wrapAssym tid src dst (, sendnodes) | 299 | mkSendNodes tid src dst sendnodes = DHTSendNodes $ wrapAsymm tid src dst (, sendnodes) |
300 | 300 | ||
301 | handlers :: Routing -> PacketKind -> Maybe Handler | 301 | handlers :: Routing -> PacketKind -> Maybe Handler |
302 | handlers routing PingType = Just $ MethodHandler (isPing snd) mkPong pingH | 302 | handlers routing PingType = Just $ MethodHandler (isPing snd) mkPong pingH |
diff --git a/src/Network/Tox/DHT/Transport.hs b/src/Network/Tox/DHT/Transport.hs index 16af0e3f..5bd9caa1 100644 --- a/src/Network/Tox/DHT/Transport.hs +++ b/src/Network/Tox/DHT/Transport.hs | |||
@@ -50,30 +50,30 @@ type HandleHi a = Maybe (Either String (DHTMessage Encrypted8, NodeInfo)) -> IO | |||
50 | 50 | ||
51 | 51 | ||
52 | data DHTMessage (f :: * -> *) | 52 | data DHTMessage (f :: * -> *) |
53 | = DHTPing (Assym (f Ping)) | 53 | = DHTPing (Asymm (f Ping)) |
54 | | DHTPong (Assym (f Pong)) | 54 | | DHTPong (Asymm (f Pong)) |
55 | | DHTGetNodes (Assym (f GetNodes)) | 55 | | DHTGetNodes (Asymm (f GetNodes)) |
56 | | DHTSendNodes (Assym (f SendNodes)) | 56 | | DHTSendNodes (Asymm (f SendNodes)) |
57 | | DHTCookieRequest (Assym (f CookieRequest)) | 57 | | DHTCookieRequest (Asymm (f CookieRequest)) |
58 | | DHTCookie Nonce24 (f Cookie) | 58 | | DHTCookie Nonce24 (f Cookie) |
59 | | DHTDHTRequest PublicKey (Assym (f DHTRequest)) | 59 | | DHTDHTRequest PublicKey (Asymm (f DHTRequest)) |
60 | 60 | ||
61 | deriving instance ( Show (f Cookie) | 61 | deriving instance ( Show (f Cookie) |
62 | , Show (Assym (f Ping)) | 62 | , Show (Asymm (f Ping)) |
63 | , Show (Assym (f Pong)) | 63 | , Show (Asymm (f Pong)) |
64 | , Show (Assym (f GetNodes)) | 64 | , Show (Asymm (f GetNodes)) |
65 | , Show (Assym (f SendNodes)) | 65 | , Show (Asymm (f SendNodes)) |
66 | , Show (Assym (f CookieRequest)) | 66 | , Show (Asymm (f CookieRequest)) |
67 | , Show (Assym (f DHTRequest)) | 67 | , Show (Asymm (f DHTRequest)) |
68 | ) => Show (DHTMessage f) | 68 | ) => Show (DHTMessage f) |
69 | 69 | ||
70 | mapMessage :: forall f b. (forall a. Nonce24 -> f a -> b) -> DHTMessage f -> b | 70 | mapMessage :: forall f b. (forall a. Nonce24 -> f a -> b) -> DHTMessage f -> b |
71 | mapMessage f (DHTPing a) = f (assymNonce a) (assymData a) | 71 | mapMessage f (DHTPing a) = f (asymmNonce a) (asymmData a) |
72 | mapMessage f (DHTPong a) = f (assymNonce a) (assymData a) | 72 | mapMessage f (DHTPong a) = f (asymmNonce a) (asymmData a) |
73 | mapMessage f (DHTGetNodes a) = f (assymNonce a) (assymData a) | 73 | mapMessage f (DHTGetNodes a) = f (asymmNonce a) (asymmData a) |
74 | mapMessage f (DHTSendNodes a) = f (assymNonce a) (assymData a) | 74 | mapMessage f (DHTSendNodes a) = f (asymmNonce a) (asymmData a) |
75 | mapMessage f (DHTCookieRequest a) = f (assymNonce a) (assymData a) | 75 | mapMessage f (DHTCookieRequest a) = f (asymmNonce a) (asymmData a) |
76 | mapMessage f (DHTDHTRequest _ a) = f (assymNonce a) (assymData a) | 76 | mapMessage f (DHTDHTRequest _ a) = f (asymmNonce a) (asymmData a) |
77 | mapMessage f (DHTCookie nonce fcookie) = f nonce fcookie | 77 | mapMessage f (DHTCookie nonce fcookie) = f nonce fcookie |
78 | 78 | ||
79 | 79 | ||
@@ -99,13 +99,13 @@ encodeDHTAddr :: (DHTMessage Encrypted8,NodeInfo) -> (ByteString, SockAddr) | |||
99 | encodeDHTAddr (msg,ni) = (runPut $ putMessage msg, nodeAddr ni) | 99 | encodeDHTAddr (msg,ni) = (runPut $ putMessage msg, nodeAddr ni) |
100 | 100 | ||
101 | dhtMessageType :: DHTMessage Encrypted8 -> ( Word8, Put ) | 101 | dhtMessageType :: DHTMessage Encrypted8 -> ( Word8, Put ) |
102 | dhtMessageType (DHTPing a) = (0x00, putAssym a) | 102 | dhtMessageType (DHTPing a) = (0x00, putAsymm a) |
103 | dhtMessageType (DHTPong a) = (0x01, putAssym a) | 103 | dhtMessageType (DHTPong a) = (0x01, putAsymm a) |
104 | dhtMessageType (DHTGetNodes a) = (0x02, putAssym a) | 104 | dhtMessageType (DHTGetNodes a) = (0x02, putAsymm a) |
105 | dhtMessageType (DHTSendNodes a) = (0x04, putAssym a) | 105 | dhtMessageType (DHTSendNodes a) = (0x04, putAsymm a) |
106 | dhtMessageType (DHTCookieRequest a) = (0x18, putAssym a) | 106 | dhtMessageType (DHTCookieRequest a) = (0x18, putAsymm a) |
107 | dhtMessageType (DHTCookie n x) = (0x19, put n >> put x) | 107 | dhtMessageType (DHTCookie n x) = (0x19, put n >> put x) |
108 | dhtMessageType (DHTDHTRequest k a) = (0x20, putPublicKey k >> putAssym a) | 108 | dhtMessageType (DHTDHTRequest k a) = (0x20, putPublicKey k >> putAsymm a) |
109 | 109 | ||
110 | putMessage :: DHTMessage Encrypted8 -> Put | 110 | putMessage :: DHTMessage Encrypted8 -> Put |
111 | putMessage msg = case dhtMessageType msg of (typ,p) -> put typ >> p | 111 | putMessage msg = case dhtMessageType msg of (typ,p) -> put typ >> p |
@@ -113,8 +113,8 @@ putMessage msg = case dhtMessageType msg of (typ,p) -> put typ >> p | |||
113 | getCookie :: Get (Nonce24, Encrypted8 Cookie) | 113 | getCookie :: Get (Nonce24, Encrypted8 Cookie) |
114 | getCookie = get | 114 | getCookie = get |
115 | 115 | ||
116 | getDHTReqest :: Get (PublicKey, Assym (Encrypted8 DHTRequest)) | 116 | getDHTReqest :: Get (PublicKey, Asymm (Encrypted8 DHTRequest)) |
117 | getDHTReqest = (,) <$> getPublicKey <*> getAssym | 117 | getDHTReqest = (,) <$> getPublicKey <*> getAsymm |
118 | 118 | ||
119 | -- ## DHT Request packets | 119 | -- ## DHT Request packets |
120 | -- | 120 | -- |
@@ -125,19 +125,19 @@ getDHTReqest = (,) <$> getPublicKey <*> getAssym | |||
125 | -- ... ... | 125 | -- ... ... |
126 | 126 | ||
127 | 127 | ||
128 | getDHT :: Sized a => Get (Assym (Encrypted8 a)) | 128 | getDHT :: Sized a => Get (Asymm (Encrypted8 a)) |
129 | getDHT = getAssym | 129 | getDHT = getAsymm |
130 | 130 | ||
131 | 131 | ||
132 | -- Throws an error if called with a non-internet socket. | 132 | -- Throws an error if called with a non-internet socket. |
133 | direct :: Sized a => ByteString | 133 | direct :: Sized a => ByteString |
134 | -> SockAddr | 134 | -> SockAddr |
135 | -> (Assym (Encrypted8 a) -> DHTMessage Encrypted8) | 135 | -> (Asymm (Encrypted8 a) -> DHTMessage Encrypted8) |
136 | -> Either String (DHTMessage Encrypted8, NodeInfo) | 136 | -> Either String (DHTMessage Encrypted8, NodeInfo) |
137 | direct bs saddr f = fanGet bs getDHT f (asymNodeInfo saddr) | 137 | direct bs saddr f = fanGet bs getDHT f (asymNodeInfo saddr) |
138 | 138 | ||
139 | -- Throws an error if called with a non-internet socket. | 139 | -- Throws an error if called with a non-internet socket. |
140 | asymNodeInfo :: SockAddr -> Assym a -> NodeInfo | 140 | asymNodeInfo :: SockAddr -> Asymm a -> NodeInfo |
141 | asymNodeInfo saddr asym = either (error . mappend "asymNodeInfo: ") id $ nodeInfo (key2id $ senderKey asym) saddr | 141 | asymNodeInfo saddr asym = either (error . mappend "asymNodeInfo: ") id $ nodeInfo (key2id $ senderKey asym) saddr |
142 | 142 | ||
143 | 143 | ||
@@ -351,11 +351,11 @@ encrypt crypto msg ni = ( transcode (encryptMessage crypto (id2key $ nodeId ni)) | |||
351 | encryptMessage :: Serialize a => | 351 | encryptMessage :: Serialize a => |
352 | TransportCrypto -> | 352 | TransportCrypto -> |
353 | PublicKey -> | 353 | PublicKey -> |
354 | Nonce24 -> Either (Nonce8,a) (Assym (Nonce8,a)) -> Encrypted8 a | 354 | Nonce24 -> Either (Nonce8,a) (Asymm (Nonce8,a)) -> Encrypted8 a |
355 | encryptMessage crypto destKey n (Right assym) = E8 $ ToxCrypto.encrypt secret plain | 355 | encryptMessage crypto destKey n (Right asymm) = E8 $ ToxCrypto.encrypt secret plain |
356 | where | 356 | where |
357 | secret = computeSharedSecret (transportSecret crypto) destKey n | 357 | secret = computeSharedSecret (transportSecret crypto) destKey n |
358 | plain = encodePlain $ swap $ assymData assym | 358 | plain = encodePlain $ swap $ asymmData asymm |
359 | encryptMessage crypto destKey n (Left plain) = _todo -- need cached public key. | 359 | encryptMessage crypto destKey n (Left plain) = _todo -- need cached public key. |
360 | 360 | ||
361 | decrypt :: TransportCrypto -> DHTMessage Encrypted8 -> NodeInfo -> Either String (DHTMessage ((,) Nonce8), NodeInfo) | 361 | decrypt :: TransportCrypto -> DHTMessage Encrypted8 -> NodeInfo -> Either String (DHTMessage ((,) Nonce8), NodeInfo) |
@@ -364,12 +364,12 @@ decrypt crypto msg ni = (, ni) <$> (sequenceMessage $ transcode (decryptMessage | |||
364 | decryptMessage :: Serialize x => | 364 | decryptMessage :: Serialize x => |
365 | TransportCrypto | 365 | TransportCrypto |
366 | -> Nonce24 | 366 | -> Nonce24 |
367 | -> Either (Encrypted8 x) (Assym (Encrypted8 x)) | 367 | -> Either (Encrypted8 x) (Asymm (Encrypted8 x)) |
368 | -> (Either String ∘ ((,) Nonce8)) x | 368 | -> (Either String ∘ ((,) Nonce8)) x |
369 | decryptMessage crypto n (Right assymE) = plain8 $ ToxCrypto.decrypt secret e | 369 | decryptMessage crypto n (Right asymmE) = plain8 $ ToxCrypto.decrypt secret e |
370 | where | 370 | where |
371 | secret = computeSharedSecret (transportSecret crypto) (senderKey assymE) n | 371 | secret = computeSharedSecret (transportSecret crypto) (senderKey asymmE) n |
372 | E8 e = assymData assymE | 372 | E8 e = asymmData asymmE |
373 | plain8 = Composed . fmap swap . (>>= decodePlain) | 373 | plain8 = Composed . fmap swap . (>>= decodePlain) |
374 | decryptMessage crypto n (Left (E8 e)) = _todo -- need cached public key | 374 | decryptMessage crypto n (Left (E8 e)) = _todo -- need cached public key |
375 | 375 | ||
@@ -382,11 +382,11 @@ sequenceMessage (DHTCookieRequest asym) = fmap DHTCookieRequest $ sequenceA | |||
382 | sequenceMessage (DHTCookie n dta) = fmap (DHTCookie n) $ uncomposed dta | 382 | sequenceMessage (DHTCookie n dta) = fmap (DHTCookie n) $ uncomposed dta |
383 | sequenceMessage (DHTDHTRequest pubkey asym) = fmap (DHTDHTRequest pubkey) $ sequenceA $ fmap uncomposed asym | 383 | sequenceMessage (DHTDHTRequest pubkey asym) = fmap (DHTDHTRequest pubkey) $ sequenceA $ fmap uncomposed asym |
384 | 384 | ||
385 | transcode :: forall f g. (forall a. Serialize a => Nonce24 -> Either (f a) (Assym (f a)) -> g a) -> DHTMessage f -> DHTMessage g | 385 | transcode :: forall f g. (forall a. Serialize a => Nonce24 -> Either (f a) (Asymm (f a)) -> g a) -> DHTMessage f -> DHTMessage g |
386 | transcode f (DHTPing asym) = DHTPing $ asym { assymData = f (assymNonce asym) (Right asym) } | 386 | transcode f (DHTPing asym) = DHTPing $ asym { asymmData = f (asymmNonce asym) (Right asym) } |
387 | transcode f (DHTPong asym) = DHTPong $ asym { assymData = f (assymNonce asym) (Right asym) } | 387 | transcode f (DHTPong asym) = DHTPong $ asym { asymmData = f (asymmNonce asym) (Right asym) } |
388 | transcode f (DHTGetNodes asym) = DHTGetNodes $ asym { assymData = f (assymNonce asym) (Right asym) } | 388 | transcode f (DHTGetNodes asym) = DHTGetNodes $ asym { asymmData = f (asymmNonce asym) (Right asym) } |
389 | transcode f (DHTSendNodes asym) = DHTSendNodes $ asym { assymData = f (assymNonce asym) (Right asym) } | 389 | transcode f (DHTSendNodes asym) = DHTSendNodes $ asym { asymmData = f (asymmNonce asym) (Right asym) } |
390 | transcode f (DHTCookieRequest asym) = DHTCookieRequest $ asym { assymData = f (assymNonce asym) (Right asym) } | 390 | transcode f (DHTCookieRequest asym) = DHTCookieRequest $ asym { asymmData = f (asymmNonce asym) (Right asym) } |
391 | transcode f (DHTCookie n dta) = DHTCookie n $ f n $ Left dta | 391 | transcode f (DHTCookie n dta) = DHTCookie n $ f n $ Left dta |
392 | transcode f (DHTDHTRequest pubkey asym) = DHTDHTRequest pubkey $ asym { assymData = f (assymNonce asym) (Right asym) } | 392 | transcode f (DHTDHTRequest pubkey asym) = DHTDHTRequest pubkey $ asym { asymmData = f (asymmNonce asym) (Right asym) } |
diff --git a/src/Network/Tox/Onion/Handlers.hs b/src/Network/Tox/Onion/Handlers.hs index 103c216b..23673273 100644 --- a/src/Network/Tox/Onion/Handlers.hs +++ b/src/Network/Tox/Onion/Handlers.hs | |||
@@ -46,8 +46,8 @@ classify :: Message -> MessageClass String PacketKind TransactionId | |||
46 | classify msg = go msg | 46 | classify msg = go msg |
47 | where | 47 | where |
48 | go (OnionAnnounce announce) = IsQuery AnnounceType | 48 | go (OnionAnnounce announce) = IsQuery AnnounceType |
49 | $ TransactionId (snd $ runIdentity $ assymData announce) | 49 | $ TransactionId (snd $ runIdentity $ asymmData announce) |
50 | (assymNonce announce) | 50 | (asymmNonce announce) |
51 | go (OnionAnnounceResponse n8 n24 resp) = IsResponse (TransactionId n8 n24) | 51 | go (OnionAnnounceResponse n8 n24 resp) = IsResponse (TransactionId n8 n24) |
52 | go (OnionToRoute {}) = IsQuery DataRequestType (TransactionId (Nonce8 0) (Nonce24 zeros24)) | 52 | go (OnionToRoute {}) = IsQuery DataRequestType (TransactionId (Nonce8 0) (Nonce24 zeros24)) |
53 | go (OnionToRouteResponse {}) = IsResponse (TransactionId (Nonce8 0) (Nonce24 zeros24)) | 53 | go (OnionToRouteResponse {}) = IsResponse (TransactionId (Nonce8 0) (Nonce24 zeros24)) |
@@ -116,7 +116,7 @@ dataToRouteH :: | |||
116 | -> addr | 116 | -> addr |
117 | -> OnionMessage f | 117 | -> OnionMessage f |
118 | -> IO () | 118 | -> IO () |
119 | dataToRouteH keydb udp _ (OnionToRoute pub assym) = do | 119 | dataToRouteH keydb udp _ (OnionToRoute pub asymm) = do |
120 | let k = key2id pub | 120 | let k = key2id pub |
121 | mb <- atomically $ do | 121 | mb <- atomically $ do |
122 | ks <- readTVar keydb | 122 | ks <- readTVar keydb |
@@ -125,7 +125,7 @@ dataToRouteH keydb udp _ (OnionToRoute pub assym) = do | |||
125 | return rpath | 125 | return rpath |
126 | forM_ mb $ \rpath -> do | 126 | forM_ mb $ \rpath -> do |
127 | -- forward | 127 | -- forward |
128 | sendMessage udp (toOnionDestination rpath) $ OnionToRouteResponse assym | 128 | sendMessage udp (toOnionDestination rpath) $ OnionToRouteResponse asymm |
129 | hPutStrLn stderr $ "Forwarding data-to-route -->"++show k | 129 | hPutStrLn stderr $ "Forwarding data-to-route -->"++show k |
130 | 130 | ||
131 | type NodeDistance = NodeId | 131 | type NodeDistance = NodeId |
@@ -150,7 +150,7 @@ insertKey tm pub toxpath d keydb = AnnouncedKeys | |||
150 | } | 150 | } |
151 | 151 | ||
152 | areq :: Message -> Either String AnnounceRequest | 152 | areq :: Message -> Either String AnnounceRequest |
153 | areq (OnionAnnounce assym) = Right $ fst $ runIdentity $ assymData assym | 153 | areq (OnionAnnounce asymm) = Right $ fst $ runIdentity $ asymmData asymm |
154 | areq _ = Left "Unexpected non-announce OnionMessage" | 154 | areq _ = Left "Unexpected non-announce OnionMessage" |
155 | 155 | ||
156 | handlers :: Transport err (OnionDestination r) Message | 156 | handlers :: Transport err (OnionDestination r) Message |
@@ -189,13 +189,13 @@ announceSerializer getTimeout = MethodSerializer | |||
189 | , method = AnnounceType | 189 | , method = AnnounceType |
190 | , wrapQuery = \(TransactionId n8 n24) src dst req -> | 190 | , wrapQuery = \(TransactionId n8 n24) src dst req -> |
191 | -- :: tid -> addr -> addr -> a -> OnionMessage Identity | 191 | -- :: tid -> addr -> addr -> a -> OnionMessage Identity |
192 | OnionAnnounce $ Assym | 192 | OnionAnnounce $ Asymm |
193 | { -- The public key is our real long term public key if we want to | 193 | { -- The public key is our real long term public key if we want to |
194 | -- announce ourselves, a temporary one if we are searching for | 194 | -- announce ourselves, a temporary one if we are searching for |
195 | -- friends. | 195 | -- friends. |
196 | senderKey = onionKey src | 196 | senderKey = onionKey src |
197 | , assymNonce = n24 | 197 | , asymmNonce = n24 |
198 | , assymData = Identity (req, n8) | 198 | , asymmData = Identity (req, n8) |
199 | } | 199 | } |
200 | , unwrapResponse = \case -- :: OnionMessage Identity -> b | 200 | , unwrapResponse = \case -- :: OnionMessage Identity -> b |
201 | OnionAnnounceResponse _ _ resp -> Just $ runIdentity resp | 201 | OnionAnnounceResponse _ _ resp -> Just $ runIdentity resp |
diff --git a/src/Network/Tox/Onion/Transport.hs b/src/Network/Tox/Onion/Transport.hs index 82f2c8a7..203d7dc7 100644 --- a/src/Network/Tox/Onion/Transport.hs +++ b/src/Network/Tox/Onion/Transport.hs | |||
@@ -78,17 +78,17 @@ type HandleLo a = Maybe (Either String (ByteString, SockAddr)) -> IO a | |||
78 | type UDPTransport = Transport String SockAddr ByteString | 78 | type UDPTransport = Transport String SockAddr ByteString |
79 | 79 | ||
80 | 80 | ||
81 | getOnionAssym :: Get (Assym (Encrypted DataToRoute)) | 81 | getOnionAsymm :: Get (Asymm (Encrypted DataToRoute)) |
82 | getOnionAssym = getAliasedAssym | 82 | getOnionAsymm = getAliasedAsymm |
83 | 83 | ||
84 | putOnionAssym :: Serialize a => Word8 -> Put -> Assym a -> Put | 84 | putOnionAsymm :: Serialize a => Word8 -> Put -> Asymm a -> Put |
85 | putOnionAssym typ p a = put typ >> p >> putAliasedAssym a | 85 | putOnionAsymm typ p a = put typ >> p >> putAliasedAsymm a |
86 | 86 | ||
87 | data OnionMessage (f :: * -> *) | 87 | data OnionMessage (f :: * -> *) |
88 | = OnionAnnounce (Assym (f (AnnounceRequest,Nonce8))) | 88 | = OnionAnnounce (Asymm (f (AnnounceRequest,Nonce8))) |
89 | | OnionAnnounceResponse Nonce8 Nonce24 (f AnnounceResponse) | 89 | | OnionAnnounceResponse Nonce8 Nonce24 (f AnnounceResponse) |
90 | | OnionToRoute PublicKey (Assym (Encrypted DataToRoute)) -- destination key, aliased Assym | 90 | | OnionToRoute PublicKey (Asymm (Encrypted DataToRoute)) -- destination key, aliased Asymm |
91 | | OnionToRouteResponse (Assym (Encrypted DataToRoute)) | 91 | | OnionToRouteResponse (Asymm (Encrypted DataToRoute)) |
92 | 92 | ||
93 | deriving instance ( Show (f (AnnounceRequest, Nonce8)) | 93 | deriving instance ( Show (f (AnnounceRequest, Nonce8)) |
94 | , Show (f AnnounceResponse) | 94 | , Show (f AnnounceResponse) |
@@ -96,10 +96,10 @@ deriving instance ( Show (f (AnnounceRequest, Nonce8)) | |||
96 | ) => Show (OnionMessage f) | 96 | ) => Show (OnionMessage f) |
97 | 97 | ||
98 | msgNonce :: OnionMessage f -> Nonce24 | 98 | msgNonce :: OnionMessage f -> Nonce24 |
99 | msgNonce (OnionAnnounce a) = assymNonce a | 99 | msgNonce (OnionAnnounce a) = asymmNonce a |
100 | msgNonce (OnionAnnounceResponse _ n24 _) = n24 | 100 | msgNonce (OnionAnnounceResponse _ n24 _) = n24 |
101 | msgNonce (OnionToRoute _ a) = assymNonce a | 101 | msgNonce (OnionToRoute _ a) = asymmNonce a |
102 | msgNonce (OnionToRouteResponse a) = assymNonce a | 102 | msgNonce (OnionToRouteResponse a) = asymmNonce a |
103 | 103 | ||
104 | data AliasSelector = SearchingAlias | AnnouncingAlias SecretKey PublicKey | 104 | data AliasSelector = SearchingAlias | AnnouncingAlias SecretKey PublicKey |
105 | deriving (Eq,Show) | 105 | deriving (Eq,Show) |
@@ -138,18 +138,18 @@ instance Serialize (OnionMessage Encrypted) where | |||
138 | get = do | 138 | get = do |
139 | typ <- get | 139 | typ <- get |
140 | case typ :: Word8 of | 140 | case typ :: Word8 of |
141 | 0x83 -> OnionAnnounce <$> getAliasedAssym | 141 | 0x83 -> OnionAnnounce <$> getAliasedAsymm |
142 | 0x85 -> OnionToRoute <$> getPublicKey <*> getAliasedAssym | 142 | 0x85 -> OnionToRoute <$> getPublicKey <*> getAliasedAsymm |
143 | t -> fail ("Unknown onion payload: " ++ show t) | 143 | t -> fail ("Unknown onion payload: " ++ show t) |
144 | `fromMaybe` getOnionReply t | 144 | `fromMaybe` getOnionReply t |
145 | put (OnionAnnounce a) = putWord8 0x83 >> putAliasedAssym a | 145 | put (OnionAnnounce a) = putWord8 0x83 >> putAliasedAsymm a |
146 | put (OnionToRoute k a) = putWord8 0x85 >> putPublicKey k >> putAliasedAssym a | 146 | put (OnionToRoute k a) = putWord8 0x85 >> putPublicKey k >> putAliasedAsymm a |
147 | put (OnionAnnounceResponse n8 n24 x) = putWord8 0x84 >> put n8 >> put n24 >> put x | 147 | put (OnionAnnounceResponse n8 n24 x) = putWord8 0x84 >> put n8 >> put n24 >> put x |
148 | put (OnionToRouteResponse a) = putWord8 0x86 >> putAliasedAssym a | 148 | put (OnionToRouteResponse a) = putWord8 0x86 >> putAliasedAsymm a |
149 | 149 | ||
150 | onionToOwner :: Assym a -> ReturnPath N3 -> SockAddr -> Either String (OnionDestination r) | 150 | onionToOwner :: Asymm a -> ReturnPath N3 -> SockAddr -> Either String (OnionDestination r) |
151 | onionToOwner assym ret3 saddr = do | 151 | onionToOwner asymm ret3 saddr = do |
152 | ni <- nodeInfo (key2id $ senderKey assym) saddr | 152 | ni <- nodeInfo (key2id $ senderKey asymm) saddr |
153 | return $ OnionToOwner ni ret3 | 153 | return $ OnionToOwner ni ret3 |
154 | -- data CookieAddress = WithoutCookie NodeInfo | CookieAddress Cookie SockAddr | 154 | -- data CookieAddress = WithoutCookie NodeInfo | CookieAddress Cookie SockAddr |
155 | 155 | ||
@@ -157,11 +157,11 @@ onionToOwner assym ret3 saddr = do | |||
157 | onion :: Sized msg => | 157 | onion :: Sized msg => |
158 | ByteString | 158 | ByteString |
159 | -> SockAddr | 159 | -> SockAddr |
160 | -> Get (Assym (Encrypted msg) -> t) | 160 | -> Get (Asymm (Encrypted msg) -> t) |
161 | -> Either String (t, OnionDestination r) | 161 | -> Either String (t, OnionDestination r) |
162 | onion bs saddr getf = do (f,(assym,ret3)) <- runGet ((,) <$> getf <*> getOnionRequest) bs | 162 | onion bs saddr getf = do (f,(asymm,ret3)) <- runGet ((,) <$> getf <*> getOnionRequest) bs |
163 | oaddr <- onionToOwner assym ret3 saddr | 163 | oaddr <- onionToOwner asymm ret3 saddr |
164 | return (f assym, oaddr) | 164 | return (f asymm, oaddr) |
165 | 165 | ||
166 | parseOnionAddr :: (SockAddr -> Nonce8 -> IO (Maybe (OnionDestination r))) | 166 | parseOnionAddr :: (SockAddr -> Nonce8 -> IO (Maybe (OnionDestination r))) |
167 | -> (ByteString, SockAddr) | 167 | -> (ByteString, SockAddr) |
@@ -187,14 +187,14 @@ parseOnionAddr lookupSender (msg,saddr) | |||
187 | 187 | ||
188 | getOnionReply :: Word8 -> Maybe (Get (OnionMessage Encrypted)) | 188 | getOnionReply :: Word8 -> Maybe (Get (OnionMessage Encrypted)) |
189 | getOnionReply 0x84 = Just $ OnionAnnounceResponse <$> get <*> get <*> get | 189 | getOnionReply 0x84 = Just $ OnionAnnounceResponse <$> get <*> get <*> get |
190 | getOnionReply 0x86 = Just $ OnionToRouteResponse <$> getOnionAssym | 190 | getOnionReply 0x86 = Just $ OnionToRouteResponse <$> getOnionAsymm |
191 | getOnionReply _ = Nothing | 191 | getOnionReply _ = Nothing |
192 | 192 | ||
193 | putOnionMsg :: OnionMessage Encrypted -> Put | 193 | putOnionMsg :: OnionMessage Encrypted -> Put |
194 | putOnionMsg (OnionAnnounce a) = putOnionAssym 0x83 (return ()) a | 194 | putOnionMsg (OnionAnnounce a) = putOnionAsymm 0x83 (return ()) a |
195 | putOnionMsg (OnionToRoute pubkey a) = putOnionAssym 0x85 (putPublicKey pubkey) a | 195 | putOnionMsg (OnionToRoute pubkey a) = putOnionAsymm 0x85 (putPublicKey pubkey) a |
196 | putOnionMsg (OnionAnnounceResponse n8 n24 x) = put (0x84 :: Word8) >> put n8 >> put n24 >> put x | 196 | putOnionMsg (OnionAnnounceResponse n8 n24 x) = put (0x84 :: Word8) >> put n8 >> put n24 >> put x |
197 | putOnionMsg (OnionToRouteResponse a) = putOnionAssym 0x86 (return ()) a | 197 | putOnionMsg (OnionToRouteResponse a) = putOnionAsymm 0x86 (return ()) a |
198 | 198 | ||
199 | encodeOnionAddr :: (NodeInfo -> r -> IO (Maybe OnionRoute)) | 199 | encodeOnionAddr :: (NodeInfo -> r -> IO (Maybe OnionRoute)) |
200 | -> (OnionMessage Encrypted,OnionDestination r) | 200 | -> (OnionMessage Encrypted,OnionDestination r) |
@@ -470,7 +470,7 @@ peelOnion :: Serialize (Addressed (Forwarding n t)) | |||
470 | -> Forwarding (S n) t | 470 | -> Forwarding (S n) t |
471 | -> Either String (Addressed (Forwarding n t)) | 471 | -> Either String (Addressed (Forwarding n t)) |
472 | peelOnion crypto nonce (Forwarding k fwd) = | 472 | peelOnion crypto nonce (Forwarding k fwd) = |
473 | fmap runIdentity $ uncomposed $ decryptMessage (dhtKey crypto) nonce (Right $ Assym k nonce fwd) | 473 | fmap runIdentity $ uncomposed $ decryptMessage (dhtKey crypto) nonce (Right $ Asymm k nonce fwd) |
474 | 474 | ||
475 | handleOnionResponse :: (KnownPeanoNat n, Sized (ReturnPath n), Serialize (ReturnPath n)) => proxy (S n) -> TransportCrypto -> SockAddr -> UDPTransport -> IO a -> OnionResponse (S n) -> IO a | 475 | handleOnionResponse :: (KnownPeanoNat n, Sized (ReturnPath n), Serialize (ReturnPath n)) => proxy (S n) -> TransportCrypto -> SockAddr -> UDPTransport -> IO a -> OnionResponse (S n) -> IO a |
476 | handleOnionResponse proxy crypto saddr udp kont (OnionResponse path msg) = do | 476 | handleOnionResponse proxy crypto saddr udp kont (OnionResponse path msg) = do |
@@ -499,13 +499,13 @@ instance S.Serialize AnnounceRequest where | |||
499 | get = AnnounceRequest <$> S.get <*> S.get <*> S.get | 499 | get = AnnounceRequest <$> S.get <*> S.get <*> S.get |
500 | put (AnnounceRequest p s k) = S.put (p,s,k) | 500 | put (AnnounceRequest p s k) = S.put (p,s,k) |
501 | 501 | ||
502 | getOnionRequest :: Sized msg => Get (Assym (Encrypted msg), ReturnPath N3) | 502 | getOnionRequest :: Sized msg => Get (Asymm (Encrypted msg), ReturnPath N3) |
503 | getOnionRequest = do | 503 | getOnionRequest = do |
504 | -- Assumes return path is constant size so that we can isolate | 504 | -- Assumes return path is constant size so that we can isolate |
505 | -- the variable-sized prefix. | 505 | -- the variable-sized prefix. |
506 | cnt <- remaining | 506 | cnt <- remaining |
507 | a <- isolate (case size :: Size (ReturnPath N3) of ConstSize n -> cnt - n) | 507 | a <- isolate (case size :: Size (ReturnPath N3) of ConstSize n -> cnt - n) |
508 | getAliasedAssym | 508 | getAliasedAsymm |
509 | path <- get | 509 | path <- get |
510 | return (a,path) | 510 | return (a,path) |
511 | 511 | ||
@@ -619,7 +619,7 @@ encrypt :: TransportCrypto -> OnionMessage Identity -> OnionDestination r -> IO | |||
619 | encrypt crypto msg rpath = do | 619 | encrypt crypto msg rpath = do |
620 | (skey,pkey) <- selectKey crypto msg rpath -- source key | 620 | (skey,pkey) <- selectKey crypto msg rpath -- source key |
621 | let okey = onionKey rpath -- destination key | 621 | let okey = onionKey rpath -- destination key |
622 | return ( transcode ( (. (runIdentity . either id assymData)) | 622 | return ( transcode ( (. (runIdentity . either id asymmData)) |
623 | . encryptMessage skey okey) | 623 | . encryptMessage skey okey) |
624 | msg | 624 | msg |
625 | , rpath) | 625 | , rpath) |
@@ -652,12 +652,12 @@ decryptMessage :: Serialize x => | |||
652 | (SecretKey,PublicKey) | 652 | (SecretKey,PublicKey) |
653 | -> Nonce24 | 653 | -> Nonce24 |
654 | -> Either (PublicKey, Encrypted x) | 654 | -> Either (PublicKey, Encrypted x) |
655 | (Assym (Encrypted x)) | 655 | (Asymm (Encrypted x)) |
656 | -> (Either String ∘ Identity) x | 656 | -> (Either String ∘ Identity) x |
657 | decryptMessage crypto n arg = plain $ ToxCrypto.decrypt secret e | 657 | decryptMessage crypto n arg = plain $ ToxCrypto.decrypt secret e |
658 | where | 658 | where |
659 | secret = computeSharedSecret (fst crypto) sender n | 659 | secret = computeSharedSecret (fst crypto) sender n |
660 | (sender,e) = either id (senderKey &&& assymData) arg | 660 | (sender,e) = either id (senderKey &&& asymmData) arg |
661 | plain = Composed . fmap Identity . (>>= decodePlain) | 661 | plain = Composed . fmap Identity . (>>= decodePlain) |
662 | 662 | ||
663 | 663 | ||
@@ -668,12 +668,12 @@ sequenceMessage (OnionToRoute pub a) = pure $ OnionToRoute pub a | |||
668 | sequenceMessage (OnionToRouteResponse a) = pure $ OnionToRouteResponse a | 668 | sequenceMessage (OnionToRouteResponse a) = pure $ OnionToRouteResponse a |
669 | -- sequenceMessage (OnionToRouteResponse a) = fmap OnionToRouteResponse $ sequenceA $ fmap uncomposed a | 669 | -- sequenceMessage (OnionToRouteResponse a) = fmap OnionToRouteResponse $ sequenceA $ fmap uncomposed a |
670 | 670 | ||
671 | transcode :: forall f g. (forall a. Serialize a => Nonce24 -> Either (f a) (Assym (f a)) -> g a) -> OnionMessage f -> OnionMessage g | 671 | transcode :: forall f g. (forall a. Serialize a => Nonce24 -> Either (f a) (Asymm (f a)) -> g a) -> OnionMessage f -> OnionMessage g |
672 | transcode f (OnionAnnounce a) = OnionAnnounce $ a { assymData = f (assymNonce a) (Right a) } | 672 | transcode f (OnionAnnounce a) = OnionAnnounce $ a { asymmData = f (asymmNonce a) (Right a) } |
673 | transcode f (OnionAnnounceResponse n8 n24 dta) = OnionAnnounceResponse n8 n24 $ f n24 $ Left dta | 673 | transcode f (OnionAnnounceResponse n8 n24 dta) = OnionAnnounceResponse n8 n24 $ f n24 $ Left dta |
674 | transcode f (OnionToRoute pub a) = OnionToRoute pub a | 674 | transcode f (OnionToRoute pub a) = OnionToRoute pub a |
675 | transcode f (OnionToRouteResponse a) = OnionToRouteResponse a | 675 | transcode f (OnionToRouteResponse a) = OnionToRouteResponse a |
676 | -- transcode f (OnionToRouteResponse a) = OnionToRouteResponse $ a { assymData = f (assymNonce a) (Right a) } | 676 | -- transcode f (OnionToRouteResponse a) = OnionToRouteResponse $ a { asymmData = f (asymmNonce a) (Right a) } |
677 | 677 | ||
678 | 678 | ||
679 | data OnionRoute = OnionRoute | 679 | data OnionRoute = OnionRoute |
@@ -738,14 +738,14 @@ instance Show Rendezvous where | |||
738 | parseDataToRoute | 738 | parseDataToRoute |
739 | :: TransportCrypto | 739 | :: TransportCrypto |
740 | -> (OnionMessage Encrypted,OnionDestination r) | 740 | -> (OnionMessage Encrypted,OnionDestination r) |
741 | -> Either (Assym (Encrypted DataToRoute),Rendezvous) (OnionMessage Encrypted, OnionDestination r) | 741 | -> Either (Asymm (Encrypted DataToRoute),Rendezvous) (OnionMessage Encrypted, OnionDestination r) |
742 | parseDataToRoute crypto (OnionToRouteResponse dta, od) | 742 | parseDataToRoute crypto (OnionToRouteResponse dta, od) |
743 | = Left ( dta | 743 | = Left ( dta |
744 | , Rendezvous (onionAliasPublic crypto) $ onionNodeInfo od ) | 744 | , Rendezvous (onionAliasPublic crypto) $ onionNodeInfo od ) |
745 | parseDataToRoute _ msg = Right msg | 745 | parseDataToRoute _ msg = Right msg |
746 | 746 | ||
747 | encodeDataToRoute :: TransportCrypto | 747 | encodeDataToRoute :: TransportCrypto |
748 | -> (Assym (Encrypted DataToRoute),Rendezvous) | 748 | -> (Asymm (Encrypted DataToRoute),Rendezvous) |
749 | -> Maybe (OnionMessage Encrypted,OnionDestination r) | 749 | -> Maybe (OnionMessage Encrypted,OnionDestination r) |
750 | encodeDataToRoute crypto (dta, Rendezvous pub ni) | 750 | encodeDataToRoute crypto (dta, Rendezvous pub ni) |
751 | = Just ( OnionToRoute pub -- Public key of destination node | 751 | = Just ( OnionToRoute pub -- Public key of destination node |
diff --git a/src/Network/Tox/Transport.hs b/src/Network/Tox/Transport.hs index d915561f..59c0cf6f 100644 --- a/src/Network/Tox/Transport.hs +++ b/src/Network/Tox/Transport.hs | |||
@@ -24,7 +24,7 @@ toxTransport :: | |||
24 | -> UDPTransport | 24 | -> UDPTransport |
25 | -> IO ( Transport String NodeInfo (DHTMessage Encrypted8) | 25 | -> IO ( Transport String NodeInfo (DHTMessage Encrypted8) |
26 | , Transport String (OnionDestination RouteId) (OnionMessage Encrypted) | 26 | , Transport String (OnionDestination RouteId) (OnionMessage Encrypted) |
27 | , Transport String Rendezvous (Assym (Encrypted DataToRoute)) | 27 | , Transport String Rendezvous (Asymm (Encrypted DataToRoute)) |
28 | , Transport String SockAddr NetCrypto ) | 28 | , Transport String SockAddr NetCrypto ) |
29 | toxTransport crypto orouter closeLookup udp = do | 29 | toxTransport crypto orouter closeLookup udp = do |
30 | (dht,udp1) <- partitionTransport parseDHTAddr (Just . encodeDHTAddr) $ forwardOnions crypto udp | 30 | (dht,udp1) <- partitionTransport parseDHTAddr (Just . encodeDHTAddr) $ forwardOnions crypto udp |
@@ -6,21 +6,13 @@ Remove (without replacement) stale routing nodes at some point. | |||
6 | 6 | ||
7 | Debug why disabled-6 does not get peer/key storage. | 7 | Debug why disabled-6 does not get peer/key storage. |
8 | 8 | ||
9 | Rename "keys" command to "toxids" | ||
10 | |||
11 | Give different networks a different minimum count to terminate bootstrap. Imperically, | 9 | Give different networks a different minimum count to terminate bootstrap. Imperically, |
12 | tox4: 6 buckets, tox6: 3 buckets | 10 | tox4: 6 buckets, tox6: 3 buckets |
13 | 11 | ||
14 | handle exception: dhtd: Network.Socket.sendTo: does not exist (Network is unreachable | 12 | handle exception: dhtd: Network.Socket.sendTo: does not exist (Network is unreachable |
15 | 13 | ||
16 | tox: rename assym to asymm (short for asymmetric) | ||
17 | |||
18 | tox: fallback to https://nodes.tox.chat/json | 14 | tox: fallback to https://nodes.tox.chat/json |
19 | 15 | ||
20 | tox: key search | ||
21 | |||
22 | tox: announce key request | ||
23 | |||
24 | tox: bootstrap motd query | 16 | tox: bootstrap motd query |
25 | 17 | ||
26 | tox: nat ping | 18 | tox: nat ping |
@@ -33,8 +25,6 @@ tox: Expire old Tox keys. | |||
33 | 25 | ||
34 | tox: Chat support. | 26 | tox: Chat support. |
35 | 27 | ||
36 | bt: announce peer request | ||
37 | |||
38 | bt: Collect PeerStore garbage: "Note that you should call .put() every hour for | 28 | bt: Collect PeerStore garbage: "Note that you should call .put() every hour for |
39 | content that you want to keep alive, since nodes may discard data nodes | 29 | content that you want to keep alive, since nodes may discard data nodes |
40 | older than 2 hours." (source: https://www.npmjs.com/package/bittorrent-dht) | 30 | older than 2 hours." (source: https://www.npmjs.com/package/bittorrent-dht) |