diff options
author | joe <joe@jerkface.net> | 2018-06-15 20:41:56 -0400 |
---|---|---|
committer | James Crayne <jim.crayne@gmail.com> | 2018-06-16 02:27:53 +0000 |
commit | 82fb11604685273a2071e75f725280dfed884730 (patch) | |
tree | e5a1b7019c658dc6918c7e6dc5c775a968939798 | |
parent | d6ed1d376d5e374428a7f9ba23e973213e9efd10 (diff) |
tox: Converted Contact struct to use TVar fields.
-rw-r--r-- | src/Network/Tox.hs | 27 | ||||
-rw-r--r-- | src/Network/Tox/ContactInfo.hs | 130 |
2 files changed, 76 insertions, 81 deletions
diff --git a/src/Network/Tox.hs b/src/Network/Tox.hs index 4d244199..091c268d 100644 --- a/src/Network/Tox.hs +++ b/src/Network/Tox.hs | |||
@@ -276,26 +276,25 @@ netCryptoWithBackoff millisecs tox myseckey theirpubkey = do | |||
276 | Just contactsVar -> do | 276 | Just contactsVar -> do |
277 | let theirkeyAsId = key2id theirpubkey | 277 | let theirkeyAsId = key2id theirpubkey |
278 | mbContact <- HashMap.lookup theirkeyAsId <$> atomically (readTVar contactsVar) | 278 | mbContact <- HashMap.lookup theirkeyAsId <$> atomically (readTVar contactsVar) |
279 | case mbContact of | 279 | tup <- atomically $ do |
280 | Nothing -> do | 280 | mc <- HashMap.lookup theirkeyAsId <$> readTVar contactsVar |
281 | kp <- fmap join $ forM mc $ \c -> readTVar (contactKeyPacket c) | ||
282 | sa <- fmap join $ forM mc $ \c -> readTVar (contactLastSeenAddr c) | ||
283 | fr <- fmap join $ forM mc $ \c -> readTVar (contactFriendRequest c) | ||
284 | cp <- fmap join $ forM mc $ \c -> readTVar (contactPolicy c) | ||
285 | return (kp,sa,fr,cp) | ||
286 | case tup of | ||
287 | (Nothing,Nothing,Nothing,Nothing) -> do | ||
281 | hPutStrLn stderr ("netCrypto: (" ++ show mykeyAsId ++") friend not found (" ++ show theirkeyAsId ++ ").") | 288 | hPutStrLn stderr ("netCrypto: (" ++ show mykeyAsId ++") friend not found (" ++ show theirkeyAsId ++ ").") |
282 | return [] | 289 | return [] |
283 | Just contact@(Contact { contactKeyPacket = mbKeyPkt | 290 | (mbKeyPkt,Nothing,mbFR,mbPolicy) -> do |
284 | , contactLastSeenAddr = Nothing | ||
285 | , contactFriendRequest = mbFR | ||
286 | , contactPolicy = mbPolicy | ||
287 | }) -> do | ||
288 | hPutStrLn stderr ("netCrypto: (" ++ show mykeyAsId ++") no SockAddr for friend (" ++ show theirkeyAsId ++ "). TODO: search their node?") | 291 | hPutStrLn stderr ("netCrypto: (" ++ show mykeyAsId ++") no SockAddr for friend (" ++ show theirkeyAsId ++ "). TODO: search their node?") |
289 | return [] | 292 | return [] |
290 | Just contact@(Contact { contactKeyPacket = Nothing | 293 | (Nothing,_,_,_) -> do |
291 | }) -> do | ||
292 | hPutStrLn stderr ("netCrypto: (" ++ show mykeyAsId ++") no DHT-key for friend (" ++ show theirkeyAsId ++ "). TODO: what?") | 294 | hPutStrLn stderr ("netCrypto: (" ++ show mykeyAsId ++") no DHT-key for friend (" ++ show theirkeyAsId ++ "). TODO: what?") |
293 | return [] | 295 | return [] |
294 | Just contact@(Contact { contactKeyPacket = Just keyPkt | 296 | (Just keyPkt,Just saddr,mbFR,mbPolicy) |
295 | , contactLastSeenAddr = Just saddr | 297 | | theirDhtKey <- DHT.dhtpk keyPkt -> do |
296 | , contactFriendRequest = mbFR | ||
297 | , contactPolicy = mbPolicy | ||
298 | }) | theirDhtKey <- DHT.dhtpk keyPkt -> do | ||
299 | -- Do we already have an active session with this user? | 298 | -- Do we already have an active session with this user? |
300 | sessionsMap <- atomically $ readTVar (netCryptoSessionsByKey (toxCryptoSessions tox) ) | 299 | sessionsMap <- atomically $ readTVar (netCryptoSessionsByKey (toxCryptoSessions tox) ) |
301 | let sessionUsesIdentity key session = key == ncMyPublicKey session | 300 | let sessionUsesIdentity key session = key == ncMyPublicKey session |
diff --git a/src/Network/Tox/ContactInfo.hs b/src/Network/Tox/ContactInfo.hs index df3365a2..7f74caff 100644 --- a/src/Network/Tox/ContactInfo.hs +++ b/src/Network/Tox/ContactInfo.hs | |||
@@ -35,55 +35,24 @@ data ContactEvent = OnionRouted { contact :: PublicKey, onionRouted :: OnionDat | |||
35 | | AddrChange { contact :: PublicKey, addrChange :: SockAddr } | 35 | | AddrChange { contact :: PublicKey, addrChange :: SockAddr } |
36 | 36 | ||
37 | data Contact = Contact | 37 | data Contact = Contact |
38 | { contactKeyPacket :: Maybe (DHT.DHTPublicKey) | 38 | { contactKeyPacket :: TVar (Maybe (DHT.DHTPublicKey)) |
39 | , contactLastSeenAddr :: Maybe SockAddr | 39 | , contactLastSeenAddr :: TVar (Maybe SockAddr) |
40 | , contactFriendRequest :: Maybe (DHT.FriendRequest) | 40 | , contactFriendRequest :: TVar (Maybe (DHT.FriendRequest)) |
41 | , contactPolicy :: Maybe (Connection.Policy) | 41 | , contactPolicy :: TVar (Maybe (Connection.Policy)) |
42 | -- Possible semantics | 42 | -- Possible semantics |
43 | -- RefusingToConnect : rejected friend-request or blocked or unknown. | 43 | -- RefusingToConnect : rejected friend-request or blocked or unknown. |
44 | -- OpenToConnect : pending friend-request. | 44 | -- OpenToConnect : pending friend-request. |
45 | -- TryingToConnect : roster entry. | 45 | -- TryingToConnect : roster entry. |
46 | } | 46 | } |
47 | 47 | ||
48 | nullContact :: Contact | ||
49 | nullContact = Contact | ||
50 | { contactKeyPacket = Nothing | ||
51 | , contactLastSeenAddr = Nothing | ||
52 | , contactFriendRequest = Nothing | ||
53 | , contactPolicy = Nothing | ||
54 | } | ||
55 | |||
56 | mergeContact :: Contact -> Maybe Contact -> Maybe Contact | ||
57 | mergeContact (Contact newk news newf newp) (Just (Contact oldk olds oldf oldp)) = | ||
58 | Just $ Contact mergek -- Prefer newer public key packet as long as its stamp | ||
59 | -- is later than the stored one. | ||
60 | (mplus news olds) -- Prefer newer last-seen | ||
61 | (mplus newf oldf) -- Prefer newer friend request. | ||
62 | (mplus newp oldp) -- Prefer newer connection policy. | ||
63 | where | ||
64 | mergek = flip mplus oldk $ do | ||
65 | n <- newk | ||
66 | stamp <- fmap DHT.dhtpkNonce oldk `mplus` return minBound | ||
67 | guard (stamp <= DHT.dhtpkNonce n) | ||
68 | return n | ||
69 | |||
70 | mergeContact new Nothing = Just new | ||
71 | |||
72 | newContactInfo :: IO ContactInfo | 48 | newContactInfo :: IO ContactInfo |
73 | newContactInfo = atomically $ ContactInfo <$> newTVar HashMap.empty | 49 | newContactInfo = atomically $ ContactInfo <$> newTVar HashMap.empty |
74 | 50 | ||
75 | newAccount :: SecretKey -> STM Account | 51 | myKeyPairs :: ContactInfo -> STM [(SecretKey,PublicKey)] |
76 | newAccount sk = Account sk <$> newTVar HashMap.empty | 52 | myKeyPairs (ContactInfo accounts) = do |
77 | <*> newTVar Set.empty | 53 | acnts <- readTVar accounts |
78 | <*> newBroadcastTChan | 54 | forM (HashMap.toList acnts) $ \(nid, Account{userSecret}) -> do |
79 | 55 | return (userSecret,id2key nid) | |
80 | addContactInfo :: ContactInfo -> SecretKey -> STM () | ||
81 | addContactInfo (ContactInfo as) sk = do | ||
82 | a <- newAccount sk | ||
83 | modifyTVar' as $ HashMap.insert (key2id $ toPublic sk) a | ||
84 | |||
85 | delContactInfo :: ContactInfo -> PublicKey -> STM () | ||
86 | delContactInfo (ContactInfo as) pk = modifyTVar' as $ HashMap.delete (key2id pk) | ||
87 | 56 | ||
88 | updateContactInfo :: ContactInfo -> Onion.AnnouncedRendezvous -> (PublicKey,Onion.OnionData) -> IO () | 57 | updateContactInfo :: ContactInfo -> Onion.AnnouncedRendezvous -> (PublicKey,Onion.OnionData) -> IO () |
89 | updateContactInfo roster Onion.AnnouncedRendezvous{remoteUserKey} (localUserKey,omsg) = do | 58 | updateContactInfo roster Onion.AnnouncedRendezvous{remoteUserKey} (localUserKey,omsg) = do |
@@ -94,44 +63,76 @@ updateContactInfo roster Onion.AnnouncedRendezvous{remoteUserKey} (localUserKey, | |||
94 | (updateAccount remoteUserKey omsg) | 63 | (updateAccount remoteUserKey omsg) |
95 | $ HashMap.lookup (key2id localUserKey) as | 64 | $ HashMap.lookup (key2id localUserKey) as |
96 | 65 | ||
97 | 66 | initContact :: STM Contact | |
98 | onionUpdate :: OnionData -> Maybe Contact -> Maybe Contact | 67 | initContact = Contact <$> newTVar Nothing |
99 | onionUpdate (Onion.OnionDHTPublicKey dhtpk) | 68 | <*> newTVar Nothing |
100 | = mergeContact nullContact { contactKeyPacket = Just dhtpk } | 69 | <*> newTVar Nothing |
101 | onionUpdate (Onion.OnionFriendRequest fr) | 70 | <*> newTVar Nothing |
102 | = mergeContact nullContact { contactFriendRequest = Just fr } | 71 | |
103 | 72 | updateAccount' :: PublicKey -> Account -> (Contact -> STM ()) -> STM () | |
104 | policyUpdate :: Policy -> Maybe Contact -> Maybe Contact | 73 | updateAccount' remoteUserKey acc updater = do |
105 | policyUpdate policy = mergeContact nullContact { contactPolicy = Just policy } | 74 | let rkey = key2id remoteUserKey |
106 | 75 | cmap <- readTVar (contacts acc) | |
107 | addrUpdate :: SockAddr -> Maybe Contact -> Maybe Contact | 76 | contact <- case HashMap.lookup rkey cmap of |
108 | addrUpdate addr = mergeContact nullContact { contactLastSeenAddr = Just addr } | 77 | Just contact -> return contact |
78 | Nothing -> do contact <- initContact | ||
79 | writeTVar (contacts acc) $ HashMap.insert rkey contact cmap | ||
80 | return contact | ||
81 | updater contact | ||
109 | 82 | ||
110 | updateAccount :: PublicKey -> Onion.OnionData -> Account -> STM () | 83 | updateAccount :: PublicKey -> Onion.OnionData -> Account -> STM () |
111 | updateAccount remoteUserKey omsg acc = do | 84 | updateAccount remoteUserKey omsg acc = do |
112 | modifyTVar' (contacts acc) $ HashMap.alter (onionUpdate omsg) (key2id remoteUserKey) | 85 | updateAccount' remoteUserKey acc $ onionUpdate omsg |
113 | writeTChan (eventChan acc) $ OnionRouted remoteUserKey omsg | 86 | writeTChan (eventChan acc) $ OnionRouted remoteUserKey omsg |
114 | 87 | ||
88 | onionUpdate :: OnionData -> Contact -> STM () | ||
89 | onionUpdate (Onion.OnionDHTPublicKey dhtpk) contact | ||
90 | = writeTVar (contactKeyPacket contact) $ Just dhtpk | ||
91 | onionUpdate (Onion.OnionFriendRequest fr) contact | ||
92 | = writeTVar (contactFriendRequest contact) $ Just fr | ||
93 | |||
94 | policyUpdate :: Policy -> Contact -> STM () | ||
95 | policyUpdate policy contact = writeTVar (contactPolicy contact) $ Just policy | ||
96 | |||
97 | addrUpdate :: SockAddr -> Contact -> STM () | ||
98 | addrUpdate addr contact = writeTVar (contactLastSeenAddr contact) $ Just addr | ||
99 | |||
115 | setContactPolicy :: PublicKey -> Policy -> Account -> STM () | 100 | setContactPolicy :: PublicKey -> Policy -> Account -> STM () |
116 | setContactPolicy remoteUserKey policy acc = do | 101 | setContactPolicy remoteUserKey policy acc = do |
117 | modifyTVar' (contacts acc) $ HashMap.alter (policyUpdate policy) (key2id remoteUserKey) | 102 | updateAccount' remoteUserKey acc $ policyUpdate policy |
118 | writeTChan (eventChan acc) $ PolicyChange remoteUserKey policy | 103 | writeTChan (eventChan acc) $ PolicyChange remoteUserKey policy |
119 | 104 | ||
120 | setContactAddr :: PublicKey -> SockAddr -> Account -> STM () | 105 | setContactAddr :: PublicKey -> SockAddr -> Account -> STM () |
121 | setContactAddr remoteUserKey addr acc = do | 106 | setContactAddr remoteUserKey addr acc = do |
122 | modifyTVar' (contacts acc) $ HashMap.alter (addrUpdate addr) (key2id remoteUserKey) | 107 | updateAccount' remoteUserKey acc $ addrUpdate addr |
123 | writeTChan (eventChan acc) $ AddrChange remoteUserKey addr | 108 | writeTChan (eventChan acc) $ AddrChange remoteUserKey addr |
124 | 109 | ||
110 | |||
111 | |||
112 | addContactInfo :: ContactInfo -> SecretKey -> STM () | ||
113 | addContactInfo (ContactInfo as) sk = do | ||
114 | a <- newAccount sk | ||
115 | modifyTVar' as $ HashMap.insert (key2id $ toPublic sk) a | ||
116 | |||
117 | delContactInfo :: ContactInfo -> PublicKey -> STM () | ||
118 | delContactInfo (ContactInfo as) pk = modifyTVar' as $ HashMap.delete (key2id pk) | ||
119 | |||
120 | newAccount :: SecretKey -> STM Account | ||
121 | newAccount sk = Account sk <$> newTVar HashMap.empty | ||
122 | <*> newTVar Set.empty | ||
123 | <*> newBroadcastTChan | ||
124 | |||
125 | dnsPresentation :: ContactInfo -> STM String | 125 | dnsPresentation :: ContactInfo -> STM String |
126 | dnsPresentation (ContactInfo accsvar) = do | 126 | dnsPresentation (ContactInfo accsvar) = do |
127 | accs <- readTVar accsvar | 127 | accs <- readTVar accsvar |
128 | ms <- forM accs $ \Account { userSecret = sec, contacts = cvar } -> do | 128 | ms <- forM accs $ \Account { userSecret = sec, contacts = cvar } -> do |
129 | cs <- readTVar cvar | 129 | cs <- readTVar cvar |
130 | rs <- forM (HashMap.toList cs) $ \(nid,c) -> do | ||
131 | mkpkt <- readTVar (contactKeyPacket c) | ||
132 | return $ fmap ((,) nid) mkpkt | ||
130 | return $ | 133 | return $ |
131 | "; local key = " ++ show (key2id $ toPublic sec) ++ "\n" | 134 | "; local key = " ++ show (key2id $ toPublic sec) ++ "\n" |
132 | ++ concatMap dnsPresentation1 | 135 | ++ concatMap dnsPresentation1 (catMaybes rs) |
133 | (mapMaybe (\(nid,m) -> ((,) nid) <$> contactKeyPacket m) | ||
134 | $ HashMap.toList cs) | ||
135 | return $ concat ms | 136 | return $ concat ms |
136 | 137 | ||
137 | dnsPresentation1 :: (NodeId,DHTPublicKey) -> String | 138 | dnsPresentation1 :: (NodeId,DHTPublicKey) -> String |
@@ -147,13 +148,8 @@ friendRequests (ContactInfo roster) = do | |||
147 | accs <- readTVar roster | 148 | accs <- readTVar roster |
148 | forM accs $ \Account { userSecret = sec, contacts = cvar } -> do | 149 | forM accs $ \Account { userSecret = sec, contacts = cvar } -> do |
149 | cs <- readTVar cvar | 150 | cs <- readTVar cvar |
150 | let remotes = mapMaybe (\(nid,m) -> ((,) nid) <$> contactFriendRequest m) | 151 | rs <- forM (HashMap.toList cs) $ \(nid,c) -> do |
151 | $ HashMap.toList cs | 152 | mfr <- readTVar (contactFriendRequest c) |
152 | return remotes | 153 | return $ fmap ((,) nid) mfr |
153 | 154 | return $ catMaybes rs | |
154 | myKeyPairs :: ContactInfo -> STM [(SecretKey,PublicKey)] | ||
155 | myKeyPairs (ContactInfo accounts) = do | ||
156 | acnts <- readTVar accounts | ||
157 | forM (HashMap.toList acnts) $ \(nid, Account{userSecret}) -> do | ||
158 | return (userSecret,id2key nid) | ||
159 | 155 | ||