diff options
-rw-r--r-- | Presence/SendMessage.hs | 13 | ||||
-rw-r--r-- | Presence/XMPP.hs | 161 | ||||
-rw-r--r-- | Presence/XMPPTypes.hs | 34 | ||||
-rw-r--r-- | Presence/main.hs | 32 |
4 files changed, 228 insertions, 12 deletions
diff --git a/Presence/SendMessage.hs b/Presence/SendMessage.hs index d1db7a4f..8b4d00f7 100644 --- a/Presence/SendMessage.hs +++ b/Presence/SendMessage.hs | |||
@@ -1,6 +1,7 @@ | |||
1 | {-# LANGUAGE CPP #-} | 1 | {-# LANGUAGE CPP #-} |
2 | {-# LANGUAGE TypeFamilies #-} | 2 | {-# LANGUAGE TypeFamilies #-} |
3 | {-# LANGUAGE FlexibleContexts #-} | 3 | {-# LANGUAGE FlexibleContexts #-} |
4 | {-# LANGUAGE OverloadedStrings #-} | ||
4 | module SendMessage | 5 | module SendMessage |
5 | ( sendMessage | 6 | ( sendMessage |
6 | , CommandCache(..) | 7 | , CommandCache(..) |
@@ -46,13 +47,15 @@ import Network.Socket | |||
46 | , SocketType(..) | 47 | , SocketType(..) |
47 | ) | 48 | ) |
48 | 49 | ||
49 | import XMPPTypes (Peer(..),discardPort,peerAddr,withPort,socketFamily) | 50 | import XMPPTypes (Peer(..),discardPort,peerAddr,withPort,socketFamily,showPeer) |
50 | import SocketLike | 51 | import SocketLike |
51 | import ServerC (packetSink) | 52 | import ServerC (packetSink) |
52 | import ControlMaybe | 53 | import ControlMaybe |
53 | import Data.Conduit (Sink,Source) | 54 | import Data.Conduit (Sink,Source) |
54 | import qualified Data.ByteString as S (ByteString) | 55 | import qualified Data.ByteString as S (ByteString) |
55 | import XMLToByteStrings | 56 | import XMLToByteStrings |
57 | import Logging | ||
58 | import ByteStringOperators | ||
56 | 59 | ||
57 | type ByteStringSink = Sink S.ByteString IO () | 60 | type ByteStringSink = Sink S.ByteString IO () |
58 | 61 | ||
@@ -94,7 +97,7 @@ newOutgoingConnections interpretCommands = do | |||
94 | 97 | ||
95 | 98 | ||
96 | sendMessage | 99 | sendMessage |
97 | :: (CommandCache a, ThreadChannelCommand (CacheableCommand a)) => | 100 | :: (Show (CacheableCommand a), CommandCache a, ThreadChannelCommand (CacheableCommand a)) => |
98 | OutgoingConnections a -> CacheableCommand a -> Peer -> IO () | 101 | OutgoingConnections a -> CacheableCommand a -> Peer -> IO () |
99 | sendMessage (OutgoingConnections cons interpretCommands) msg peer0 = do | 102 | sendMessage (OutgoingConnections cons interpretCommands) msg peer0 = do |
100 | let peer = discardPort peer0 | 103 | let peer = discardPort peer0 |
@@ -192,7 +195,7 @@ type OutBoundXML sock cache msg = | |||
192 | -> Source IO [XML.Event] | 195 | -> Source IO [XML.Event] |
193 | 196 | ||
194 | handleOutgoingToPeer | 197 | handleOutgoingToPeer |
195 | :: SocketLike sock => | 198 | :: (SocketLike sock, Show msg) => |
196 | OutBoundXML sock cache msg | 199 | OutBoundXML sock cache msg |
197 | -> sock | 200 | -> sock |
198 | -> cache | 201 | -> cache |
@@ -201,11 +204,11 @@ handleOutgoingToPeer | |||
201 | -> IO (Maybe msg) | 204 | -> IO (Maybe msg) |
202 | handleOutgoingToPeer toPeer sock cache chan snk = do | 205 | handleOutgoingToPeer toPeer sock cache chan snk = do |
203 | p <- getPeerName sock | 206 | p <- getPeerName sock |
204 | -- L.putStrLn $ "(>P) connected " <++> showPeer (RemotePeer p) | 207 | debugL $ "(>P) connected " <++> showPeer (RemotePeer p) |
205 | failed <- newIORef Nothing | 208 | failed <- newIORef Nothing |
206 | let failure cmd = do | 209 | let failure cmd = do |
207 | writeIORef failed cmd | 210 | writeIORef failed cmd |
208 | -- putStrLn $ "Failed: " ++ show cmd | 211 | debugStr $ "Failed: " ++ show cmd |
209 | finally ( | 212 | finally ( |
210 | handleIO_ (return ()) $ toPeer sock cache chan failure `xmlToByteStrings` snk | 213 | handleIO_ (return ()) $ toPeer sock cache chan failure `xmlToByteStrings` snk |
211 | ) $ return () -- logging L.putStrLn $ "(>P) disconnected " <++> showPeer (RemotePeer p) | 214 | ) $ return () -- logging L.putStrLn $ "(>P) disconnected " <++> showPeer (RemotePeer p) |
diff --git a/Presence/XMPP.hs b/Presence/XMPP.hs index 6c802fb4..1c6336b9 100644 --- a/Presence/XMPP.hs +++ b/Presence/XMPP.hs | |||
@@ -24,12 +24,14 @@ import ControlMaybe | |||
24 | import XMLToByteStrings | 24 | import XMLToByteStrings |
25 | import SendMessage | 25 | import SendMessage |
26 | import Logging | 26 | import Logging |
27 | import Todo | ||
27 | 28 | ||
28 | import Data.Maybe (catMaybes) | 29 | import Data.Maybe (catMaybes) |
29 | import Data.HList | 30 | import Data.HList |
30 | import Network.Socket ( Family ) | 31 | import Network.Socket ( Family ) |
31 | import Control.Concurrent.STM | 32 | import Control.Concurrent.STM |
32 | import Data.Conduit | 33 | import Data.Conduit |
34 | import Data.Maybe | ||
33 | import Data.ByteString (ByteString) | 35 | import Data.ByteString (ByteString) |
34 | import qualified Data.ByteString.Lazy.Char8 as L | 36 | import qualified Data.ByteString.Lazy.Char8 as L |
35 | ( fromChunks | 37 | ( fromChunks |
@@ -42,7 +44,7 @@ import Control.Monad.Trans.Class | |||
42 | import Control.Monad.Trans.Maybe | 44 | import Control.Monad.Trans.Maybe |
43 | import Text.XML.Stream.Parse (def,parseBytes,content) | 45 | import Text.XML.Stream.Parse (def,parseBytes,content) |
44 | import Data.XML.Types as XML | 46 | import Data.XML.Types as XML |
45 | import qualified Data.Text as S (takeWhile) | 47 | import qualified Data.Text as S (Text,takeWhile) |
46 | import Data.Text.Encoding as S (decodeUtf8,encodeUtf8) | 48 | import Data.Text.Encoding as S (decodeUtf8,encodeUtf8) |
47 | import Data.Text.Lazy.Encoding as L (decodeUtf8) | 49 | import Data.Text.Lazy.Encoding as L (decodeUtf8) |
48 | import Data.Text.Lazy (toStrict) | 50 | import Data.Text.Lazy (toStrict) |
@@ -383,6 +385,7 @@ handleClientPresence session stanza = do | |||
383 | log $ "requesting presence: "<++>bshow stat' | 385 | log $ "requesting presence: "<++>bshow stat' |
384 | return () | 386 | return () |
385 | 387 | ||
388 | |||
386 | fromClient :: (MonadThrow m,MonadIO m, JabberClientSession session) => | 389 | fromClient :: (MonadThrow m,MonadIO m, JabberClientSession session) => |
387 | session -> TChan ClientCommands -> Sink XML.Event m () | 390 | session -> TChan ClientCommands -> Sink XML.Event m () |
388 | fromClient session cmdChan = doNestingXML $ do | 391 | fromClient session cmdChan = doNestingXML $ do |
@@ -421,6 +424,7 @@ fromClient session cmdChan = doNestingXML $ do | |||
421 | -> clientRejectsSubscription session stanza | 424 | -> clientRejectsSubscription session stanza |
422 | _ | stanza `isClientPresenceOf` presenceTypeOnline | 425 | _ | stanza `isClientPresenceOf` presenceTypeOnline |
423 | -> handleClientPresence session stanza | 426 | -> handleClientPresence session stanza |
427 | _ | isMessageStanza stanza -> handleClientMessage session stanza | ||
424 | _ | otherwise -> unhandledStanza | 428 | _ | otherwise -> unhandledStanza |
425 | 429 | ||
426 | awaitCloser stanza_lvl | 430 | awaitCloser stanza_lvl |
@@ -474,6 +478,7 @@ toClient session pchan cmdChan rchan = toClient' False False | |||
474 | CmdChan InterestedInRoster -> do | 478 | CmdChan InterestedInRoster -> do |
475 | liftIO . debugStr $ "Roster: interested" | 479 | liftIO . debugStr $ "Roster: interested" |
476 | toClient' isBound True | 480 | toClient' isBound True |
481 | CmdChan (Chat msg) -> return () -- TODO | ||
477 | -- CmdChan cmd -> liftIO (debugStr $ "unhandled event: "++show cmd) >> loop | 482 | -- CmdChan cmd -> liftIO (debugStr $ "unhandled event: "++show cmd) >> loop |
478 | RChan (RequestedSubscription who contact) -> do | 483 | RChan (RequestedSubscription who contact) -> do |
479 | jid <- liftIO $ getJID session | 484 | jid <- liftIO $ getJID session |
@@ -667,6 +672,23 @@ handlePeerPresence session stanza True = do | |||
667 | liftIO $ announcePresence session (Presence pjid stat') | 672 | liftIO $ announcePresence session (Presence pjid stat') |
668 | log $ bshow (Presence pjid stat') | 673 | log $ bshow (Presence pjid stat') |
669 | 674 | ||
675 | handlePeerMessage session stanza = do | ||
676 | withJust (lookupAttrib "from" (tagAttrs stanza)) $ \fromstr-> do | ||
677 | withJust (lookupAttrib "to" (tagAttrs stanza)) $ \tostr -> do | ||
678 | fromjid <- liftIO $ parseAddressJID (textToByteString fromstr) | ||
679 | tojid <- liftIO $ parseAddressJID (textToByteString tostr) | ||
680 | let log = liftIO . debugL . ("(P) " <++>) | ||
681 | log $ "handlePeerMessage "<++>bshow stanza | ||
682 | msg <- parseMessage ("{jabber:server}body" | ||
683 | ,"{jabber:server}subject" | ||
684 | ,"{jabber:server}thread" | ||
685 | ) | ||
686 | log | ||
687 | fromjid | ||
688 | tojid | ||
689 | stanza | ||
690 | liftIO $ sendChatToClient session msg | ||
691 | |||
670 | matchAttribMaybe name (Just value) attrs = | 692 | matchAttribMaybe name (Just value) attrs = |
671 | case find ( (==name) . fst) attrs of | 693 | case find ( (==name) . fst) attrs of |
672 | Just (_,[ContentText x]) | x==value -> True | 694 | Just (_,[ContentText x]) | x==value -> True |
@@ -692,6 +714,14 @@ isPresenceOf (EventBeginElement name attrs) testType | |||
692 | = True | 714 | = True |
693 | isPresenceOf _ _ = False | 715 | isPresenceOf _ _ = False |
694 | 716 | ||
717 | isMessageStanza (EventBeginElement name attrs) | ||
718 | | name=="{jabber:client}message" | ||
719 | = True | ||
720 | isMessageStanza (EventBeginElement name attrs) | ||
721 | | name=="{jabber:server}message" | ||
722 | = True | ||
723 | isMessageStanza _ = False | ||
724 | |||
695 | isClientPresenceOf (EventBeginElement name attrs) testType | 725 | isClientPresenceOf (EventBeginElement name attrs) testType |
696 | | name=="{jabber:client}presence" | 726 | | name=="{jabber:client}presence" |
697 | && matchAttribMaybe "type" testType attrs | 727 | && matchAttribMaybe "type" testType attrs |
@@ -878,6 +908,8 @@ fromPeer session = doNestingXML $ do | |||
878 | -> peerApprovesSubscription session stanza | 908 | -> peerApprovesSubscription session stanza |
879 | _ | stanza `isPresenceOf` presenceTypeUnsubscribed | 909 | _ | stanza `isPresenceOf` presenceTypeUnsubscribed |
880 | -> peerRejectsSubscription session stanza | 910 | -> peerRejectsSubscription session stanza |
911 | _ | isMessageStanza stanza | ||
912 | -> handlePeerMessage session stanza | ||
881 | _ -> unhandledStanza | 913 | _ -> unhandledStanza |
882 | 914 | ||
883 | awaitCloser stanza_lvl | 915 | awaitCloser stanza_lvl |
@@ -914,6 +946,7 @@ instance CommandCache CachedMessages where | |||
914 | cache { approvals= mmInsert (True,from) to $ approvals cache } | 946 | cache { approvals= mmInsert (True,from) to $ approvals cache } |
915 | updateCache (Rejection from to) cache = | 947 | updateCache (Rejection from to) cache = |
916 | cache { approvals= mmInsert (False,from) to $ approvals cache } | 948 | cache { approvals= mmInsert (False,from) to $ approvals cache } |
949 | updateCache (OutBoundMessage msg) cache = cache -- TODO | ||
917 | 950 | ||
918 | instance ThreadChannelCommand OutBoundMessage where | 951 | instance ThreadChannelCommand OutBoundMessage where |
919 | isQuitCommand Disconnect = True | 952 | isQuitCommand Disconnect = True |
@@ -991,12 +1024,15 @@ toPeer sock cache chan fail = do | |||
991 | (if approve then "subscribed" else "unsubscribed")) | 1024 | (if approve then "subscribed" else "unsubscribed")) |
992 | (if approve then Approval from to | 1025 | (if approve then Approval from to |
993 | else Rejection from to) | 1026 | else Rejection from to) |
1027 | sendMessage msg = | ||
1028 | sendOrFail (xmlifyMessageForPeer sock msg) | ||
1029 | (OutBoundMessage msg) | ||
994 | 1030 | ||
995 | 1031 | ||
996 | send greetPeer | 1032 | send greetPeer |
997 | forM_ (Map.assocs . approvals $ cache) $ \(to,froms) -> do | 1033 | forM_ (Map.assocs . approvals $ cache) $ \(to,froms) -> do |
998 | forM_ (Set.toList froms) $ \(approve,from) -> do | 1034 | forM_ (Set.toList froms) $ \(approve,from) -> do |
999 | liftIO $ debugL "sending cached approval..." | 1035 | liftIO $ debugL "sending cached approval/rejection..." |
1000 | sendApproval approve from to | 1036 | sendApproval approve from to |
1001 | forM_ (Map.assocs . presences $ cache) $ \(jid,st) -> do | 1037 | forM_ (Map.assocs . presences $ cache) $ \(jid,st) -> do |
1002 | sendPresence (Presence jid st) | 1038 | sendPresence (Presence jid st) |
@@ -1027,9 +1063,13 @@ toPeer sock cache chan fail = do | |||
1027 | Rejection from to -> do | 1063 | Rejection from to -> do |
1028 | liftIO . debugL $ "sending rejection "<++>bshow (from,to) | 1064 | liftIO . debugL $ "sending rejection "<++>bshow (from,to) |
1029 | sendApproval False from to | 1065 | sendApproval False from to |
1066 | OutBoundMessage msg -> sendMessage msg | ||
1030 | Disconnect -> return () | 1067 | Disconnect -> return () |
1031 | when (not . isQuitCommand $ event) loop | 1068 | when (not . isQuitCommand $ event) loop |
1032 | send goodbyePeer | 1069 | return () |
1070 | -- send goodbyePeer -- TODO: why does this cause an exception? | ||
1071 | -- Text/XML/Stream/Render.hs:169:5-15: | ||
1072 | -- Irrefutable pattern failed for pattern (sl : s') | ||
1033 | 1073 | ||
1034 | 1074 | ||
1035 | 1075 | ||
@@ -1079,3 +1119,118 @@ xmlifyPresenceForPeer sock (Presence jid stat) = do | |||
1079 | [ EventBeginElement "{jabber:server}show" [] | 1119 | [ EventBeginElement "{jabber:server}show" [] |
1080 | , EventContent (ContentText stat) | 1120 | , EventContent (ContentText stat) |
1081 | , EventEndElement "{jabber:server}show" ] | 1121 | , EventEndElement "{jabber:server}show" ] |
1122 | |||
1123 | xmlifyMessageForPeer sock msg = do | ||
1124 | addr <- getSocketName sock | ||
1125 | remote <- getPeerName sock | ||
1126 | let n = name (msgFrom msg) | ||
1127 | rsc = resource (msgFrom msg) | ||
1128 | jidstr = toStrict . L.decodeUtf8 | ||
1129 | $ n <$++> "@" <?++> showPeer (RemotePeer addr) <++?> "/" <++$> rsc | ||
1130 | tostr = toStrict . L.decodeUtf8 | ||
1131 | $ name (msgTo msg) <$++> "@" | ||
1132 | <?++> showPeer (RemotePeer remote) <++?> "/" | ||
1133 | <++$> resource (msgTo msg) | ||
1134 | return $ | ||
1135 | [ EventBeginElement "{jabber:server}message" | ||
1136 | [ attr "from" jidstr | ||
1137 | , attr "to" tostr | ||
1138 | ] | ||
1139 | ] | ||
1140 | ++ xmlifyMsgElements (msgLangMap msg) ++ | ||
1141 | [ EventEndElement "{jabber:server}message" ] | ||
1142 | |||
1143 | xmlifyMsgElements langmap = concatMap (uncurry langElements) . Map.toList $ langmap | ||
1144 | |||
1145 | langElements lang msg = | ||
1146 | ( maybeToList (msgSubject msg) | ||
1147 | >>= wrap "{jabber:server}subject" ) | ||
1148 | ++ ( maybeToList (msgBody msg) | ||
1149 | >>= wrap "{jabber:server}body" ) | ||
1150 | ++ ( Set.toList (msgElements msg) | ||
1151 | >>= wrapTriple ) | ||
1152 | where | ||
1153 | wrap name content = | ||
1154 | [ EventBeginElement name | ||
1155 | ( if lang/="" then [attr "xml:lang" lang] | ||
1156 | else [] ) | ||
1157 | , EventContent (ContentText content) | ||
1158 | , EventEndElement name | ||
1159 | ] | ||
1160 | wrapTriple (name,attrs,content) = | ||
1161 | [ EventBeginElement name attrs -- Note: we assume lang specified in attrs | ||
1162 | , EventContent (ContentText content) | ||
1163 | , EventEndElement name | ||
1164 | ] | ||
1165 | |||
1166 | |||
1167 | handleClientMessage session stanza = do | ||
1168 | let log = liftIO . debugL . ("(C) " <++>) | ||
1169 | log $ "handleClientMessage "<++>bshow stanza | ||
1170 | from <- liftIO $ getJID session | ||
1171 | withJust (lookupAttrib "to" (tagAttrs stanza)) $ \to_str -> do | ||
1172 | log $ " to = "<++>bshow to_str | ||
1173 | tojid <- liftIO $ parseHostNameJID (textToByteString to_str) | ||
1174 | msg <- parseMessage ("{jabber:client}body" | ||
1175 | ,"{jabber:client}subject" | ||
1176 | ,"{jabber:client}thread" | ||
1177 | ) | ||
1178 | log | ||
1179 | from | ||
1180 | tojid | ||
1181 | stanza | ||
1182 | liftIO $ sendChat session msg | ||
1183 | |||
1184 | {- | ||
1185 | unhandled-C: <message | ||
1186 | unhandled-C: type="chat" | ||
1187 | unhandled-C: id="purplea0a7fd24" | ||
1188 | unhandled-C: to="user@vm2" | ||
1189 | unhandled-C: xmlns="jabber:client"> | ||
1190 | unhandled-C: <active xmlns="http://jabber.org/protocol/chatstates"/> | ||
1191 | unhandled-C: <body> | ||
1192 | unhandled-C: hello dude | ||
1193 | unhandled-C: </body> | ||
1194 | unhandled-C: </message> | ||
1195 | -} | ||
1196 | parseMessage (bodytag,subjecttag,threadtag) log from tojid stanza = do | ||
1197 | let emptyMsg = LangSpecificMessage { msgBody=Nothing, msgSubject=Nothing, msgElements=Set.empty } | ||
1198 | parseChildren (th,cmap) = do | ||
1199 | child <- nextElement | ||
1200 | lvl <- nesting | ||
1201 | xmllang <- xmlLang | ||
1202 | let lang = maybe "" id xmllang | ||
1203 | let c = maybe emptyMsg id (Map.lookup lang cmap) | ||
1204 | log $ " child: "<++> bshow child | ||
1205 | case child of | ||
1206 | Just tag | tagName tag==bodytag | ||
1207 | -> do | ||
1208 | txt <- lift content | ||
1209 | awaitCloser lvl | ||
1210 | parseChildren (th,Map.insert lang (c { msgBody=Just txt }) cmap) | ||
1211 | Just tag | tagName tag==subjecttag | ||
1212 | -> do | ||
1213 | txt <- lift content | ||
1214 | awaitCloser lvl | ||
1215 | parseChildren (th,Map.insert lang (c { msgSubject=Just txt }) cmap) | ||
1216 | Just tag | tagName tag==threadtag | ||
1217 | -> do | ||
1218 | txt <- lift content | ||
1219 | awaitCloser lvl | ||
1220 | parseChildren (th {msgThreadContent=txt},cmap) | ||
1221 | Just tag -> do | ||
1222 | let nm = tagName tag | ||
1223 | attrs = tagAttrs tag | ||
1224 | elems = msgElements c | ||
1225 | txt <- lift content | ||
1226 | awaitCloser lvl | ||
1227 | parseChildren (th,Map.insert lang (c {msgElements=Set.insert (nm,attrs,txt) elems}) cmap) | ||
1228 | Nothing -> return (th,cmap) | ||
1229 | (th,langmap) <- parseChildren ( MessageThread {msgThreadParent=Nothing, msgThreadContent=""} | ||
1230 | , Map.empty ) | ||
1231 | return Message { | ||
1232 | msgTo = tojid, | ||
1233 | msgFrom = from, | ||
1234 | msgLangMap = langmap, | ||
1235 | msgThread = if msgThreadContent th/="" then Just th else Nothing | ||
1236 | } | ||
diff --git a/Presence/XMPPTypes.hs b/Presence/XMPPTypes.hs index b654b320..7ee09189 100644 --- a/Presence/XMPPTypes.hs +++ b/Presence/XMPPTypes.hs | |||
@@ -33,20 +33,24 @@ import Data.ByteString.Lazy.Char8 as L | |||
33 | , takeWhile | 33 | , takeWhile |
34 | , fromChunks | 34 | , fromChunks |
35 | ) | 35 | ) |
36 | import Text.Show.ByteString as L | 36 | import qualified Text.Show.ByteString as L |
37 | import qualified Data.Text as S hiding (pack) | ||
37 | import Data.Binary.Builder as B | 38 | import Data.Binary.Builder as B |
38 | import Data.Binary.Put | 39 | import Data.Binary.Put |
40 | import Data.Set as Set (Set) | ||
41 | import Data.Map as Map (Map) | ||
39 | import Control.DeepSeq | 42 | import Control.DeepSeq |
40 | import ByteStringOperators | 43 | import ByteStringOperators |
41 | import SocketLike | 44 | import SocketLike |
42 | import GetHostByAddr | 45 | import GetHostByAddr |
43 | import Data.Maybe (listToMaybe) | 46 | import Data.Maybe (listToMaybe) |
44 | import Data.XML.Types as XML (Event) | 47 | import Data.XML.Types as XML (Event,Name,Content) |
45 | 48 | ||
46 | data ClientCommands = | 49 | data ClientCommands = |
47 | Send [XML.Event] | 50 | Send [XML.Event] |
48 | | BoundToResource | 51 | | BoundToResource |
49 | | InterestedInRoster | 52 | | InterestedInRoster |
53 | | Chat Message | ||
50 | | QuitThread | 54 | | QuitThread |
51 | deriving Prelude.Show | 55 | deriving Prelude.Show |
52 | 56 | ||
@@ -73,6 +77,7 @@ class JabberClientSession session where | |||
73 | isBuddy :: session -> ByteString -> IO Bool | 77 | isBuddy :: session -> ByteString -> IO Bool |
74 | approveSubscriber :: session -> ByteString -> IO () | 78 | approveSubscriber :: session -> ByteString -> IO () |
75 | rejectSubscriber :: session -> ByteString -> IO () | 79 | rejectSubscriber :: session -> ByteString -> IO () |
80 | sendChat :: session -> Message -> IO () | ||
76 | 81 | ||
77 | class JabberPeerSession session where | 82 | class JabberPeerSession session where |
78 | data XMPPPeerClass session | 83 | data XMPPPeerClass session |
@@ -88,6 +93,7 @@ class JabberPeerSession session where | |||
88 | processApproval :: session -> ByteString -> JID -> IO () | 93 | processApproval :: session -> ByteString -> JID -> IO () |
89 | processRejection :: session -> ByteString -> JID -> IO () | 94 | processRejection :: session -> ByteString -> JID -> IO () |
90 | processRequest :: session -> ByteString -> JID -> IO () | 95 | processRequest :: session -> ByteString -> JID -> IO () |
96 | sendChatToClient :: session -> Message -> IO () | ||
91 | 97 | ||
92 | -- | Jabber ID (JID) datatype | 98 | -- | Jabber ID (JID) datatype |
93 | data JID = JID { name :: Maybe ByteString | 99 | data JID = JID { name :: Maybe ByteString |
@@ -243,11 +249,35 @@ withPort (SockAddrInet6 _ a b c) port = SockAddrInet6 (toEnum port) a b c | |||
243 | 249 | ||
244 | withoutPort = (`withPort` 0) | 250 | withoutPort = (`withPort` 0) |
245 | 251 | ||
252 | |||
253 | data MessageThread = MessageThread { | ||
254 | msgThreadParent :: Maybe S.Text, | ||
255 | msgThreadContent :: S.Text | ||
256 | } | ||
257 | deriving (Show,Eq) | ||
258 | |||
259 | data LangSpecificMessage = LangSpecificMessage { | ||
260 | msgBody :: Maybe S.Text, | ||
261 | msgSubject :: Maybe S.Text, | ||
262 | msgElements :: Set (XML.Name, [(Name, [Content])], S.Text ) | ||
263 | } | ||
264 | deriving (Show,Eq) | ||
265 | |||
266 | |||
267 | data Message = Message { | ||
268 | msgTo :: JID, | ||
269 | msgFrom :: JID, | ||
270 | msgThread :: Maybe MessageThread, | ||
271 | msgLangMap :: Map S.Text (LangSpecificMessage) | ||
272 | } | ||
273 | deriving (Show,Eq) | ||
274 | |||
246 | data OutBoundMessage = OutBoundPresence Presence | 275 | data OutBoundMessage = OutBoundPresence Presence |
247 | | PresenceProbe JID JID | 276 | | PresenceProbe JID JID |
248 | | Solicitation JID JID | 277 | | Solicitation JID JID |
249 | | Approval JID JID | 278 | | Approval JID JID |
250 | | Rejection JID JID | 279 | | Rejection JID JID |
280 | | OutBoundMessage Message | ||
251 | | Disconnect | 281 | | Disconnect |
252 | deriving Prelude.Show | 282 | deriving Prelude.Show |
253 | 283 | ||
diff --git a/Presence/main.hs b/Presence/main.hs index d7510f94..784faaca 100644 --- a/Presence/main.hs +++ b/Presence/main.hs | |||
@@ -56,7 +56,10 @@ import Network.Socket (Family(AF_INET,AF_INET6)) | |||
56 | import Holumbus.Data.MultiMap as MM (MultiMap) | 56 | import Holumbus.Data.MultiMap as MM (MultiMap) |
57 | import qualified Holumbus.Data.MultiMap as MM | 57 | import qualified Holumbus.Data.MultiMap as MM |
58 | 58 | ||
59 | data Client = Client { clientShow :: JabberShow } | 59 | data Client = Client { |
60 | clientShow :: JabberShow, | ||
61 | clientChan :: TChan ClientCommands | ||
62 | } | ||
60 | 63 | ||
61 | -- see Data.Map.Lazy.fromSet | 64 | -- see Data.Map.Lazy.fromSet |
62 | fromSet f = Map.fromList . map (\a -> (a,f a)) . Set.toList | 65 | fromSet f = Map.fromList . map (\a -> (a,f a)) . Set.toList |
@@ -195,7 +198,12 @@ instance JabberClientSession ClientSession where | |||
195 | let au = activeUsers . presence_state $ s | 198 | let au = activeUsers . presence_state $ s |
196 | us <- readTVar au | 199 | us <- readTVar au |
197 | sequenceA $ Map.lookup (user,tty) us >>= \(ttypid,cs) -> do | 200 | sequenceA $ Map.lookup (user,tty) us >>= \(ttypid,cs) -> do |
198 | let entry = (ttypid,Map.insert client_pid (Client {clientShow=stat}) cs) | 201 | let entry = (ttypid, Map.insert client_pid |
202 | (Client { | ||
203 | clientShow = stat, | ||
204 | clientChan = Main.clientChannel s | ||
205 | }) | ||
206 | cs) | ||
199 | Just $ do | 207 | Just $ do |
200 | writeTVar au (Map.insert (user,tty) entry us) | 208 | writeTVar au (Map.insert (user,tty) entry us) |
201 | subs <- readTVar $ subscriberMap (presence_state s) | 209 | subs <- readTVar $ subscriberMap (presence_state s) |
@@ -394,6 +402,11 @@ instance JabberClientSession ClientSession where | |||
394 | (peer cjid) | 402 | (peer cjid) |
395 | return () | 403 | return () |
396 | 404 | ||
405 | sendChat s msg = do | ||
406 | sendMessage (remotePeers . presence_state $ s) | ||
407 | (OutBoundMessage msg) | ||
408 | (peer . msgTo $ msg) | ||
409 | |||
397 | 410 | ||
398 | {- PeerSession | 411 | {- PeerSession |
399 | - | 412 | - |
@@ -508,6 +521,21 @@ instance JabberPeerSession PeerSession where | |||
508 | withJust mbuddy $ \buddy -> do | 521 | withJust mbuddy $ \buddy -> do |
509 | rosterPush (PendingSubscriber user buddy) (peer_global session) | 522 | rosterPush (PendingSubscriber user buddy) (peer_global session) |
510 | 523 | ||
524 | sendChatToClient session msg = do | ||
525 | let rsc = resource (msgTo msg) | ||
526 | g = peer_global session | ||
527 | (curtty,cmap) <- atomically $ liftM2 (,) (readTVar (currentTTY g)) | ||
528 | (readTVar (activeUsers g)) | ||
529 | |||
530 | let rsc' = maybe curtty id rsc | ||
531 | withJust (name (msgTo msg)) $ \nto -> do | ||
532 | case Map.lookup (nto,rsc') cmap of | ||
533 | Just (ttypid,clients) -> | ||
534 | forM_ (Map.toList clients) $ \(pid,client) -> do | ||
535 | atomically $ writeTChan (clientChan client) (Chat msg) | ||
536 | Nothing -> | ||
537 | -- todo: fallback | ||
538 | return () | ||
511 | 539 | ||
512 | 540 | ||
513 | type RefCount = Int | 541 | type RefCount = Int |