Browse Source

add timeout parameter to sendIQ'

master
Philipp Balzarek 12 years ago
parent
commit
664daa540a
  1. 1
      pontarius-xmpp.cabal
  2. 26
      source/Network/Xmpp/Concurrent/IQ.hs
  3. 14
      source/Network/Xmpp/IM/Roster.hs

1
pontarius-xmpp.cabal

@ -67,6 +67,7 @@ Library
, tls >=1.1.3 , tls >=1.1.3
, tls-extra >=0.6.0 , tls-extra >=0.6.0
, transformers >=0.2.2.0 , transformers >=0.2.2.0
, unbounded-delays >=0.1
, void >=0.5.5 , void >=0.5.5
, xml-types >=0.3.1 , xml-types >=0.3.1
, xml-conduit >=1.1.0.7 , xml-conduit >=1.1.0.7

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

@ -1,8 +1,10 @@
{-# OPTIONS_HADDOCK hide #-} {-# OPTIONS_HADDOCK hide #-}
module Network.Xmpp.Concurrent.IQ where module Network.Xmpp.Concurrent.IQ where
import Control.Concurrent (forkIO, threadDelay) import Control.Concurrent (forkIO)
import Control.Concurrent.Thread.Delay (delay)
import Control.Concurrent.STM import Control.Concurrent.STM
import Control.Monad import Control.Monad
import qualified Data.Map as Map import qualified Data.Map as Map
@ -16,17 +18,17 @@ import Network.Xmpp.Types
-- | Sends an IQ, returns Just a 'TMVar' that will be filled with the first -- | Sends an IQ, returns Just a 'TMVar' that will be filled with the first
-- inbound IQ with a matching ID that has type @result@ or @error@ or Nothing if -- inbound IQ with a matching ID that has type @result@ or @error@ or Nothing if
-- the stanza could not be sent -- the stanza could not be sent
sendIQ :: Maybe Int -- ^ Timeout . When the timeout is reached the response sendIQ :: Maybe Integer -- ^ Timeout . When the timeout is reached the response
-- TMVar will be filled with 'IQResponseTimeout' and the id -- TMVar will be filled with 'IQResponseTimeout' and the
-- is removed from the list of IQ handlers. 'Nothing' -- id is removed from the list of IQ handlers. 'Nothing'
-- deactivates the timeout -- deactivates the timeout
-> Maybe Jid -- ^ Recipient (to) -> 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)
-> Session -> Session
-> IO (Maybe (TMVar IQResponse)) -> IO (Maybe (TMVar (Maybe IQResponse)))
sendIQ timeOut to tp lang body session = do -- TODO: Add timeout sendIQ timeOut to tp lang body session = do -- TODO: Add timeout
newId <- idGenerator session newId <- idGenerator session
ref <- atomically $ do ref <- atomically $ do
@ -41,7 +43,7 @@ sendIQ timeOut to tp lang body session = do -- TODO: Add timeout
case timeOut of case timeOut of
Nothing -> return () Nothing -> return ()
Just t -> void . forkIO $ do Just t -> void . forkIO $ do
threadDelay t delay t
doTimeOut (iqHandlers session) newId ref doTimeOut (iqHandlers session) newId ref
return $ Just ref return $ Just ref
else return Nothing else return Nothing
@ -53,16 +55,16 @@ sendIQ timeOut to tp lang body session = do -- TODO: Add timeout
writeTVar handlers (byNS, Map.delete iqid byId) writeTVar handlers (byNS, Map.delete iqid byId)
return () return ()
-- | Like 'sendIQ', but waits for the answer IQ.
-- | Like 'sendIQ', but waits for the answer IQ. Times out after 30 seconds sendIQ' :: Maybe Integer
sendIQ' :: Maybe Jid -> Maybe Jid
-> IQRequestType -> IQRequestType
-> Maybe LangTag -> Maybe LangTag
-> Element -> Element
-> Session -> Session
-> IO (Maybe IQResponse) -> IO (Maybe IQResponse)
sendIQ' to tp lang body session = do sendIQ' timeout to tp lang body session = do
ref <- sendIQ (Just 30000000) to tp lang body session ref <- sendIQ timeout to tp lang body session
maybe (return Nothing) (fmap Just . atomically . takeTMVar) ref maybe (return Nothing) (fmap Just . atomically . takeTMVar) ref

14
source/Network/Xmpp/IM/Roster.hs

@ -27,12 +27,16 @@ import Network.Xmpp.IM.Roster.Types
import Network.Xmpp.Marshal import Network.Xmpp.Marshal
import Network.Xmpp.Types import Network.Xmpp.Types
-- | Timeout to use with IQ requests
timeout :: Maybe Integer
timeout = Just 3000000 -- 3 seconds
-- | Push a roster item to the server. The values for approved and ask are -- | Push a roster item to the server. The values for approved and ask are
-- ignored and all values for subsciption except "remove" are ignored -- ignored and all values for subsciption except "remove" are ignored
rosterPush :: Item -> Session -> IO (Maybe IQResponse) rosterPush :: Item -> Session -> IO (Maybe IQResponse)
rosterPush item session = do rosterPush item session = do
let el = pickleElem xpQuery (Query Nothing [fromItem item]) let el = pickleElem xpQuery (Query Nothing [fromItem item])
sendIQ' Nothing Set Nothing el session sendIQ' timeout Nothing Set Nothing el session
-- | Add or update an item to the roster. -- | Add or update an item to the roster.
-- --
@ -51,7 +55,7 @@ rosterAdd j n gs session = do
, qiSubscription = Nothing , qiSubscription = Nothing
, qiGroups = nub gs , qiGroups = nub gs
}]) }])
sendIQ' Nothing Set Nothing el session sendIQ' timeout Nothing Set Nothing el session
-- | Remove an item from the roster. Return True when the item is sucessfully -- | Remove an item from the roster. Return True when the item is sucessfully
-- removed or if it wasn't in the roster to begin with. -- removed or if it wasn't in the roster to begin with.
@ -121,9 +125,9 @@ retrieveRoster mbOldRoster sess = do
Nothing -> Just "" Nothing -> Just ""
Just oldRoster -> ver oldRoster Just oldRoster -> ver oldRoster
else Nothing else Nothing
res <- sendIQ' Nothing Get Nothing res <- sendIQ' timeout Nothing Get Nothing
(pickleElem xpQuery (Query version [])) (pickleElem xpQuery (Query version []))
sess sess
case res of case res of
Nothing -> do Nothing -> do
errorM "Pontarius.Xmpp.Roster" "getRoster: sending stanza failed" errorM "Pontarius.Xmpp.Roster" "getRoster: sending stanza failed"

Loading…
Cancel
Save