diff options
author | joe <joe@jerkface.net> | 2017-10-19 05:23:41 -0400 |
---|---|---|
committer | joe <joe@jerkface.net> | 2017-10-19 05:23:41 -0400 |
commit | 27dfb777280028b5ca6dad44f481783d8bab602e (patch) | |
tree | 691f915e873b61ad25a5984b75bbe57a9fdeead2 /src | |
parent | 3b8c8d74db95fa8dc345a73101d2c1921655c70d (diff) |
Encrypt Tox's store-key announcement with the key being stored.
Diffstat (limited to 'src')
-rw-r--r-- | src/Crypto/Tox.hs | 1 | ||||
-rw-r--r-- | src/Network/QueryResponse.hs | 32 | ||||
-rw-r--r-- | src/Network/Tox.hs | 4 | ||||
-rw-r--r-- | src/Network/Tox/Onion/Transport.hs | 33 |
4 files changed, 53 insertions, 17 deletions
diff --git a/src/Crypto/Tox.hs b/src/Crypto/Tox.hs index b86a5395..645ca53e 100644 --- a/src/Crypto/Tox.hs +++ b/src/Crypto/Tox.hs | |||
@@ -366,6 +366,7 @@ data TransportCrypto = TransportCrypto | |||
366 | , rendezvousPublic :: PublicKey | 366 | , rendezvousPublic :: PublicKey |
367 | , transportSymmetric :: STM SymmetricKey | 367 | , transportSymmetric :: STM SymmetricKey |
368 | , transportNewNonce :: STM Nonce24 | 368 | , transportNewNonce :: STM Nonce24 |
369 | , userKeys :: TVar [(SecretKey,PublicKey)] | ||
369 | } | 370 | } |
370 | 371 | ||
371 | getPublicKey :: S.Get PublicKey | 372 | getPublicKey :: S.Get PublicKey |
diff --git a/src/Network/QueryResponse.hs b/src/Network/QueryResponse.hs index 27c89674..1901e164 100644 --- a/src/Network/QueryResponse.hs +++ b/src/Network/QueryResponse.hs | |||
@@ -53,24 +53,44 @@ data Transport err addr x = Transport | |||
53 | -- packet representations. It could be used to change UDP 'ByteString's into | 53 | -- packet representations. It could be used to change UDP 'ByteString's into |
54 | -- bencoded syntax trees or to add an encryption layer in which addresses have | 54 | -- bencoded syntax trees or to add an encryption layer in which addresses have |
55 | -- associated public keys. | 55 | -- associated public keys. |
56 | layerTransport :: | 56 | layerTransportM :: |
57 | (x -> addr -> Either err (x', addr')) | 57 | (x -> addr -> IO (Either err (x', addr'))) |
58 | -- ^ Function that attempts to transform a low-level address/packet | 58 | -- ^ Function that attempts to transform a low-level address/packet |
59 | -- pair into a higher level representation. | 59 | -- pair into a higher level representation. |
60 | -> (x' -> addr' -> (x, addr)) | 60 | -> (x' -> addr' -> IO (x, addr)) |
61 | -- ^ Function to encode a high-level address/packet into a lower level | 61 | -- ^ Function to encode a high-level address/packet into a lower level |
62 | -- representation. | 62 | -- representation. |
63 | -> Transport err addr x | 63 | -> Transport err addr x |
64 | -- ^ The low-level transport to be transformed. | 64 | -- ^ The low-level transport to be transformed. |
65 | -> Transport err addr' x' | 65 | -> Transport err addr' x' |
66 | layerTransport parse encode tr = | 66 | layerTransportM parse encode tr = |
67 | tr { awaitMessage = \kont -> | 67 | tr { awaitMessage = \kont -> |
68 | awaitMessage tr $ \m -> kont $ fmap (>>= uncurry parse) m | 68 | awaitMessage tr $ \m -> mapM (mapM $ uncurry parse) m >>= kont . fmap join |
69 | , sendMessage = \addr' msg' -> do | 69 | , sendMessage = \addr' msg' -> do |
70 | let (msg,addr) = encode msg' addr' | 70 | (msg,addr) <- encode msg' addr' |
71 | sendMessage tr addr msg | 71 | sendMessage tr addr msg |
72 | } | 72 | } |
73 | 73 | ||
74 | |||
75 | -- | This function modifies a 'Transport' to use higher-level addresses and | ||
76 | -- packet representations. It could be used to change UDP 'ByteString's into | ||
77 | -- bencoded syntax trees or to add an encryption layer in which addresses have | ||
78 | -- associated public keys. | ||
79 | layerTransport :: | ||
80 | (x -> addr -> Either err (x', addr')) | ||
81 | -- ^ Function that attempts to transform a low-level address/packet | ||
82 | -- pair into a higher level representation. | ||
83 | -> (x' -> addr' -> (x, addr)) | ||
84 | -- ^ Function to encode a high-level address/packet into a lower level | ||
85 | -- representation. | ||
86 | -> Transport err addr x | ||
87 | -- ^ The low-level transport to be transformed. | ||
88 | -> Transport err addr' x' | ||
89 | layerTransport parse encode tr = | ||
90 | layerTransportM (\x addr -> return $ parse x addr) | ||
91 | (\x' addr' -> return $ encode x' addr') | ||
92 | tr | ||
93 | |||
74 | -- | Paritions a 'Transport' into two higher-level transports. Note: An 'MVar' | 94 | -- | Paritions a 'Transport' into two higher-level transports. Note: An 'MVar' |
75 | -- is used to share the same underlying socket, so be sure to fork a thread for | 95 | -- is used to share the same underlying socket, so be sure to fork a thread for |
76 | -- both returned 'Transport's to avoid hanging. | 96 | -- both returned 'Transport's to avoid hanging. |
diff --git a/src/Network/Tox.hs b/src/Network/Tox.hs index 98e9691b..f41b0f25 100644 --- a/src/Network/Tox.hs +++ b/src/Network/Tox.hs | |||
@@ -105,6 +105,7 @@ newCrypto = do | |||
105 | let pubkey = toPublic secret | 105 | let pubkey = toPublic secret |
106 | aliaspub = toPublic alias | 106 | aliaspub = toPublic alias |
107 | raliaspub = toPublic ralias | 107 | raliaspub = toPublic ralias |
108 | ukeys <- atomically $ newTVar [] | ||
108 | (symkey, drg) <- do | 109 | (symkey, drg) <- do |
109 | drg0 <- getSystemDRG | 110 | drg0 <- getSystemDRG |
110 | return $ randomBytesGenerate 32 drg0 :: IO (ByteString, SystemDRG) | 111 | return $ randomBytesGenerate 32 drg0 :: IO (ByteString, SystemDRG) |
@@ -125,6 +126,7 @@ newCrypto = do | |||
125 | let (nonce, drg2) = withDRG drg1 (Nonce24 <$> getRandomBytes 24) | 126 | let (nonce, drg2) = withDRG drg1 (Nonce24 <$> getRandomBytes 24) |
126 | writeTVar noncevar drg2 | 127 | writeTVar noncevar drg2 |
127 | return nonce | 128 | return nonce |
129 | , userKeys = ukeys | ||
128 | } | 130 | } |
129 | 131 | ||
130 | updateIP :: TVar (R.BucketList NodeInfo) -> SockAddr -> STM () | 132 | updateIP :: TVar (R.BucketList NodeInfo) -> SockAddr -> STM () |
@@ -266,7 +268,7 @@ newTox keydb addr = do | |||
266 | nil <- nullSessionTokens | 268 | nil <- nullSessionTokens |
267 | atomically $ newTVar nil { maxInterval = 20 } -- 20 second timeout on announce ping-ids. | 269 | atomically $ newTVar nil { maxInterval = 20 } -- 20 second timeout on announce ping-ids. |
268 | oniondrg <- drgNew | 270 | oniondrg <- drgNew |
269 | let onionnet = layerTransport (Onion.decrypt crypto) (Onion.encrypt crypto) onioncrypt | 271 | let onionnet = layerTransportM (Onion.decrypt crypto) (Onion.encrypt crypto) onioncrypt |
270 | onionclient <- newClient oniondrg onionnet Onion.classify | 272 | onionclient <- newClient oniondrg onionnet Onion.classify |
271 | (getOnionAlias crypto $ R.thisNode <$> readTVar (DHT.routing4 routing)) | 273 | (getOnionAlias crypto $ R.thisNode <$> readTVar (DHT.routing4 routing)) |
272 | (Onion.handlers onionnet routing toks keydb) | 274 | (Onion.handlers onionnet routing toks keydb) |
diff --git a/src/Network/Tox/Onion/Transport.hs b/src/Network/Tox/Onion/Transport.hs index 3e3596a6..34ba23f6 100644 --- a/src/Network/Tox/Onion/Transport.hs +++ b/src/Network/Tox/Onion/Transport.hs | |||
@@ -598,18 +598,31 @@ instance Sized OnionData where | |||
598 | ConstSize n -> n | 598 | ConstSize n -> n |
599 | VarSize f -> f req | 599 | VarSize f -> f req |
600 | 600 | ||
601 | encrypt :: TransportCrypto -> OnionMessage Identity -> OnionDestination r -> (OnionMessage Encrypted, OnionDestination r) | 601 | |
602 | encrypt crypto msg rpath = ( transcode ( (. (runIdentity . either id assymData)) | 602 | selectKey :: TransportCrypto -> OnionMessage Identity -> OnionDestination r -> IO (SecretKey, PublicKey) |
603 | . encryptMessage skey okey) | 603 | selectKey crypto |
604 | msg | 604 | (OnionAnnounce a@Assym { assymData = Identity (AnnounceRequest _ pkey akey, _) }) |
605 | , rpath) | 605 | rpath |
606 | where | 606 | | (akey /= zeroID) = atomically $ do |
607 | skey = fst $ aliasKey crypto rpath | 607 | ks <- filter (\(sk,pk) -> pk == id2key pkey) |
608 | <$> readTVar (userKeys crypto) | ||
609 | maybe (return $ aliasKey crypto rpath) | ||
610 | return | ||
611 | (listToMaybe ks) | ||
612 | selectKey crypto msg rpath = return $ aliasKey crypto rpath | ||
613 | |||
614 | encrypt :: TransportCrypto -> OnionMessage Identity -> OnionDestination r -> IO (OnionMessage Encrypted, OnionDestination r) | ||
615 | encrypt crypto msg rpath = do | ||
616 | (skey,pkey) <- selectKey crypto msg rpath | ||
617 | let skey = fst $ aliasKey crypto rpath | ||
608 | 618 | ||
609 | -- The OnionToMe case shouldn't happen, but we'll use our own public | 619 | -- The OnionToMe case shouldn't happen, but we'll use our own public |
610 | -- key in this situation. | 620 | -- key in this situation. |
611 | okey = fromMaybe (transportPublic crypto) $ onionKey rpath | 621 | okey = fromMaybe (transportPublic crypto) $ onionKey rpath |
612 | 622 | return ( transcode ( (. (runIdentity . either id assymData)) | |
623 | . encryptMessage skey okey) | ||
624 | msg | ||
625 | , rpath) | ||
613 | 626 | ||
614 | encryptMessage :: Serialize a => | 627 | encryptMessage :: Serialize a => |
615 | SecretKey -> PublicKey -> Nonce24 -> a -> Encrypted a | 628 | SecretKey -> PublicKey -> Nonce24 -> a -> Encrypted a |
@@ -618,8 +631,8 @@ encryptMessage skey destKey n a = ToxCrypto.encrypt secret plain | |||
618 | secret = computeSharedSecret skey destKey n | 631 | secret = computeSharedSecret skey destKey n |
619 | plain = encodePlain a | 632 | plain = encodePlain a |
620 | 633 | ||
621 | decrypt :: TransportCrypto -> OnionMessage Encrypted -> OnionDestination r -> Either String (OnionMessage Identity, OnionDestination r) | 634 | decrypt :: TransportCrypto -> OnionMessage Encrypted -> OnionDestination r -> IO (Either String (OnionMessage Identity, OnionDestination r)) |
622 | decrypt crypto msg addr = do | 635 | decrypt crypto msg addr = return $ do |
623 | msg <- sequenceMessage $ transcode (\n -> decryptMessage (aliasKey crypto addr) n . left (senderkey addr)) msg | 636 | msg <- sequenceMessage $ transcode (\n -> decryptMessage (aliasKey crypto addr) n . left (senderkey addr)) msg |
624 | Right (msg, addr) | 637 | Right (msg, addr) |
625 | 638 | ||