diff options
-rw-r--r-- | xmppServer.hs | 76 |
1 files changed, 61 insertions, 15 deletions
diff --git a/xmppServer.hs b/xmppServer.hs index e787f973..8f13e2d8 100644 --- a/xmppServer.hs +++ b/xmppServer.hs | |||
@@ -1,6 +1,8 @@ | |||
1 | {-# LANGUAGE OverloadedStrings #-} | 1 | {-# LANGUAGE OverloadedStrings #-} |
2 | {-# LANGUAGE TupleSections #-} | ||
2 | import System.Posix.Signals | 3 | import System.Posix.Signals |
3 | import Control.Concurrent.STM | 4 | import Control.Concurrent.STM |
5 | import Control.Concurrent.STM.TMVar | ||
4 | import Control.Monad.Trans.Resource (runResourceT) | 6 | import Control.Monad.Trans.Resource (runResourceT) |
5 | import Control.Monad.IO.Class (MonadIO, liftIO) | 7 | import Control.Monad.IO.Class (MonadIO, liftIO) |
6 | import Network.Socket | 8 | import Network.Socket |
@@ -8,9 +10,10 @@ import Network.Socket | |||
8 | , getAddrInfo | 10 | , getAddrInfo |
9 | , defaultHints | 11 | , defaultHints |
10 | , addrFlags | 12 | , addrFlags |
11 | , AddrInfoFlag(AI_CANONNAME) | 13 | , AddrInfoFlag(AI_CANONNAME,AI_V4MAPPED) |
12 | , SockAddr | 14 | , SockAddr(..) |
13 | ) | 15 | ) |
16 | import System.Endian (fromBE32) | ||
14 | import Data.Monoid ( (<>) ) | 17 | import Data.Monoid ( (<>) ) |
15 | import qualified Data.Text as Text | 18 | import qualified Data.Text as Text |
16 | import qualified Data.Text.IO as Text | 19 | import qualified Data.Text.IO as Text |
@@ -29,7 +32,25 @@ import qualified ConfigFiles | |||
29 | import UTmp (ProcessID,users) | 32 | import UTmp (ProcessID,users) |
30 | import LocalPeerCred | 33 | import LocalPeerCred |
31 | import XMPPServer | 34 | import XMPPServer |
32 | import Server | 35 | -- import Server |
36 | |||
37 | |||
38 | splitJID :: Text -> (Maybe Text,Text,Maybe Text) | ||
39 | splitJID bjid = | ||
40 | let xs = splitAll '@' bjid | ||
41 | ys = splitAll '/' (last xs) | ||
42 | splitAll c bjid = take 1 xs0 ++ map (Text.drop 1) (drop 1 xs0) | ||
43 | where xs0 = Text.groupBy (\x y-> y/=c) bjid | ||
44 | server = head ys | ||
45 | name | ||
46 | = case xs of | ||
47 | (n:s:_) -> Just n | ||
48 | (s:_) -> Nothing | ||
49 | rsrc = case ys of | ||
50 | (s:_:_) -> Just $ last ys | ||
51 | _ -> Nothing | ||
52 | in (name,server,rsrc) | ||
53 | |||
33 | 54 | ||
34 | textHostName = fmap Text.pack BSD.getHostName | 55 | textHostName = fmap Text.pack BSD.getHostName |
35 | 56 | ||
@@ -46,8 +67,21 @@ data ClientState = ClientState | |||
46 | data PresenceState = PresenceState | 67 | data PresenceState = PresenceState |
47 | { clients :: TVar (Map ConnectionKey ClientState) | 68 | { clients :: TVar (Map ConnectionKey ClientState) |
48 | , associatedPeers :: TVar (Map SockAddr ()) | 69 | , associatedPeers :: TVar (Map SockAddr ()) |
70 | , server :: TMVar XMPPServer | ||
49 | } | 71 | } |
50 | 72 | ||
73 | |||
74 | make6mapped4 addr@(SockAddrInet6 {}) = addr | ||
75 | make6mapped4 addr@(SockAddrInet port a) = SockAddrInet6 port 0 (0,0,0xFFFF,fromBE32 a) 0 | ||
76 | |||
77 | resolvePeer :: Text -> IO [SockAddr] | ||
78 | resolvePeer addrtext = do | ||
79 | fmap (map $ make6mapped4 . addrAddress) $ | ||
80 | getAddrInfo (Just $ defaultHints { addrFlags = [ AI_CANONNAME, AI_V4MAPPED ]}) | ||
81 | (Just $ Text.unpack addrtext) | ||
82 | (Just "5269") | ||
83 | |||
84 | |||
51 | getConsolePids :: PresenceState -> IO [(Text,ProcessID)] | 85 | getConsolePids :: PresenceState -> IO [(Text,ProcessID)] |
52 | getConsolePids state = do -- return [("tty7", 23)] -- todo | 86 | getConsolePids state = do -- return [("tty7", 23)] -- todo |
53 | us <- UTmp.users | 87 | us <- UTmp.users |
@@ -106,11 +140,29 @@ tellClientHisName state k = forClient state k fallback go | |||
106 | fallback = localJID "nobody" "fallback" | 140 | fallback = localJID "nobody" "fallback" |
107 | go client = localJID (clientUser client) (clientResource client) | 141 | go client = localJID (clientUser client) (clientResource client) |
108 | 142 | ||
143 | toMapUnit xs = Map.fromList $ map (,()) xs | ||
144 | |||
145 | resolveAllPeers hosts = fmap (toMapUnit . concat) $ mapM (fmap (take 1) . resolvePeer) hosts | ||
146 | |||
109 | rosterGetStuff what state k = forClient state k (return []) | 147 | rosterGetStuff what state k = forClient state k (return []) |
110 | $ \client -> do | 148 | $ \client -> do |
111 | fmap (map lazyByteStringToText) | 149 | jids <- |
112 | $ what (textToLazyByteString $ clientUser client) | 150 | fmap (map lazyByteStringToText) |
113 | 151 | $ what (textToLazyByteString $ clientUser client) | |
152 | let hosts = map ((\(_,h,_)->h) . splitJID) jids | ||
153 | addrs <- resolveAllPeers hosts | ||
154 | peers <- atomically $ readTVar (associatedPeers state) | ||
155 | addrs <- return $ addrs `Map.difference` peers | ||
156 | sv <- atomically $ takeTMVar $ server state | ||
157 | forM_ (Map.keys addrs) $ \addr -> do | ||
158 | putStrLn $ "new addr: "++show addr | ||
159 | addPeer sv addr | ||
160 | atomically $ do | ||
161 | writeTVar (associatedPeers state) (addrs `Map.union` peers) | ||
162 | putTMVar (server state) sv | ||
163 | return jids | ||
164 | |||
165 | rosterGetBuddies :: PresenceState -> ConnectionKey -> IO [Text] | ||
114 | rosterGetBuddies = rosterGetStuff ConfigFiles.getBuddies | 166 | rosterGetBuddies = rosterGetStuff ConfigFiles.getBuddies |
115 | rosterGetSolicited = rosterGetStuff ConfigFiles.getSolicited | 167 | rosterGetSolicited = rosterGetStuff ConfigFiles.getSolicited |
116 | rosterGetOthers = rosterGetStuff ConfigFiles.getOthers | 168 | rosterGetOthers = rosterGetStuff ConfigFiles.getOthers |
@@ -118,13 +170,14 @@ rosterGetSubscribers = rosterGetStuff ConfigFiles.getSubscribers | |||
118 | 170 | ||
119 | 171 | ||
120 | main = runResourceT $ do | 172 | main = runResourceT $ do |
121 | -- hostname <- liftIO textHostName | ||
122 | state <- liftIO . atomically $ do | 173 | state <- liftIO . atomically $ do |
123 | clients <- newTVar Map.empty | 174 | clients <- newTVar Map.empty |
124 | associatedPeers <- newTVar Map.empty | 175 | associatedPeers <- newTVar Map.empty |
176 | xmpp <- newEmptyTMVar | ||
125 | return PresenceState | 177 | return PresenceState |
126 | { clients = clients | 178 | { clients = clients |
127 | , associatedPeers = associatedPeers | 179 | , associatedPeers = associatedPeers |
180 | , server = xmpp | ||
128 | } | 181 | } |
129 | sv <- xmppServer | 182 | sv <- xmppServer |
130 | XMPPServerParameters | 183 | XMPPServerParameters |
@@ -151,14 +204,7 @@ main = runResourceT $ do | |||
151 | , xmppInformClientPresence = \k stanza -> return () | 204 | , xmppInformClientPresence = \k stanza -> return () |
152 | } | 205 | } |
153 | liftIO $ do | 206 | liftIO $ do |
154 | let testaddr0 = "fd97:ca88:fa7c:b94b:c8b8:fad4:1021:a54d" | 207 | atomically $ putTMVar (server state) sv |
155 | -- testaddr0 = "fdef:9e0b:b502:52c3:c074:28d3:fcd7:bfb7" | ||
156 | testaddr<- fmap (addrAddress . head) $ | ||
157 | getAddrInfo (Just $ defaultHints { addrFlags = [ AI_CANONNAME ]}) | ||
158 | (Just testaddr0) | ||
159 | (Just "5269") | ||
160 | putStrLn $ "Connecting to "++show testaddr | ||
161 | addPeer sv testaddr | ||
162 | 208 | ||
163 | quitVar <- newEmptyTMVarIO | 209 | quitVar <- newEmptyTMVarIO |
164 | installHandler sigTERM (CatchOnce (atomically $ putTMVar quitVar True)) Nothing | 210 | installHandler sigTERM (CatchOnce (atomically $ putTMVar quitVar True)) Nothing |