Browse Source

handle timeouts in sendIQ response processing

master
Philipp Balzarek 14 years ago
parent
commit
c89cf91a70
  1. 1
      source/Network/Xmpp.hs
  2. 24
      source/Network/Xmpp/Concurrent/IQ.hs
  3. 3
      source/Network/Xmpp/Concurrent/Threads.hs
  4. 2
      source/Network/Xmpp/Concurrent/Types.hs
  5. 4
      source/Network/Xmpp/Session.hs
  6. 11
      source/Network/Xmpp/Types.hs
  7. 11
      source/Network/Xmpp/Xep/ServiceDiscovery.hs
  8. 34
      tests/Tests.hs

1
source/Network/Xmpp.hs

@ -133,6 +133,7 @@ module Network.Xmpp
, IQRequestType(..) , IQRequestType(..)
, IQResult(..) , IQResult(..)
, IQError(..) , IQError(..)
, IQResponse(..)
, sendIQ , sendIQ
, sendIQ' , sendIQ'
, answerIQ , answerIQ

24
source/Network/Xmpp/Concurrent/IQ.hs

@ -1,6 +1,8 @@
module Network.Xmpp.Concurrent.IQ where module Network.Xmpp.Concurrent.IQ where
import Control.Concurrent.STM import Control.Concurrent.STM
import Control.Concurrent (forkIO, threadDelay)
import Control.Monad
import Control.Monad.IO.Class import Control.Monad.IO.Class
import Control.Monad.Trans.Reader import Control.Monad.Trans.Reader
@ -13,13 +15,14 @@ import Network.Xmpp.Types
-- | Sends an IQ, returns a 'TMVar' that will be filled with the first inbound -- | Sends an IQ, returns a 'TMVar' that will be filled with the first inbound
-- IQ with a matching ID that has type @result@ or @error@. -- IQ with a matching ID that has type @result@ or @error@.
sendIQ :: Maybe Jid -- ^ Recipient (to) sendIQ :: Maybe Int -- ^ Timeout
-> Maybe Jid -- ^ Recipient (to)
-> IQRequestType -- ^ IQ type (@Get@ or @Set@) -> IQRequestType -- ^ IQ type (@Get@ or @Set@)
-> Maybe LangTag -- ^ Language tag of the payload (@Nothing@ for -> Maybe LangTag -- ^ Language tag of the payload (@Nothing@ for
-- default) -- default)
-> Element -- ^ The IQ body (there has to be exactly one) -> Element -- ^ The IQ body (there has to be exactly one)
-> Xmpp (TMVar IQResponse) -> Xmpp (TMVar IQResponse)
sendIQ to tp lang body = do -- TODO: Add timeout sendIQ timeOut to tp lang body = do -- TODO: Add timeout
newId <- liftIO =<< asks idGenerator newId <- liftIO =<< asks idGenerator
handlers <- asks iqHandlers handlers <- asks iqHandlers
ref <- liftIO . atomically $ do ref <- liftIO . atomically $ do
@ -29,18 +32,31 @@ sendIQ to tp lang body = do -- TODO: Add timeout
-- TODO: Check for id collisions (shouldn't happen?) -- TODO: Check for id collisions (shouldn't happen?)
return resRef return resRef
sendStanza . IQRequestS $ IQRequest newId Nothing to lang tp body sendStanza . IQRequestS $ IQRequest newId Nothing to lang tp body
case timeOut of
Nothing -> return ()
Just t -> void . liftIO . forkIO $ do
threadDelay t
doTimeOut handlers newId ref
return ref return ref
where
doTimeOut handlers iqid var = atomically $ do
p <- tryPutTMVar var IQResponseTimeout
when p $ do
(byNS, byId) <- readTVar handlers
writeTVar handlers (byNS, Map.delete iqid byId)
return ()
-- | Like 'sendIQ', but waits for the answer IQ. -- | Like 'sendIQ', but waits for the answer IQ. Times out after 3 seconds
sendIQ' :: Maybe Jid sendIQ' :: Maybe Jid
-> IQRequestType -> IQRequestType
-> Maybe LangTag -> Maybe LangTag
-> Element -> Element
-> Xmpp IQResponse -> Xmpp IQResponse
sendIQ' to tp lang body = do sendIQ' to tp lang body = do
ref <- sendIQ to tp lang body ref <- sendIQ (Just 3000000) to tp lang body
liftIO . atomically $ takeTMVar ref liftIO . atomically $ takeTMVar ref
answerIQ :: IQRequestTicket answerIQ :: IQRequestTicket
-> Either StanzaError (Maybe Element) -> Either StanzaError (Maybe Element)
-> Xmpp Bool -> Xmpp Bool

3
source/Network/Xmpp/Concurrent/Threads.hs

@ -129,7 +129,8 @@ handleIQResponse handlers iq = do
case Map.updateLookupWithKey (\_ _ -> Nothing) (iqID iq) byID of case Map.updateLookupWithKey (\_ _ -> Nothing) (iqID iq) byID of
(Nothing, _) -> return () -- We are not supposed to send an error. (Nothing, _) -> return () -- We are not supposed to send an error.
(Just tmvar, byID') -> do (Just tmvar, byID') -> do
_ <- tryPutTMVar tmvar iq -- Don't block. let answer = either IQResponseError IQResponseResult iq
_ <- tryPutTMVar tmvar answer -- Don't block.
writeTVar handlers (byNS, byID') writeTVar handlers (byNS, byID')
where where
iqID (Left err) = iqErrorID err iqID (Left err) = iqErrorID err

2
source/Network/Xmpp/Concurrent/Types.hs

@ -19,7 +19,7 @@ import Network.Xmpp.Types
-- Map between the IQ request type and the "query" namespace pair, and the TChan -- Map between the IQ request type and the "query" namespace pair, and the TChan
-- for the IQ request and "sent" boolean pair. -- for the IQ request and "sent" boolean pair.
type IQHandlers = (Map.Map (IQRequestType, Text) (TChan IQRequestTicket) type IQHandlers = (Map.Map (IQRequestType, Text) (TChan IQRequestTicket)
, Map.Map StanzaId (TMVar IQResponse) , Map.Map StanzaId (TMVar (IQResponse))
) )
-- Handlers to be run when the Xmpp session ends and when the Xmpp connection is -- Handlers to be run when the Xmpp session ends and when the Xmpp connection is

4
source/Network/Xmpp/Session.hs

@ -39,5 +39,5 @@ startSession :: Xmpp ()
startSession = do startSession = do
answer <- sendIQ' Nothing Set Nothing sessionXML answer <- sendIQ' Nothing Set Nothing sessionXML
case answer of case answer of
Left e -> error $ show e IQResponseResult _ -> return ()
Right _ -> return () e -> error $ show e

11
source/Network/Xmpp/Types.hs

@ -10,7 +10,7 @@ module Network.Xmpp.Types
( IQError(..) ( IQError(..)
, IQRequest(..) , IQRequest(..)
, IQRequestType(..) , IQRequestType(..)
, IQResponse , IQResponse(..)
, IQResult(..) , IQResult(..)
, IdGenerator(..) , IdGenerator(..)
, LangTag (..) , LangTag (..)
@ -111,9 +111,12 @@ instance Read IQRequestType where
readsPrec _ "set" = [(Set, "")] readsPrec _ "set" = [(Set, "")]
readsPrec _ _ = [] readsPrec _ _ = []
-- | A "response" Info/Query (IQ) stanza is either an 'IQError' or an IQ stanza -- | A "response" Info/Query (IQ) stanza is either an 'IQError', an IQ stanza
-- with the type "result" ('IQResult'). -- of type "result" ('IQResult') or a Timeout.
type IQResponse = Either IQError IQResult data IQResponse = IQResponseError IQError
| IQResponseResult IQResult
| IQResponseTimeout
deriving Show
-- | The (non-error) answer to an IQ request. -- | The (non-error) answer to an IQ request.
data IQResult = IQResult { iqResultID :: StanzaId data IQResult = IQResult { iqResultID :: StanzaId

11
source/Network/Xmpp/Xep/ServiceDiscovery.hs

@ -27,6 +27,7 @@ import Network.Xmpp
data DiscoError = DiscoNoQueryElement data DiscoError = DiscoNoQueryElement
| DiscoIQError IQError | DiscoIQError IQError
| DiscoTimeout
| DiscoXMLError Element UnpickleError | DiscoXMLError Element UnpickleError
deriving (Show) deriving (Show)
@ -83,8 +84,9 @@ queryInfo :: Jid -- ^ Entity to query
queryInfo to node = do queryInfo to node = do
res <- sendIQ' (Just to) Get Nothing queryBody res <- sendIQ' (Just to) Get Nothing queryBody
return $ case res of return $ case res of
Left e -> Left $ DiscoIQError e IQResponseError e -> Left $ DiscoIQError e
Right r -> case iqResultPayload r of IQResponseTimeout -> Left $ DiscoTimeout
IQResponseResult r -> case iqResultPayload r of
Nothing -> Left DiscoNoQueryElement Nothing -> Left DiscoNoQueryElement
Just p -> case unpickleElem xpQueryInfo p of Just p -> case unpickleElem xpQueryInfo p of
Left e -> Left $ DiscoXMLError p e Left e -> Left $ DiscoXMLError p e
@ -127,8 +129,9 @@ queryItems :: Jid -- ^ Entity to query
queryItems to node = do queryItems to node = do
res <- sendIQ' (Just to) Get Nothing queryBody res <- sendIQ' (Just to) Get Nothing queryBody
return $ case res of return $ case res of
Left e -> Left $ DiscoIQError e IQResponseError e -> Left $ DiscoIQError e
Right r -> case iqResultPayload r of IQResponseTimeout -> Left $ DiscoTimeout
IQResponseResult r -> case iqResultPayload r of
Nothing -> Left DiscoNoQueryElement Nothing -> Left DiscoNoQueryElement
Just p -> case unpickleElem xpQueryItems p of Just p -> case unpickleElem xpQueryItems p of
Left e -> Left $ DiscoXMLError p e Left e -> Left $ DiscoXMLError p e

34
tests/Tests.hs

@ -16,6 +16,7 @@ import Data.XML.Types
import Network.Xmpp import Network.Xmpp
import Network.Xmpp.IM.Presence import Network.Xmpp.IM.Presence
import Network.Xmpp.Pickle import Network.Xmpp.Pickle
import Network.Xmpp.Xep.ServiceDiscovery
import System.Environment import System.Environment
import Text.XML.Stream.Elements import Text.XML.Stream.Elements
@ -57,15 +58,16 @@ invertPayload (Payload count flag message) = Payload (count + 1) (not flag) (Tex
iqResponder = do iqResponder = do
chan' <- listenIQChan Get testNS chan' <- listenIQChan Get testNS
chan <- case chan' of chan <- case chan' of
Nothing -> liftIO $ putStrLn "Channel was already taken" Left _ -> liftIO $ putStrLn "Channel was already taken"
>> error "hanging up" >> error "hanging up"
Just c -> return c Right c -> return c
forever $ do forever $ do
next <- liftIO . atomically $ readTChan chan next <- liftIO . atomically $ readTChan chan
let Right payload = unpickleElem payloadP . iqRequestPayload $ let Right payload = unpickleElem payloadP . iqRequestPayload $
iqRequestBody next iqRequestBody next
let answerPayload = invertPayload payload let answerPayload = invertPayload payload
let answerBody = pickleElem payloadP answerPayload let answerBody = pickleElem payloadP answerPayload
unless (payloadCounter payload == 3) . void $
answerIQ next (Right $ Just answerBody) answerIQ next (Right $ Just answerBody)
when (payloadCounter payload == 10) $ do when (payloadCounter payload == 10) $ do
liftIO $ threadDelay 1000000 liftIO $ threadDelay 1000000
@ -134,6 +136,24 @@ runMain debug number = do
sendPresence $ presenceSubscribe them sendPresence $ presenceSubscribe them
fork iqResponder fork iqResponder
when active $ do when active $ do
q <- queryInfo "species64739.dyndns.org" Nothing
case q of
Left (DiscoXMLError el e) -> do
debug' (ppElement el)
debug' (Text.unpack $ ppUnpickleError e)
debug' (show $ length $ elementNodes el)
x -> debug' $ show x
q <- queryItems "species64739.dyndns.org"
(Just "http://jabber.org/protocol/commands")
case q of
Left (DiscoXMLError el e) -> do
debug' (ppElement el)
debug' (Text.unpack $ ppUnpickleError e)
debug' (show $ length $ elementNodes el)
x -> debug' $ show x
liftIO $ threadDelay 1000000 -- Wait for the other thread to go online liftIO $ threadDelay 1000000 -- Wait for the other thread to go online
void . fork $ do void . fork $ do
forM [1..10] $ \count -> do forM [1..10] $ \count -> do
@ -141,11 +161,17 @@ runMain debug number = do
let payload = Payload count (even count) (Text.pack $ show count) let payload = Payload count (even count) (Text.pack $ show count)
let body = pickleElem payloadP payload let body = pickleElem payloadP payload
debug' "sending" debug' "sending"
Right answer <- sendIQ' (Just them) Get Nothing body answer <- sendIQ' (Just them) Get Nothing body
case answer of
IQResponseResult r -> do
debug' "received" debug' "received"
let Right answerPayload = unpickleElem payloadP let Right answerPayload = unpickleElem payloadP
(fromJust $ iqResultPayload answer) (fromJust $ iqResultPayload r)
expect debug' (invertPayload payload) answerPayload expect debug' (invertPayload payload) answerPayload
IQResponseTimeout -> do
debug' $ "Timeout in packet: " ++ show count
IQResponseError e -> do
debug' $ "Error in packet: " ++ show count
liftIO $ threadDelay 100000 liftIO $ threadDelay 100000
sendUser "All tests done" sendUser "All tests done"
debug' "ending session" debug' "ending session"

Loading…
Cancel
Save