diff options
Diffstat (limited to 'Presence/XMPPServer.hs')
-rw-r--r-- | Presence/XMPPServer.hs | 160 |
1 files changed, 120 insertions, 40 deletions
diff --git a/Presence/XMPPServer.hs b/Presence/XMPPServer.hs index ccdffabe..10928892 100644 --- a/Presence/XMPPServer.hs +++ b/Presence/XMPPServer.hs | |||
@@ -1,6 +1,12 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | 1 | {-# LANGUAGE OverloadedStrings #-} |
2 | module XMPPServer | 2 | module XMPPServer |
3 | ( xmppServer | 3 | ( xmppServer |
4 | , ConnectionKey(..) | ||
5 | , XMPPServerParameters(..) | ||
6 | , Stanza(..) | ||
7 | , StanzaType(..) | ||
8 | , StanzaOrigin(..) | ||
9 | , dupStanza | ||
4 | ) where | 10 | ) where |
5 | import Control.Monad.Trans.Resource (runResourceT) | 11 | import Control.Monad.Trans.Resource (runResourceT) |
6 | import Control.Monad.Trans (lift) | 12 | import Control.Monad.Trans (lift) |
@@ -17,6 +23,7 @@ import System.Posix.Signals | |||
17 | import Data.ByteString (ByteString) | 23 | import Data.ByteString (ByteString) |
18 | import qualified Data.ByteString.Char8 as Strict8 | 24 | import qualified Data.ByteString.Char8 as Strict8 |
19 | -- import qualified Data.ByteString.Lazy.Char8 as Lazy8 | 25 | -- import qualified Data.ByteString.Lazy.Char8 as Lazy8 |
26 | import Data.Int (Int8) | ||
20 | 27 | ||
21 | import Data.Conduit | 28 | import Data.Conduit |
22 | import qualified Data.Conduit.List as CL | 29 | import qualified Data.Conduit.List as CL |
@@ -29,7 +36,7 @@ import Data.XML.Types as XML | |||
29 | import Data.Maybe (catMaybes,fromJust,isNothing) | 36 | import Data.Maybe (catMaybes,fromJust,isNothing) |
30 | import Data.Monoid ( (<>) ) | 37 | import Data.Monoid ( (<>) ) |
31 | import Data.Text (Text) | 38 | import Data.Text (Text) |
32 | import qualified Data.Text as Text (pack) | 39 | import qualified Data.Text as Text (pack,unpack) |
33 | import Data.Char (toUpper) | 40 | import Data.Char (toUpper) |
34 | 41 | ||
35 | import qualified Control.Concurrent.STM.UpdateStream as Slotted | 42 | import qualified Control.Concurrent.STM.UpdateStream as Slotted |
@@ -37,13 +44,71 @@ import ControlMaybe | |||
37 | import Nesting | 44 | import Nesting |
38 | import EventUtil | 45 | import EventUtil |
39 | import Server | 46 | import Server |
40 | import ResourcePolicy (getResourceName) | ||
41 | 47 | ||
42 | peerport = 5269 | 48 | peerport = 5269 |
43 | clientport = 5222 | 49 | clientport = 5222 |
44 | 50 | ||
45 | my_uuid = "154ae29f-98f2-4af4-826d-a40c8a188574" | 51 | my_uuid = "154ae29f-98f2-4af4-826d-a40c8a188574" |
46 | 52 | ||
53 | data ConnectionKey | ||
54 | = PeerKey { callBackAddress :: SockAddr } | ||
55 | | ClientKey { localAddress :: SockAddr } | ||
56 | deriving (Show, Ord, Eq) | ||
57 | |||
58 | data JabberShow = Offline | ||
59 | | ExtendedAway | ||
60 | | Away | ||
61 | | DoNotDisturb | ||
62 | | Available | ||
63 | | Chatty | ||
64 | deriving (Show,Enum,Ord,Eq,Read) | ||
65 | |||
66 | data MessageThread = MessageThread { | ||
67 | msgThreadParent :: Maybe Text, | ||
68 | msgThreadContent :: Text | ||
69 | } | ||
70 | deriving (Show,Eq) | ||
71 | |||
72 | data LangSpecificMessage = | ||
73 | LangSpecificMessage { msgBody :: Maybe Text | ||
74 | , msgSubject :: Maybe Text | ||
75 | } | ||
76 | deriving (Show,Eq) | ||
77 | |||
78 | data StanzaType = Unrecognized | Ping | Pong | RequestResource (Maybe Text) | SetResource | ||
79 | | SessionRequest | UnrecognizedQuery Name | Error | ||
80 | | PresenceStatus { presenceShow :: JabberShow | ||
81 | , presencePriority :: Maybe Int8 | ||
82 | , presenceStatus :: [(Lang,Text)] | ||
83 | } | ||
84 | | PresenceInformError | ||
85 | | PresenceInformSubscription Bool | ||
86 | | PresenceRequestStatus | ||
87 | | PresenceRequestSubscription Bool | ||
88 | | Message { msgThread :: Maybe MessageThread | ||
89 | , msgLangMap :: [(Lang,LangSpecificMessage)] | ||
90 | } | ||
91 | deriving Show | ||
92 | |||
93 | data StanzaOrigin = LocalPeer | NetworkOrigin ConnectionKey (TChan Stanza) | ||
94 | |||
95 | data Stanza = Stanza | ||
96 | { stanzaType :: StanzaType | ||
97 | , stanzaId :: Maybe Text | ||
98 | , stanzaTo :: Maybe Text | ||
99 | , stanzaFrom :: Maybe Text | ||
100 | , stanzaChan :: TChan XML.Event | ||
101 | , stanzaClosers :: TVar (Maybe [XML.Event]) | ||
102 | , stanzaInterrupt :: TMVar () | ||
103 | , stanzaOrigin :: StanzaOrigin | ||
104 | } | ||
105 | |||
106 | data XMPPServerParameters = | ||
107 | XMPPServerParameters | ||
108 | { xmppChooseResourceName :: ConnectionKey -> Socket -> Maybe Text -> IO Text | ||
109 | , xmppNewConnection :: ConnectionKey -> TChan Stanza -> IO () | ||
110 | , xmppEOF :: ConnectionKey -> IO () | ||
111 | } | ||
47 | 112 | ||
48 | -- TODO: http://xmpp.org/rfcs/rfc6120.html#rules-remote-error | 113 | -- TODO: http://xmpp.org/rfcs/rfc6120.html#rules-remote-error |
49 | -- client connection | 114 | -- client connection |
@@ -93,31 +158,6 @@ type FlagCommand = STM Bool | |||
93 | type ReadCommand = IO (Maybe ByteString) | 158 | type ReadCommand = IO (Maybe ByteString) |
94 | type WriteCommand = ByteString -> IO Bool | 159 | type WriteCommand = ByteString -> IO Bool |
95 | 160 | ||
96 | {- | ||
97 | data Stanza | ||
98 | = UnrecognizedStanza { stanzaChan :: TChan (Maybe XML.Event) } | ||
99 | | PingStanza { stanzaId :: Maybe Text | ||
100 | , stanzaChan :: TChan (Maybe XML.Event) } | ||
101 | | PongStanza { -- stanzaId :: Maybe Text | ||
102 | stanzaChan :: TChan (Maybe XML.Event) } | ||
103 | -} | ||
104 | |||
105 | data StanzaType = Unrecognized | Ping | Pong | RequestResource (Maybe Text) | SetResource | ||
106 | | SessionRequest | UnrecognizedQuery Name | Error | ||
107 | deriving Show | ||
108 | |||
109 | data StanzaOrigin = LocalPeer | NetworkOrigin ConnectionKey (TChan Stanza) | ||
110 | |||
111 | data Stanza = Stanza | ||
112 | { stanzaType :: StanzaType | ||
113 | , stanzaId :: Maybe Text | ||
114 | , stanzaTo :: Maybe Text | ||
115 | , stanzaFrom :: Maybe Text | ||
116 | , stanzaChan :: TChan XML.Event | ||
117 | , stanzaClosers :: TVar (Maybe [XML.Event]) | ||
118 | , stanzaInterrupt :: TMVar () | ||
119 | , stanzaOrigin :: StanzaOrigin | ||
120 | } | ||
121 | dupStanza stanza = do | 161 | dupStanza stanza = do |
122 | dupped <- dupTChan (stanzaChan stanza) | 162 | dupped <- dupTChan (stanzaChan stanza) |
123 | return stanza { stanzaChan = dupped } | 163 | return stanza { stanzaChan = dupped } |
@@ -212,6 +252,47 @@ C->Unrecognized </iq> | |||
212 | 252 | ||
213 | ioWriteChan c v = liftIO . atomically $ writeTChan c v | 253 | ioWriteChan c v = liftIO . atomically $ writeTChan c v |
214 | 254 | ||
255 | parsePresenceStatus ns = do | ||
256 | |||
257 | let toStat "away" = Away | ||
258 | toStat "xa" = ExtendedAway | ||
259 | toStat "dnd" = DoNotDisturb | ||
260 | toStat "chat" = Chatty | ||
261 | |||
262 | showv <- liftIO . atomically $ newTVar Available | ||
263 | priov <- liftIO . atomically $ newTVar Nothing | ||
264 | statusv <- liftIO . atomically $ newTChan | ||
265 | fix $ \loop -> do | ||
266 | mtag <- nextElement | ||
267 | flip (maybe $ return ()) mtag $ \tag -> do | ||
268 | when (nameNamespace (tagName tag) == Just ns) $ do | ||
269 | case nameLocalName (tagName tag) of | ||
270 | "show" -> do t <- XML.content | ||
271 | liftIO . atomically $ writeTVar showv (toStat t) | ||
272 | "priority" -> do t <- XML.content | ||
273 | liftIO . handleIO_ (return ()) $ do | ||
274 | prio <- readIO (Text.unpack t) | ||
275 | atomically $ writeTVar priov (Just prio) | ||
276 | "status" -> do t <- XML.content | ||
277 | lang <- xmlLang | ||
278 | ioWriteChan statusv (maybe "" id lang,t) | ||
279 | _ -> return () | ||
280 | loop | ||
281 | show <- liftIO . atomically $ readTVar showv | ||
282 | prio <- liftIO . atomically $ readTVar priov | ||
283 | status <- liftIO $ chanContents statusv -- Could use unsafeInterleaveIO to | ||
284 | -- avoid multiple passes, but whatever. | ||
285 | return . Just $ PresenceStatus { presenceShow = show | ||
286 | , presencePriority = prio | ||
287 | , presenceStatus = status | ||
288 | } | ||
289 | grokPresence stanzaTag = do | ||
290 | let typ = lookupAttrib "type" (tagAttrs stanzaTag) | ||
291 | case typ of | ||
292 | Nothing -> parsePresenceStatus "jabber:client" | ||
293 | Just "unavailable" -> fmap (fmap (\p -> p {presenceShow=Offline})) | ||
294 | $ parsePresenceStatus "jabber:client" | ||
295 | _ -> return Nothing -- todo | ||
215 | 296 | ||
216 | grokStanza "jabber:server" stanzaTag = | 297 | grokStanza "jabber:server" stanzaTag = |
217 | case () of | 298 | case () of |
@@ -224,6 +305,7 @@ grokStanza "jabber:client" stanzaTag = | |||
224 | _ | stanzaTag `isClientIQOf` "get" -> grokStanzaIQGet stanzaTag | 305 | _ | stanzaTag `isClientIQOf` "get" -> grokStanzaIQGet stanzaTag |
225 | _ | stanzaTag `isClientIQOf` "set" -> grokStanzaIQSet stanzaTag | 306 | _ | stanzaTag `isClientIQOf` "set" -> grokStanzaIQSet stanzaTag |
226 | _ | stanzaTag `isClientIQOf` "result" -> grokStanzaIQResult stanzaTag | 307 | _ | stanzaTag `isClientIQOf` "result" -> grokStanzaIQResult stanzaTag |
308 | _ | tagName stanzaTag == "{jabber:client}presence" -> grokPresence stanzaTag | ||
227 | _ -> return $ Just Unrecognized | 309 | _ -> return $ Just Unrecognized |
228 | 310 | ||
229 | xmppInbound :: Server ConnectionKey | 311 | xmppInbound :: Server ConnectionKey |
@@ -524,11 +606,6 @@ forkConnection sv k pingflag src snk stanzas = do | |||
524 | wlog $ "end reader fork: " ++ show k | 606 | wlog $ "end reader fork: " ++ show k |
525 | return output | 607 | return output |
526 | 608 | ||
527 | data ConnectionKey | ||
528 | = PeerKey { callBackAddress :: SockAddr } | ||
529 | | ClientKey { localAddress :: SockAddr } | ||
530 | deriving (Show, Ord, Eq) | ||
531 | |||
532 | {- | 609 | {- |
533 | data Peer = Peer | 610 | data Peer = Peer |
534 | { peerWanted :: TVar Bool -- ^ False when this peer is on a you-call-me basis | 611 | { peerWanted :: TVar Bool -- ^ False when this peer is on a you-call-me basis |
@@ -574,7 +651,7 @@ socketFromKey :: Server k -> k -> IO Socket | |||
574 | socketFromKey sv k = do | 651 | socketFromKey sv k = do |
575 | return todo | 652 | return todo |
576 | 653 | ||
577 | monitor sv params = do | 654 | monitor sv params xmpp = do |
578 | chan <- return $ serverEvent sv | 655 | chan <- return $ serverEvent sv |
579 | stanzas <- atomically newTChan | 656 | stanzas <- atomically newTChan |
580 | quitVar <- atomically newEmptyTMVar | 657 | quitVar <- atomically newEmptyTMVar |
@@ -585,10 +662,12 @@ monitor sv params = do | |||
585 | Connection pingflag conread conwrite -> do | 662 | Connection pingflag conread conwrite -> do |
586 | wlog $ tomsg k "Connection" | 663 | wlog $ tomsg k "Connection" |
587 | let (xsrc,xsnk) = xmlStream conread conwrite | 664 | let (xsrc,xsnk) = xmlStream conread conwrite |
588 | forkConnection sv k pingflag xsrc xsnk stanzas | 665 | outs <- forkConnection sv k pingflag xsrc xsnk stanzas |
666 | xmppNewConnection xmpp k outs | ||
589 | return () | 667 | return () |
590 | ConnectFailure addr -> return () -- wlog $ tomsg k "ConnectFailure" | 668 | ConnectFailure addr -> return () -- wlog $ tomsg k "ConnectFailure" |
591 | EOF -> wlog $ tomsg k "EOF" | 669 | EOF -> do wlog $ tomsg k "EOF" |
670 | xmppEOF xmpp k | ||
592 | HalfConnection In -> do | 671 | HalfConnection In -> do |
593 | wlog $ tomsg k "ReadOnly" | 672 | wlog $ tomsg k "ReadOnly" |
594 | control sv (Connect (callBackAddress k) params) | 673 | control sv (Connect (callBackAddress k) params) |
@@ -602,7 +681,7 @@ monitor sv params = do | |||
602 | case stanzaType stanza of | 681 | case stanzaType stanza of |
603 | RequestResource wanted -> do | 682 | RequestResource wanted -> do |
604 | sock <- socketFromKey sv k | 683 | sock <- socketFromKey sv k |
605 | rsc <- getResourceName sock wanted | 684 | rsc <- xmppChooseResourceName xmpp k sock wanted |
606 | let reply = iq_bind_reply (stanzaId stanza) rsc | 685 | let reply = iq_bind_reply (stanzaId stanza) rsc |
607 | sendReply quitVar SetResource reply replyto | 686 | sendReply quitVar SetResource reply replyto |
608 | SessionRequest -> do | 687 | SessionRequest -> do |
@@ -629,9 +708,10 @@ monitor sv params = do | |||
629 | where | 708 | where |
630 | _ = str :: String | 709 | _ = str :: String |
631 | 710 | ||
632 | 711 | xmppServer :: ( MonadResource m | |
633 | xmppServer :: (MonadResource m, MonadIO m) => m (Server ConnectionKey,ConnectionParameters ConnectionKey) | 712 | , MonadIO m |
634 | xmppServer = do | 713 | ) => XMPPServerParameters -> m (Server ConnectionKey,ConnectionParameters ConnectionKey) |
714 | xmppServer xmpp = do | ||
635 | sv <- server | 715 | sv <- server |
636 | let peer_params = (connectionDefaults peerKey) | 716 | let peer_params = (connectionDefaults peerKey) |
637 | { pingInterval = 15000 | 717 | { pingInterval = 15000 |
@@ -642,7 +722,7 @@ xmppServer = do | |||
642 | , timeout = 0 | 722 | , timeout = 0 |
643 | } | 723 | } |
644 | liftIO $ do | 724 | liftIO $ do |
645 | forkIO $ monitor sv peer_params | 725 | forkIO $ monitor sv peer_params xmpp |
646 | control sv (Listen peerport peer_params) | 726 | control sv (Listen peerport peer_params) |
647 | control sv (Listen clientport client_params) | 727 | control sv (Listen clientport client_params) |
648 | return (sv,peer_params) | 728 | return (sv,peer_params) |