summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Data/InOrOut.hs13
-rw-r--r--src/Network/Tox/Crypto/Handlers.hs60
2 files changed, 68 insertions, 5 deletions
diff --git a/src/Data/InOrOut.hs b/src/Data/InOrOut.hs
new file mode 100644
index 00000000..2c14a0f9
--- /dev/null
+++ b/src/Data/InOrOut.hs
@@ -0,0 +1,13 @@
1module Data.InOrOut where
2
3
4-- | This wrapper is useful for tagging another type
5-- as being of either an In variety or an Out variety.
6--
7-- For example, incoming messages can be tagged as In
8-- and outgoing messages could be tagged as Out.
9--
10-- Another use case is tagging handles so that
11-- you only output to Out Handle and only input
12-- from In Handle.
13data InOrOut a = In a | Out a
diff --git a/src/Network/Tox/Crypto/Handlers.hs b/src/Network/Tox/Crypto/Handlers.hs
index 9567ea87..0ad868a7 100644
--- a/src/Network/Tox/Crypto/Handlers.hs
+++ b/src/Network/Tox/Crypto/Handlers.hs
@@ -42,6 +42,7 @@ import GHC.Conc (labelThread)
42import PingMachine 42import PingMachine
43import qualified Data.IntMap.Strict as IntMap 43import qualified Data.IntMap.Strict as IntMap
44import Control.Concurrent.Supply 44import Control.Concurrent.Supply
45import Data.InOrOut
45 46
46-- util, todo: move to another module 47-- util, todo: move to another module
47maybeToEither :: Maybe b -> Either String b 48maybeToEither :: Maybe b -> Either String b
@@ -92,6 +93,54 @@ data SessionView = SessionView
92 , svDownloadDir :: TVar FilePath -- ^ where to put files the user downloads 93 , svDownloadDir :: TVar FilePath -- ^ where to put files the user downloads
93 } 94 }
94 95
96-- | A static version of 'SessionView'
97-- useful for serializing to logs
98-- or storing in the ncLastNMsgs queue
99data ViewSnapshot = ViewSnapshot
100 { vNick :: ByteString
101 , vStatus :: UserStatus
102 , vStatusMsg :: ByteString
103 , vTyping :: TypingStatus
104 , vNoSpam :: Maybe NoSpam
105 , vTheirNick :: ByteString
106 , vTheirStatus :: UserStatus
107 , vTheirStatusMsg :: ByteString
108 , vTheirTyping :: TypingStatus
109 , vTheirNoSpam :: Maybe NoSpam
110 , vGroups :: Map.Map GroupChatId (Set.Set SockAddr)
111 }
112
113-- | Take snapshot of SessionView
114--
115-- This is useful for storing the context of
116-- remembered messages.
117viewSnapshot :: SessionView -> STM ViewSnapshot
118viewSnapshot v = do
119 nick <- readTVar (svNick v)
120 status <- readTVar (svStatus v)
121 statusMsg <- readTVar (svStatusMsg v)
122 typing <- readTVar (svTyping v)
123 noSpam <- readTVar (svNoSpam v)
124 theirNick <- readTVar (svTheirNick v)
125 theirStatus <- readTVar (svTheirStatus v)
126 theirStatusMsg <- readTVar (svTheirStatusMsg v)
127 theirTyping <- readTVar (svTheirTyping v)
128 theirNoSpam <- readTVar (svTheirNoSpam v)
129 groups <- readTVar (svGroups v)
130 return ViewSnapshot
131 { vNick = nick
132 , vStatus = status
133 , vStatusMsg = statusMsg
134 , vTyping = typing
135 , vNoSpam = noSpam
136 , vTheirNick = theirNick
137 , vTheirStatus = theirStatus
138 , vTheirStatusMsg = theirStatusMsg
139 , vTheirTyping = theirTyping
140 , vTheirNoSpam = theirNoSpam
141 , vGroups = groups
142 }
143
95type SessionID = Word64 144type SessionID = Word64
96 145
97-- | Application specific listener type (Word64) 146-- | Application specific listener type (Word64)
@@ -141,15 +190,14 @@ data NetCryptoSession = NCrypto
141 CryptoMessage 190 CryptoMessage
142 (CryptoPacket Encrypted) 191 (CryptoPacket Encrypted)
143 CryptoData 192 CryptoData
144 , ncLastNMsgs :: PacketQueue (Bool{-Handled?-},CryptoMessage) 193 , ncLastNMsgs :: PacketQueue (Bool{-Handled?-},(ViewSnapshot,InOrOut CryptoMessage))
145 -- ^ cyclic buffer, holds the last N non-handshake crypto messages 194 -- ^ cyclic buffer, holds the last N non-handshake crypto messages
146 -- even if there is no attached user interface. 195 -- even if there is no attached user interface.
147 , ncListeners :: TVar (IntMap.IntMap (ListenerType,TMChan CryptoMessage)) 196 , ncListeners :: TVar (IntMap.IntMap (ListenerType,TMChan CryptoMessage))
148 -- ^ user interfaces may "listen" by inserting themselves into this map 197 -- ^ user interfaces may "listen" by inserting themselves into this map
149 -- with a unique id and a new TChan, and then reading from the TChan 198 -- with a unique id and a new TChan, and then reading from the TChan
150 , ncMsgNumVar :: TVar Word32 199 , ncMsgNumVar :: TVar Word32
151 -- ^ The number of non-handshake crypto messages recieved in this session 200 -- ^ The number of non-handshake crypto messages written to ncLastNMsgs total
152 -- TODO: there is already a packet num etc, do we need two?
153 , ncDropCntVar :: TVar Word32 201 , ncDropCntVar :: TVar Word32
154 -- ^ The number of crypto messages that were overwritten in the ncLastNMsgs 202 -- ^ The number of crypto messages that were overwritten in the ncLastNMsgs
155 -- before anybody got to see them. 203 -- before anybody got to see them.
@@ -400,7 +448,7 @@ freshCryptoSession sessions
400 writeTVar ncMyPacketNonce0 n24plus1 448 writeTVar ncMyPacketNonce0 n24plus1
401 return (return (f n24, n24, ncOutgoingIdMap0)) 449 return (return (f n24, n24, ncOutgoingIdMap0))
402 pktoq <- atomically $ PQ.newOutGoing pktq ncToWire toWireIO 0 (outboundQueueCapacity sessions) 0 450 pktoq <- atomically $ PQ.newOutGoing pktq ncToWire toWireIO 0 (outboundQueueCapacity sessions) 0
403 msgQ <- atomically (PQ.newOverwrite 10 0 :: STM (PacketQueue (Bool,CryptoMessage))) 451 msgQ <- atomically (PQ.newOverwrite 10 0 :: STM (PacketQueue (Bool,(ViewSnapshot,InOrOut CryptoMessage))))
404 listeners <- atomically $ newTVar IntMap.empty 452 listeners <- atomically $ newTVar IntMap.empty
405 msgNum <- atomically $ newTVar 0 453 msgNum <- atomically $ newTVar 0
406 dropNum <- atomically $ newTVar 0 454 dropNum <- atomically $ newTVar 0
@@ -816,7 +864,9 @@ hookHelper handledFlg typ session cm = do
816 dropCntVar = ncDropCntVar session 864 dropCntVar = ncDropCntVar session
817 atomically $ do 865 atomically $ do
818 num <- readTVar msgNumVar 866 num <- readTVar msgNumVar
819 (wraps,offset) <- PQ.enqueue msgQ num (handledFlg,cm) 867 view <- readTVar (ncView session)
868 snapshot <- viewSnapshot view
869 (wraps,offset) <- PQ.enqueue msgQ num (handledFlg,(snapshot,Out cm))
820 capacity <- PQ.getCapacity msgQ 870 capacity <- PQ.getCapacity msgQ
821 let dropped = wraps * capacity + offset 871 let dropped = wraps * capacity + offset
822 modifyTVar' msgNumVar (+1) 872 modifyTVar' msgNumVar (+1)