summaryrefslogtreecommitdiff
path: root/src/Network/Tox
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network/Tox')
-rw-r--r--src/Network/Tox/TCP.hs44
1 files changed, 31 insertions, 13 deletions
diff --git a/src/Network/Tox/TCP.hs b/src/Network/Tox/TCP.hs
index 5c6456f6..353b5ea3 100644
--- a/src/Network/Tox/TCP.hs
+++ b/src/Network/Tox/TCP.hs
@@ -22,6 +22,7 @@ import Data.Word
22import qualified Data.Vector as Vector 22import qualified Data.Vector as Vector
23import Network.Socket (SockAddr(..)) 23import Network.Socket (SockAddr(..))
24import qualified Text.ParserCombinators.ReadP as RP 24import qualified Text.ParserCombinators.ReadP as RP
25import System.IO.Error
25 26
26import Crypto.Tox 27import Crypto.Tox
27import Data.ByteString (hPut,hGet,ByteString,length) 28import Data.ByteString (hPut,hGet,ByteString,length)
@@ -95,7 +96,7 @@ nodeAddr ni = setPort (tcpPort ni) $ UDP.nodeAddr $ udpNodeInfo ni
95nodeIP :: NodeInfo -> IP 96nodeIP :: NodeInfo -> IP
96nodeIP ni = UDP.nodeIP $ udpNodeInfo ni 97nodeIP ni = UDP.nodeIP $ udpNodeInfo ni
97 98
98tcpStream :: (Serialize y, Sized y, Serialize x, Sized x) => 99tcpStream :: (Show y, Show x, Serialize y, Sized y, Serialize x, Sized x) =>
99 TransportCrypto -> StreamHandshake NodeInfo x y 100 TransportCrypto -> StreamHandshake NodeInfo x y
100tcpStream crypto = StreamHandshake 101tcpStream crypto = StreamHandshake
101 { streamHello = \addr h -> do 102 { streamHello = \addr h -> do
@@ -112,28 +113,45 @@ tcpStream crypto = StreamHandshake
112 } 113 }
113 } 114 }
114 noncef <- lookupNonceFunction crypto (transportSecret crypto) (UDP.id2key $ nodeId addr) 115 noncef <- lookupNonceFunction crypto (transportSecret crypto) (UDP.id2key $ nodeId addr)
116 dput XTCP $ "TCP:" ++ show addr ++ " <-- " ++ show hello
115 hPut h $ encode $ encryptPayload (noncef $ helloNonce hello) hello 117 hPut h $ encode $ encryptPayload (noncef $ helloNonce hello) hello
116 welcomeE <- withSize $ fmap decode . hGet h . constSize 118 welcomeE <- withSize $ fmap decode . hGet h . constSize
117 let Right welcome = welcomeE >>= \w -> decryptPayload (noncef $ welcomeNonce w) w 119 let Right welcome = welcomeE >>= \w -> decryptPayload (noncef $ welcomeNonce w) w
120 dput XTCP $ "TCP:" ++ show addr ++ " --> " ++ show welcome
118 noncef' <- lookupNonceFunction crypto skey (sessionPublicKey $ runIdentity $ welcomeData welcome) 121 noncef' <- lookupNonceFunction crypto skey (sessionPublicKey $ runIdentity $ welcomeData welcome)
119 nsend <- newMVar (sessionBaseNonce $ runIdentity $ helloData hello) 122 nsend <- newMVar (sessionBaseNonce $ runIdentity $ helloData hello)
120 nread <- newMVar (sessionBaseNonce $ runIdentity $ welcomeData welcome) 123 nread <- newMVar (sessionBaseNonce $ runIdentity $ welcomeData welcome)
121 let them = sessionPublicKey $ runIdentity $ welcomeData welcome 124 let them = sessionPublicKey $ runIdentity $ welcomeData welcome
122 return SessionProtocol 125 return SessionProtocol
123 { streamGoodbye = return () -- No goodbye packet? Seems rude. 126 { streamGoodbye = do
124 , streamDecode = do 127 dput XTCP $ "Closing " ++ show addr
125 decode <$> hGet h 2 >>= \case 128 return () -- No goodbye packet? Seems rude.
126 Left _ -> return Nothing 129 , streamDecode =
127 Right len -> do 130 let go = decode <$> hGet h 2 >>= \case
128 decode <$> hGet h (fromIntegral (len :: Word16)) >>= \case 131 Left e -> do
129 Left _ -> return Nothing 132 dput XTCP $ "TCP: Failed to get length: " ++ e
130 Right x -> do 133 return Nothing
131 n24 <- takeMVar nread 134 Right len -> do
132 let r = decrypt (noncef' n24) x >>= decodePlain 135 decode <$> hGet h (fromIntegral (len :: Word16)) >>= \case
133 putMVar nread (incrementNonce24 n24) 136 Left e -> do
134 return $ either (const Nothing) Just r 137 dput XTCP $ "TCP: Failed to decode packet."
138 return Nothing
139 Right x -> do
140 n24 <- takeMVar nread
141 let r = decrypt (noncef' n24) x >>= decodePlain
142 putMVar nread (incrementNonce24 n24)
143 either (dput XTCP)
144 (\x' -> do
145 dput XTCP $ "TCP:" ++ show addr ++ " --> " ++ show x'
146 return ())
147 r
148 return $ either (const Nothing) Just r
149 in go `catchIOError` \e -> do
150 dput XTCP $ "TCP exception: " ++ show e
151 return Nothing
135 , streamEncode = \y -> do 152 , streamEncode = \y -> do
136 n24 <- takeMVar nsend 153 n24 <- takeMVar nsend
154 dput XTCP $ "TCP:" ++ show addr ++ " <-- " ++ show y
137 let bs = encode $ encrypt (noncef' n24) $ encodePlain y 155 let bs = encode $ encrypt (noncef' n24) $ encodePlain y
138 hPut h $ encode (fromIntegral $ Data.ByteString.length bs :: Word16) 156 hPut h $ encode (fromIntegral $ Data.ByteString.length bs :: Word16)
139 <> bs 157 <> bs