|
|
|
@ -3,6 +3,7 @@ module Example where |
|
|
|
|
|
|
|
|
|
|
|
import Control.Concurrent |
|
|
|
import Control.Concurrent |
|
|
|
import Control.Concurrent.STM |
|
|
|
import Control.Concurrent.STM |
|
|
|
|
|
|
|
import qualified Control.Exception.Lifted as Ex |
|
|
|
import Control.Monad |
|
|
|
import Control.Monad |
|
|
|
import Control.Monad.IO.Class |
|
|
|
import Control.Monad.IO.Class |
|
|
|
|
|
|
|
|
|
|
|
@ -17,7 +18,7 @@ import Network.Xmpp.IM.Presence |
|
|
|
import Network.Xmpp.Pickle |
|
|
|
import Network.Xmpp.Pickle |
|
|
|
|
|
|
|
|
|
|
|
import System.Environment |
|
|
|
import System.Environment |
|
|
|
import Text.XML.Stream.Elements |
|
|
|
import Text.XML.Stream.Elements |
|
|
|
|
|
|
|
|
|
|
|
testUser1 :: Jid |
|
|
|
testUser1 :: Jid |
|
|
|
testUser1 = read "testuser1@species64739.dyndns.org/bot1" |
|
|
|
testUser1 = read "testuser1@species64739.dyndns.org/bot1" |
|
|
|
@ -114,19 +115,20 @@ runMain debug number = do |
|
|
|
debug . (("Thread " ++ show number ++ ":") ++) |
|
|
|
debug . (("Thread " ++ show number ++ ":") ++) |
|
|
|
wait <- newEmptyTMVarIO |
|
|
|
wait <- newEmptyTMVarIO |
|
|
|
withNewSession $ do |
|
|
|
withNewSession $ do |
|
|
|
setSessionEndHandler (liftIO . atomically $ putTMVar wait ()) |
|
|
|
|
|
|
|
setConnectionClosedHandler (\e -> do |
|
|
|
setConnectionClosedHandler (\e -> do |
|
|
|
liftIO (debug' $ "connection lost because " ++ show e) |
|
|
|
liftIO (debug' $ "connection lost because " ++ show e) |
|
|
|
endSession ) |
|
|
|
endSession ) |
|
|
|
debug' "running" |
|
|
|
debug' "running" |
|
|
|
withConnection $ do |
|
|
|
withConnection $ Ex.catch (do |
|
|
|
connect "localhost" "species64739.dyndns.org" |
|
|
|
connect "localhost" "species64739.dyndns.org" |
|
|
|
startTLS exampleParams |
|
|
|
startTLS exampleParams |
|
|
|
saslResponse <- auth (fromJust $ localpart we) "pwd" (resourcepart we) |
|
|
|
saslResponse <- simpleAuth |
|
|
|
|
|
|
|
(fromJust $ localpart we) "pwd" (resourcepart we) |
|
|
|
case saslResponse of |
|
|
|
case saslResponse of |
|
|
|
Right _ -> return () |
|
|
|
Right _ -> return () |
|
|
|
Left e -> error $ show e |
|
|
|
Left e -> error $ show e |
|
|
|
debug' "session standing" |
|
|
|
debug' "session standing") |
|
|
|
|
|
|
|
(\e -> liftIO (print (e ::Ex.SomeException) >> Ex.throwIO e) ) |
|
|
|
sendPresence presenceOnline |
|
|
|
sendPresence presenceOnline |
|
|
|
fork autoAccept |
|
|
|
fork autoAccept |
|
|
|
sendPresence $ presenceSubscribe them |
|
|
|
sendPresence $ presenceSubscribe them |
|
|
|
@ -148,7 +150,7 @@ runMain debug number = do |
|
|
|
sendUser "All tests done" |
|
|
|
sendUser "All tests done" |
|
|
|
debug' "ending session" |
|
|
|
debug' "ending session" |
|
|
|
liftIO . atomically $ putTMVar wait () |
|
|
|
liftIO . atomically $ putTMVar wait () |
|
|
|
endSession |
|
|
|
closeConnection |
|
|
|
liftIO . atomically $ takeTMVar wait |
|
|
|
liftIO . atomically $ takeTMVar wait |
|
|
|
return () |
|
|
|
return () |
|
|
|
return () |
|
|
|
return () |
|
|
|
|