diff options
Diffstat (limited to 'Presence/XMPPServer.hs')
-rw-r--r-- | Presence/XMPPServer.hs | 78 |
1 files changed, 76 insertions, 2 deletions
diff --git a/Presence/XMPPServer.hs b/Presence/XMPPServer.hs index 7e42c7ae..062fcacb 100644 --- a/Presence/XMPPServer.hs +++ b/Presence/XMPPServer.hs | |||
@@ -6,6 +6,7 @@ | |||
6 | -- {-# LANGUAGE GADTs #-} | 6 | -- {-# LANGUAGE GADTs #-} |
7 | module XMPPServer where -- ( listenForXmppClients ) where | 7 | module XMPPServer where -- ( listenForXmppClients ) where |
8 | 8 | ||
9 | import Todo | ||
9 | import Data.HList.TypeEqGeneric1() | 10 | import Data.HList.TypeEqGeneric1() |
10 | import Data.HList.TypeCastGeneric1() | 11 | import Data.HList.TypeCastGeneric1() |
11 | import ByteStringOperators | 12 | import ByteStringOperators |
@@ -14,6 +15,7 @@ import Server | |||
14 | import Data.ByteString.Lazy.Char8 as L | 15 | import Data.ByteString.Lazy.Char8 as L |
15 | ( hPutStrLn | 16 | ( hPutStrLn |
16 | , unlines | 17 | , unlines |
18 | , splitWith | ||
17 | , ByteString | 19 | , ByteString |
18 | , pack | 20 | , pack |
19 | , unpack ) | 21 | , unpack ) |
@@ -47,6 +49,8 @@ import Control.Exception | |||
47 | import Text.Show.ByteString as L | 49 | import Text.Show.ByteString as L |
48 | import Data.Binary.Builder as B | 50 | import Data.Binary.Builder as B |
49 | import Data.Binary.Put | 51 | import Data.Binary.Put |
52 | import qualified Data.Map as Map | ||
53 | import GHC.Conc | ||
50 | 54 | ||
51 | -- | Jabber ID (JID) datatype | 55 | -- | Jabber ID (JID) datatype |
52 | data JID = JID { name :: Maybe ByteString | 56 | data JID = JID { name :: Maybe ByteString |
@@ -98,6 +102,9 @@ class XMPPSession session where | |||
98 | closeSession :: session -> IO () | 102 | closeSession :: session -> IO () |
99 | subscribe :: session -> Maybe JID -> IO (TChan Presence) | 103 | subscribe :: session -> Maybe JID -> IO (TChan Presence) |
100 | 104 | ||
105 | class XMPPConfig config where | ||
106 | getBuddies :: config -> ByteString -> IO [ByteString] | ||
107 | getSubscribers :: config -> ByteString -> IO [ByteString] | ||
101 | 108 | ||
102 | greet host = L.unlines | 109 | greet host = L.unlines |
103 | [ "<?xml version='1.0'?>" | 110 | [ "<?xml version='1.0'?>" |
@@ -353,5 +360,72 @@ listenForRemotePeers session_factory port st = do | |||
353 | dopkt | 360 | dopkt |
354 | start | 361 | start |
355 | 362 | ||
356 | seekRemotePeers session_factory st = do | 363 | newServerConnections = atomically $ newTVar Map.empty |
357 | return () | 364 | {- |
365 | sendMessage cons msg peer = do | ||
366 | (is_new,entry) <- atomically $ do | ||
367 | consmap <- readTVar cons | ||
368 | let found = Map.lookup peer consmap | ||
369 | newEntry = () | ||
370 | entry = maybe newEntry id found | ||
371 | is_new = isNothing found | ||
372 | when is_new | ||
373 | $ writeTVar cons (Map.insert peer entry consmap) | ||
374 | return (is_new,entry) | ||
375 | L.putStrLn $ "sendMessage ->"<++>peer<++>": "<++>bshow msg | ||
376 | when is_new $ connect_to_server entry peer | ||
377 | |||
378 | -} | ||
379 | |||
380 | sendMessage cons msg peer = do | ||
381 | found <- atomically $ do | ||
382 | consmap <- readTVar cons | ||
383 | return (Map.lookup peer consmap) | ||
384 | let newEntry = do | ||
385 | chan <- atomically newTChan | ||
386 | t <- forkIO $ connect_to_server chan peer | ||
387 | return (chan,t) | ||
388 | entry <- maybe newEntry | ||
389 | ( \(chan,t) -> do | ||
390 | st <- threadStatus t | ||
391 | case st of | ||
392 | ThreadRunning -> return (chan,t) | ||
393 | _ -> newEntry | ||
394 | ) | ||
395 | found | ||
396 | L.putStrLn $ "sendMessage ->"<++>peer<++>": "<++>bshow msg | ||
397 | |||
398 | connect_to_server chan peer = return () | ||
399 | |||
400 | parseJID :: ByteString -> JID | ||
401 | parseJID bjid = | ||
402 | let xs = L.splitWith (=='@') bjid | ||
403 | ys = L.splitWith (=='/') (last xs) | ||
404 | (name,server) | ||
405 | = case xs of | ||
406 | (n:s:_) -> (Just n,s) | ||
407 | (s:_) -> (Nothing,s) | ||
408 | rsrc = case ys of | ||
409 | (s:_:_) -> Just $ last ys | ||
410 | _ -> Nothing | ||
411 | in JID name server rsrc | ||
412 | |||
413 | seekRemotePeers :: XMPPConfig config => | ||
414 | (ByteString -> Bool) -> config -> TChan Presence -> IO b0 | ||
415 | seekRemotePeers is_peer config chan = do | ||
416 | server_connections <- newServerConnections | ||
417 | fix $ \loop -> do | ||
418 | event <- atomically $ readTChan chan | ||
419 | case event of | ||
420 | p@(Presence jid stat) -> do | ||
421 | L.putStrLn $ "seekRemotePeers: " <++> L.show jid <++> " " <++> bshow stat | ||
422 | runMaybeT $ do | ||
423 | u <- MaybeT . return $ name jid | ||
424 | subscribers <- liftIO $ getSubscribers config u | ||
425 | liftIO . L.putStrLn $ "subscribers: " <++> bshow subscribers | ||
426 | forM_ subscribers $ \bjid -> do | ||
427 | let jid = parseJID bjid | ||
428 | peer = server jid | ||
429 | when (is_peer peer) $ | ||
430 | liftIO $ sendMessage server_connections p peer | ||
431 | loop | ||