diff options
-rw-r--r-- | Presence/ClientState.hs | 15 | ||||
-rw-r--r-- | Presence/ConfigFiles.hs | 111 | ||||
-rw-r--r-- | Presence/ConsoleWriter.hs | 17 | ||||
-rw-r--r-- | Presence/Presence.hs | 213 | ||||
-rw-r--r-- | Presence/XMPPServer.hs | 65 |
5 files changed, 250 insertions, 171 deletions
diff --git a/Presence/ClientState.hs b/Presence/ClientState.hs index 30a53131..08cc54ed 100644 --- a/Presence/ClientState.hs +++ b/Presence/ClientState.hs | |||
@@ -9,11 +9,18 @@ import UTmp ( ProcessID ) | |||
9 | import XMPPServer ( Stanza ) | 9 | import XMPPServer ( Stanza ) |
10 | 10 | ||
11 | data ClientState = ClientState | 11 | data ClientState = ClientState |
12 | -- | The unix tty or the jabber resource for this client. | ||
12 | { clientResource :: Text | 13 | { clientResource :: Text |
13 | , clientUser :: Text | 14 | -- | Unix user that is running this client. |
14 | , clientPid :: Maybe ProcessID | 15 | , clientUser :: Text |
15 | , clientStatus :: TVar (Maybe Stanza) | 16 | -- | The specific roster/identity of the user that this client presenting. |
16 | , clientFlags :: TVar Int8 | 17 | , clientProfile :: Text |
18 | -- | The unix process id of the client if we know it. | ||
19 | , clientPid :: Maybe ProcessID | ||
20 | -- | The presence (away/available) stanza this client is indicating. | ||
21 | , clientStatus :: TVar (Maybe Stanza) | ||
22 | -- | XMPP client flags (read access via 'clientIsAvailable' and 'clientIsInterested') | ||
23 | , clientFlags :: TVar Int8 | ||
17 | } | 24 | } |
18 | 25 | ||
19 | cf_available :: Int8 | 26 | cf_available :: Int8 |
diff --git a/Presence/ConfigFiles.hs b/Presence/ConfigFiles.hs index 808e6dd8..b745094f 100644 --- a/Presence/ConfigFiles.hs +++ b/Presence/ConfigFiles.hs | |||
@@ -18,32 +18,42 @@ import Data.List (partition) | |||
18 | import Data.Maybe (catMaybes,isJust) | 18 | import Data.Maybe (catMaybes,isJust) |
19 | 19 | ||
20 | type User = ByteString | 20 | type User = ByteString |
21 | type Profile = String | ||
21 | 22 | ||
22 | configDir = ".presence" | 23 | configDir, buddyFile, subscriberFile, |
23 | buddyFile = "buddies" | 24 | otherFile, pendingFile, solicitedFile, |
25 | secretsFile :: FilePath | ||
26 | |||
27 | configDir = ".presence" | ||
28 | buddyFile = "buddies" | ||
24 | subscriberFile = "subscribers" | 29 | subscriberFile = "subscribers" |
25 | otherFile = "others" | 30 | otherFile = "others" |
26 | pendingFile = "pending" | 31 | pendingFile = "pending" |
27 | solicitedFile = "solicited" | 32 | solicitedFile = "solicited" |
33 | secretsFile = "secrets" | ||
28 | 34 | ||
29 | 35 | ||
30 | configPath :: User -> String -> IO String | 36 | configPath :: User -> Profile -> String -> IO String |
31 | configPath user filename = do | 37 | configPath user "." filename = do |
32 | ue <- getUserEntryForName (unpack user) | 38 | ue <- getUserEntryForName (unpack user) |
33 | return $ (++("/"++configDir++"/"++filename)) $ homeDirectory ue | 39 | return $ (++("/"++configDir++"/"++filename)) $ homeDirectory ue |
40 | configPath user profile filename = do | ||
41 | ue <- getUserEntryForName (unpack user) | ||
42 | return $ (++("/"++configDir++"/"++profile++"/"++filename)) $ homeDirectory ue | ||
34 | 43 | ||
35 | 44 | createConfigFile :: ByteString -> FilePath -> IO () | |
36 | createConfigFile tag path = do | 45 | createConfigFile tag path = do |
37 | let dir = dropFileName path | 46 | let dir = dropFileName path |
38 | doesDirectoryExist dir >>= flip unless (do | 47 | doesDirectoryExist dir >>= flip unless (do |
39 | createDirectory dir | 48 | createDirectory dir |
40 | ) | 49 | ) |
41 | withFile path WriteMode $ \h -> do | 50 | withFile path WriteMode $ \h -> do |
42 | L.hPutStrLn h tag | 51 | L.hPutStrLn h tag |
43 | 52 | ||
53 | addItem :: ByteString -> ByteString -> FilePath -> IO () | ||
44 | addItem item tag path = | 54 | addItem item tag path = |
45 | let doit = do | 55 | let doit = do |
46 | handle (\e -> when (isDoesNotExistError e) | 56 | handle (\e -> when (isDoesNotExistError e) |
47 | (createConfigFile tag path >> doit)) | 57 | (createConfigFile tag path >> doit)) |
48 | $ do exists <- fileExist path | 58 | $ do exists <- fileExist path |
49 | if exists | 59 | if exists |
@@ -55,16 +65,27 @@ addItem item tag path = | |||
55 | in doit | 65 | in doit |
56 | 66 | ||
57 | 67 | ||
68 | -- | Modify a presence configuration file. This function will iterate over all | ||
69 | -- items in the file and invoke a test function. If the function returns | ||
70 | -- Nothing, that item is removed from the file. Otherwise, the function may | ||
71 | -- rename the item by returning the new name. | ||
72 | -- | ||
73 | -- If the last argument is populated, it is a new item to append to the end of | ||
74 | -- the file. | ||
75 | -- | ||
76 | -- Note that the entire file is read in, processed, and then rewritten from | ||
77 | -- scratch. | ||
58 | modifyFile :: | 78 | modifyFile :: |
59 | (ByteString,FilePath) | 79 | (ByteString,FilePath) |
60 | -> ByteString | 80 | -> User |
61 | -> (ByteString -> IO (Maybe ByteString)) | 81 | -> Profile |
62 | -> Maybe ByteString | 82 | -> (ByteString -> IO (Maybe ByteString)) -- Returns Just for each item you want to keep. |
83 | -> Maybe ByteString -- Optionally append this item. | ||
63 | -> IO Bool -- Returns True if test function ever returned Nothing | 84 | -> IO Bool -- Returns True if test function ever returned Nothing |
64 | modifyFile (tag,file) user test appending = configPath user file >>= doit | 85 | modifyFile (tag,file) user profile test appending = configPath user profile file >>= doit |
65 | where | 86 | where |
66 | doit path = do | 87 | doit path = do |
67 | handle (\e -> if (isDoesNotExistError e) | 88 | handle (\e -> if (isDoesNotExistError e) |
68 | then (createConfigFile tag path >> doit path) | 89 | then (createConfigFile tag path >> doit path) |
69 | else return False) | 90 | else return False) |
70 | $ do exists <- fileExist path | 91 | $ do exists <- fileExist path |
@@ -85,46 +106,48 @@ modifyFile (tag,file) user test appending = configPath user file >>= doit | |||
85 | withFile path WriteMode $ \h -> do | 106 | withFile path WriteMode $ \h -> do |
86 | L.hPutStrLn h tag | 107 | L.hPutStrLn h tag |
87 | withJust appending (L.hPutStrLn h) | 108 | withJust appending (L.hPutStrLn h) |
88 | return False | 109 | return False |
89 | |||
90 | 110 | ||
91 | modifySolicited = modifyFile ("<? solicited ?>" , solicitedFile) | 111 | modifySolicited, modifyBuddies, modifyOthers, modifyPending, modifySubscribers |
92 | modifyBuddies = modifyFile ("<? buddies ?>" , buddyFile) | 112 | :: User -> Profile -> (ByteString -> IO (Maybe ByteString)) -> Maybe ByteString -> IO Bool |
93 | modifyOthers = modifyFile ("<? others ?>" , otherFile) | ||
94 | modifyPending = modifyFile ("<? pending ?>" , pendingFile) | ||
95 | modifySubscribers = modifyFile ("<? subscribers ?>", subscriberFile) | ||
96 | 113 | ||
97 | addBuddy :: User -> ByteString -> IO () | 114 | modifySolicited = modifyFile ("<? solicited ?>" , solicitedFile) |
98 | addBuddy user buddy = | 115 | modifyBuddies = modifyFile ("<? buddies ?>" , buddyFile) |
99 | configPath user buddyFile >>= addItem buddy "<? buddies ?>" | 116 | modifyOthers = modifyFile ("<? others ?>" , otherFile) |
117 | modifyPending = modifyFile ("<? pending ?>" , pendingFile) | ||
118 | modifySubscribers = modifyFile ("<? subscribers ?>" , subscriberFile) | ||
100 | 119 | ||
101 | addSubscriber :: User -> ByteString -> IO () | 120 | addBuddy :: User -> Profile -> ByteString -> IO () |
102 | addSubscriber user subscriber = | 121 | addBuddy user profile buddy = |
103 | configPath user subscriberFile >>= addItem subscriber "<? subscribers ?>" | 122 | configPath user profile buddyFile >>= addItem buddy "<? buddies ?>" |
104 | 123 | ||
105 | addSolicited :: User -> ByteString -> IO () | 124 | addSubscriber :: User -> Profile -> ByteString -> IO () |
106 | addSolicited user solicited = | 125 | addSubscriber user profile subscriber = |
107 | configPath user solicitedFile >>= addItem solicited "<? solicited ?>" | 126 | configPath user profile subscriberFile >>= addItem subscriber "<? subscribers ?>" |
108 | 127 | ||
128 | addSolicited :: User -> Profile -> ByteString -> IO () | ||
129 | addSolicited user profile solicited = | ||
130 | configPath user profile solicitedFile >>= addItem solicited "<? solicited ?>" | ||
109 | 131 | ||
110 | getConfigList path = | 132 | getConfigList :: FilePath -> IO [ByteString] |
133 | getConfigList path = | ||
111 | handle (\e -> if isDoesNotExistError e then (return []) else throw e) | 134 | handle (\e -> if isDoesNotExistError e then (return []) else throw e) |
112 | $ withFile path ReadMode $ | 135 | $ withFile path ReadMode $ |
113 | L.hGetContents | 136 | L.hGetContents |
114 | >=> return . Prelude.tail . L.lines | 137 | >=> return . Prelude.tail . L.lines |
115 | >=> (\a -> seq (rnf a) (return a)) | 138 | >=> (\a -> seq (rnf a) (return a)) |
116 | 139 | ||
117 | getBuddies :: User -> IO [ByteString] | 140 | getBuddies :: User -> Profile -> IO [ByteString] |
118 | getBuddies user = configPath user buddyFile >>= getConfigList | 141 | getBuddies user profile = configPath user profile buddyFile >>= getConfigList |
119 | 142 | ||
120 | getSubscribers :: User -> IO [ByteString] | 143 | getSubscribers :: User -> Profile -> IO [ByteString] |
121 | getSubscribers user = configPath user subscriberFile >>= getConfigList | 144 | getSubscribers user profile = configPath user profile subscriberFile >>= getConfigList |
122 | 145 | ||
123 | getOthers :: User -> IO [ByteString] | 146 | getOthers :: User -> Profile -> IO [ByteString] |
124 | getOthers user = configPath user otherFile >>= getConfigList | 147 | getOthers user profile = configPath user profile otherFile >>= getConfigList |
125 | 148 | ||
126 | getPending :: User -> IO [ByteString] | 149 | getPending :: User -> Profile -> IO [ByteString] |
127 | getPending user = configPath user pendingFile >>= getConfigList | 150 | getPending user profile = configPath user profile pendingFile >>= getConfigList |
128 | 151 | ||
129 | getSolicited :: User -> IO [ByteString] | 152 | getSolicited :: User -> Profile -> IO [ByteString] |
130 | getSolicited user = configPath user solicitedFile >>= getConfigList | 153 | getSolicited user profile = configPath user profile solicitedFile >>= getConfigList |
diff --git a/Presence/ConsoleWriter.hs b/Presence/ConsoleWriter.hs index 986294f4..b80e477a 100644 --- a/Presence/ConsoleWriter.hs +++ b/Presence/ConsoleWriter.hs | |||
@@ -100,8 +100,8 @@ onLogin cs start = \e -> do | |||
100 | $ \tuvar -> do | 100 | $ \tuvar -> do |
101 | tu <- readTVar tuvar | 101 | tu <- readTVar tuvar |
102 | return (tty,tu) | 102 | return (tty,tu) |
103 | 103 | ||
104 | forM_ (Map.elems newborn) $ | 104 | forM_ (Map.elems newborn) $ |
105 | forkIO . start getActive | 105 | forkIO . start getActive |
106 | -- forM_ (Map.elems dead ) $ putStrLn . ("gone: "++) . show | 106 | -- forM_ (Map.elems dead ) $ putStrLn . ("gone: "++) . show |
107 | 107 | ||
@@ -297,7 +297,7 @@ writeAllPty cw msg = do | |||
297 | && Text.all isDigit (Text.drop 4 k) | 297 | && Text.all isDigit (Text.drop 4 k) |
298 | bs <- forM (Map.toList ptys) $ \(tty,utmp) -> do | 298 | bs <- forM (Map.toList ptys) $ \(tty,utmp) -> do |
299 | deliverTerminalMessage cw ("/dev/" <> tty) utmp msg | 299 | deliverTerminalMessage cw ("/dev/" <> tty) utmp msg |
300 | return $ or bs | 300 | return $ or bs |
301 | 301 | ||
302 | resource :: UtmpRecord -> Text | 302 | resource :: UtmpRecord -> Text |
303 | resource u = | 303 | resource u = |
@@ -341,10 +341,11 @@ newCon log cw activeTTY utmp = do | |||
341 | statusv <- atomically $ newTVar (Just stanza) | 341 | statusv <- atomically $ newTVar (Just stanza) |
342 | flgs <- atomically $ newTVar 0 | 342 | flgs <- atomically $ newTVar 0 |
343 | let client = ClientState { clientResource = r | 343 | let client = ClientState { clientResource = r |
344 | , clientUser = utmpUser u | 344 | , clientUser = utmpUser u |
345 | , clientPid = Nothing | 345 | , clientProfile = "." |
346 | , clientStatus = statusv | 346 | , clientPid = Nothing |
347 | , clientFlags = flgs } | 347 | , clientStatus = statusv |
348 | , clientFlags = flgs } | ||
348 | atomically $ do | 349 | atomically $ do |
349 | modifyTVar (cwClients cw) $ Map.insert r client | 350 | modifyTVar (cwClients cw) $ Map.insert r client |
350 | putTMVar (cwPresenceChan cw) (client,stanza) | 351 | putTMVar (cwPresenceChan cw) (client,stanza) |
@@ -359,7 +360,7 @@ newCon log cw activeTTY utmp = do | |||
359 | guard (not $ Text.null $ utmpHost tu) | 360 | guard (not $ Text.null $ utmpHost tu) |
360 | return tu | 361 | return tu |
361 | match mtu = searchstr mtu `Text.isInfixOf` Text.dropWhile (/=':') r | 362 | match mtu = searchstr mtu `Text.isInfixOf` Text.dropWhile (/=':') r |
362 | jstatus r ttynum tu = | 363 | jstatus r ttynum tu = |
363 | if bstatus r ttynum tu | 364 | if bstatus r ttynum tu |
364 | then Available | 365 | then Available |
365 | else Away | 366 | else Away |
diff --git a/Presence/Presence.hs b/Presence/Presence.hs index 15775857..9b91dc1d 100644 --- a/Presence/Presence.hs +++ b/Presence/Presence.hs | |||
@@ -32,7 +32,7 @@ import System.IO.Error (isDoesNotExistError) | |||
32 | import System.Posix.User (getUserEntryForID,userName) | 32 | import System.Posix.User (getUserEntryForID,userName) |
33 | import qualified Data.ByteString.Lazy.Char8 as L | 33 | import qualified Data.ByteString.Lazy.Char8 as L |
34 | import qualified ConfigFiles | 34 | import qualified ConfigFiles |
35 | import Data.Maybe (maybeToList,listToMaybe,mapMaybe) | 35 | import Data.Maybe |
36 | import Data.Bits | 36 | import Data.Bits |
37 | import Data.Int (Int8) | 37 | import Data.Int (Int8) |
38 | import Data.XML.Types (Event) | 38 | import Data.XML.Types (Event) |
@@ -56,10 +56,12 @@ isPeerKey k = case k of { PeerKey {} -> True ; _ -> False } | |||
56 | isClientKey :: ConnectionKey -> Bool | 56 | isClientKey :: ConnectionKey -> Bool |
57 | isClientKey k = case k of { ClientKey {} -> True ; _ -> False } | 57 | isClientKey k = case k of { ClientKey {} -> True ; _ -> False } |
58 | 58 | ||
59 | localJID :: Text -> Text -> IO Text | 59 | localJID :: Text -> Text -> Text -> IO Text |
60 | localJID user resource = do | 60 | localJID user "." resource = do |
61 | hostname <- textHostName | 61 | hostname <- textHostName |
62 | return $ user <> "@" <> hostname <> "/" <> resource | 62 | return $ user <> "@" <> hostname <> "/" <> resource |
63 | localJID user profile resource = | ||
64 | return $ user <> "@" <> profile <> "/" <> resource | ||
63 | 65 | ||
64 | data PresenceState = forall status. PresenceState | 66 | data PresenceState = forall status. PresenceState |
65 | { clients :: TVar (Map ConnectionKey ClientState) | 67 | { clients :: TVar (Map ConnectionKey ClientState) |
@@ -72,6 +74,9 @@ data PresenceState = forall status. PresenceState | |||
72 | } | 74 | } |
73 | 75 | ||
74 | 76 | ||
77 | newPresenceState :: Maybe ConsoleWriter | ||
78 | -> TMVar (XMPPServer, Connection.Manager status Text) | ||
79 | -> IO PresenceState | ||
75 | newPresenceState cw xmpp = atomically $ do | 80 | newPresenceState cw xmpp = atomically $ do |
76 | clients <- newTVar Map.empty | 81 | clients <- newTVar Map.empty |
77 | clientsByUser <- newTVar Map.empty | 82 | clientsByUser <- newTVar Map.empty |
@@ -87,6 +92,7 @@ newPresenceState cw xmpp = atomically $ do | |||
87 | } | 92 | } |
88 | 93 | ||
89 | 94 | ||
95 | presenceHooks :: PresenceState -> Int -> XMPPServerParameters | ||
90 | presenceHooks state verbosity = XMPPServerParameters | 96 | presenceHooks state verbosity = XMPPServerParameters |
91 | { xmppChooseResourceName = chooseResourceName state | 97 | { xmppChooseResourceName = chooseResourceName state |
92 | , xmppTellClientHisName = tellClientHisName state | 98 | , xmppTellClientHisName = tellClientHisName state |
@@ -165,21 +171,25 @@ identifyTTY' ttypids uid inode = ttypid | |||
165 | textify (tty,pid) = (fmap lazyByteStringToText tty, pid) | 171 | textify (tty,pid) = (fmap lazyByteStringToText tty, pid) |
166 | 172 | ||
167 | chooseResourceName :: PresenceState | 173 | chooseResourceName :: PresenceState |
168 | -> ConnectionKey -> SockAddr -> t -> IO Text | 174 | -> ConnectionKey -> SockAddr -> Maybe Text -> Maybe Text -> IO Text |
169 | chooseResourceName state k addr desired = do | 175 | chooseResourceName state k addr clientsNameForMe desired = do |
170 | muid <- getLocalPeerCred' addr | 176 | muid <- getLocalPeerCred' addr |
171 | (mtty,pid) <- getTTYandPID muid | 177 | (mtty,pid) <- getTTYandPID muid |
172 | user <- getJabberUserForId muid | 178 | user <- getJabberUserForId muid |
173 | status <- atomically $ newTVar Nothing | 179 | status <- atomically $ newTVar Nothing |
174 | flgs <- atomically $ newTVar 0 | 180 | flgs <- atomically $ newTVar 0 |
181 | profile <- fmap (fromMaybe ".") $ forM clientsNameForMe $ \wanted_profile -> do | ||
182 | -- TODO: allow user to select profile | ||
183 | return "." | ||
175 | let client = ClientState { clientResource = maybe "fallback" id mtty | 184 | let client = ClientState { clientResource = maybe "fallback" id mtty |
176 | , clientUser = user | 185 | , clientUser = user |
177 | , clientPid = pid | 186 | , clientProfile = profile |
178 | , clientStatus = status | 187 | , clientPid = pid |
179 | , clientFlags = flgs } | 188 | , clientStatus = status |
189 | , clientFlags = flgs } | ||
180 | 190 | ||
181 | do -- forward-lookup of the buddies so that it is cached for reversing. | 191 | do -- forward-lookup of the buddies so that it is cached for reversing. |
182 | buds <- configText ConfigFiles.getBuddies (clientUser client) | 192 | buds <- configText ConfigFiles.getBuddies (clientUser client) (clientProfile client) |
183 | forM_ buds $ \bud -> do | 193 | forM_ buds $ \bud -> do |
184 | let (_,h,_) = splitJID bud | 194 | let (_,h,_) = splitJID bud |
185 | forkIO $ void $ resolvePeer h | 195 | forkIO $ void $ resolvePeer h |
@@ -191,7 +201,7 @@ chooseResourceName state k addr desired = do | |||
191 | (pcInsertNetworkClient k client) | 201 | (pcInsertNetworkClient k client) |
192 | mb | 202 | mb |
193 | 203 | ||
194 | localJID (clientUser client) (clientResource client) | 204 | localJID (clientUser client) (clientProfile client) (clientResource client) |
195 | 205 | ||
196 | where | 206 | where |
197 | getTTYandPID muid = do | 207 | getTTYandPID muid = do |
@@ -226,8 +236,8 @@ forClient state k fallback f = do | |||
226 | tellClientHisName :: PresenceState -> ConnectionKey -> IO Text | 236 | tellClientHisName :: PresenceState -> ConnectionKey -> IO Text |
227 | tellClientHisName state k = forClient state k fallback go | 237 | tellClientHisName state k = forClient state k fallback go |
228 | where | 238 | where |
229 | fallback = localJID "nobody" "fallback" | 239 | fallback = localJID "nobody" "." "fallback" |
230 | go client = localJID (clientUser client) (clientResource client) | 240 | go client = localJID (clientUser client) (clientProfile client) (clientResource client) |
231 | 241 | ||
232 | toMapUnit :: Ord k => [k] -> Map k () | 242 | toMapUnit :: Ord k => [k] -> Map k () |
233 | toMapUnit xs = Map.fromList $ map (,()) xs | 243 | toMapUnit xs = Map.fromList $ map (,()) xs |
@@ -237,11 +247,11 @@ resolveAllPeers hosts = fmap (toMapUnit . concat) $ Prelude.mapM (fmap (take 1) | |||
237 | 247 | ||
238 | 248 | ||
239 | rosterGetStuff | 249 | rosterGetStuff |
240 | :: (L.ByteString -> IO [L.ByteString]) | 250 | :: (ConfigFiles.User -> ConfigFiles.Profile -> IO [L.ByteString]) |
241 | -> PresenceState -> ConnectionKey -> IO [Text] | 251 | -> PresenceState -> ConnectionKey -> IO [Text] |
242 | rosterGetStuff what state k = forClient state k (return []) | 252 | rosterGetStuff what state k = forClient state k (return []) |
243 | $ \client -> do | 253 | $ \client -> do |
244 | jids <- configText what (clientUser client) | 254 | jids <- configText what (clientUser client) (clientProfile client) |
245 | let hosts = map ((\(_,h,_)->h) . splitJID) jids | 255 | let hosts = map ((\(_,h,_)->h) . splitJID) jids |
246 | case state of | 256 | case state of |
247 | PresenceState { server = svVar } -> do | 257 | PresenceState { server = svVar } -> do |
@@ -267,13 +277,16 @@ data Conn = Conn { connChan :: TChan Stanza | |||
267 | , auxAddr :: SockAddr } | 277 | , auxAddr :: SockAddr } |
268 | 278 | ||
269 | configText :: Functor f => | 279 | configText :: Functor f => |
270 | (L.ByteString -> f [L.ByteString]) -> Text -> f [Text] | 280 | (ConfigFiles.User -> ConfigFiles.Profile -> f [L.ByteString]) |
271 | configText what u = fmap (map lazyByteStringToText) | 281 | -> Text -- user |
272 | $ what (textToLazyByteString u) | 282 | -> Text -- profile |
273 | 283 | -> f [Text] -- items | |
274 | getBuddies' :: Text -> IO [Text] | 284 | configText what u p = fmap (map lazyByteStringToText) |
285 | $ what (textToLazyByteString u) (Text.unpack p) | ||
286 | |||
287 | getBuddies' :: Text -> Text -> IO [Text] | ||
275 | getBuddies' = configText ConfigFiles.getBuddies | 288 | getBuddies' = configText ConfigFiles.getBuddies |
276 | getSolicited' :: Text -> IO [Text] | 289 | getSolicited' :: Text -> Text -> IO [Text] |
277 | getSolicited' = configText ConfigFiles.getSolicited | 290 | getSolicited' = configText ConfigFiles.getSolicited |
278 | 291 | ||
279 | sendProbesAndSolicitations :: PresenceState | 292 | sendProbesAndSolicitations :: PresenceState |
@@ -282,10 +295,11 @@ sendProbesAndSolicitations state k laddr chan = do | |||
282 | -- get all buddies & solicited matching k for all users | 295 | -- get all buddies & solicited matching k for all users |
283 | xs <- runTraversableT $ do | 296 | xs <- runTraversableT $ do |
284 | cbu <- lift $ atomically $ readTVar $ clientsByUser state | 297 | cbu <- lift $ atomically $ readTVar $ clientsByUser state |
285 | user <- liftT $ Map.keys cbu | 298 | (user,LocalPresence cmap) <- liftT $ Map.toList cbu |
299 | profile <- liftT $ nub $ map clientProfile $ Map.elems cmap | ||
286 | (isbud,getter) <- liftT [(True ,getBuddies' ) | 300 | (isbud,getter) <- liftT [(True ,getBuddies' ) |
287 | ,(False,getSolicited')] | 301 | ,(False,getSolicited')] |
288 | bud <- liftMT $ getter user | 302 | bud <- liftMT $ getter user profile |
289 | let (u,h,r) = splitJID bud | 303 | let (u,h,r) = splitJID bud |
290 | addr <- liftMT $ nub `fmap` resolvePeer h | 304 | addr <- liftMT $ nub `fmap` resolvePeer h |
291 | liftT $ guard (PeerKey addr == k) | 305 | liftT $ guard (PeerKey addr == k) |
@@ -294,10 +308,10 @@ sendProbesAndSolicitations state k laddr chan = do | |||
294 | -- is a bad idea. Perhaps due to laziness and an | 308 | -- is a bad idea. Perhaps due to laziness and an |
295 | -- unforced list? Instead, we will return a list | 309 | -- unforced list? Instead, we will return a list |
296 | -- of (Bool,Text) for processing outside. | 310 | -- of (Bool,Text) for processing outside. |
297 | return (isbud,u,if isbud then "" else user) | 311 | return (isbud,u,user,profile) |
298 | -- XXX: The following O(n²) nub may be a little | 312 | -- XXX: The following O(n²) nub may be a little |
299 | -- too onerous. | 313 | -- too onerous. |
300 | forM_ (nub xs) $ \(isbud,u,user) -> do | 314 | forM_ (nub xs) $ \(isbud,u,user,profile) -> do |
301 | let make = if isbud then presenceProbe | 315 | let make = if isbud then presenceProbe |
302 | else presenceSolicitation | 316 | else presenceSolicitation |
303 | toh = peerKeyToText k | 317 | toh = peerKeyToText k |
@@ -378,13 +392,17 @@ rewriteJIDForClient laddr jid buds = do | |||
378 | else peerKeyToResolvedName buds (PeerKey addr) | 392 | else peerKeyToResolvedName buds (PeerKey addr) |
379 | return (mine,(n,h',r)) | 393 | return (mine,(n,h',r)) |
380 | 394 | ||
395 | -- This attempts to reverse resolve a peers address to give the human-friendly | ||
396 | -- domain name as it appears in the roster. It prefers host names that occur | ||
397 | -- in the given list of JIDs, but will fall back to any reverse-resolved name | ||
398 | -- and if it was unable to reverse the address, it will yield an ip address. | ||
381 | peerKeyToResolvedName :: [Text] -> ConnectionKey -> IO Text | 399 | peerKeyToResolvedName :: [Text] -> ConnectionKey -> IO Text |
382 | peerKeyToResolvedName buds k@(ClientKey { localAddress=addr }) = return "ErrorClIeNt1" | 400 | peerKeyToResolvedName buds k@(ClientKey { localAddress=addr }) = return "ErrorClIeNt1" |
383 | peerKeyToResolvedName buds pk = do | 401 | peerKeyToResolvedName buds pk = do |
384 | ns <- peerKeyToResolvedNames pk | 402 | ns <- peerKeyToResolvedNames pk |
385 | let hs = map (\jid -> let (_,h,_)=splitJID jid in h) buds | 403 | let hs = map (\jid -> let (_,h,_)=splitJID jid in h) buds |
386 | ns' = sortBy (comparing $ not . flip elem hs) ns | 404 | ns' = sortBy (comparing $ not . flip elem hs) ns |
387 | return $ maybe (peerKeyToText pk) id (listToMaybe ns') | 405 | return $ fromMaybe (peerKeyToText pk) (listToMaybe ns') |
388 | 406 | ||
389 | 407 | ||
390 | multiplyJIDForClient :: SockAddr -> Text -> IO (Bool,[(Maybe Text,Text,Maybe Text)]) | 408 | multiplyJIDForClient :: SockAddr -> Text -> IO (Bool,[(Maybe Text,Text,Maybe Text)]) |
@@ -468,33 +486,46 @@ deliverMessage state fail msg = | |||
468 | if not mine then fail else do | 486 | if not mine then fail else do |
469 | let to' = unsplitJID (n,h,r) | 487 | let to' = unsplitJID (n,h,r) |
470 | cmap <- atomically . readTVar $ clientsByUser state | 488 | cmap <- atomically . readTVar $ clientsByUser state |
471 | (from',chans,ks) <- do | 489 | chans <- fmap (fromMaybe []) $ do |
472 | flip (maybe $ return (Nothing,[],[])) n $ \n -> do | 490 | forM (n >>= flip Map.lookup cmap) $ \presence_container -> do |
473 | buds <- configText ConfigFiles.getBuddies n | 491 | let ks = Map.keys (networkClients presence_container) |
492 | chans = do | ||
493 | (k,client) <- Map.toList $ networkClients presence_container | ||
494 | chan <- maybeToList $ Map.lookup k key_to_chan | ||
495 | return (clientProfile client, chan) | ||
496 | forM chans $ \(profile,chan) -> do | ||
497 | buds <- configText ConfigFiles.getBuddies (fromJust n) profile | ||
474 | from' <- do | 498 | from' <- do |
475 | flip (maybe $ return Nothing) (stanzaFrom msg) $ \from -> do | 499 | flip (maybe $ return Nothing) (stanzaFrom msg) $ \from -> do |
476 | (_,trip) <- rewriteJIDForClient laddr from buds | 500 | (_,trip) <- rewriteJIDForClient laddr from buds |
477 | return . Just $ unsplitJID trip | 501 | return . Just $ unsplitJID trip |
478 | let nope = return (from',[],[]) | 502 | return (from',chan) |
479 | flip (maybe nope) (Map.lookup n cmap) $ \presence_container -> do | ||
480 | let ks = Map.keys (networkClients presence_container) | ||
481 | chans = mapMaybe (flip Map.lookup key_to_chan) ks | ||
482 | return (from',chans,ks) | ||
483 | putStrLn $ "chan count: " ++ show (length chans) | 503 | putStrLn $ "chan count: " ++ show (length chans) |
484 | let msg' = msg { stanzaTo=Just to' | 504 | if null chans then do |
485 | , stanzaFrom=from' } | 505 | forM_ (stanzaFrom msg) $ \from -> do |
486 | if null chans then deliverToConsole state fail msg' else do | 506 | from' <- do |
487 | forM_ chans $ \Conn { connChan=chan} -> do | 507 | -- Fallback to "." profile when no clients. |
488 | putStrLn $ "sending "++show (stanzaId msg)++" to clients "++show ks | 508 | buds <- maybe (return []) |
489 | -- TODO: Cloning isn't really neccessary unless there are multiple | 509 | (\n -> configText ConfigFiles.getBuddies n ".") |
490 | -- destinations and we should probably transition to minimal cloning, | 510 | n |
491 | -- or else we should distinguish between announcable stanzas and | 511 | (_,trip) <- rewriteJIDForClient laddr from buds |
492 | -- consumable stanzas and announcables use write-only broadcast | 512 | return . Just $ unsplitJID trip |
493 | -- channels that must be cloned in order to be consumed. | 513 | let msg' = msg { stanzaTo=Just to' |
494 | -- For now, we are doing redundant cloning. | 514 | , stanzaFrom=from' } |
495 | dup <- cloneStanza msg' | 515 | deliverToConsole state fail msg' |
496 | sendModifiedStanzaToClient dup | 516 | else do |
497 | chan | 517 | forM_ chans $ \(from',Conn { connChan=chan}) -> do |
518 | -- TODO: Cloning isn't really neccessary unless there are multiple | ||
519 | -- destinations and we should probably transition to minimal cloning, | ||
520 | -- or else we should distinguish between announcable stanzas and | ||
521 | -- consumable stanzas and announcables use write-only broadcast | ||
522 | -- channels that must be cloned in order to be consumed. | ||
523 | -- For now, we are doing redundant cloning. | ||
524 | let msg' = msg { stanzaTo=Just to' | ||
525 | , stanzaFrom=from' } | ||
526 | dup <- cloneStanza msg' | ||
527 | sendModifiedStanzaToClient dup | ||
528 | chan | ||
498 | 529 | ||
499 | 530 | ||
500 | setClientFlag :: PresenceState -> ConnectionKey -> Int8 -> IO () | 531 | setClientFlag :: PresenceState -> ConnectionKey -> Int8 -> IO () |
@@ -513,9 +544,9 @@ informSentRoster state k = do | |||
513 | setClientFlag state k cf_interested | 544 | setClientFlag state k cf_interested |
514 | 545 | ||
515 | 546 | ||
516 | subscribedPeers :: Text -> IO [SockAddr] | 547 | subscribedPeers :: Text -> Text -> IO [SockAddr] |
517 | subscribedPeers user = do | 548 | subscribedPeers user profile = do |
518 | jids <- configText ConfigFiles.getSubscribers user | 549 | jids <- configText ConfigFiles.getSubscribers user profile |
519 | let hosts = map ((\(_,h,_)->h) . splitJID) jids | 550 | let hosts = map ((\(_,h,_)->h) . splitJID) jids |
520 | fmap Map.keys $ resolveAllPeers hosts | 551 | fmap Map.keys $ resolveAllPeers hosts |
521 | 552 | ||
@@ -546,7 +577,7 @@ informClientPresence0 state mbk client stanza = do | |||
546 | when (not is_avail) $ do | 577 | when (not is_avail) $ do |
547 | atomically $ setClientFlag0 client cf_available | 578 | atomically $ setClientFlag0 client cf_available |
548 | maybe (return ()) (sendCachedPresence state) mbk | 579 | maybe (return ()) (sendCachedPresence state) mbk |
549 | addrs <- subscribedPeers (clientUser client) | 580 | addrs <- subscribedPeers (clientUser client) (clientProfile client) |
550 | ktc <- atomically $ readTVar (keyToChan state) | 581 | ktc <- atomically $ readTVar (keyToChan state) |
551 | let connected = mapMaybe (flip Map.lookup ktc . PeerKey) addrs | 582 | let connected = mapMaybe (flip Map.lookup ktc . PeerKey) addrs |
552 | forM_ connected $ \con -> do | 583 | forM_ connected $ \con -> do |
@@ -649,7 +680,7 @@ answerProbe state mto k chan = do | |||
649 | 680 | ||
650 | flip (maybe $ return ()) muser $ \(u,conn,ch) -> do | 681 | flip (maybe $ return ()) muser $ \(u,conn,ch) -> do |
651 | 682 | ||
652 | resolved_subs <- resolvedFromRoster ConfigFiles.getSubscribers u | 683 | resolved_subs <- resolvedFromRoster ConfigFiles.getSubscribers u (_todo {- profile -}) |
653 | let gaddrs = groupBy (\a b -> snd a == snd b) (sort resolved_subs) | 684 | let gaddrs = groupBy (\a b -> snd a == snd b) (sort resolved_subs) |
654 | whitelist = do | 685 | whitelist = do |
655 | xs <- gaddrs | 686 | xs <- gaddrs |
@@ -693,7 +724,7 @@ sendCachedPresence :: PresenceState -> ConnectionKey -> IO () | |||
693 | sendCachedPresence state k = do | 724 | sendCachedPresence state k = do |
694 | forClient state k (return ()) $ \client -> do | 725 | forClient state k (return ()) $ \client -> do |
695 | rbp <- atomically $ readTVar (remotesByPeer state) | 726 | rbp <- atomically $ readTVar (remotesByPeer state) |
696 | jids <- configText ConfigFiles.getBuddies (clientUser client) | 727 | jids <- configText ConfigFiles.getBuddies (clientUser client) (clientProfile client) |
697 | let hosts = map ((\(_,h,_)->h) . splitJID) jids | 728 | let hosts = map ((\(_,h,_)->h) . splitJID) jids |
698 | addrs <- resolveAllPeers hosts | 729 | addrs <- resolveAllPeers hosts |
699 | let onlines = rbp `Map.intersection` Map.mapKeys PeerKey addrs | 730 | let onlines = rbp `Map.intersection` Map.mapKeys PeerKey addrs |
@@ -714,7 +745,7 @@ sendCachedPresence state k = do | |||
714 | sendModifiedStanzaToClient (dup { stanzaFrom=Just from' }) | 745 | sendModifiedStanzaToClient (dup { stanzaFrom=Just from' }) |
715 | (connChan con) | 746 | (connChan con) |
716 | 747 | ||
717 | pending <- configText ConfigFiles.getPending (clientUser client) | 748 | pending <- configText ConfigFiles.getPending (clientUser client) (clientProfile client) |
718 | hostname <- textHostName | 749 | hostname <- textHostName |
719 | forM_ pending $ \pending_jid -> do | 750 | forM_ pending $ \pending_jid -> do |
720 | let cjid = unsplitJID ( Just $ clientUser client | 751 | let cjid = unsplitJID ( Just $ clientUser client |
@@ -728,27 +759,39 @@ sendCachedPresence state k = do | |||
728 | return () | 759 | return () |
729 | 760 | ||
730 | addToRosterFile :: (MonadPlus t, Traversable t) => | 761 | addToRosterFile :: (MonadPlus t, Traversable t) => |
731 | (L.ByteString -> (L.ByteString -> IO (t L.ByteString)) | 762 | (ConfigFiles.User |
763 | -> ConfigFiles.Profile | ||
764 | -> (L.ByteString -> IO (t L.ByteString)) | ||
732 | -> Maybe L.ByteString | 765 | -> Maybe L.ByteString |
733 | -> t1) | 766 | -> t1) |
734 | -> Text -> Text -> [SockAddr] -> t1 | 767 | -> Text -- user |
735 | addToRosterFile doit whose to addrs = | 768 | -> Text -- profile |
736 | modifyRosterFile doit whose to addrs True | 769 | -> Text -> [SockAddr] -> t1 |
770 | addToRosterFile doit whose profile to addrs = | ||
771 | modifyRosterFile doit whose profile to addrs True | ||
737 | 772 | ||
738 | removeFromRosterFile :: (MonadPlus t, Traversable t) => | 773 | removeFromRosterFile :: (MonadPlus t, Traversable t) => |
739 | (L.ByteString -> (L.ByteString -> IO (t L.ByteString)) | 774 | (ConfigFiles.User |
775 | -> ConfigFiles.Profile | ||
776 | -> (L.ByteString -> IO (t L.ByteString)) | ||
740 | -> Maybe L.ByteString | 777 | -> Maybe L.ByteString |
741 | -> t1) | 778 | -> t1) |
742 | -> Text -> Text -> [SockAddr] -> t1 | 779 | -> Text -- user |
743 | removeFromRosterFile doit whose to addrs = | 780 | -> Text -- profile |
744 | modifyRosterFile doit whose to addrs False | 781 | -> Text -> [SockAddr] -> t1 |
782 | removeFromRosterFile doit whose profile to addrs = | ||
783 | modifyRosterFile doit whose profile to addrs False | ||
745 | 784 | ||
746 | modifyRosterFile :: (Traversable t, MonadPlus t) => | 785 | modifyRosterFile :: (Traversable t, MonadPlus t) => |
747 | (L.ByteString -> (L.ByteString -> IO (t L.ByteString)) | 786 | (ConfigFiles.User |
787 | -> ConfigFiles.Profile | ||
788 | -> (L.ByteString -> IO (t L.ByteString)) | ||
748 | -> Maybe L.ByteString | 789 | -> Maybe L.ByteString |
749 | -> t1) | 790 | -> t1) |
750 | -> Text -> Text -> [SockAddr] -> Bool -> t1 | 791 | -> Text -- user |
751 | modifyRosterFile doit whose to addrs bAdd = do | 792 | -> Text -- profile |
793 | -> Text -> [SockAddr] -> Bool -> t1 | ||
794 | modifyRosterFile doit whose profile to addrs bAdd = do | ||
752 | let (mu,_,_) = splitJID to | 795 | let (mu,_,_) = splitJID to |
753 | cmp jid = runTraversableT $ do | 796 | cmp jid = runTraversableT $ do |
754 | let (msu,stored_h,mr) = splitJID (lazyByteStringToText jid) | 797 | let (msu,stored_h,mr) = splitJID (lazyByteStringToText jid) |
@@ -767,7 +810,7 @@ modifyRosterFile doit whose to addrs bAdd = do | |||
767 | if null (stored_addrs \\ addrs) then mzero else do | 810 | if null (stored_addrs \\ addrs) then mzero else do |
768 | -- keep | 811 | -- keep |
769 | return jid | 812 | return jid |
770 | doit (textToLazyByteString whose) | 813 | doit (textToLazyByteString whose) (Text.unpack profile) |
771 | cmp | 814 | cmp |
772 | (guard bAdd >> Just (textToLazyByteString to)) | 815 | (guard bAdd >> Just (textToLazyByteString to)) |
773 | 816 | ||
@@ -781,9 +824,9 @@ clientSubscriptionRequest state fail k stanza chan = do | |||
781 | flip (maybe fail) mu $ \u -> do | 824 | flip (maybe fail) mu $ \u -> do |
782 | -- add to-address to from's solicited | 825 | -- add to-address to from's solicited |
783 | addrs <- resolvePeer h | 826 | addrs <- resolvePeer h |
784 | addToRosterFile ConfigFiles.modifySolicited (clientUser client) to addrs | 827 | addToRosterFile ConfigFiles.modifySolicited (clientUser client) (clientProfile client) to addrs |
785 | removeFromRosterFile ConfigFiles.modifyBuddies (clientUser client) to addrs | 828 | removeFromRosterFile ConfigFiles.modifyBuddies (clientUser client) (clientProfile client) to addrs |
786 | resolved_subs <- resolvedFromRoster ConfigFiles.getSubscribers (clientUser client) | 829 | resolved_subs <- resolvedFromRoster ConfigFiles.getSubscribers (clientUser client) (clientProfile client) |
787 | let is_subscribed = not . null $ intersect (map ((mu,).PeerKey) addrs) resolved_subs | 830 | let is_subscribed = not . null $ intersect (map ((mu,).PeerKey) addrs) resolved_subs |
788 | -- subscribers: "from" | 831 | -- subscribers: "from" |
789 | -- buddies: "to" | 832 | -- buddies: "to" |
@@ -831,10 +874,10 @@ clientSubscriptionRequest state fail k stanza chan = do | |||
831 | 874 | ||
832 | 875 | ||
833 | resolvedFromRoster | 876 | resolvedFromRoster |
834 | :: (L.ByteString -> IO [L.ByteString]) | 877 | :: (ConfigFiles.User -> ConfigFiles.Profile -> IO [L.ByteString]) |
835 | -> UserName -> IO [(Maybe UserName, ConnectionKey)] | 878 | -> UserName -> Text -> IO [(Maybe UserName, ConnectionKey)] |
836 | resolvedFromRoster doit u = do | 879 | resolvedFromRoster doit u profile = do |
837 | subs <- configText doit u | 880 | subs <- configText doit u profile |
838 | runTraversableT $ do | 881 | runTraversableT $ do |
839 | (mu,h,_) <- liftT $ splitJID `fmap` subs | 882 | (mu,h,_) <- liftT $ splitJID `fmap` subs |
840 | addr <- liftMT $ fmap nub $ resolvePeer h | 883 | addr <- liftMT $ fmap nub $ resolvePeer h |
@@ -870,7 +913,7 @@ peerSubscriptionRequest state fail k stanza chan = do | |||
870 | (_,fromtup) <- rewriteJIDForClient laddr from [] | 913 | (_,fromtup) <- rewriteJIDForClient laddr from [] |
871 | flip (maybe fail) mto_u $ \u -> do | 914 | flip (maybe fail) mto_u $ \u -> do |
872 | flip (maybe fail) mfrom_u $ \from_u -> do | 915 | flip (maybe fail) mfrom_u $ \from_u -> do |
873 | resolved_subs <- resolvedFromRoster ConfigFiles.getSubscribers u | 916 | resolved_subs <- resolvedFromRoster ConfigFiles.getSubscribers u (_todo {- profile -}) |
874 | let already_subscribed = elem (mfrom_u,k) resolved_subs | 917 | let already_subscribed = elem (mfrom_u,k) resolved_subs |
875 | is_wanted = case stanzaType stanza of | 918 | is_wanted = case stanzaType stanza of |
876 | PresenceRequestSubscription b -> b | 919 | PresenceRequestSubscription b -> b |
@@ -900,9 +943,9 @@ peerSubscriptionRequest state fail k stanza chan = do | |||
900 | 943 | ||
901 | already_pending <- | 944 | already_pending <- |
902 | if is_wanted then | 945 | if is_wanted then |
903 | addToRosterFile ConfigFiles.modifyPending u from' addrs | 946 | addToRosterFile ConfigFiles.modifyPending u (_todo {- profile -}) from' addrs |
904 | else do | 947 | else do |
905 | removeFromRosterFile ConfigFiles.modifySubscribers u from' addrs | 948 | removeFromRosterFile ConfigFiles.modifySubscribers u (_todo {- profile -}) from' addrs |
906 | reply <- makeInformSubscription "jabber:server" to from is_wanted | 949 | reply <- makeInformSubscription "jabber:server" to from is_wanted |
907 | sendModifiedStanzaToPeer reply chan | 950 | sendModifiedStanzaToPeer reply chan |
908 | return False | 951 | return False |
@@ -933,9 +976,9 @@ clientInformSubscription state fail k stanza = do | |||
933 | let (mu,h,mr) = splitJID to | 976 | let (mu,h,mr) = splitJID to |
934 | addrs <- resolvePeer h | 977 | addrs <- resolvePeer h |
935 | -- remove from pending | 978 | -- remove from pending |
936 | buds <- resolvedFromRoster ConfigFiles.getBuddies (clientUser client) | 979 | buds <- resolvedFromRoster ConfigFiles.getBuddies (clientUser client) (clientProfile client) |
937 | let is_buddy = not . null $ map ((mu,) . PeerKey) addrs `intersect` buds | 980 | let is_buddy = not . null $ map ((mu,) . PeerKey) addrs `intersect` buds |
938 | removeFromRosterFile ConfigFiles.modifyPending (clientUser client) to addrs | 981 | removeFromRosterFile ConfigFiles.modifyPending (clientUser client) (clientProfile client) to addrs |
939 | let (relationship,addf,remf) = | 982 | let (relationship,addf,remf) = |
940 | case stanzaType stanza of | 983 | case stanzaType stanza of |
941 | PresenceInformSubscription True -> | 984 | PresenceInformSubscription True -> |
@@ -947,8 +990,8 @@ clientInformSubscription state fail k stanza = do | |||
947 | else "none" ) | 990 | else "none" ) |
948 | , ConfigFiles.modifyOthers | 991 | , ConfigFiles.modifyOthers |
949 | , ConfigFiles.modifySubscribers ) | 992 | , ConfigFiles.modifySubscribers ) |
950 | addToRosterFile addf (clientUser client) to addrs | 993 | addToRosterFile addf (clientUser client) (clientProfile client) to addrs |
951 | removeFromRosterFile remf (clientUser client) to addrs | 994 | removeFromRosterFile remf (clientUser client) (clientProfile client) to addrs |
952 | 995 | ||
953 | do | 996 | do |
954 | cbu <- atomically $ readTVar (clientsByUser state) | 997 | cbu <- atomically $ readTVar (clientsByUser state) |
@@ -1009,8 +1052,8 @@ peerInformSubscription state fail k stanza = do | |||
1009 | -- This would allow us to answer anonymous probes with 'unsubscribed'. | 1052 | -- This would allow us to answer anonymous probes with 'unsubscribed'. |
1010 | flip (maybe fail) muser $ \user -> do | 1053 | flip (maybe fail) muser $ \user -> do |
1011 | addrs <- resolvePeer from_h | 1054 | addrs <- resolvePeer from_h |
1012 | was_solicited <- removeFromRosterFile ConfigFiles.modifySolicited user from'' addrs | 1055 | was_solicited <- removeFromRosterFile ConfigFiles.modifySolicited user (_todo {- profile -}) from'' addrs |
1013 | subs <- resolvedFromRoster ConfigFiles.getSubscribers user | 1056 | subs <- resolvedFromRoster ConfigFiles.getSubscribers user (_todo {- profile -}) |
1014 | let is_sub = not . null $ map ((from_u,) . PeerKey) addrs `intersect` subs | 1057 | let is_sub = not . null $ map ((from_u,) . PeerKey) addrs `intersect` subs |
1015 | let (relationship,addf,remf) = | 1058 | let (relationship,addf,remf) = |
1016 | case stanzaType stanza of | 1059 | case stanzaType stanza of |
@@ -1023,8 +1066,8 @@ peerInformSubscription state fail k stanza = do | |||
1023 | else "none") | 1066 | else "none") |
1024 | , ConfigFiles.modifyOthers | 1067 | , ConfigFiles.modifyOthers |
1025 | , ConfigFiles.modifyBuddies ) | 1068 | , ConfigFiles.modifyBuddies ) |
1026 | addToRosterFile addf user from'' addrs | 1069 | addToRosterFile addf user (_todo {- profile -}) from'' addrs |
1027 | removeFromRosterFile remf user from'' addrs | 1070 | removeFromRosterFile remf user (_todo {- profile -}) from'' addrs |
1028 | 1071 | ||
1029 | hostname <- textHostName | 1072 | hostname <- textHostName |
1030 | let to' = unsplitJID (Just user, hostname, Nothing) | 1073 | let to' = unsplitJID (Just user, hostname, Nothing) |
diff --git a/Presence/XMPPServer.hs b/Presence/XMPPServer.hs index 5a0ed20e..6f4a191b 100644 --- a/Presence/XMPPServer.hs +++ b/Presence/XMPPServer.hs | |||
@@ -134,7 +134,7 @@ data StanzaType | |||
134 | = Unrecognized | 134 | = Unrecognized |
135 | | Ping | 135 | | Ping |
136 | | Pong | 136 | | Pong |
137 | | RequestResource (Maybe Text) | 137 | | RequestResource (Maybe Text) (Maybe Text) -- ^ Client's name for this host followed by client's requested resource id. |
138 | | SetResource | 138 | | SetResource |
139 | | SessionRequest | 139 | | SessionRequest |
140 | | UnrecognizedQuery Name | 140 | | UnrecognizedQuery Name |
@@ -179,39 +179,40 @@ type Stanza = StanzaWrap (LockedChan XML.Event) | |||
179 | 179 | ||
180 | data XMPPServerParameters = | 180 | data XMPPServerParameters = |
181 | XMPPServerParameters | 181 | XMPPServerParameters |
182 | { -- | Called when a client requests a resource id. The Maybe value is the | 182 | { -- | Called when a client requests a resource id. The first Maybe indicates |
183 | -- client's preference. | 183 | -- the name the client referred to this server by. The second Maybe is the |
184 | xmppChooseResourceName :: ConnectionKey -> SockAddr -> Maybe Text -> IO Text | 184 | -- client's preferred resource name. |
185 | xmppChooseResourceName :: ConnectionKey -> SockAddr -> Maybe Text -> Maybe Text -> IO Text | ||
185 | , -- | This should indicate the server's hostname that all client's see. | 186 | , -- | This should indicate the server's hostname that all client's see. |
186 | xmppTellMyNameToClient :: IO Text | 187 | xmppTellMyNameToClient :: IO Text |
187 | , xmppTellMyNameToPeer :: SockAddr -> IO Text | 188 | , xmppTellMyNameToPeer :: SockAddr -> IO Text |
188 | , xmppTellClientHisName :: ConnectionKey -> IO Text | 189 | , xmppTellClientHisName :: ConnectionKey -> IO Text |
189 | , xmppTellPeerHisName :: ConnectionKey -> IO Text | 190 | , xmppTellPeerHisName :: ConnectionKey -> IO Text |
190 | , xmppNewConnection :: ConnectionKey -> SockAddr -> TChan Stanza -> IO () | 191 | , xmppNewConnection :: ConnectionKey -> SockAddr -> TChan Stanza -> IO () |
191 | , xmppEOF :: ConnectionKey -> IO () | 192 | , xmppEOF :: ConnectionKey -> IO () |
192 | , xmppRosterBuddies :: ConnectionKey -> IO [Text] | 193 | , xmppRosterBuddies :: ConnectionKey -> IO [Text] |
193 | , xmppRosterSubscribers :: ConnectionKey -> IO [Text] | 194 | , xmppRosterSubscribers :: ConnectionKey -> IO [Text] |
194 | , xmppRosterSolicited :: ConnectionKey -> IO [Text] | 195 | , xmppRosterSolicited :: ConnectionKey -> IO [Text] |
195 | , xmppRosterOthers :: ConnectionKey -> IO [Text] | 196 | , xmppRosterOthers :: ConnectionKey -> IO [Text] |
196 | , -- | Called when after sending a roster to a client. Usually this means | 197 | , -- | Called when after sending a roster to a client. Usually this means |
197 | -- the client status should change from "available" to "interested". | 198 | -- the client status should change from "available" to "interested". |
198 | xmppSubscribeToRoster :: ConnectionKey -> IO () | 199 | xmppSubscribeToRoster :: ConnectionKey -> IO () |
199 | -- , xmppLookupClientJID :: ConnectionKey -> IO Text | 200 | -- , xmppLookupClientJID :: ConnectionKey -> IO Text |
200 | , xmppTellClientNameOfPeer :: ConnectionKey -> [Text] -> IO Text | 201 | , xmppTellClientNameOfPeer :: ConnectionKey -> [Text] -> IO Text |
201 | , xmppDeliverMessage :: (IO ()) -> Stanza -> IO () | 202 | , xmppDeliverMessage :: (IO ()) -> Stanza -> IO () |
202 | -- | Called whenever a local client's presence changes. | 203 | -- | Called whenever a local client's presence changes. |
203 | , xmppInformClientPresence :: ConnectionKey -> Stanza -> IO () | 204 | , xmppInformClientPresence :: ConnectionKey -> Stanza -> IO () |
204 | -- | Called whenever a remote peer's presence changes. | 205 | -- | Called whenever a remote peer's presence changes. |
205 | , xmppInformPeerPresence :: ConnectionKey -> Stanza -> IO () | 206 | , xmppInformPeerPresence :: ConnectionKey -> Stanza -> IO () |
206 | , -- | Called when a remote peer requests our status. | 207 | , -- | Called when a remote peer requests our status. |
207 | xmppAnswerProbe :: ConnectionKey -> Stanza -> TChan Stanza -> IO () | 208 | xmppAnswerProbe :: ConnectionKey -> Stanza -> TChan Stanza -> IO () |
208 | , xmppClientSubscriptionRequest :: IO () -> ConnectionKey -> Stanza -> TChan Stanza -> IO () | 209 | , xmppClientSubscriptionRequest :: IO () -> ConnectionKey -> Stanza -> TChan Stanza -> IO () |
209 | , -- | Called when a remote peer sends subscription request. | 210 | , -- | Called when a remote peer sends subscription request. |
210 | xmppPeerSubscriptionRequest :: IO () -> ConnectionKey -> Stanza -> TChan Stanza -> IO () | 211 | xmppPeerSubscriptionRequest :: IO () -> ConnectionKey -> Stanza -> TChan Stanza -> IO () |
211 | , xmppClientInformSubscription :: IO () -> ConnectionKey -> Stanza -> IO () | 212 | , xmppClientInformSubscription :: IO () -> ConnectionKey -> Stanza -> IO () |
212 | , -- | Called when a remote peer informs us of our subscription status. | 213 | , -- | Called when a remote peer informs us of our subscription status. |
213 | xmppPeerInformSubscription :: IO () -> ConnectionKey -> Stanza -> IO () | 214 | xmppPeerInformSubscription :: IO () -> ConnectionKey -> Stanza -> IO () |
214 | , xmppVerbosity :: IO Int | 215 | , xmppVerbosity :: IO Int |
215 | } | 216 | } |
216 | 217 | ||
217 | 218 | ||
@@ -584,9 +585,9 @@ grokStanzaIQSet stanza = do | |||
584 | case fmap tagName mchild of | 585 | case fmap tagName mchild of |
585 | Just "{urn:ietf:params:xml:ns:xmpp-bind}resource" -> do | 586 | Just "{urn:ietf:params:xml:ns:xmpp-bind}resource" -> do |
586 | rsc <- XML.content -- TODO: MonadThrow??? | 587 | rsc <- XML.content -- TODO: MonadThrow??? |
587 | return . Just $ RequestResource (Just rsc) | 588 | return . Just $ RequestResource Nothing (Just rsc) |
588 | Just _ -> return Nothing | 589 | Just _ -> return Nothing |
589 | Nothing -> return . Just $ RequestResource Nothing | 590 | Nothing -> return . Just $ RequestResource Nothing Nothing |
590 | "{urn:ietf:params:xml:ns:xmpp-session}session" -> do | 591 | "{urn:ietf:params:xml:ns:xmpp-session}session" -> do |
591 | return $ Just SessionRequest | 592 | return $ Just SessionRequest |
592 | _ -> return Nothing | 593 | _ -> return Nothing |
@@ -886,10 +887,10 @@ xmppInbound :: Server ConnectionKey SockAddr ReleaseKey XML.Event | |||
886 | -> XMPPServerParameters | 887 | -> XMPPServerParameters |
887 | -> ConnectionKey | 888 | -> ConnectionKey |
888 | -> SockAddr | 889 | -> SockAddr |
889 | -> FlagCommand -- ^ action to check whether the connection needs a ping | 890 | -> FlagCommand -- ^ action to check whether the connection needs a ping |
890 | -> TChan Stanza -- ^ channel to announce incomming stanzas on | 891 | -> TChan Stanza -- ^ channel to announce incoming stanzas on |
891 | -> TChan Stanza -- ^ channel used to send stanzas | 892 | -> TChan Stanza -- ^ channel used to send stanzas |
892 | -> TMVar () -- ^ mvar that is filled when the connection quits | 893 | -> TMVar () -- ^ mvar that is filled when the connection quits |
893 | -> Sink XML.Event IO () | 894 | -> Sink XML.Event IO () |
894 | xmppInbound sv xmpp k laddr pingflag stanzas output donevar = doNestingXML $ do | 895 | xmppInbound sv xmpp k laddr pingflag stanzas output donevar = doNestingXML $ do |
895 | let (namespace,tellmyname,tellyourname) = case k of | 896 | let (namespace,tellmyname,tellyourname) = case k of |
@@ -906,6 +907,9 @@ xmppInbound sv xmpp k laddr pingflag stanzas output donevar = doNestingXML $ do | |||
906 | when (begindoc==EventBeginDocument) $ do | 907 | when (begindoc==EventBeginDocument) $ do |
907 | whenJust nextElement $ \xml -> do | 908 | whenJust nextElement $ \xml -> do |
908 | withJust (elementAttrs "stream" xml) $ \stream_attrs -> do | 909 | withJust (elementAttrs "stream" xml) $ \stream_attrs -> do |
910 | -- liftIO $ hPutStrLn stderr $ "STREAM ATTRS "++show stream_attrs | ||
911 | let stream_name = lookupAttrib "to" stream_attrs | ||
912 | -- xmpp_version = lookupAttrib "version" stream_attrs | ||
909 | fix $ \loop -> do | 913 | fix $ \loop -> do |
910 | -- liftIO . wlog $ "waiting for stanza." | 914 | -- liftIO . wlog $ "waiting for stanza." |
911 | (chan,clsrs) <- liftIO . atomically $ | 915 | (chan,clsrs) <- liftIO . atomically $ |
@@ -916,9 +920,9 @@ xmppInbound sv xmpp k laddr pingflag stanzas output donevar = doNestingXML $ do | |||
916 | writeLChan chan stanzaTag | 920 | writeLChan chan stanzaTag |
917 | modifyTVar' clsrs (fmap (closerFor stanzaTag:)) | 921 | modifyTVar' clsrs (fmap (closerFor stanzaTag:)) |
918 | copyToChannel id chan clsrs =$= do | 922 | copyToChannel id chan clsrs =$= do |
919 | let mid = lookupAttrib "id" (tagAttrs stanzaTag) | 923 | let mid = lookupAttrib "id" $ tagAttrs stanzaTag |
920 | mfrom = lookupAttrib "from" (tagAttrs stanzaTag) | 924 | mfrom = lookupAttrib "from" $ tagAttrs stanzaTag |
921 | mto = lookupAttrib "to" (tagAttrs stanzaTag) | 925 | mto = lookupAttrib "to" $ tagAttrs stanzaTag |
922 | dispatch <- grokStanza namespace stanzaTag | 926 | dispatch <- grokStanza namespace stanzaTag |
923 | let unrecog = do | 927 | let unrecog = do |
924 | let stype = Unrecognized | 928 | let stype = Unrecognized |
@@ -960,14 +964,15 @@ xmppInbound sv xmpp k laddr pingflag stanzas output donevar = doNestingXML $ do | |||
960 | } | 964 | } |
961 | #endif | 965 | #endif |
962 | stype -> ioWriteChan stanzas Stanza | 966 | stype -> ioWriteChan stanzas Stanza |
963 | { stanzaType = stype | 967 | { stanzaType = case stype of |
964 | , stanzaId = mid | 968 | RequestResource _ rsc -> RequestResource stream_name rsc |
965 | , stanzaTo = mto | 969 | , stanzaId = mid |
966 | , stanzaFrom = mfrom | 970 | , stanzaTo = mto |
967 | , stanzaChan = chan | 971 | , stanzaFrom = mfrom |
968 | , stanzaClosers = clsrs | 972 | , stanzaChan = chan |
973 | , stanzaClosers = clsrs | ||
969 | , stanzaInterrupt = donevar | 974 | , stanzaInterrupt = donevar |
970 | , stanzaOrigin = NetworkOrigin k output | 975 | , stanzaOrigin = NetworkOrigin k output |
971 | } | 976 | } |
972 | awaitCloser stanza_lvl | 977 | awaitCloser stanza_lvl |
973 | liftIO . atomically $ writeTVar clsrs Nothing | 978 | liftIO . atomically $ writeTVar clsrs Nothing |
@@ -1670,9 +1675,9 @@ monitor sv params xmpp = do | |||
1670 | case stanzaOrigin stanza of | 1675 | case stanzaOrigin stanza of |
1671 | NetworkOrigin k@(ClientKey {}) replyto -> | 1676 | NetworkOrigin k@(ClientKey {}) replyto -> |
1672 | case stanzaType stanza of | 1677 | case stanzaType stanza of |
1673 | RequestResource wanted -> do | 1678 | RequestResource clientsNameForMe wanted -> do |
1674 | sockaddr <- socketFromKey sv k | 1679 | sockaddr <- socketFromKey sv k |
1675 | rsc <- xmppChooseResourceName xmpp k sockaddr wanted | 1680 | rsc <- xmppChooseResourceName xmpp k sockaddr clientsNameForMe wanted |
1676 | let reply = iq_bind_reply (stanzaId stanza) rsc | 1681 | let reply = iq_bind_reply (stanzaId stanza) rsc |
1677 | -- sendReply quitVar SetResource reply replyto | 1682 | -- sendReply quitVar SetResource reply replyto |
1678 | hostname <- xmppTellMyNameToClient xmpp | 1683 | hostname <- xmppTellMyNameToClient xmpp |