diff options
Diffstat (limited to 'Presence')
-rw-r--r-- | Presence/SendMessage.hs | 17 | ||||
-rw-r--r-- | Presence/XMPP.hs | 7 | ||||
-rw-r--r-- | Presence/XMPPTypes.hs | 1 | ||||
-rw-r--r-- | Presence/main.hs | 1 |
4 files changed, 19 insertions, 7 deletions
diff --git a/Presence/SendMessage.hs b/Presence/SendMessage.hs index 6e8ea2b9..d1db7a4f 100644 --- a/Presence/SendMessage.hs +++ b/Presence/SendMessage.hs | |||
@@ -1,8 +1,10 @@ | |||
1 | {-# LANGUAGE CPP #-} | 1 | {-# LANGUAGE CPP #-} |
2 | {-# LANGUAGE TypeFamilies #-} | 2 | {-# LANGUAGE TypeFamilies #-} |
3 | {-# LANGUAGE FlexibleContexts #-} | ||
3 | module SendMessage | 4 | module SendMessage |
4 | ( sendMessage | 5 | ( sendMessage |
5 | , CommandCache(..) | 6 | , CommandCache(..) |
7 | , ThreadChannelCommand(..) | ||
6 | , newOutgoingConnections | 8 | , newOutgoingConnections |
7 | , OutgoingConnections | 9 | , OutgoingConnections |
8 | ) where | 10 | ) where |
@@ -47,7 +49,7 @@ import Network.Socket | |||
47 | import XMPPTypes (Peer(..),discardPort,peerAddr,withPort,socketFamily) | 49 | import XMPPTypes (Peer(..),discardPort,peerAddr,withPort,socketFamily) |
48 | import SocketLike | 50 | import SocketLike |
49 | import ServerC (packetSink) | 51 | import ServerC (packetSink) |
50 | import ControlMaybe (handleIO,handleIO_) | 52 | import ControlMaybe |
51 | import Data.Conduit (Sink,Source) | 53 | import Data.Conduit (Sink,Source) |
52 | import qualified Data.ByteString as S (ByteString) | 54 | import qualified Data.ByteString as S (ByteString) |
53 | import XMLToByteStrings | 55 | import XMLToByteStrings |
@@ -64,11 +66,12 @@ modifyIORef' ref f = do | |||
64 | 66 | ||
65 | class CommandCache cache where | 67 | class CommandCache cache where |
66 | type CacheableCommand cache | 68 | type CacheableCommand cache |
67 | |||
68 | emptyCache :: cache | 69 | emptyCache :: cache |
69 | |||
70 | updateCache :: CacheableCommand cache -> cache -> cache | 70 | updateCache :: CacheableCommand cache -> cache -> cache |
71 | 71 | ||
72 | class ThreadChannelCommand cmd where | ||
73 | isQuitCommand :: cmd -> Bool | ||
74 | |||
72 | 75 | ||
73 | data OutgoingConnections cache = | 76 | data OutgoingConnections cache = |
74 | OutgoingConnections (TVar (Map Peer (TChan (CacheableCommand cache), ThreadId))) | 77 | OutgoingConnections (TVar (Map Peer (TChan (CacheableCommand cache), ThreadId))) |
@@ -91,7 +94,7 @@ newOutgoingConnections interpretCommands = do | |||
91 | 94 | ||
92 | 95 | ||
93 | sendMessage | 96 | sendMessage |
94 | :: CommandCache a => | 97 | :: (CommandCache a, ThreadChannelCommand (CacheableCommand a)) => |
95 | OutgoingConnections a -> CacheableCommand a -> Peer -> IO () | 98 | OutgoingConnections a -> CacheableCommand a -> Peer -> IO () |
96 | sendMessage (OutgoingConnections cons interpretCommands) msg peer0 = do | 99 | sendMessage (OutgoingConnections cons interpretCommands) msg peer0 = do |
97 | let peer = discardPort peer0 | 100 | let peer = discardPort peer0 |
@@ -136,14 +139,16 @@ connect_to_server chan peer toPeer = (>> return ()) . runMaybeT $ do | |||
136 | fix $ \sendmsgs -> do | 139 | fix $ \sendmsgs -> do |
137 | connected <- liftIO . async $ connect' (peerAddr peer) port | 140 | connected <- liftIO . async $ connect' (peerAddr peer) port |
138 | 141 | ||
139 | sock <- MaybeT . fix $ \loop -> do | 142 | msock <- MaybeT . fix $ \loop -> do |
140 | e <- atomically $ orElse | 143 | e <- atomically $ orElse |
141 | (fmap Right $ waitSTM connected) | 144 | (fmap Right $ waitSTM connected) |
142 | (fmap Left $ readTChan chan) | 145 | (fmap Left $ readTChan chan) |
143 | case e of | 146 | case e of |
147 | Left cmd | isQuitCommand cmd -> return Nothing | ||
144 | Left cmd -> cacheCmd cmd cached >> loop | 148 | Left cmd -> cacheCmd cmd cached >> loop |
145 | Right sock -> return sock | 149 | Right sock -> return (Just sock) |
146 | 150 | ||
151 | withJust msock $ \sock -> do | ||
147 | retry <- do | 152 | retry <- do |
148 | (cache,snk) <- liftIO $ do | 153 | (cache,snk) <- liftIO $ do |
149 | h <- socketToHandle sock ReadWriteMode | 154 | h <- socketToHandle sock ReadWriteMode |
diff --git a/Presence/XMPP.hs b/Presence/XMPP.hs index 2c01d456..3caad740 100644 --- a/Presence/XMPP.hs +++ b/Presence/XMPP.hs | |||
@@ -885,6 +885,10 @@ instance CommandCache CachedMessages where | |||
885 | updateCache (Rejection from to) cache = | 885 | updateCache (Rejection from to) cache = |
886 | cache { approvals= mmInsert (False,from) to $ approvals cache } | 886 | cache { approvals= mmInsert (False,from) to $ approvals cache } |
887 | 887 | ||
888 | instance ThreadChannelCommand OutBoundMessage where | ||
889 | isQuitCommand Disconnect = True | ||
890 | isQuitCommand _ = False | ||
891 | |||
888 | mmInsert val key mm = Map.alter f key mm | 892 | mmInsert val key mm = Map.alter f key mm |
889 | where | 893 | where |
890 | f Nothing = Just $ Set.singleton val | 894 | f Nothing = Just $ Set.singleton val |
@@ -993,7 +997,8 @@ toPeer sock cache chan fail = do | |||
993 | Rejection from to -> do | 997 | Rejection from to -> do |
994 | liftIO . debugL $ "sending rejection "<++>bshow (from,to) | 998 | liftIO . debugL $ "sending rejection "<++>bshow (from,to) |
995 | sendApproval False from to | 999 | sendApproval False from to |
996 | loop | 1000 | Disconnect -> return () |
1001 | when (not . isQuitCommand $ event) loop | ||
997 | send goodbyePeer | 1002 | send goodbyePeer |
998 | 1003 | ||
999 | 1004 | ||
diff --git a/Presence/XMPPTypes.hs b/Presence/XMPPTypes.hs index 8d0bd242..6b0d9ed1 100644 --- a/Presence/XMPPTypes.hs +++ b/Presence/XMPPTypes.hs | |||
@@ -244,6 +244,7 @@ data OutBoundMessage = OutBoundPresence Presence | |||
244 | | Solicitation JID JID | 244 | | Solicitation JID JID |
245 | | Approval JID JID | 245 | | Approval JID JID |
246 | | Rejection JID JID | 246 | | Rejection JID JID |
247 | | Disconnect | ||
247 | deriving Prelude.Show | 248 | deriving Prelude.Show |
248 | 249 | ||
249 | getNamesForPeer :: Peer -> IO [S.ByteString] | 250 | getNamesForPeer :: Peer -> IO [S.ByteString] |
diff --git a/Presence/main.hs b/Presence/main.hs index dedd546a..593bb4bb 100644 --- a/Presence/main.hs +++ b/Presence/main.hs | |||
@@ -385,6 +385,7 @@ instance JabberPeerSession PeerSession where | |||
385 | let offline jid = Presence jid Offline | 385 | let offline jid = Presence jid Offline |
386 | unrefFromMap (remoteUsers . peer_global $ session) (peer_name session) | 386 | unrefFromMap (remoteUsers . peer_global $ session) (peer_name session) |
387 | $ do | 387 | $ do |
388 | sendPeerMessage session Disconnect | ||
388 | debugStr ("unrefFromMap!") | 389 | debugStr ("unrefFromMap!") |
389 | js <- fmap (MM.toAscList) (readTVarIO . announced $ session) | 390 | js <- fmap (MM.toAscList) (readTVarIO . announced $ session) |
390 | forM_ js $ \(u,rs) -> do | 391 | forM_ js $ \(u,rs) -> do |