summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Presence/ConfigFiles.hs20
-rw-r--r--Presence/XMPP.hs83
-rw-r--r--Presence/XMPPTypes.hs31
-rw-r--r--Presence/main.hs53
-rwxr-xr-xb2
5 files changed, 143 insertions, 46 deletions
diff --git a/Presence/ConfigFiles.hs b/Presence/ConfigFiles.hs
index 32ed8b86..39442ffd 100644
--- a/Presence/ConfigFiles.hs
+++ b/Presence/ConfigFiles.hs
@@ -60,12 +60,13 @@ modifyFile ::
60 -> ByteString 60 -> ByteString
61 -> (ByteString -> IO (Maybe ByteString)) 61 -> (ByteString -> IO (Maybe ByteString))
62 -> Maybe ByteString 62 -> Maybe ByteString
63 -> IO () 63 -> IO Bool -- Returns True if test function ever returned Nothing
64modifyFile (tag,file) user test appending = configPath user file >>= doit 64modifyFile (tag,file) user test appending = configPath user file >>= doit
65 where 65 where
66 doit path = do 66 doit path = do
67 handle (\e -> when (isDoesNotExistError e) 67 handle (\e -> if (isDoesNotExistError e)
68 (createConfigFile tag path >> doit path)) 68 then (createConfigFile tag path >> doit path)
69 else return False)
69 $ do exists <- fileExist path 70 $ do exists <- fileExist path
70 if exists 71 if exists
71 then do 72 then do
@@ -79,12 +80,17 @@ modifyFile (tag,file) user test appending = configPath user file >>= doit
79 L.hPutStrLn h tag 80 L.hPutStrLn h tag
80 forM_ (catMaybes keepers) (L.hPutStrLn h) 81 forM_ (catMaybes keepers) (L.hPutStrLn h)
81 withJust appending (L.hPutStrLn h) 82 withJust appending (L.hPutStrLn h)
82 else withFile path WriteMode $ \h -> do 83 return . not . Prelude.null $ deleted
83 L.hPutStrLn h tag 84 else do
84 withJust appending (L.hPutStrLn h) 85 withFile path WriteMode $ \h -> do
86 L.hPutStrLn h tag
87 withJust appending (L.hPutStrLn h)
88 return False
85 89
86 90
87modifySolicited = modifyFile ("<? solicited ?>",solicitedFile) 91modifySolicited = modifyFile ("<? solicited ?>", solicitedFile)
92modifyBuddies = modifyFile ("<? buddies ?>" , buddyFile)
93modifyOthers = modifyFile ("<? others ?>" , otherFile)
88 94
89addBuddy :: User -> ByteString -> IO () 95addBuddy :: User -> ByteString -> IO ()
90addBuddy user buddy = 96addBuddy user buddy =
diff --git a/Presence/XMPP.hs b/Presence/XMPP.hs
index e4f60712..9190ee3c 100644
--- a/Presence/XMPP.hs
+++ b/Presence/XMPP.hs
@@ -76,7 +76,6 @@ import qualified Data.Text as S (takeWhile)
76import Data.Text.Encoding as S (decodeUtf8,encodeUtf8) 76import Data.Text.Encoding as S (decodeUtf8,encodeUtf8)
77import Data.Text.Lazy.Encoding as L (decodeUtf8,encodeUtf8) 77import Data.Text.Lazy.Encoding as L (decodeUtf8,encodeUtf8)
78import Data.Text.Lazy (toStrict) 78import Data.Text.Lazy (toStrict)
79import GetHostByAddr
80import Data.Monoid 79import Data.Monoid
81import qualified Data.Sequence as Seq 80import qualified Data.Sequence as Seq
82import Data.Foldable (toList) 81import Data.Foldable (toList)
@@ -106,13 +105,6 @@ data Commands =
106 | QuitThread 105 | QuitThread
107 deriving Prelude.Show 106 deriving Prelude.Show
108 107
109getNamesForPeer :: Peer -> IO [ByteString]
110getNamesForPeer LocalHost = fmap ((:[]) . S.pack) getHostName
111getNamesForPeer peer@(RemotePeer addr) = do
112 ent <- getHostByAddr addr -- AF_UNSPEC addr
113 let names = hostName ent : hostAliases ent
114 return . map S.pack $ names
115
116 108
117xmlifyPresenceForClient :: Presence -> IO [XML.Event] 109xmlifyPresenceForClient :: Presence -> IO [XML.Event]
118xmlifyPresenceForClient (Presence jid stat) = do 110xmlifyPresenceForClient (Presence jid stat) = do
@@ -343,7 +335,9 @@ iq_service_unavailable host iq_id mjid req =
343 , EventEndElement "{jabber:client}iq" 335 , EventEndElement "{jabber:client}iq"
344 ] 336 ]
345 337
346attr name value = (name,[ContentText value]) 338attr name value = (name,[ContentText value])
339attrbs name value = (name,[ContentText (toStrict . L.decodeUtf8 $ value)])
340
347 341
348getRoster session iqid = do 342getRoster session iqid = do
349 let getlist f = do 343 let getlist f = do
@@ -524,6 +518,25 @@ toClient session pchan cmdChan rchan = toClient' False False
524 r <- liftIO $ rosterPush jid (toStrict . L.decodeUtf8 $ contact) [attr "ask" "subscribe"] 518 r <- liftIO $ rosterPush jid (toStrict . L.decodeUtf8 $ contact) [attr "ask" "subscribe"]
525 send r 519 send r
526 loop 520 loop
521 RChan (NewBuddy who contact) -> do
522 liftIO . putStrLn $ "Roster push: NewBuddy "++show (isInterested,who,contact)
523 jid <- liftIO $ getJID session
524 when (isInterested && Just who==name jid) $ do
525 send [ EventBeginElement "{jabber:client}presence"
526 [ attrbs "from" contact
527 , attrbs "to" (L.show jid)
528 , attr "type" "subscribed"
529 ]
530 , EventEndElement "{jabber:client}presence" ]
531 let f True = "from"
532 f False = "to"
533 subscription <- fmap f (liftIO $ isSubscribed session contact)
534 r <- liftIO . handleIO (\e -> putStrLn ("Roster NewBuddy error: "++show e) >> return []) $ do
535 rosterPush jid
536 (toStrict . L.decodeUtf8 $ contact)
537 [attr "subscription" subscription]
538 send r
539 loop
527 PChan presence -> do 540 PChan presence -> do
528 when isBound $ do 541 when isBound $ do
529 xs <- liftIO $ xmlifyPresenceForClient presence 542 xs <- liftIO $ xmlifyPresenceForClient presence
@@ -552,7 +565,7 @@ handleClient st src snk = do
552 =$= discardFlush 565 =$= discardFlush
553 =$ snk ) 566 =$ snk )
554#else 567#else
555 writer <- async ( toClient pchan cmdChan $$ renderChunks =$ snk ) 568 writer <- async ( toClient session pchan cmdChan rchan $$ renderChunks =$ snk )
556#endif 569#endif
557 finally ( src $= parseBytes def $$ fromClient session cmdChan ) 570 finally ( src $= parseBytes def $$ fromClient session cmdChan )
558 $ do 571 $ do
@@ -752,31 +765,45 @@ clientRequestsSubscription session cmdChan stanza = do
752 atomically $ writeTChan cmdChan (Send r) 765 atomically $ writeTChan cmdChan (Send r)
753 return () 766 return ()
754 767
768
769stanzaFromTo ::
770 JabberPeerSession session =>
771 session -> Event -> IO (Maybe (JID, JID))
772stanzaFromTo session stanza =
773 let lookup key = fmap textToByteString (lookupAttrib key (tagAttrs stanza))
774 parse jidstr = handleIO_ (return Nothing) (fmap Just $ parseAddressJID jidstr)
775 in case liftM2 (,) (lookup "from") (lookup "to") of
776 Nothing -> return Nothing
777 Just (from,to) -> do
778 mfrom <- parse from
779 mto <- parse to
780 case liftM2 (,) mfrom mto of
781 Nothing -> return Nothing
782 Just (from,to) -> do
783 let fromjid = JID (name from) (peerAddress session) Nothing
784 return $ Just (fromjid,to)
785
755peerRequestsSubsription session stanza = do 786peerRequestsSubsription session stanza = do
756 liftIO $ putStrLn $ "PEER PRESENCE SUBSCRIBE " ++ show stanza 787 liftIO $ putStrLn $ "PEER PRESENCE SUBSCRIBE " ++ show stanza
757 withJust (lookupAttrib "from" (tagAttrs stanza)) $ \from0-> do 788
758 withJust (lookupAttrib "to" (tagAttrs stanza)) $ \to0 -> do 789 whenJust (liftIO . handleIO (\e -> putStrLn ("peerRequestsSubsription: "++show e) >> return Nothing)
759 let to = textToByteString to0 790 $ stanzaFromTo session stanza) $ \(fromjid,tojid) -> do
760 from = textToByteString from0
761 factory = peerSessionFactory session
762 mjid <- liftIO $ handleIO_ (return Nothing) (fmap Just $ parseAddressJID to)
763 mfrom <- liftIO $ handleIO_ (return Nothing) (fmap Just $ parseAddressJID from)
764 withJust (mfrom >>= name) $ \from -> do
765 withJust mjid $ \tojid -> do
766 withJust (name tojid) $ \user -> do 791 withJust (name tojid) $ \user -> do
792
767 subs <- liftIO $ do 793 subs <- liftIO $ do
768 subs <- getSubscribers factory user 794 subs <- getSubscribers (peerSessionFactory session) user
769 msubs <- flip mapM subs $ \str -> do 795 msubs <- flip mapM subs $ \str -> do
770 handleIO_ (return Nothing) 796 handleIO_ (return Nothing)
771 (fmap Just $ parseHostNameJID str) 797 (fmap Just $ parseHostNameJID str)
772 return (catMaybes msubs) 798 return (catMaybes msubs)
773 let peer = peerAddress session
774 fromjid = JID (Just from) peer Nothing
775 if elem fromjid subs 799 if elem fromjid subs
776 then do 800 then do
777 liftIO . L.putStrLn $ bshow fromjid <++> " already subscribed to " <++> user 801 liftIO . L.putStrLn $ bshow fromjid <++> " already subscribed to " <++> user
778 -- if already subscribed, reply 802 -- if already subscribed, reply
779 liftIO $ sendPeerMessage session (Approval tojid fromjid) 803 liftIO $ do
804 sendPeerMessage session (Approval tojid fromjid)
805 ps <- userStatus session user
806 mapM_ (announcePresence session) ps
780 else 807 else
781 -- TODO 808 -- TODO
782 -- if no client: 809 -- if no client:
@@ -796,12 +823,10 @@ clientApprovesSubscription session stanza = do
796 823
797peerApprovesSubscription session stanza = do 824peerApprovesSubscription session stanza = do
798 liftIO $ putStrLn $ "PEER APPROVES SUBSCRIPTION" 825 liftIO $ putStrLn $ "PEER APPROVES SUBSCRIPTION"
799 -- if solicited: 826 whenJust (liftIO . handleIO (\e -> putStrLn ("peerApprovesSubscription: "++show e) >> return Nothing)
800 -- add buddies 827 $ stanzaFromTo session stanza) $ \(fromjid,tojid) -> do
801 -- remove others 828 withJust (name tojid) $ \user -> do
802 -- remove solicited 829 liftIO $ processApproval session user fromjid
803 -- notify client
804 return ()
805 830
806fromPeer :: (MonadThrow m,MonadIO m, JabberPeerSession session) => 831fromPeer :: (MonadThrow m,MonadIO m, JabberPeerSession session) =>
807 session -> Sink XML.Event m () 832 session -> Sink XML.Event m ()
diff --git a/Presence/XMPPTypes.hs b/Presence/XMPPTypes.hs
index 275f644e..e05d0782 100644
--- a/Presence/XMPPTypes.hs
+++ b/Presence/XMPPTypes.hs
@@ -13,9 +13,14 @@ import Network.Socket
13 , AddrInfo(..) 13 , AddrInfo(..)
14 , AddrInfoFlag(..) 14 , AddrInfoFlag(..)
15 ) 15 )
16import Network.BSD (getHostName) 16import Network.BSD
17 ( getHostName
18 , hostName
19 , hostAliases
20 )
17import System.IO (Handle) 21import System.IO (Handle)
18import Control.Concurrent.STM (TChan) 22import Control.Concurrent.STM (TChan)
23import qualified Data.ByteString.Char8 as S (ByteString,pack,putStr,putStrLn,append)
19import Data.ByteString.Lazy.Char8 as L 24import Data.ByteString.Lazy.Char8 as L
20 ( ByteString 25 ( ByteString
21 , unpack 26 , unpack
@@ -23,6 +28,7 @@ import Data.ByteString.Lazy.Char8 as L
23 , splitWith 28 , splitWith
24 , uncons 29 , uncons
25 , takeWhile 30 , takeWhile
31 , fromChunks
26 ) 32 )
27import Text.Show.ByteString as L 33import Text.Show.ByteString as L
28import Data.Binary.Builder as B 34import Data.Binary.Builder as B
@@ -30,6 +36,8 @@ import Data.Binary.Put
30import Control.DeepSeq 36import Control.DeepSeq
31import ByteStringOperators 37import ByteStringOperators
32import SocketLike 38import SocketLike
39import GetHostByAddr
40import Data.Maybe (listToMaybe,catMaybes)
33 41
34class JabberClientSession session where 42class JabberClientSession session where
35 data XMPPClass session 43 data XMPPClass session
@@ -46,6 +54,7 @@ class JabberClientSession session where
46 getMyPending :: session -> IO [ByteString] 54 getMyPending :: session -> IO [ByteString]
47 getMySolicited :: session -> IO [ByteString] 55 getMySolicited :: session -> IO [ByteString]
48 addSolicited :: session -> ByteString -> JID -> IO () 56 addSolicited :: session -> ByteString -> JID -> IO ()
57 isSubscribed :: session -> ByteString -> IO Bool
49 58
50class JabberPeerSession session where 59class JabberPeerSession session where
51 data XMPPPeerClass session 60 data XMPPPeerClass session
@@ -58,6 +67,7 @@ class JabberPeerSession session where
58 sendPeerMessage :: session -> OutBoundMessage -> IO () 67 sendPeerMessage :: session -> OutBoundMessage -> IO ()
59 getBuddies :: XMPPPeerClass session -> ByteString -> IO [ByteString] 68 getBuddies :: XMPPPeerClass session -> ByteString -> IO [ByteString]
60 getSubscribers :: XMPPPeerClass session -> ByteString -> IO [ByteString] 69 getSubscribers :: XMPPPeerClass session -> ByteString -> IO [ByteString]
70 processApproval :: session -> ByteString -> JID -> IO ()
61 71
62-- | Jabber ID (JID) datatype 72-- | Jabber ID (JID) datatype
63data JID = JID { name :: Maybe ByteString 73data JID = JID { name :: Maybe ByteString
@@ -77,6 +87,9 @@ data Presence = Presence JID JabberShow
77data RosterEvent = RequestedSubscription 87data RosterEvent = RequestedSubscription
78 {- user: -} ByteString 88 {- user: -} ByteString
79 {- contact: -} ByteString 89 {- contact: -} ByteString
90 | NewBuddy
91 {- user: -} ByteString
92 {- contact: -} ByteString
80 deriving Prelude.Show 93 deriving Prelude.Show
81 94
82data Peer = LocalHost | RemotePeer SockAddr 95data Peer = LocalHost | RemotePeer SockAddr
@@ -198,3 +211,19 @@ data OutBoundMessage = OutBoundPresence Presence
198 | Approval JID JID 211 | Approval JID JID
199 deriving Prelude.Show 212 deriving Prelude.Show
200 213
214getNamesForPeer :: Peer -> IO [S.ByteString]
215getNamesForPeer LocalHost = fmap ((:[]) . S.pack) getHostName
216getNamesForPeer peer@(RemotePeer addr) = do
217 ent <- getHostByAddr addr -- AF_UNSPEC addr
218 let names = hostName ent : hostAliases ent
219 return . map S.pack $ names
220
221
222asHostNameJID :: JID -> IO (Maybe ByteString)
223asHostNameJID jid = do
224 let n = name jid
225 rsc = resource jid
226 names <- getNamesForPeer (peer jid)
227 let tostr p = n <$++> "@" <?++> L.fromChunks [p] <++?> "/" <++$> rsc
228 jidstrs = fmap tostr names
229 return (listToMaybe jidstrs)
diff --git a/Presence/main.hs b/Presence/main.hs
index 303c4b05..eab02e88 100644
--- a/Presence/main.hs
+++ b/Presence/main.hs
@@ -106,14 +106,24 @@ data ClientSession = ClientSession {
106 presence_state :: PresenceState 106 presence_state :: PresenceState
107} 107}
108 108
109addJid modify user jid = do 109cmpJID newitem jid = do
110 -- putStrLn $ "Comparing "<++>bshow jid
111 olditem <- parseHostNameJID jid
112 if olditem==newitem then return Nothing
113 else return $ Just jid
114
115
116addRawJid modify user jid = do
110 newitem <- parseHostNameJID jid 117 newitem <- parseHostNameJID jid
111 let cmp jid = do 118 modify user (cmpJID newitem) (Just jid)
112 -- putStrLn $ "Comparing "<++>bshow jid 119 return ()
113 olditem <- parseHostNameJID jid 120
114 if olditem==newitem then return Nothing 121addJid modify user jid = do
115 else return $ Just jid 122 hjid <- asHostNameJID jid
116 modify user cmp (Just jid) 123 putStrLn $ "addJid (asHostNameJID) --> "<++>bshow hjid
124 withJust hjid $ \hjid -> do
125 modify user (cmpJID jid) (Just hjid)
126 return ()
117 127
118instance JabberClientSession ClientSession where 128instance JabberClientSession ClientSession where
119 data XMPPClass ClientSession = ClientSessions PresenceState 129 data XMPPClass ClientSession = ClientSessions PresenceState
@@ -200,7 +210,7 @@ instance JabberClientSession ClientSession where
200 addSolicited s jid_str jid = do 210 addSolicited s jid_str jid = do
201 me <- getJID s 211 me <- getJID s
202 withJust (name me) $ \user -> do 212 withJust (name me) $ \user -> do
203 addJid ConfigFiles.modifySolicited user jid_str 213 addRawJid ConfigFiles.modifySolicited user jid_str
204 let rchan = rosterChannel . presence_state $ s 214 let rchan = rosterChannel . presence_state $ s
205 atomically $ do 215 atomically $ do
206 isempty <- isEmptyTMVar rchan 216 isempty <- isEmptyTMVar rchan
@@ -228,6 +238,14 @@ instance JabberClientSession ClientSession where
228 user <- readIORef (unix_uid s) >>= getJabberUserForId 238 user <- readIORef (unix_uid s) >>= getJabberUserForId
229 ConfigFiles.getSolicited user 239 ConfigFiles.getSolicited user
230 240
241 isSubscribed s contact = do
242 handleIO (\e -> return False) $ do
243 user <- readIORef (unix_uid s) >>= getJabberUserForId
244 subs <- ConfigFiles.getSubscribers user
245 putStrLn $ "isSubscribed parsing: "<++>contact
246 cjid <- parseHostNameJID contact
247 msubs <- mapM (cmpJID cjid) subs
248 return (Nothing `elem` msubs)
231 249
232tupleToJID (user,tty,pid) = jid user LocalHost tty 250tupleToJID (user,tty,pid) = jid user LocalHost tty
233 251
@@ -295,6 +313,25 @@ instance JabberPeerSession PeerSession where
295 getBuddies _ user = ConfigFiles.getBuddies user 313 getBuddies _ user = ConfigFiles.getBuddies user
296 getSubscribers _ user = ConfigFiles.getSubscribers user 314 getSubscribers _ user = ConfigFiles.getSubscribers user
297 315
316 processApproval session user buddy = do
317 solicited <- ConfigFiles.getSolicited user
318 let rmjid modify user buddy = modify user (cmpJID buddy) Nothing
319 was_sol <- rmjid ConfigFiles.modifySolicited user buddy
320 putStrLn $ "was_sol = "<++>bshow was_sol
321 when was_sol $ do -- if buddy ∈ solicited:
322 addJid ConfigFiles.modifyBuddies user buddy -- add buddies
323 rmjid ConfigFiles.modifyOthers user buddy -- remove others
324 let rchan = rosterChannel . peer_global $ session
325 mbuddy <- asHostNameJID buddy
326 withJust mbuddy $ \buddy -> do
327 atomically $ do
328 isempty <- isEmptyTMVar rchan
329 when (not isempty) $ do
330 (_,ch) <- readTMVar rchan
331 writeTChan ch (NewBuddy user buddy)
332 return ()
333
334
298 335
299data RefCountedChan = forall a. RefCountedChan (TMVar (RefCount,TChan a)) 336data RefCountedChan = forall a. RefCountedChan (TMVar (RefCount,TChan a))
300 337
diff --git a/b b/b
index 88474475..a116163e 100755
--- a/b
+++ b/b
@@ -1,5 +1,5 @@
1#!/bin/bash 1#!/bin/bash
2args="-O2 -fwarn-unused-imports -rtsopts -DRENDERFLUSH" 2args="-fwarn-unused-imports -rtsopts -DRENDERFLUSH"
3 3
4root=${0%/*} 4root=${0%/*}
5cd "$root" 5cd "$root"