diff options
Diffstat (limited to 'src/Network/Tox')
-rw-r--r-- | src/Network/Tox/Session.hs | 138 |
1 files changed, 138 insertions, 0 deletions
diff --git a/src/Network/Tox/Session.hs b/src/Network/Tox/Session.hs new file mode 100644 index 00000000..a52e9478 --- /dev/null +++ b/src/Network/Tox/Session.hs | |||
@@ -0,0 +1,138 @@ | |||
1 | {-# LANGUAGE TupleSections #-} | ||
2 | module Network.Tox.Session where | ||
3 | |||
4 | import Control.Concurrent.STM | ||
5 | import Control.Monad | ||
6 | import Data.Functor.Identity | ||
7 | import Data.Word | ||
8 | import Network.Socket | ||
9 | |||
10 | import Crypto.Tox | ||
11 | import Data.PacketBuffer (PacketInboundEvent (..)) | ||
12 | import Data.Tox.Message | ||
13 | import Network.Lossless | ||
14 | import Network.QueryResponse | ||
15 | import Network.SessionTransports | ||
16 | import Network.Tox.Crypto.Transport | ||
17 | import Network.Tox.DHT.Transport (Cookie) | ||
18 | import Network.Tox.Handshake | ||
19 | |||
20 | type SessionKey = SecretKey | ||
21 | |||
22 | data SessionParams = SessionParams | ||
23 | { spCrypto :: TransportCrypto | ||
24 | , spSessions :: Sessions (CryptoPacket Encrypted) | ||
25 | , spGetSentHandshake :: SecretKey -> SockAddr | ||
26 | -> Cookie Identity | ||
27 | -> Cookie Encrypted | ||
28 | -> IO (Maybe (SessionKey, HandshakeData)) | ||
29 | , spOnNewSession :: Session -> IO () | ||
30 | } | ||
31 | |||
32 | data Session = Session | ||
33 | { sOurKey :: SecretKey | ||
34 | , sTheirAddr :: SockAddr | ||
35 | , sSentHandshake :: HandshakeData | ||
36 | , sReceivedHandshake :: Handshake Identity | ||
37 | , sResendPackets :: [Word32] -> IO () | ||
38 | -- ^ If they request that we re-send certain packets, this method is how | ||
39 | -- that is accomplished. | ||
40 | , sMissingInbound :: IO ([Word32],Word32) | ||
41 | -- ^ This list of sequence numbers should be periodically polled and if | ||
42 | -- it is not empty, we should request they re-send these packets. For | ||
43 | -- convenience, a lower bound for the numbers in the list is also | ||
44 | -- returned. Suggested polling interval: a few seconds. | ||
45 | , sTransport :: Transport String () CryptoMessage | ||
46 | } | ||
47 | |||
48 | handshakeH :: SessionParams | ||
49 | -> SockAddr | ||
50 | -> Handshake Encrypted | ||
51 | -> IO (Maybe a) | ||
52 | handshakeH sp saddr handshake = do | ||
53 | decryptHandshake (spCrypto sp) handshake | ||
54 | >>= either (\err -> return ()) | ||
55 | (uncurry $ plainHandshakeH sp saddr) | ||
56 | return Nothing | ||
57 | |||
58 | |||
59 | plainHandshakeH :: SessionParams | ||
60 | -> SockAddr | ||
61 | -> SecretKey | ||
62 | -> Handshake Identity | ||
63 | -> IO () | ||
64 | plainHandshakeH sp saddr skey handshake = do | ||
65 | let hd = runIdentity $ handshakeData handshake | ||
66 | sent <- spGetSentHandshake sp skey saddr (handshakeCookie handshake) (otherCookie hd) | ||
67 | forM_ sent $ \(hd_skey,hd_sent) -> do | ||
68 | sk <- SessionKeys (spCrypto sp) | ||
69 | hd_skey | ||
70 | (sessionKey hd) | ||
71 | <$> atomically (newTVar $ baseNonce hd) | ||
72 | <*> atomically (newTVar $ baseNonce hd_sent) | ||
73 | m <- newSession (spSessions sp) (\() p -> return p) (decryptPacket sk) saddr | ||
74 | forM_ m $ \t -> do | ||
75 | (t2,resend,getMissing) | ||
76 | <- lossless (\cp a -> return $ fmap (,a) $ checkLossless $ runIdentity $ pktData cp) | ||
77 | (\seqno p _ -> encryptPacket sk $ bookKeeping seqno p) | ||
78 | () | ||
79 | t | ||
80 | let _ = t :: TransportA String () (CryptoPacket Identity) (CryptoPacket Encrypted) | ||
81 | _ = t2 :: Transport String () CryptoMessage | ||
82 | spOnNewSession sp Session | ||
83 | { sOurKey = skey | ||
84 | , sTheirAddr = saddr | ||
85 | , sSentHandshake = hd_sent | ||
86 | , sReceivedHandshake = handshake | ||
87 | , sResendPackets = resend | ||
88 | , sMissingInbound = getMissing | ||
89 | , sTransport = t2 | ||
90 | } | ||
91 | return () | ||
92 | |||
93 | decryptPacket :: SessionKeys -> SockAddr -> CryptoPacket Encrypted -> IO (Maybe (CryptoPacket Identity, ())) | ||
94 | decryptPacket sk saddr (CryptoPacket n16 ciphered) = do | ||
95 | (n,δ) <- atomically $ do | ||
96 | n <- readTVar (skNonceIncoming sk) | ||
97 | let δ = n16 - nonce24ToWord16 n | ||
98 | return ( n `addtoNonce24` fromIntegral δ, δ ) | ||
99 | secret <- lookupSharedSecret (skCrypto sk) (skMe sk) (skThem sk) n | ||
100 | case decodePlain =<< decrypt secret ciphered of | ||
101 | Left e -> return Nothing | ||
102 | Right x -> do | ||
103 | when ( δ > 43690 ) | ||
104 | $ atomically $ writeTVar (skNonceIncoming sk) (n `addtoNonce24` 21845) | ||
105 | return $ Just ( CryptoPacket n16 (pure x), () ) | ||
106 | |||
107 | encryptPacket :: SessionKeys -> CryptoData -> IO (CryptoPacket Encrypted) | ||
108 | encryptPacket sk plain = do | ||
109 | n24 <- atomically $ do | ||
110 | n24 <- readTVar (skNonceOutgoing sk) | ||
111 | modifyTVar' (skNonceOutgoing sk) incrementNonce24 | ||
112 | return n24 | ||
113 | secret <- lookupSharedSecret (skCrypto sk) (skMe sk) (skThem sk) n24 | ||
114 | let ciphered = encrypt secret $ encodePlain $ plain | ||
115 | return $ CryptoPacket (nonce24ToWord16 n24) ciphered | ||
116 | |||
117 | data SessionKeys = SessionKeys | ||
118 | { skCrypto :: TransportCrypto | ||
119 | , skMe :: SecretKey | ||
120 | , skThem :: PublicKey | ||
121 | , skNonceIncoming :: TVar Nonce24 -- +21845 when a threshold is reached. | ||
122 | , skNonceOutgoing :: TVar Nonce24 -- +1 on every packet | ||
123 | } | ||
124 | |||
125 | bookKeeping :: SequenceInfo -> CryptoMessage -> CryptoData | ||
126 | bookKeeping (SequenceInfo seqno ack) m = CryptoData | ||
127 | { bufferStart = seqno :: Word32 | ||
128 | , bufferEnd = ack :: Word32 | ||
129 | , bufferData = m | ||
130 | } | ||
131 | |||
132 | checkLossless :: CryptoData -> PacketInboundEvent CryptoMessage | ||
133 | checkLossless CryptoData{ bufferStart = ack | ||
134 | , bufferEnd = no | ||
135 | , bufferData = x } = tag no x ack | ||
136 | where | ||
137 | tag = case lossyness (msgID x) of Lossy -> PacketReceivedLossy | ||
138 | _ -> PacketReceived | ||