summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Presence/LocalPeerCred.hs4
-rw-r--r--Presence/XMPP.hs15
-rw-r--r--Presence/XMPPTypes.hs10
-rw-r--r--Presence/main.hs34
4 files changed, 40 insertions, 23 deletions
diff --git a/Presence/LocalPeerCred.hs b/Presence/LocalPeerCred.hs
index 14f5234a..f66421f8 100644
--- a/Presence/LocalPeerCred.hs
+++ b/Presence/LocalPeerCred.hs
@@ -104,6 +104,9 @@ parseProcNet port host h = do
104unmap6mapped4 addr@(SockAddrInet6 port _ (0,0,0xFFFF,a) _) = SockAddrInet port (toBE32 a) 104unmap6mapped4 addr@(SockAddrInet6 port _ (0,0,0xFFFF,a) _) = SockAddrInet port (toBE32 a)
105unmap6mapped4 addr = addr 105unmap6mapped4 addr = addr
106 106
107identifyTTY ::
108 [(W8.ByteString, ProcessID)]
109 -> UserID -> W8.ByteString -> IO (Maybe W8.ByteString, Maybe CPid)
107identifyTTY tty_pids uid inode = do 110identifyTTY tty_pids uid inode = do
108 pid <- scanProc (show uid) (L.unpack inode) 111 pid <- scanProc (show uid) (L.unpack inode)
109 -- putStrLn $ "scanProc --> "++show pid 112 -- putStrLn $ "scanProc --> "++show pid
@@ -122,6 +125,7 @@ identifyTTY tty_pids uid inode = do
122 parseTty :: String -> Float 125 parseTty :: String -> Float
123 parseTty = read . tail . dropWhile (/=':') 126 parseTty = read . tail . dropWhile (/=':')
124 127
128ttyToXorgs :: Show a => [(t, a)] -> IO [([Char], t)]
125ttyToXorgs tty_pids = do 129ttyToXorgs tty_pids = do
126 dts' <- flip mapM tty_pids $ \(tty,pid) -> do 130 dts' <- flip mapM tty_pids $ \(tty,pid) -> do
127 cmd' <- readFile $ "/proc/"++show pid++"/cmdline" 131 cmd' <- readFile $ "/proc/"++show pid++"/cmdline"
diff --git a/Presence/XMPP.hs b/Presence/XMPP.hs
index 4c103880..378c6785 100644
--- a/Presence/XMPP.hs
+++ b/Presence/XMPP.hs
@@ -59,13 +59,6 @@ import Data.Map as Map (Map)
59textToByteString x = L.fromChunks [S.encodeUtf8 x] 59textToByteString x = L.fromChunks [S.encodeUtf8 x]
60 60
61 61
62data Commands =
63 Send [XML.Event]
64 | BoundToResource
65 | InterestedInRoster
66 | QuitThread
67 deriving Prelude.Show
68
69 62
70xmlifyPresenceForClient :: Presence -> IO [XML.Event] 63xmlifyPresenceForClient :: Presence -> IO [XML.Event]
71xmlifyPresenceForClient (Presence jid stat) = do 64xmlifyPresenceForClient (Presence jid stat) = do
@@ -364,7 +357,7 @@ handleIQGet session cmdChan tag = do
364 357
365 358
366fromClient :: (MonadThrow m,MonadIO m, JabberClientSession session) => 359fromClient :: (MonadThrow m,MonadIO m, JabberClientSession session) =>
367 session -> TChan Commands -> Sink XML.Event m () 360 session -> TChan ClientCommands -> Sink XML.Event m ()
368fromClient session cmdChan = doNestingXML $ do 361fromClient session cmdChan = doNestingXML $ do
369 let log = liftIO . L.putStrLn . ("(C) " <++>) 362 let log = liftIO . L.putStrLn . ("(C) " <++>)
370 send = liftIO . atomically . writeTChan cmdChan . Send 363 send = liftIO . atomically . writeTChan cmdChan . Send
@@ -429,12 +422,12 @@ rosterPush to contact attrs = do
429 , EventEndElement "{jabber:client}iq" 422 , EventEndElement "{jabber:client}iq"
430 ] 423 ]
431 424
432data EventsForClient = CmdChan Commands 425data EventsForClient = CmdChan ClientCommands
433 | PChan Presence 426 | PChan Presence
434 | RChan RosterEvent 427 | RChan RosterEvent
435 428
436toClient :: (MonadIO m, JabberClientSession session ) => 429toClient :: (MonadIO m, JabberClientSession session ) =>
437 session -> TChan Presence -> TChan Commands -> TChan RosterEvent -> Source m [XML.Event] 430 session -> TChan Presence -> TChan ClientCommands -> TChan RosterEvent -> Source m [XML.Event]
438toClient session pchan cmdChan rchan = toClient' False False 431toClient session pchan cmdChan rchan = toClient' False False
439 where 432 where
440 toClient' isBound isInterested = do 433 toClient' isBound isInterested = do
@@ -573,7 +566,7 @@ handleClient st src snk = do
573 Prelude.putStrLn $ "PEER NAME: "++Prelude.show pname 566 Prelude.putStrLn $ "PEER NAME: "++Prelude.show pname
574 pchan <- subscribe session Nothing 567 pchan <- subscribe session Nothing
575 rchan <- subscribeToRoster session 568 rchan <- subscribeToRoster session
576 cmdChan <- atomically newTChan 569 let cmdChan = clientChannel session
577 570
578 writer <- async ( toClient session pchan cmdChan rchan `xmlToByteStrings` snk ) 571 writer <- async ( toClient session pchan cmdChan rchan `xmlToByteStrings` snk )
579 finally ( src $= parseBytes def $$ fromClient session cmdChan ) 572 finally ( src $= parseBytes def $$ fromClient session cmdChan )
diff --git a/Presence/XMPPTypes.hs b/Presence/XMPPTypes.hs
index a44f7fb1..84da2fed 100644
--- a/Presence/XMPPTypes.hs
+++ b/Presence/XMPPTypes.hs
@@ -41,6 +41,15 @@ import ByteStringOperators
41import SocketLike 41import SocketLike
42import GetHostByAddr 42import GetHostByAddr
43import Data.Maybe (listToMaybe) 43import Data.Maybe (listToMaybe)
44import Data.XML.Types as XML (Event)
45
46data ClientCommands =
47 Send [XML.Event]
48 | BoundToResource
49 | InterestedInRoster
50 | QuitThread
51 deriving Prelude.Show
52
44 53
45class JabberClientSession session where 54class JabberClientSession session where
46 data XMPPClass session 55 data XMPPClass session
@@ -50,6 +59,7 @@ class JabberClientSession session where
50 closeSession :: session -> IO () 59 closeSession :: session -> IO ()
51 subscribe :: session -> Maybe JID -> IO (TChan Presence) 60 subscribe :: session -> Maybe JID -> IO (TChan Presence)
52 subscribeToRoster :: session -> IO (TChan RosterEvent) 61 subscribeToRoster :: session -> IO (TChan RosterEvent)
62 clientChannel :: session -> TChan ClientCommands
53 forCachedPresence :: session -> (Presence -> IO ()) -> IO () 63 forCachedPresence :: session -> (Presence -> IO ()) -> IO ()
54 sendPending :: session -> IO () 64 sendPending :: session -> IO ()
55 getMyBuddies :: session -> IO [ByteString] 65 getMyBuddies :: session -> IO [ByteString]
diff --git a/Presence/main.hs b/Presence/main.hs
index 92ef7034..83f11df3 100644
--- a/Presence/main.hs
+++ b/Presence/main.hs
@@ -125,6 +125,8 @@ data ClientSession = ClientSession {
125 -- (*not* the login name of the user) 125 -- (*not* the login name of the user)
126 unix_uid :: (IORef (Maybe (UserID,L.ByteString))), 126 unix_uid :: (IORef (Maybe (UserID,L.ByteString))),
127 127
128 unix_pid :: Maybe CPid,
129
128 -- unix_resource: This is the detected TTY of the connecting client. 130 -- unix_resource: This is the detected TTY of the connecting client.
129 unix_resource :: (IORef (Maybe L.ByteString)), 131 unix_resource :: (IORef (Maybe L.ByteString)),
130 132
@@ -134,6 +136,8 @@ data ClientSession = ClientSession {
134 -- localSubscriber & rosterChannel of the global state record. 136 -- localSubscriber & rosterChannel of the global state record.
135 chans :: TVar [RefCountedChan], 137 chans :: TVar [RefCountedChan],
136 138
139 clientChannel :: TChan ClientCommands,
140
137 -- presence_state: a reference to the global state. 141 -- presence_state: a reference to the global state.
138 presence_state :: PresenceState 142 presence_state :: PresenceState
139} 143}
@@ -147,20 +151,25 @@ instance JabberClientSession ClientSession where
147 muid <- getLocalPeerCred' addr 151 muid <- getLocalPeerCred' addr
148 L.putStrLn $ "CLIENT SESSION: open " <++> bshow muid 152 L.putStrLn $ "CLIENT SESSION: open " <++> bshow muid
149 uid_ref <- newIORef muid 153 uid_ref <- newIORef muid
150 res_ref <- newIORef Nothing 154 (mtty,pid) <- getTTYandPID muid
155 res_ref <- newIORef mtty
151 chans <- atomically $ newTVar [] 156 chans <- atomically $ newTVar []
152 return $ ClientSession (hostname state) uid_ref res_ref chans state 157 clientChan <- atomically $ newTChan
153 158 return $ ClientSession (hostname state) uid_ref pid res_ref chans clientChan state
154 setResource s resource = do 159 where
160 getTTYandPID muid = do
161 us <- fmap Set.toList . readTVarIO $ activeUsers state
162 let tailOf3 (_,a,b) = (a,b)
163 (t,pid) <- case muid of
164 Just (uid,inode) -> identifyTTY (map tailOf3 us) uid inode
165 Nothing -> return (Nothing,Nothing)
166 let rsc = t `mplus` fmap ( ("pid."<++>) . bshow ) pid
167 return (rsc,pid)
168
169 setResource s wanted_resource = do
155 -- TODO: handle resource = empty string 170 -- TODO: handle resource = empty string
156 us <- fmap Set.toList . readTVarIO $ activeUsers (presence_state s) 171 rsc <- readIORef (unix_resource s)
157 muid <- readIORef (unix_uid s) 172 let rsc' = maybe wanted_resource id rsc
158 let tailOf3 (_,a,b) = (a,b)
159 (t,pid) <- case muid of
160 Just (uid,inode) -> identifyTTY (map tailOf3 us) uid inode
161 Nothing -> return (Nothing,Nothing)
162 let rsc = t `mplus` fmap ( ("pid."<++>) . bshow ) pid
163 rsc' = maybe resource id rsc
164 writeIORef (unix_resource s) (Just rsc') 173 writeIORef (unix_resource s) (Just rsc')
165 L.putStrLn $ "CLIENT SESSION: resource " <++> rsc' 174 L.putStrLn $ "CLIENT SESSION: resource " <++> rsc'
166 175
@@ -197,6 +206,7 @@ instance JabberClientSession ClientSession where
197 writeTVar (chans session) (RefCountedChan rchan:cs) 206 writeTVar (chans session) (RefCountedChan rchan:cs)
198 subscribeToChan rchan 207 subscribeToChan rchan
199 208
209 clientChannel session = Main.clientChannel session
200 210
201 forCachedPresence s action = do 211 forCachedPresence s action = do
202 jid <- getJID s 212 jid <- getJID s