summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Network/Tox/Session.hs75
1 files changed, 58 insertions, 17 deletions
diff --git a/src/Network/Tox/Session.hs b/src/Network/Tox/Session.hs
index 7b84ba80..e8be4d01 100644
--- a/src/Network/Tox/Session.hs
+++ b/src/Network/Tox/Session.hs
@@ -1,5 +1,11 @@
1-- | This module implements the lossless Tox session protocol.
1{-# LANGUAGE TupleSections #-} 2{-# LANGUAGE TupleSections #-}
2module Network.Tox.Session where 3module Network.Tox.Session
4 ( SessionParams(..)
5 , SessionKey
6 , Session(..)
7 , handshakeH
8 ) where
3 9
4import Control.Concurrent.STM 10import Control.Concurrent.STM
5import Control.Monad 11import Control.Monad
@@ -18,35 +24,64 @@ import Network.Tox.Crypto.Transport
18import Network.Tox.DHT.Transport (Cookie,key2id) 24import Network.Tox.DHT.Transport (Cookie,key2id)
19import Network.Tox.Handshake 25import Network.Tox.Handshake
20 26
27-- | Alias for 'SecretKey' to document that it is used as the temporary Tox
28-- session key corresponding to the 'PublicKey' we sent in the handshake.
21type SessionKey = SecretKey 29type SessionKey = SecretKey
22 30
31-- | These inputs to 'handshakeH' indicate how to respond to handshakes, how to
32-- assign packets to sessions, and what to do with established sessions after
33-- they are made lossless by queuing packets and appending sequence numbers.
23data SessionParams = SessionParams 34data SessionParams = SessionParams
24 { spCrypto :: TransportCrypto 35 { -- | The database of secret keys necessary to encrypt handshake packets.
36 spCrypto :: TransportCrypto
37 -- | This is used to create sessions and dispatch packets to them.
25 , spSessions :: Sessions (CryptoPacket Encrypted) 38 , spSessions :: Sessions (CryptoPacket Encrypted)
39 -- | This method returns the session information corresponding to the
40 -- cookie pair for the remote address. If no handshake was sent, this
41 -- should send one immediately. It should return 'Nothing' if anything
42 -- goes wrong.
26 , spGetSentHandshake :: SecretKey -> SockAddr 43 , spGetSentHandshake :: SecretKey -> SockAddr
27 -> Cookie Identity 44 -> Cookie Identity
28 -> Cookie Encrypted 45 -> Cookie Encrypted
29 -> IO (Maybe (SessionKey, HandshakeData)) 46 -> IO (Maybe (SessionKey, HandshakeData))
47 -- | This method is invoked on each new session and is responsible for
48 -- launching any threads necessary to keep the session alive.
30 , spOnNewSession :: Session -> IO () 49 , spOnNewSession :: Session -> IO ()
31 } 50 }
32 51
52-- | After a session is established, this information is given to the
53-- 'spOnNewSession' callback.
33data Session = Session 54data Session = Session
34 { sOurKey :: SecretKey 55 { -- | This is the secret user (toxid) key that corresponds to the
56 -- local-end of this session.
57 sOurKey :: SecretKey
58 -- | The remote address for this session. (Not unique, see 'sSessionID').
35 , sTheirAddr :: SockAddr 59 , sTheirAddr :: SockAddr
60 -- | The information we sent in the handshake for this session.
36 , sSentHandshake :: HandshakeData 61 , sSentHandshake :: HandshakeData
62 -- | The information we received in a handshake for this session.
37 , sReceivedHandshake :: Handshake Identity 63 , sReceivedHandshake :: Handshake Identity
64 -- | This method can be used to trigger packets to be re-sent given a
65 -- list of their sequence numbers. It should be used when the remote end
66 -- indicates they lost packets.
38 , sResendPackets :: [Word32] -> IO () 67 , sResendPackets :: [Word32] -> IO ()
39 -- ^ If they request that we re-send certain packets, this method is how 68 -- | This list of sequence numbers should be periodically polled and if
40 -- that is accomplished.
41 , sMissingInbound :: IO ([Word32],Word32)
42 -- ^ This list of sequence numbers should be periodically polled and if
43 -- it is not empty, we should request they re-send these packets. For 69 -- it is not empty, we should request they re-send these packets. For
44 -- convenience, a lower bound for the numbers in the list is also 70 -- convenience, a lower bound for the numbers in the list is also
45 -- returned. Suggested polling interval: a few seconds. 71 -- returned. Suggested polling interval: a few seconds.
72 , sMissingInbound :: IO ([Word32],Word32)
73 -- | A lossless transport for sending and receiving packets in this
74 -- session. It is up to the caller to spawn the await-loop to handle
75 -- inbound packets.
46 , sTransport :: Transport String () CryptoMessage 76 , sTransport :: Transport String () CryptoMessage
77 -- | A unique small integer that identifies this session for as long as
78 -- it is established.
47 , sSessionID :: Int 79 , sSessionID :: Int
48 } 80 }
49 81
82-- | Call this whenever a new handshake arrives so that a session is
83-- negotiated. It always returns Nothing which makes it convenient to use with
84-- 'Network.QueryResponse.addHandler'.
50handshakeH :: SessionParams 85handshakeH :: SessionParams
51 -> SockAddr 86 -> SockAddr
52 -> Handshake Encrypted 87 -> Handshake Encrypted
@@ -101,6 +136,18 @@ plainHandshakeH sp saddr skey handshake = do
101 } 136 }
102 return () 137 return ()
103 138
139
140-- | The per-session nonce and key state maintained by 'decryptPacket' and
141-- 'encryptPacket'.
142data SessionKeys = SessionKeys
143 { skCrypto :: TransportCrypto -- ^ Cache of shared-secrets.
144 , skMe :: SessionKey -- ^ My session key
145 , skThem :: PublicKey -- ^ Their session key
146 , skNonceIncoming :: TVar Nonce24 -- ^ +21845 when a threshold is reached.
147 , skNonceOutgoing :: TVar Nonce24 -- ^ +1 on every packet
148 }
149
150-- | Decrypt an inbound session packet and update the nonce for the next one.
104decryptPacket :: SessionKeys -> SockAddr -> CryptoPacket Encrypted -> IO (Maybe (CryptoPacket Identity, ())) 151decryptPacket :: SessionKeys -> SockAddr -> CryptoPacket Encrypted -> IO (Maybe (CryptoPacket Identity, ()))
105decryptPacket sk saddr (CryptoPacket n16 ciphered) = do 152decryptPacket sk saddr (CryptoPacket n16 ciphered) = do
106 (n24,δ) <- atomically $ do 153 (n24,δ) <- atomically $ do
@@ -121,6 +168,7 @@ decryptPacket sk saddr (CryptoPacket n16 ciphered) = do
121 168
122 return $ Just ( CryptoPacket n16 (pure x), () ) 169 return $ Just ( CryptoPacket n16 (pure x), () )
123 170
171-- | Encrypt an outbound session packet and update the nonce for the next one.
124encryptPacket :: SessionKeys -> CryptoData -> IO (CryptoPacket Encrypted) 172encryptPacket :: SessionKeys -> CryptoData -> IO (CryptoPacket Encrypted)
125encryptPacket sk plain = do 173encryptPacket sk plain = do
126 n24 <- atomically $ do 174 n24 <- atomically $ do
@@ -136,15 +184,9 @@ encryptPacket sk plain = do
136 184
137 return $ CryptoPacket (nonce24ToWord16 n24) ciphered 185 return $ CryptoPacket (nonce24ToWord16 n24) ciphered
138 186
139data SessionKeys = SessionKeys
140 { skCrypto :: TransportCrypto
141 , skMe :: SecretKey -- My session key
142 , skThem :: PublicKey -- Their session key
143 , skNonceIncoming :: TVar Nonce24 -- +21845 when a threshold is reached.
144 , skNonceOutgoing :: TVar Nonce24 -- +1 on every packet
145 }
146
147 187
188-- | Add sequence information to an outbound packet.
189--
148-- From spec.md: 190-- From spec.md:
149-- 191--
150-- Data in the encrypted packets: 192-- Data in the encrypted packets:
@@ -152,8 +194,6 @@ data SessionKeys = SessionKeys
152-- [our recvbuffers buffer_start, (highest packet number handled + 1), (big endian)] 194-- [our recvbuffers buffer_start, (highest packet number handled + 1), (big endian)]
153-- [uint32_t packet number if lossless, sendbuffer buffer_end if lossy, (big endian)] 195-- [uint32_t packet number if lossless, sendbuffer buffer_end if lossy, (big endian)]
154-- [data] 196-- [data]
155
156
157bookKeeping :: SequenceInfo -> CryptoMessage -> CryptoData 197bookKeeping :: SequenceInfo -> CryptoMessage -> CryptoData
158bookKeeping (SequenceInfo seqno ack) m = CryptoData 198bookKeeping (SequenceInfo seqno ack) m = CryptoData
159 { bufferStart = ack :: Word32 199 { bufferStart = ack :: Word32
@@ -161,6 +201,7 @@ bookKeeping (SequenceInfo seqno ack) m = CryptoData
161 , bufferData = m 201 , bufferData = m
162 } 202 }
163 203
204-- | Classify an inbound packet as lossy or lossless based on its id byte.
164checkLossless :: CryptoData -> PacketInboundEvent CryptoMessage 205checkLossless :: CryptoData -> PacketInboundEvent CryptoMessage
165checkLossless cd@CryptoData{ bufferStart = ack 206checkLossless cd@CryptoData{ bufferStart = ack
166 , bufferEnd = no 207 , bufferEnd = no